10
1
mirror of https://gitlab.com/scemama/qmcchem.git synced 2024-06-02 03:15:19 +02:00
qmcchem/ocaml/Block.ml

161 lines
3.7 KiB
OCaml
Raw Normal View History

2017-10-10 09:39:58 +02:00
open Qptypes
2015-12-19 02:35:13 +01:00
type t =
{ property : Property.t ;
value : Sample.t ;
weight : Weight.t ;
compute_node : Compute_node.t ;
2019-07-14 18:50:44 +02:00
pid : int ;
2015-12-19 02:35:13 +01:00
block_id : Block_id.t ;
}
let re =
Str.regexp "[ |#|\n]+"
let of_string s =
try
let lst =
Str.split re s
|> List.rev
in
match lst with
| b :: pid :: c:: p :: w :: v :: [] -> Some
{ property = Property.of_string p ;
2019-07-14 18:50:44 +02:00
value = Sample.of_float (float_of_string v) ;
weight = Weight.of_float (float_of_string w) ;
2015-12-19 02:35:13 +01:00
compute_node = Compute_node.of_string c;
2019-07-14 18:50:44 +02:00
pid = int_of_string pid;
block_id = Block_id.of_int (int_of_string b) ;
2015-12-19 02:35:13 +01:00
}
| b :: pid :: c:: p :: w :: v ->
let v =
List.rev v
|> Array.of_list
2019-07-14 18:50:44 +02:00
|> Array.map float_of_string
2015-12-19 02:35:13 +01:00
in
let dim =
Array.length v
in
Some
{ property = Property.of_string p ;
value = Sample.of_float_array ~dim v ;
2019-07-14 18:50:44 +02:00
weight = Weight.of_float (float_of_string w) ;
2015-12-19 02:35:13 +01:00
compute_node = Compute_node.of_string c;
2019-07-14 18:50:44 +02:00
pid = int_of_string pid;
block_id = Block_id.of_int (int_of_string b) ;
2015-12-19 02:35:13 +01:00
}
| _ -> None
with
| _ -> None
let to_string b =
Printf.sprintf "%s %s # %s %s %s %d"
(Sample.to_string b.value )
2019-07-14 18:50:44 +02:00
(Weight.to_float b.weight |> string_of_float)
2015-12-19 02:35:13 +01:00
(Property.to_string b.property)
(Compute_node.to_string b.compute_node)
2019-07-14 18:50:44 +02:00
(string_of_int b.pid)
2015-12-19 02:35:13 +01:00
(Block_id.to_int b.block_id)
let dir_name = lazy(
let ezfio_filename =
Lazy.force Qputils.ezfio_filename
in
let md5 =
2018-03-14 17:02:52 +01:00
QmcMd5.hash ()
2015-12-19 02:35:13 +01:00
in
2019-07-31 15:07:04 +02:00
let d = Filename.concat ezfio_filename "blocks" in
if not ( Sys.file_exists d ) then
Unix.mkdir d 0o755;
2019-07-14 18:50:44 +02:00
List.fold_right Filename.concat
[ ezfio_filename ; "blocks" ; md5 ; Filename.dir_sep ] ""
2015-12-19 02:35:13 +01:00
)
(* Fetch raw data from the EZFIO file *)
let _raw_data =
ref None
let update_raw_data ?(locked=true) () =
(* Create array of files to read *)
let dir_name =
Lazy.force dir_name
in
let files =
let result =
2019-07-23 17:27:02 +02:00
if Sys.file_exists dir_name && Sys.is_directory dir_name then
2015-12-19 02:35:13 +01:00
begin
Sys.readdir dir_name
2019-07-14 18:50:44 +02:00
|> Array.map (fun x -> dir_name^x)
2015-12-19 02:35:13 +01:00
|> Array.to_list
end
2019-07-14 18:50:44 +02:00
else []
2015-12-19 02:35:13 +01:00
in
if locked then
result
else
2019-07-14 18:50:44 +02:00
List.filter (fun x ->
try
let _ =
Str.search_backward (Str.regexp "locked") x ((String.length x) - 1)
in false
with
| Not_found -> true
) result
2015-12-19 02:35:13 +01:00
in
let rec transform new_list = function
| [] -> new_list
| head :: tail ->
2019-07-14 18:50:44 +02:00
let head = String.trim head in
2015-12-19 02:35:13 +01:00
let item = of_string head in
match item with
| None -> transform new_list tail
| Some x -> transform (x::new_list) tail
in
let result =
2019-07-14 18:50:44 +02:00
let rec aux ic accu =
try
aux ic ( (input_line ic)::accu )
with
| End_of_file -> List.rev accu
in
2020-04-15 14:40:33 +02:00
List.concat_map (fun filename ->
2019-07-14 18:50:44 +02:00
let ic = open_in filename in
let result = aux ic [] in
close_in ic;
result ) files
|> transform []
2015-12-19 02:35:13 +01:00
in
result
let raw_data ?(locked=true) () =
match !_raw_data with
| Some x -> x
| None ->
let result =
update_raw_data ~locked ()
in
_raw_data := Some result;
result
let properties = lazy (
2019-07-19 11:46:29 +02:00
let h = Hashtbl.create 63 in
List.iter (fun x ->
2019-07-23 17:34:58 +02:00
Hashtbl.replace h (Property.to_string x.property) x.property)
2019-07-19 11:46:29 +02:00
(raw_data ());
Hashtbl.fold (fun k v a -> v :: a) h []
2015-12-19 02:35:13 +01:00
)