2014-10-21 23:32:47 +02:00
|
|
|
open Qptypes;;
|
|
|
|
open Qputils;;
|
|
|
|
open Core.Std;;
|
|
|
|
|
|
|
|
module Full_ci : sig
|
|
|
|
type t =
|
2014-10-28 17:16:51 +01:00
|
|
|
{ n_det_max_fci : 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-27 23:05:26 +01:00
|
|
|
val read : unit -> t option
|
2014-11-12 10:27:04 +01:00
|
|
|
val write : t-> unit
|
2014-10-21 23:32:47 +02:00
|
|
|
val to_string : t -> string
|
2014-10-29 22:13:03 +01:00
|
|
|
val to_rst : t -> Rst_string.t
|
2014-11-12 17:17:44 +01:00
|
|
|
val of_rst : Rst_string.t -> t option
|
2014-10-21 23:32:47 +02:00
|
|
|
end = struct
|
|
|
|
type t =
|
2014-10-28 17:16:51 +01:00
|
|
|
{ n_det_max_fci : 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
|
|
|
;;
|
|
|
|
|
|
|
|
let get_default = Qpackage.get_ezfio_default "full_ci";;
|
|
|
|
|
|
|
|
let read_n_det_max_fci () =
|
|
|
|
if not (Ezfio.has_full_ci_n_det_max_fci ()) then
|
|
|
|
get_default "n_det_max_fci"
|
|
|
|
|> Int.of_string
|
|
|
|
|> Ezfio.set_full_ci_n_det_max_fci
|
|
|
|
;
|
|
|
|
Ezfio.get_full_ci_n_det_max_fci ()
|
2014-10-28 17:16:51 +01:00
|
|
|
|> Det_number_max.of_int
|
2014-10-21 23:32:47 +02:00
|
|
|
;;
|
|
|
|
|
2014-11-12 10:27:04 +01:00
|
|
|
let write_n_det_max_fci ndet =
|
|
|
|
Det_number_max.to_int ndet
|
|
|
|
|> Ezfio.set_full_ci_n_det_max_fci
|
|
|
|
;;
|
|
|
|
|
2014-10-21 23:32:47 +02:00
|
|
|
let read_pt2_max () =
|
|
|
|
if not (Ezfio.has_full_ci_pt2_max ()) then
|
|
|
|
get_default "pt2_max"
|
|
|
|
|> Float.of_string
|
|
|
|
|> Ezfio.set_full_ci_pt2_max
|
|
|
|
;
|
|
|
|
Ezfio.get_full_ci_pt2_max ()
|
2014-10-22 00:12:23 +02:00
|
|
|
|> PT2_energy.of_float
|
2014-10-21 23:32:47 +02:00
|
|
|
;;
|
|
|
|
|
2014-11-12 10:27:04 +01:00
|
|
|
let write_pt2_max pt2_max =
|
|
|
|
PT2_energy.to_float pt2_max
|
|
|
|
|> Ezfio.set_full_ci_pt2_max
|
|
|
|
;;
|
|
|
|
|
2014-10-21 23:32:47 +02:00
|
|
|
let read_do_pt2_end () =
|
|
|
|
if not (Ezfio.has_full_ci_do_pt2_end ()) then
|
|
|
|
get_default "do_pt2_end"
|
|
|
|
|> Bool.of_string
|
|
|
|
|> Ezfio.set_full_ci_do_pt2_end
|
|
|
|
;
|
|
|
|
Ezfio.get_full_ci_do_pt2_end ()
|
|
|
|
;;
|
|
|
|
|
2014-11-12 10:27:04 +01:00
|
|
|
let write_do_pt2_end =
|
|
|
|
Ezfio.set_full_ci_do_pt2_end
|
|
|
|
;;
|
|
|
|
|
2014-10-21 23:32:47 +02:00
|
|
|
|
|
|
|
let read () =
|
2014-11-27 23:05:26 +01:00
|
|
|
Some
|
|
|
|
{ n_det_max_fci = read_n_det_max_fci ();
|
|
|
|
pt2_max = read_pt2_max ();
|
|
|
|
do_pt2_end = read_do_pt2_end ();
|
2014-10-21 23:32:47 +02:00
|
|
|
}
|
|
|
|
;;
|
|
|
|
|
2014-11-12 10:27:04 +01:00
|
|
|
|
|
|
|
let write { n_det_max_fci ;
|
|
|
|
pt2_max ;
|
|
|
|
do_pt2_end ;
|
|
|
|
} =
|
|
|
|
write_n_det_max_fci n_det_max_fci;
|
|
|
|
write_pt2_max pt2_max;
|
|
|
|
write_do_pt2_end do_pt2_end;
|
|
|
|
;;
|
|
|
|
|
2014-10-21 23:32:47 +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_fci = %s
|
|
|
|
pt2_max = %s
|
|
|
|
do_pt2_end = %s
|
|
|
|
"
|
|
|
|
(Det_number_max.to_string b.n_det_max_fci)
|
|
|
|
(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_fci` ::
|
|
|
|
|
|
|
|
n_det_max_fci = %s
|
|
|
|
|
|
|
|
Stop when -E(PT2) < `pt2_max` ::
|
|
|
|
|
|
|
|
pt2_max = %s
|
|
|
|
|
|
|
|
Compute E(PT2) at the end ::
|
|
|
|
|
|
|
|
do_pt2_end = %s
|
|
|
|
|
2014-10-21 23:32:47 +02:00
|
|
|
"
|
2014-10-28 17:16:51 +01:00
|
|
|
(Det_number_max.to_string b.n_det_max_fci)
|
2014-10-22 00:12:23 +02:00
|
|
|
(PT2_energy.to_string b.pt2_max)
|
2014-10-21 23:32:47 +02:00
|
|
|
(Bool.to_string b.do_pt2_end)
|
2014-10-29 22:13:03 +01:00
|
|
|
|> Rst_string.of_string
|
|
|
|
;;
|
2014-10-31 22:21:38 +01:00
|
|
|
|
2014-11-12 17:17:44 +01:00
|
|
|
include Generic_input_of_rst;;
|
|
|
|
let of_rst = of_rst t_of_sexp;;
|
2014-10-31 22:21:38 +01:00
|
|
|
|
|
|
|
|
2014-10-21 23:32:47 +02:00
|
|
|
end
|
|
|
|
|
|
|
|
|