open Qptypes type t = { property : Property.t ; value : Sample.t ; weight : Weight.t ; compute_node : Compute_node.t ; pid : int ; 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 ; value = Sample.of_float (float_of_string v) ; weight = Weight.of_float (float_of_string w) ; compute_node = Compute_node.of_string c; pid = int_of_string pid; block_id = Block_id.of_int (int_of_string b) ; } | b :: pid :: c:: p :: w :: v -> let v = List.rev v |> Array.of_list |> Array.map float_of_string in let dim = Array.length v in Some { property = Property.of_string p ; value = Sample.of_float_array ~dim v ; weight = Weight.of_float (float_of_string w) ; compute_node = Compute_node.of_string c; pid = int_of_string pid; block_id = Block_id.of_int (int_of_string b) ; } | _ -> None with | _ -> None let to_string b = Printf.sprintf "%s %s # %s %s %s %d" (Sample.to_string b.value ) (Weight.to_float b.weight |> string_of_float) (Property.to_string b.property) (Compute_node.to_string b.compute_node) (string_of_int b.pid) (Block_id.to_int b.block_id) let dir_name = lazy( let ezfio_filename = Lazy.force Qputils.ezfio_filename in let md5 = QmcMd5.hash () in let d = Filename.concat ezfio_filename "blocks" in if not ( Sys.file_exists d ) then Unix.mkdir d 0o755; List.fold_right Filename.concat [ ezfio_filename ; "blocks" ; md5 ; Filename.dir_sep ] "" ) (* 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 = if Sys.file_exists dir_name && Sys.is_directory dir_name then begin Sys.readdir dir_name |> Array.map (fun x -> dir_name^x) |> Array.to_list end else [] in if locked then result else List.filter (fun x -> try let _ = Str.search_backward (Str.regexp "locked") x ((String.length x) - 1) in false with | Not_found -> true ) result in let rec transform new_list = function | [] -> new_list | head :: tail -> let head = String.trim head in let item = of_string head in match item with | None -> transform new_list tail | Some x -> transform (x::new_list) tail in let result = let rec aux ic accu = try aux ic ( (input_line ic)::accu ) with | End_of_file -> List.rev accu in List.concat_map (fun filename -> let ic = open_in filename in let result = aux ic [] in close_in ic; result ) files |> transform [] 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 ( let h = Hashtbl.create 63 in List.iter (fun x -> Hashtbl.replace h (Property.to_string x.property) x.property) (raw_data ()); Hashtbl.fold (fun k v a -> v :: a) h [] )