2017-06-13 12:20:55 +02:00
|
|
|
open Qptypes
|
|
|
|
open Qputils
|
2017-08-18 18:28:33 +02:00
|
|
|
open Core
|
2014-10-24 00:25:15 +02:00
|
|
|
|
2015-03-26 18:24:40 +01:00
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
module Mo_basis : sig
|
2017-09-19 18:59:32 +02:00
|
|
|
type t =
|
|
|
|
{ mo_tot_num : MO_number.t ;
|
|
|
|
mo_label : MO_label.t;
|
|
|
|
mo_class : MO_class.t array;
|
|
|
|
mo_occ : MO_occ.t array;
|
|
|
|
mo_coef : (MO_coef.t array) array;
|
|
|
|
ao_md5 : MD5.t;
|
|
|
|
} [@@deriving sexp]
|
2014-11-27 23:05:26 +01:00
|
|
|
val read : unit -> t option
|
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
|
2014-10-24 00:25:15 +02:00
|
|
|
end = struct
|
2017-09-19 18:59:32 +02:00
|
|
|
type t =
|
|
|
|
{ mo_tot_num : MO_number.t ;
|
|
|
|
mo_label : MO_label.t;
|
|
|
|
mo_class : MO_class.t array;
|
|
|
|
mo_occ : MO_occ.t array;
|
|
|
|
mo_coef : (MO_coef.t array) array;
|
|
|
|
ao_md5 : MD5.t;
|
|
|
|
} [@@deriving sexp]
|
2017-06-13 12:20:55 +02:00
|
|
|
let get_default = Qpackage.get_ezfio_default "mo_basis"
|
2014-10-24 00:25:15 +02:00
|
|
|
|
|
|
|
let read_mo_label () =
|
|
|
|
if not (Ezfio.has_mo_basis_mo_label ()) then
|
2017-06-13 12:20:55 +02:00
|
|
|
Ezfio.set_mo_basis_mo_label "None"
|
2014-10-24 00:25:15 +02:00
|
|
|
;
|
|
|
|
Ezfio.get_mo_basis_mo_label ()
|
2014-10-29 16:56:16 +01:00
|
|
|
|> MO_label.of_string
|
2017-06-13 12:20:55 +02:00
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
|
2014-12-25 23:53:29 +01:00
|
|
|
let read_ao_md5 () =
|
|
|
|
let ao_md5 =
|
|
|
|
match (Input_ao_basis.Ao_basis.read ()) with
|
|
|
|
| None -> failwith "Unable to read AO basis"
|
|
|
|
| Some result -> Input_ao_basis.Ao_basis.to_md5 result
|
|
|
|
in
|
|
|
|
let result =
|
|
|
|
if not (Ezfio.has_mo_basis_ao_md5 ()) then
|
|
|
|
begin
|
|
|
|
MD5.to_string ao_md5
|
|
|
|
|> Ezfio.set_mo_basis_ao_md5
|
|
|
|
end;
|
|
|
|
Ezfio.get_mo_basis_ao_md5 ()
|
|
|
|
|> MD5.of_string
|
|
|
|
in
|
|
|
|
if (ao_md5 <> result) then
|
|
|
|
failwith "The current MOs don't correspond to the current AOs.";
|
|
|
|
result
|
2017-06-13 12:20:55 +02:00
|
|
|
|
2014-12-25 23:53:29 +01:00
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
let read_mo_tot_num () =
|
|
|
|
Ezfio.get_mo_basis_mo_tot_num ()
|
|
|
|
|> MO_number.of_int
|
2017-06-13 12:20:55 +02:00
|
|
|
|
|
|
|
|
|
|
|
let read_mo_class () =
|
|
|
|
if not (Ezfio.has_mo_basis_mo_class ()) then
|
|
|
|
begin
|
|
|
|
let mo_tot_num = MO_number.to_int (read_mo_tot_num ()) in
|
|
|
|
let data =
|
|
|
|
Array.init mo_tot_num ~f:(fun _ -> MO_class.(to_string (Active [])))
|
|
|
|
|> Array.to_list
|
|
|
|
in
|
|
|
|
Ezfio.ezfio_array_of_list ~rank:1
|
|
|
|
~dim:[| mo_tot_num |] ~data:data
|
|
|
|
|> Ezfio.set_mo_basis_mo_class
|
|
|
|
end;
|
|
|
|
Ezfio.flattened_ezfio (Ezfio.get_mo_basis_mo_class () )
|
|
|
|
|> Array.map ~f:MO_class.of_string
|
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
|
|
|
|
let read_mo_occ () =
|
|
|
|
if not (Ezfio.has_mo_basis_mo_label ()) then
|
|
|
|
begin
|
|
|
|
let elec_alpha_num = Ezfio.get_electrons_elec_alpha_num ()
|
|
|
|
and elec_beta_num = Ezfio.get_electrons_elec_beta_num ()
|
|
|
|
and mo_tot_num = MO_number.to_int (read_mo_tot_num ()) in
|
|
|
|
let data = Array.init mo_tot_num ~f:(fun i ->
|
2017-06-13 12:20:55 +02:00
|
|
|
if (i<elec_beta_num) then 2.
|
|
|
|
else if (i < elec_alpha_num) then 1.
|
|
|
|
else 0.) |> Array.to_list in
|
2014-10-24 00:25:15 +02:00
|
|
|
Ezfio.ezfio_array_of_list ~rank:1
|
|
|
|
~dim:[| mo_tot_num |] ~data:data
|
|
|
|
|> Ezfio.set_mo_basis_mo_occ
|
|
|
|
end;
|
2014-11-03 17:37:16 +01:00
|
|
|
Ezfio.flattened_ezfio (Ezfio.get_mo_basis_mo_occ () )
|
2014-10-29 16:56:16 +01:00
|
|
|
|> Array.map ~f:MO_occ.of_float
|
2017-06-13 12:20:55 +02:00
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
|
|
|
|
let read_mo_coef () =
|
2014-11-03 17:37:16 +01:00
|
|
|
let a = Ezfio.get_mo_basis_mo_coef ()
|
2017-06-13 12:20:55 +02:00
|
|
|
|> Ezfio.flattened_ezfio
|
|
|
|
|> Array.map ~f:MO_coef.of_float
|
2014-10-29 16:56:16 +01:00
|
|
|
in
|
|
|
|
let mo_tot_num = read_mo_tot_num () |> MO_number.to_int in
|
|
|
|
let ao_num = (Array.length a)/mo_tot_num in
|
|
|
|
Array.init mo_tot_num ~f:(fun j ->
|
2017-06-13 12:20:55 +02:00
|
|
|
Array.sub ~pos:(j*ao_num) ~len:(ao_num) a
|
|
|
|
)
|
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
|
|
|
|
let read () =
|
2014-11-27 23:05:26 +01:00
|
|
|
if (Ezfio.has_mo_basis_mo_tot_num ()) then
|
|
|
|
Some
|
2017-06-13 12:20:55 +02:00
|
|
|
{ mo_tot_num = read_mo_tot_num ();
|
|
|
|
mo_label = read_mo_label () ;
|
|
|
|
mo_class = read_mo_class ();
|
|
|
|
mo_occ = read_mo_occ ();
|
|
|
|
mo_coef = read_mo_coef ();
|
|
|
|
ao_md5 = read_ao_md5 ();
|
|
|
|
}
|
2014-11-27 23:05:26 +01:00
|
|
|
else
|
|
|
|
None
|
2017-06-13 12:20:55 +02:00
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
|
2014-10-29 16:56:16 +01:00
|
|
|
let mo_coef_to_string mo_coef =
|
|
|
|
let ao_num = Array.length mo_coef.(0)
|
|
|
|
and mo_tot_num = Array.length mo_coef in
|
|
|
|
let rec print_five imin imax =
|
|
|
|
match (imax-imin+1) with
|
|
|
|
| 1 ->
|
2017-06-13 12:20:55 +02:00
|
|
|
let header = [ Printf.sprintf " #%15d" (imin+1) ; ] in
|
|
|
|
let new_lines =
|
|
|
|
List.init ao_num ~f:(fun i ->
|
2014-10-29 16:56:16 +01:00
|
|
|
Printf.sprintf " %3d %15.10f " (i+1)
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_coef.to_float mo_coef.(imin ).(i)) )
|
|
|
|
in header @ new_lines
|
2014-10-29 16:56:16 +01:00
|
|
|
| 2 ->
|
2017-06-13 12:20:55 +02:00
|
|
|
let header = [ Printf.sprintf " #%15d %15d" (imin+1) (imin+2) ; ] in
|
|
|
|
let new_lines =
|
|
|
|
List.init ao_num ~f:(fun i ->
|
2014-10-29 16:56:16 +01:00
|
|
|
Printf.sprintf " %3d %15.10f %15.10f" (i+1)
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_coef.to_float mo_coef.(imin ).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+1).(i)) )
|
|
|
|
in header @ new_lines
|
2014-10-29 16:56:16 +01:00
|
|
|
| 3 ->
|
2017-06-13 12:20:55 +02:00
|
|
|
let header = [ Printf.sprintf " #%15d %15d %15d"
|
|
|
|
(imin+1) (imin+2) (imin+3); ] in
|
|
|
|
let new_lines =
|
|
|
|
List.init ao_num ~f:(fun i ->
|
2014-10-29 16:56:16 +01:00
|
|
|
Printf.sprintf " %3d %15.10f %15.10f %15.10f" (i+1)
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_coef.to_float mo_coef.(imin ).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+1).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+2).(i)) )
|
|
|
|
in header @ new_lines
|
2014-10-29 16:56:16 +01:00
|
|
|
| 4 ->
|
2017-06-13 12:20:55 +02:00
|
|
|
let header = [ Printf.sprintf " #%15d %15d %15d %15d"
|
|
|
|
(imin+1) (imin+2) (imin+3) (imin+4) ; ] in
|
|
|
|
let new_lines =
|
|
|
|
List.init ao_num ~f:(fun i ->
|
2014-10-29 16:56:16 +01:00
|
|
|
Printf.sprintf " %3d %15.10f %15.10f %15.10f %15.10f" (i+1)
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_coef.to_float mo_coef.(imin ).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+1).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+2).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+3).(i)) )
|
|
|
|
in header @ new_lines
|
2014-10-29 16:56:16 +01:00
|
|
|
| 5 ->
|
2017-06-13 12:20:55 +02:00
|
|
|
let header = [ Printf.sprintf " #%15d %15d %15d %15d %15d"
|
|
|
|
(imin+1) (imin+2) (imin+3) (imin+4) (imin+5) ; ] in
|
|
|
|
let new_lines =
|
|
|
|
List.init ao_num ~f:(fun i ->
|
2014-10-29 16:56:16 +01:00
|
|
|
Printf.sprintf " %3d %15.10f %15.10f %15.10f %15.10f %15.10f" (i+1)
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_coef.to_float mo_coef.(imin ).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+1).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+2).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+3).(i))
|
|
|
|
(MO_coef.to_float mo_coef.(imin+4).(i)) )
|
|
|
|
in header @ new_lines
|
2014-10-29 16:56:16 +01:00
|
|
|
| _ -> assert false
|
|
|
|
in
|
|
|
|
let rec create_list accu i =
|
2014-10-29 22:13:03 +01:00
|
|
|
if (i+4 < mo_tot_num) then
|
|
|
|
create_list ( (print_five i (i+3) |> String.concat ~sep:"\n")::accu ) (i+4)
|
2014-10-29 16:56:16 +01:00
|
|
|
else
|
|
|
|
(print_five i (mo_tot_num-1) |> String.concat ~sep:"\n")::accu |> List.rev
|
|
|
|
in
|
|
|
|
create_list [] 0 |> String.concat ~sep:"\n\n"
|
2017-06-13 12:20:55 +02:00
|
|
|
|
2014-10-29 16:56:16 +01:00
|
|
|
|
2014-10-29 22:13:03 +01:00
|
|
|
let to_rst b =
|
2014-10-24 00:25:15 +02:00
|
|
|
Printf.sprintf "
|
2014-10-29 00:12:45 +01:00
|
|
|
Label of the molecular orbitals ::
|
|
|
|
|
|
|
|
mo_label = %s
|
|
|
|
|
|
|
|
Total number of MOs ::
|
|
|
|
|
|
|
|
mo_tot_num = %s
|
|
|
|
|
2014-10-29 16:56:16 +01:00
|
|
|
MO coefficients ::
|
|
|
|
|
|
|
|
%s
|
2014-10-28 17:16:51 +01:00
|
|
|
"
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_label.to_string b.mo_label)
|
|
|
|
(MO_number.to_string b.mo_tot_num)
|
|
|
|
(mo_coef_to_string b.mo_coef)
|
2014-10-29 22:13:03 +01:00
|
|
|
|> Rst_string.of_string
|
2014-10-28 17:16:51 +01:00
|
|
|
|
2017-06-13 12:20:55 +02:00
|
|
|
|
2014-10-28 17:16:51 +01:00
|
|
|
|
2014-10-29 22:13:03 +01:00
|
|
|
let to_string b =
|
2014-10-28 17:16:51 +01:00
|
|
|
Printf.sprintf "
|
|
|
|
mo_label = %s
|
2014-10-24 00:25:15 +02:00
|
|
|
mo_tot_num = \"%s\"
|
2017-06-13 12:20:55 +02:00
|
|
|
mo_clas = %s
|
2014-10-24 00:25:15 +02:00
|
|
|
mo_occ = %s
|
|
|
|
mo_coef = %s
|
|
|
|
"
|
2017-06-13 12:20:55 +02:00
|
|
|
(MO_label.to_string b.mo_label)
|
|
|
|
(MO_number.to_string b.mo_tot_num)
|
|
|
|
(b.mo_class |> Array.to_list |> List.map
|
|
|
|
~f:(MO_class.to_string) |> String.concat ~sep:", " )
|
|
|
|
(b.mo_occ |> Array.to_list |> List.map
|
|
|
|
~f:(MO_occ.to_string) |> String.concat ~sep:", " )
|
|
|
|
(b.mo_coef |> Array.map
|
|
|
|
~f:(fun x-> Array.map ~f:MO_coef.to_string x |> String.concat_array
|
|
|
|
~sep:"," ) |>
|
|
|
|
String.concat_array ~sep:"\n" )
|
|
|
|
|
2014-10-24 00:25:15 +02:00
|
|
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|