10
0
mirror of https://github.com/LCPQ/quantum_package synced 2024-09-27 12:00:56 +02:00
quantum_package/ocaml/Input_mo_basis.ml

131 lines
3.3 KiB
OCaml
Raw Normal View History

2018-10-17 16:28:57 +02:00
(* =~=~ *)
(* Init *)
(* =~=~ *)
2014-10-24 00:25:15 +02:00
2018-10-17 16:28:57 +02:00
open Qptypes;;
open Qputils;;
open Core;;
2015-03-26 18:24:40 +01:00
2014-10-24 00:25:15 +02:00
module Mo_basis : sig
2018-10-17 16:28:57 +02:00
(* Generate type *)
type t =
{
disk_access_mo_one_integrals : Disk_access.t;
} [@@deriving sexp]
;;
val read : unit -> t option
val write : t-> unit
2014-10-24 00:25:15 +02:00
val to_string : t -> string
2014-10-29 22:13:03 +01:00
val to_rst : t -> Rst_string.t
2018-10-17 16:28:57 +02:00
val of_rst : Rst_string.t -> t option
2014-10-24 00:25:15 +02:00
end = struct
2018-10-17 16:28:57 +02:00
(* Generate type *)
type t =
{
disk_access_mo_one_integrals : Disk_access.t;
} [@@deriving sexp]
;;
let get_default = Qpackage.get_ezfio_default "mo_basis";;
(* =~=~=~=~=~=~==~=~=~=~=~=~ *)
(* Generate Special Function *)
(* =~=~=~==~=~~=~=~=~=~=~=~=~ *)
(* Read snippet for disk_access_mo_one_integrals *)
let read_disk_access_mo_one_integrals () =
if not (Ezfio.has_mo_basis_disk_access_mo_one_integrals ()) then
get_default "disk_access_mo_one_integrals"
|> String.of_string
|> Ezfio.set_mo_basis_disk_access_mo_one_integrals
2014-10-24 00:25:15 +02:00
;
2018-10-17 16:28:57 +02:00
Ezfio.get_mo_basis_disk_access_mo_one_integrals ()
|> Disk_access.of_string
;;
(* Write snippet for disk_access_mo_one_integrals *)
let write_disk_access_mo_one_integrals var =
Disk_access.to_string var
|> Ezfio.set_mo_basis_disk_access_mo_one_integrals
;;
(* Read snippet for integral_kinetic *)
let read_integral_kinetic () =
if not (Ezfio.has_mo_basis_integral_kinetic ()) then
get_default "integral_kinetic"
|> Float.of_string
|> Ezfio.set_mo_basis_integral_kinetic
;
Ezfio.get_mo_basis_integral_kinetic ()
;;
(* Write snippet for integral_kinetic *)
let write_integral_kinetic =
Ezfio.set_mo_basis_integral_kinetic
;;
(* Read snippet for integral_nuclear *)
let read_integral_nuclear () =
if not (Ezfio.has_mo_basis_integral_nuclear ()) then
get_default "integral_nuclear"
|> Float.of_string
|> Ezfio.set_mo_basis_integral_nuclear
;
Ezfio.get_mo_basis_integral_nuclear ()
;;
(* Write snippet for integral_nuclear *)
let write_integral_nuclear =
Ezfio.set_mo_basis_integral_nuclear
;;
(* Read snippet for integral_pseudo *)
let read_integral_pseudo () =
if not (Ezfio.has_mo_basis_integral_pseudo ()) then
get_default "integral_pseudo"
|> Float.of_string
|> Ezfio.set_mo_basis_integral_pseudo
;
Ezfio.get_mo_basis_integral_pseudo ()
;;
(* Write snippet for integral_pseudo *)
let write_integral_pseudo =
Ezfio.set_mo_basis_integral_pseudo
;;
(* =~=~=~=~=~=~=~=~=~=~=~=~ *)
(* Generate Global Function *)
(* =~=~=~=~=~=~=~=~=~=~=~=~ *)
(* Read all *)
let read() =
Some
{
disk_access_mo_one_integrals = read_disk_access_mo_one_integrals ();
}
;;
(* Write all *)
let write{
disk_access_mo_one_integrals;
} =
write_disk_access_mo_one_integrals disk_access_mo_one_integrals;
;;
(* to_string*)
let to_string b =
Printf.sprintf "
disk_access_mo_one_integrals = %s
"
(Disk_access.to_string b.disk_access_mo_one_integrals)
;;
(* to_rst*)
let to_rst b =
Printf.sprintf "
Read/Write MO one-electron integrals from/to disk [ Write | Read | None ] ::
disk_access_mo_one_integrals = %s
"
(Disk_access.to_string b.disk_access_mo_one_integrals)
|> Rst_string.of_string
;;
include Generic_input_of_rst;;
let of_rst = of_rst t_of_sexp;;
end