10
0
mirror of https://github.com/LCPQ/quantum_package synced 2024-06-01 10:55:25 +02:00
quantum_package/ocaml/qptypes_generator.ml

210 lines
4.4 KiB
OCaml
Raw Normal View History

2014-08-26 15:31:16 +02:00
open Core.Std;;
let input_data = "
* Positive_float : float
assert (x >= 0.) ;
* Strictly_positive_float : float
assert (x > 0.) ;
* Negative_float : float
assert (x <= 0.) ;
* Strictly_negative_float : float
assert (x < 0.) ;
* Positive_int : int
assert (x >= 0) ;
* Strictly_positive_int : int
assert (x > 0) ;
* Negative_int : int
assert (x <= 0) ;
2014-10-20 12:19:12 +02:00
* Det_coef : float
assert (x >= -1.) ;
assert (x <= 1.) ;
* Normalized_float : float
assert (x <= 1.) ;
assert (x >= 0.) ;
2014-08-26 15:31:16 +02:00
* Strictly_negative_int : int
assert (x < 0) ;
* Non_empty_string : string
assert (x <> \"\") ;
* MO_number : int
assert (x > 0) ;
2014-09-17 11:49:00 +02:00
if (x > 1000) then
warning \"More than 1000 MOs\";
2014-08-26 15:31:16 +02:00
if (Ezfio.has_mo_basis_mo_tot_num ()) then
assert (x <= (Ezfio.get_mo_basis_mo_tot_num ()));
* AO_number : int
assert (x > 0) ;
2014-09-17 11:49:00 +02:00
if (x > 1000) then
warning \"More than 1000 AOs\";
2014-08-26 15:31:16 +02:00
if (Ezfio.has_ao_basis_ao_num ()) then
assert (x <= (Ezfio.get_ao_basis_ao_num ()));
2014-10-17 15:07:07 +02:00
* Nucl_number : int
assert (x > 0) ;
if (x > 1000) then
2014-10-23 14:42:14 +02:00
warning \"More than 1000 atoms\";
2014-10-17 15:07:07 +02:00
if (Ezfio.has_nuclei_nucl_num ()) then
assert (x <= (Ezfio.get_nuclei_nucl_num ()));
2014-08-26 15:31:16 +02:00
* N_int_number : int
assert (x > 0) ;
2014-09-17 11:49:00 +02:00
if (x > 100) then
warning \"N_int > 100\";
2014-08-26 15:31:16 +02:00
if (Ezfio.has_determinants_n_int ()) then
2014-09-18 17:01:43 +02:00
assert (x = (Ezfio.get_determinants_n_int ()));
2014-08-26 15:31:16 +02:00
* Det_number : int
assert (x > 0) ;
2014-09-17 11:49:00 +02:00
if (x > 100000000) then
warning \"More than 100 million determinants\";
2014-10-28 17:16:51 +01:00
if (Ezfio.has_determinants_n_det ()) then
assert (x <= (Ezfio.get_determinants_n_det ()));
* Det_number_max : int
assert (x > 0) ;
if (x > 100000000) then
warning \"More than 100 million determinants\";
2014-09-17 11:49:00 +02:00
2014-10-20 12:19:12 +02:00
* States_number : int
assert (x > 0) ;
if (x > 100) then
warning \"More than 100 states\";
if (Ezfio.has_determinants_n_states_diag ()) then
assert (x <= (Ezfio.get_determinants_n_states_diag ()))
else if (Ezfio.has_determinants_n_states ()) then
assert (x <= (Ezfio.get_determinants_n_states ()));
2014-09-17 11:49:00 +02:00
* Bit_kind_size : int
begin match x with
| 8 | 16 | 32 | 64 -> ()
| _ -> raise (Failure \"Bit_kind_size should be (8|16|32|64).\")
end;
* Bit_kind : int
begin match x with
| 1 | 2 | 4 | 8 -> ()
| _ -> raise (Failure \"Bit_kind should be (1|2|4|8).\")
end;
2014-10-22 00:12:23 +02:00
* Bitmask_number : int
assert (x > 0) ;
2014-09-18 17:01:43 +02:00
* MO_coef : float
2014-10-29 16:56:16 +01:00
* MO_occ : float
assert (x >= 0.);
2014-09-18 17:01:43 +02:00
* AO_coef : float
2014-10-22 00:12:23 +02:00
* AO_expo : float
assert (x >= 0.) ;
* AO_prim_number : int
assert (x > 0) ;
* Threshold : float
assert (x >= 0.) ;
assert (x <= 1.) ;
* PT2_energy : float
assert (x >=0.) ;
* Elec_alpha_number : int
assert (x > 0) ;
* Elec_beta_number : int
assert (x >= 0) ;
* Elec_number : int
assert (x > 0) ;
* MD5 : string
assert ((String.length x) = 32);
2014-10-29 22:13:03 +01:00
* Rst_string : string
2014-08-26 15:31:16 +02:00
"
;;
2014-10-20 12:19:12 +02:00
let untouched = "
2014-10-29 00:12:45 +01:00
(*
2014-10-20 12:19:12 +02:00
module Determinant : sig
2014-10-25 21:24:21 +02:00
type t with sexp
2014-10-20 12:19:12 +02:00
val to_int64_array : t -> int64 array
val of_int64_array : int64 array -> t
val to_string : t -> string
end = struct
2014-10-25 21:24:21 +02:00
type t = int64 array with sexp
2014-10-20 12:19:12 +02:00
let to_int64_array x = x
let of_int64_array x =
if (Ezfio.has_determinants_n_int ()) then
begin
let n_int = Ezfio.get_determinants_n_int () in
assert ((Array.length x) = n_int*2)
end
; x
let to_string x = Array.to_list x
|> List.map ~f:Int64.to_string
|> String.concat ~sep:\", \"
end
2014-10-29 00:12:45 +01:00
*)
2014-10-20 12:19:12 +02:00
"
2014-08-26 15:31:16 +02:00
let template = format_of_string "
module %s : sig
2014-10-25 21:24:21 +02:00
type t with sexp
2014-08-26 15:31:16 +02:00
val to_%s : t -> %s
val of_%s : %s -> t
2014-10-17 15:07:07 +02:00
val to_string : t -> string
2014-08-26 15:31:16 +02:00
end = struct
2014-10-25 21:24:21 +02:00
type t = %s with sexp
2014-08-26 15:31:16 +02:00
let to_%s x = x
let of_%s x = ( %s x )
2014-09-18 17:01:43 +02:00
let to_string x = %s.to_string x
2014-08-26 15:31:16 +02:00
end
"
;;
let parse_input input=
2014-09-18 17:01:43 +02:00
print_string "open Core.Std;;\nlet warning = print_string;;\n" ;
2014-08-26 15:31:16 +02:00
let rec parse result = function
| [] -> result
| ( "" , "" )::tail -> parse result tail
| ( t , text )::tail ->
let name , typ = String.lsplit2_exn ~on:':' t
in
let typ = String.strip typ
2014-09-18 17:01:43 +02:00
and name = String.strip name in
let typ_cap = String.capitalize typ in
2014-10-17 15:07:07 +02:00
let newstring = Printf.sprintf template name typ typ typ typ typ typ typ
2014-09-18 17:01:43 +02:00
( String.strip text ) typ_cap
2014-08-26 15:31:16 +02:00
in
List.rev (parse (newstring::result) tail )
in
String.split ~on:'*' input
|> List.map ~f:(String.lsplit2_exn ~on:'\n')
|> parse []
|> String.concat
|> print_string
;;
2014-10-20 12:19:12 +02:00
let () =
parse_input input_data ;
print_endline untouched
;;
2014-08-26 15:31:16 +02:00