10
0
mirror of https://github.com/LCPQ/quantum_package synced 2024-09-27 12:00:56 +02:00
quantum_package/ocaml/Qpackage.ml

141 lines
3.4 KiB
OCaml
Raw Normal View History

2017-08-18 18:28:33 +02:00
open Core;;
2014-09-17 11:49:00 +02:00
open Qptypes;;
2014-10-10 00:26:49 +02:00
open Qputils;;
2014-08-27 16:38:13 +02:00
(** Variables related to the quantum package installation *)
2019-01-14 15:20:51 +01:00
let root =
2015-06-08 15:16:28 +02:00
match (Sys.getenv "QP_ROOT") with
| None -> failwith "QP_ROOT environment variable is not set.
2014-08-27 16:38:13 +02:00
Please source the quantum_package.rc file."
2019-01-14 15:20:51 +01:00
| Some x -> x
2014-08-27 16:38:13 +02:00
;;
2014-09-17 12:34:31 +02:00
let bit_kind_size = lazy (
2018-12-19 14:33:42 +01:00
let filename = root^"/src/bitmask/bitmasks_module.f90" in
2014-09-17 11:49:00 +02:00
if not (Sys.file_exists_exn filename) then
raise (Failure ("File "^filename^" not found"));
let in_channel = In_channel.create filename in
let lines = In_channel.input_lines in_channel in
In_channel.close in_channel;
let rec get_data = function
2019-01-14 15:20:51 +01:00
| [] -> raise (Failure ("bit_kind_size not found in "^filename))
| line::tail ->
let line =
2014-09-17 11:49:00 +02:00
begin match String.split ~on:'!' line |> List.hd with
| Some x -> x
| None -> ""
end in
begin match (String.rsplit2 ~on:':' line) with
2019-01-14 15:20:51 +01:00
| Some (_ ,buffer) ->
2014-09-17 11:49:00 +02:00
begin match (String.split ~on:'=' buffer |> List.map ~f:String.strip) with
2019-01-14 15:20:51 +01:00
| ["bit_kind_size"; x] ->
2014-09-17 11:49:00 +02:00
Int.of_string x |> Bit_kind_size.of_int
| _ -> get_data tail
end
| _ -> get_data tail
end
in
2014-09-17 12:34:31 +02:00
get_data lines )
2014-09-17 11:49:00 +02:00
;;
2014-10-10 00:26:49 +02:00
2014-10-18 00:10:25 +02:00
let bit_kind = lazy (
Lazy.force bit_kind_size
|> Bit_kind_size.to_int
|> fun x -> x / 8
|> Bit_kind.of_int
)
;;
2014-10-10 00:26:49 +02:00
let executables = lazy (
2019-01-14 15:20:51 +01:00
let filename = root^"/data/executables"
2014-10-10 00:26:49 +02:00
and func in_channel =
In_channel.input_lines in_channel
|> List.map ~f:(fun x ->
let e = String.split ~on:' ' x
|> List.filter ~f:(fun x -> x <> "")
in
match e with
2015-06-08 15:16:28 +02:00
| [a;b] -> (a,String.substr_replace_all ~pattern:"$QP_ROOT" ~with_:root b)
2014-10-10 00:26:49 +02:00
| _ -> ("","")
)
in
In_channel.with_file filename ~f:func
2019-01-14 15:20:51 +01:00
|> List.sort ~compare:(fun (x,_) (y,_) ->
2014-10-10 00:26:49 +02:00
if x < y then -1
else if x > y then 1
2019-01-14 15:20:51 +01:00
else 0)
2014-10-10 00:26:49 +02:00
)
2015-03-26 18:24:40 +01:00
let get_ezfio_default_in_file ~directory ~data ~filename =
2014-10-17 22:25:45 +02:00
let lines = In_channel.with_file filename ~f:(fun in_channel ->
In_channel.input_lines in_channel) in
let rec find_dir = function
| line :: rest ->
if ((String.strip line) = directory) then
rest
else
find_dir rest
2018-10-17 19:27:58 +02:00
| [] -> raise Caml.Not_found
2019-01-14 15:20:51 +01:00
in
2014-10-17 22:25:45 +02:00
let rec find_data = function
| line :: rest ->
if (line = "") then
2018-10-17 19:27:58 +02:00
raise Caml.Not_found
2014-10-17 22:25:45 +02:00
else if (line.[0] <> ' ') then
2018-10-17 19:27:58 +02:00
raise Caml.Not_found
2019-01-14 15:20:51 +01:00
else
2014-10-17 22:25:45 +02:00
begin
match (String.lsplit2 ~on:' ' (String.strip line)) with
2019-01-14 15:20:51 +01:00
| Some (l,r) ->
if (l = data) then
2015-04-07 10:17:38 +02:00
String.strip r
2015-03-26 18:24:40 +01:00
else
find_data rest
2018-10-17 19:27:58 +02:00
| None -> raise Caml.Not_found
2014-10-17 22:25:45 +02:00
end
2018-10-17 19:27:58 +02:00
| [] -> raise Caml.Not_found
2014-10-17 22:25:45 +02:00
in
find_dir lines
|> find_data ;
;;
2015-03-26 18:24:40 +01:00
let get_ezfio_default directory data =
let dirname = root^"/data/ezfio_defaults/" in
2019-01-14 15:20:51 +01:00
let rec aux = function
| [] ->
2015-06-11 16:25:35 +02:00
begin
Printf.printf "%s/%s not found\n%!" directory data;
2018-10-17 19:27:58 +02:00
raise Caml.Not_found
2015-06-11 16:25:35 +02:00
end
2015-03-26 18:24:40 +01:00
| filename :: tail ->
2019-01-14 15:20:51 +01:00
let filename =
2015-03-26 18:24:40 +01:00
dirname^filename
in
try
get_ezfio_default_in_file ~directory ~data ~filename
with
2018-10-17 19:27:58 +02:00
| Caml.Not_found -> aux tail
2015-03-26 18:24:40 +01:00
in
Sys.readdir dirname
|> Array.to_list
2019-01-14 15:20:51 +01:00
|> aux
2015-03-26 18:24:40 +01:00
;;
2019-01-14 15:20:51 +01:00
let ezfio_work ezfio_file =
let result =
2016-10-12 11:26:21 +02:00
Filename.concat ezfio_file "work"
in
begin
match Sys.is_directory result with
| `Yes -> ()
| _ -> ( Ezfio.set_file ezfio_file ; Ezfio.set_work_empty false)
2016-10-12 11:26:21 +02:00
end;
result
;;