2014-10-22 00:12:23 +02:00
|
|
|
open Qptypes;;
|
|
|
|
open Qputils;;
|
|
|
|
open Core.Std;;
|
|
|
|
|
|
|
|
module Hartree_fock : sig
|
|
|
|
type t =
|
|
|
|
{ n_it_scf_max : Strictly_positive_int.t;
|
|
|
|
thresh_scf : Threshold.t;
|
2015-03-20 11:21:26 +01:00
|
|
|
guess : MO_guess.t;
|
2014-10-25 21:24:21 +02:00
|
|
|
} with sexp
|
2014-10-22 00:12:23 +02:00
|
|
|
;;
|
2014-11-27 23:05:26 +01:00
|
|
|
val read : unit -> t option
|
2014-11-12 10:34:54 +01:00
|
|
|
val write : t -> unit
|
2014-10-22 00:12:23 +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-22 00:12:23 +02:00
|
|
|
end = struct
|
|
|
|
type t =
|
|
|
|
{ n_it_scf_max : Strictly_positive_int.t;
|
|
|
|
thresh_scf : Threshold.t;
|
2015-03-20 11:21:26 +01:00
|
|
|
guess : MO_guess.t;
|
2014-10-25 21:24:21 +02:00
|
|
|
} with sexp
|
2014-10-22 00:12:23 +02:00
|
|
|
;;
|
|
|
|
|
|
|
|
let get_default = Qpackage.get_ezfio_default "hartree_fock";;
|
|
|
|
|
|
|
|
let read_n_it_scf_max () =
|
|
|
|
if not (Ezfio.has_hartree_fock_n_it_scf_max ()) then
|
|
|
|
get_default "n_it_scf_max"
|
|
|
|
|> Int.of_string
|
|
|
|
|> Ezfio.set_hartree_fock_n_it_scf_max
|
|
|
|
;
|
|
|
|
Ezfio.get_hartree_fock_n_it_scf_max ()
|
|
|
|
|> Strictly_positive_int.of_int
|
|
|
|
;;
|
|
|
|
|
2014-11-12 10:34:54 +01:00
|
|
|
let write_n_it_scf_max n_it_scf_max =
|
|
|
|
Strictly_positive_int.to_int n_it_scf_max
|
|
|
|
|> Ezfio.set_hartree_fock_n_it_scf_max
|
|
|
|
;;
|
|
|
|
|
|
|
|
let read_thresh_scf () =
|
2014-10-22 00:12:23 +02:00
|
|
|
if not (Ezfio.has_hartree_fock_thresh_scf()) then
|
|
|
|
get_default "thresh_scf"
|
|
|
|
|> Float.of_string
|
|
|
|
|> Ezfio.set_hartree_fock_thresh_scf
|
|
|
|
;
|
|
|
|
Ezfio.get_hartree_fock_thresh_scf ()
|
2014-11-12 10:34:54 +01:00
|
|
|
|> Threshold.of_float
|
|
|
|
;;
|
|
|
|
|
|
|
|
let write_thresh_scf thresh_scf =
|
|
|
|
Threshold.to_float thresh_scf
|
|
|
|
|> Ezfio.set_hartree_fock_thresh_scf
|
|
|
|
;;
|
2014-10-22 00:12:23 +02:00
|
|
|
|
2015-03-20 11:21:26 +01:00
|
|
|
let read_guess () =
|
|
|
|
if not (Ezfio.has_hartree_fock_guess ()) then
|
|
|
|
get_default "guess"
|
|
|
|
|> String.strip ~drop:(fun x -> x = '"')
|
|
|
|
|> Ezfio.set_hartree_fock_guess
|
|
|
|
;
|
|
|
|
Ezfio.get_hartree_fock_guess ()
|
|
|
|
|> MO_guess.of_string
|
|
|
|
;;
|
|
|
|
|
|
|
|
let write_guess guess =
|
|
|
|
MO_guess.to_string guess
|
|
|
|
|> Ezfio.set_hartree_fock_guess
|
|
|
|
;;
|
2014-10-22 00:12:23 +02:00
|
|
|
|
|
|
|
let read () =
|
2014-11-27 23:05:26 +01:00
|
|
|
Some
|
2014-10-22 00:12:23 +02:00
|
|
|
{ n_it_scf_max = read_n_it_scf_max ();
|
|
|
|
thresh_scf = read_thresh_scf ();
|
2015-03-20 11:21:26 +01:00
|
|
|
guess = read_guess ();
|
2014-10-22 00:12:23 +02:00
|
|
|
}
|
|
|
|
;;
|
|
|
|
|
2014-11-12 10:34:54 +01:00
|
|
|
|
|
|
|
let write { n_it_scf_max ;
|
|
|
|
thresh_scf ;
|
2015-03-20 11:21:26 +01:00
|
|
|
guess ;
|
2014-11-12 10:34:54 +01:00
|
|
|
} =
|
|
|
|
write_n_it_scf_max n_it_scf_max;
|
2015-03-20 11:21:26 +01:00
|
|
|
write_thresh_scf thresh_scf;
|
|
|
|
write_guess guess
|
2014-11-12 10:34:54 +01:00
|
|
|
;;
|
|
|
|
|
|
|
|
|
2014-10-22 00:12:23 +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_it_scf_max = %s
|
2015-03-20 11:21:26 +01:00
|
|
|
thresh_scf = %s
|
|
|
|
guess = %s
|
2014-10-29 22:13:03 +01:00
|
|
|
"
|
|
|
|
(Strictly_positive_int.to_string b.n_it_scf_max)
|
|
|
|
(Threshold.to_string b.thresh_scf)
|
2015-03-20 11:21:26 +01:00
|
|
|
(MO_guess.to_string b.guess)
|
2014-10-29 22:13:03 +01:00
|
|
|
;;
|
|
|
|
|
|
|
|
let to_rst b =
|
|
|
|
Printf.sprintf "
|
2015-03-20 11:21:26 +01:00
|
|
|
Type of MO guess [ Huckel | HCore ] ::
|
|
|
|
|
|
|
|
guess = %s
|
|
|
|
|
2014-10-29 00:12:45 +01:00
|
|
|
Max number of SCF iterations ::
|
|
|
|
|
|
|
|
n_it_scf_max = %s
|
|
|
|
|
|
|
|
SCF convergence criterion (on energy) ::
|
|
|
|
|
|
|
|
thresh_scf = %s
|
|
|
|
|
2014-10-22 00:12:23 +02:00
|
|
|
"
|
2015-03-20 11:21:26 +01:00
|
|
|
(MO_guess.to_string b.guess)
|
|
|
|
(Strictly_positive_int.to_string b.n_it_scf_max)
|
|
|
|
(Threshold.to_string b.thresh_scf)
|
2014-10-29 22:13:03 +01:00
|
|
|
|> Rst_string.of_string
|
|
|
|
;;
|
|
|
|
|
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:19:39 +01:00
|
|
|
|
2014-10-22 00:12:23 +02:00
|
|
|
end
|
|
|
|
|
|
|
|
|