10
0
mirror of https://github.com/LCPQ/quantum_package synced 2024-06-28 16:12:26 +02:00
quantum_package/ocaml/Input_cisd_sc2.ml

141 lines
3.1 KiB
OCaml
Raw Normal View History

2014-10-21 22:18:57 +02:00
open Qptypes;;
open Qputils;;
open Core.Std;;
module Cisd_sc2 : sig
2014-10-21 23:32:47 +02:00
type t =
2014-10-28 17:16:51 +01:00
{ n_det_max_cisd_sc2 : Det_number_max.t;
2014-10-22 00:12:23 +02:00
pt2_max : PT2_energy.t;
2014-10-21 23:32:47 +02:00
do_pt2_end : bool;
2014-10-25 21:24:21 +02:00
} with sexp
2014-10-21 23:32:47 +02:00
;;
2014-11-03 22:42:39 +01:00
val read : unit -> t
val write : t -> unit
2014-10-21 22:18:57 +02:00
val to_string : t -> string
2014-10-29 22:13:03 +01:00
val to_rst : t -> Rst_string.t
2014-10-31 19:26:27 +01:00
val of_rst : Rst_string.t -> t
2014-10-21 22:18:57 +02:00
end = struct
type t =
2014-10-28 17:16:51 +01:00
{ n_det_max_cisd_sc2 : Det_number_max.t;
2014-10-22 00:12:23 +02:00
pt2_max : PT2_energy.t;
2014-10-21 22:18:57 +02:00
do_pt2_end : bool;
2014-10-25 21:24:21 +02:00
} with sexp
2014-10-21 22:18:57 +02:00
;;
let get_default = Qpackage.get_ezfio_default "cisd_sc2_selected";;
let read_n_det_max_cisd_sc2 () =
if not (Ezfio.has_cisd_sc2_selected_n_det_max_cisd_sc2 ()) then
get_default "n_det_max_cisd_sc2"
|> Int.of_string
|> Ezfio.set_cisd_sc2_selected_n_det_max_cisd_sc2
;
Ezfio.get_cisd_sc2_selected_n_det_max_cisd_sc2 ()
2014-10-28 17:16:51 +01:00
|> Det_number_max.of_int
2014-10-21 22:18:57 +02:00
;;
2014-11-03 22:42:39 +01:00
let write_n_det_max_cisd_sc2 n =
Det_number_max.to_int n
|> Ezfio.set_cisd_sc2_selected_n_det_max_cisd_sc2
;;
2014-10-21 22:18:57 +02:00
let read_pt2_max () =
if not (Ezfio.has_cisd_sc2_selected_pt2_max ()) then
get_default "pt2_max"
|> Float.of_string
|> Ezfio.set_cisd_sc2_selected_pt2_max
;
Ezfio.get_cisd_sc2_selected_pt2_max ()
2014-10-22 00:12:23 +02:00
|> PT2_energy.of_float
2014-10-21 22:18:57 +02:00
;;
2014-11-03 22:42:39 +01:00
let write_pt2_max p =
PT2_energy.to_float p
|> Ezfio.set_cisd_sc2_selected_pt2_max
;;
2014-10-21 22:18:57 +02:00
let read_do_pt2_end () =
if not (Ezfio.has_cisd_sc2_selected_do_pt2_end ()) then
get_default "do_pt2_end"
|> Bool.of_string
|> Ezfio.set_cisd_sc2_selected_do_pt2_end
;
Ezfio.get_cisd_sc2_selected_do_pt2_end ()
;;
2014-11-03 22:42:39 +01:00
let write_do_pt2_end =
Ezfio.set_cisd_sc2_selected_do_pt2_end
;;
2014-10-21 22:18:57 +02:00
let read () =
{ n_det_max_cisd_sc2 = read_n_det_max_cisd_sc2 ();
pt2_max = read_pt2_max ();
do_pt2_end = read_do_pt2_end ();
}
;;
2014-11-03 22:42:39 +01:00
let write { n_det_max_cisd_sc2 ;
pt2_max ;
do_pt2_end ;
} =
write_n_det_max_cisd_sc2 n_det_max_cisd_sc2;
write_pt2_max pt2_max;
write_do_pt2_end do_pt2_end;
;;
2014-10-21 22:18:57 +02:00
let to_string b =
2014-10-29 00:12:45 +01:00
Printf.sprintf "
2014-10-29 22:13:03 +01:00
n_det_max_cisd_sc2 = %s
pt2_max = %s
do_pt2_end = %s
"
(Det_number_max.to_string b.n_det_max_cisd_sc2)
(PT2_energy.to_string b.pt2_max)
(Bool.to_string b.do_pt2_end)
;;
let to_rst b =
Printf.sprintf "
2014-10-29 00:12:45 +01:00
Stop when the `n_det` > `n_det_max_cisd_sc2` ::
n_det_max_cisd_sc2 = %s
Stop when -E(PT2) < `pt2_max` ::
pt2_max = %s
Compute E(PT2) at the end ::
do_pt2_end = %s
2014-10-21 22:18:57 +02:00
"
2014-10-28 17:16:51 +01:00
(Det_number_max.to_string b.n_det_max_cisd_sc2)
2014-10-22 00:12:23 +02:00
(PT2_energy.to_string b.pt2_max)
2014-10-21 22:18:57 +02:00
(Bool.to_string b.do_pt2_end)
2014-10-29 22:13:03 +01:00
|> Rst_string.of_string
2014-10-31 19:26:27 +01:00
;;
let of_rst s =
let s = Rst_string.to_string s
|> String.split ~on:'\n'
|> List.filter ~f:(fun line ->
String.contains line '=')
|> List.map ~f:(fun line ->
"("^(
String.tr line ~target:'=' ~replacement:' '
)^")" )
|> String.concat
in
Sexp.of_string ("("^s^")")
|> t_of_sexp
;;
2014-10-29 22:13:03 +01:00
2014-10-21 22:18:57 +02:00
end