Removed Qcaml_ prefixes

This commit is contained in:
Anthony Scemama 2020-10-09 09:47:57 +02:00
parent b9fb5e7903
commit 6217dc5a0a
75 changed files with 147 additions and 149 deletions

View File

@ -1,4 +1,4 @@
open Qcaml_linear_algebra
open Linear_algebra
type basis =
| Unknown
@ -14,7 +14,7 @@ let of_nuclei_and_basis_filename ?(kind=`Gaussian) ?operators ?(cartesian=false)
match kind with
| `Gaussian ->
let basis =
Qcaml_gaussian_basis.Basis.of_nuclei_and_basis_filename ~nuclei filename
Gaussian_basis.Basis.of_nuclei_and_basis_filename ~nuclei filename
in
let ao_basis =
Gaussian (Basis_gaussian.make ~basis ?operators ~cartesian nuclei )

View File

@ -1,9 +1,9 @@
(** Data structure for Atomic Orbitals. *)
open Qcaml_common
open Qcaml_particles
open Qcaml_operators
open Qcaml_linear_algebra
open Common
open Particles
open Operators
open Linear_algebra
type basis =
| Unknown

View File

@ -1,9 +1,9 @@
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Qcaml_gaussian_integrals
open Qcaml_operators
open Linear_algebra
open Gaussian_basis
open Gaussian_integrals
open Operators
module Basis = Qcaml_gaussian_basis.Basis
module Basis = Gaussian_basis.Basis
type t =
{

View File

@ -1,9 +1,9 @@
(** Data structure for Atomic Orbitals. *)
open Qcaml_common
open Qcaml_particles
open Qcaml_linear_algebra
open Qcaml_gaussian_integrals
open Qcaml_operators
open Common
open Particles
open Linear_algebra
open Gaussian_integrals
open Operators
type t
@ -12,7 +12,7 @@ type t
val size : t -> int
(** Number of atomic orbitals *)
val basis : t -> Qcaml_gaussian_basis.Basis.t
val basis : t -> Gaussian_basis.Basis.t
(** One-electron basis set *)
val overlap : t -> Overlap.t
@ -45,14 +45,14 @@ val kin_ints : t -> Kinetic.t
val cartesian : t -> bool
(** If true, use cartesian Gaussians (6d, 10f, ...) *)
val values : t -> Coordinate.t -> Qcaml_gaussian_basis.Basis.t Vector.t
val values : t -> Coordinate.t -> Gaussian_basis.Basis.t Vector.t
(** Values of the AOs evaluated at a given point *)
(** {1 Creators} *)
val make : basis:Qcaml_gaussian_basis.Basis.t -> ?operators:Operator.t list ->
val make : basis:Gaussian_basis.Basis.t -> ?operators:Operator.t list ->
?cartesian:bool -> Nuclei.t -> t
(** Creates the data structure for atomic orbitals from a Gaussian basis and the
molecular geometry {Nuclei.t} *)

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_ao)
(name ao)
(public_name qcaml.ao)
(libraries
qcaml.common

View File

@ -1,11 +1,10 @@
open Alcotest
open Qcaml_common
open Qcaml_particles
open Qcaml_operators
open Qcaml_linear_algebra
open Qcaml_ao.Basis
open Particles
open Operators
open Linear_algebra
open Ao.Basis
let wd = Qcaml.root ^ Filename.dir_sep ^ "test"
let wd = Common.Qcaml.root ^ Filename.dir_sep ^ "test"
let make_tests name t =
@ -90,7 +89,7 @@ let tests =
let rs = 0.5 in
let operators = [ Operator.of_range_separation rs ] in
let ao_basis =
Qcaml_ao.Basis.of_nuclei_and_basis_filename ~kind:`Gaussian
Ao.Basis.of_nuclei_and_basis_filename ~kind:`Gaussian
~operators ~cartesian:false ~nuclei basis_filename
in
make_tests "water" ao_basis ;

View File

@ -1,13 +1,12 @@
open Alcotest
open Qcaml_common
open Qcaml_gaussian_integrals
open Qcaml_gaussian_basis
open Qcaml_particles
open Qcaml_operators
open Qcaml_linear_algebra
open Qcaml_ao.Basis_gaussian
open Gaussian_integrals
open Gaussian_basis
open Particles
open Operators
open Linear_algebra
open Ao.Basis_gaussian
let wd = Qcaml.root ^ Filename.dir_sep ^ "test"
let wd = Common.Qcaml.root ^ Filename.dir_sep ^ "test"
let make_tests name t =
@ -92,7 +91,7 @@ let tests =
let rs = 0.5 in
let operators = [ Operator.of_range_separation rs ] in
let ao_basis =
Qcaml_ao.Basis_gaussian.make ~basis ~operators nuclei
Ao.Basis_gaussian.make ~basis ~operators nuclei
in
make_tests "water" ao_basis ;

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_common)
(name common)
(public_name qcaml.common)
(libraries
str

View File

@ -1,4 +1,4 @@
open Qcaml_common.Bitstring
open Common.Bitstring
let check msg x = Alcotest.(check bool) msg true x

View File

@ -1,4 +1,4 @@
open Qcaml_common.Util
open Common.Util
open Alcotest
let test_external () =

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t = {
expo : float array array;

View File

@ -30,7 +30,7 @@ where:
type t
open Qcaml_common
open Common
val make : ?index:int -> Contracted_shell.t array -> t
(** Creates a contracted shell from a list of coefficients and primitives. *)

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t =
{

View File

@ -3,7 +3,7 @@
type t
open Qcaml_common
open Common
val make : ?cutoff:float -> Atomic_shell.t -> Atomic_shell.t -> t option

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t =
{

View File

@ -13,7 +13,7 @@ acting on different electrons, since they will be coupled by a two-electron oper
type t
open Qcaml_common
open Common
val make : ?cutoff:float -> Atomic_shell_pair.t -> Atomic_shell_pair.t -> t option
(** Creates an atomic shell pair couple using two atomic shell pairs.

View File

@ -2,7 +2,7 @@
type t
open Qcaml_particles
open Particles
val of_nuclei_and_general_basis : Nuclei.t -> General_basis.t -> t
(** Takes an array of {!Nuclei.t}, and a {!GeneralBasis.t} (such as cc-pVDZ

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t = {
expo : float array;

View File

@ -28,7 +28,7 @@ where:
type t
open Qcaml_common
open Common
val make : ?index:int -> (float * Primitive_shell.t) array -> t
(** Creates a contracted shell from a list of coefficients and primitives. *)

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t =
{

View File

@ -13,7 +13,7 @@ A contracted shell pair is a product of two {!Contracted_shell.t}:
type t
open Qcaml_common
open Common
val make : ?cutoff:float -> Contracted_shell.t -> Contracted_shell.t -> t option
(** Creates an contracted shell pair {% $\varphi_{ab}$ %} from a contracted

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t =
{

View File

@ -13,7 +13,7 @@ acting on different electrons, since they will be coupled by a two-electron oper
type t
open Qcaml_common
open Common
val make : ?cutoff:float -> Contracted_shell_pair.t -> Contracted_shell_pair.t -> t option
(** Creates a contracted shell pair couple using two contracted shell pairs.

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_gaussian_basis)
(name gaussian_basis)
(public_name qcaml.gaussian_basis)
(libraries
str

View File

@ -1,7 +1,7 @@
(** General basis set read from a file *)
open Qcaml_common
open Qcaml_particles
open Common
open Particles
type primitive =
{

View File

@ -28,8 +28,8 @@ are created by picking the data from the general basis set. This data structure
simplifies the creation of the atomic basis set.
*)
open Qcaml_common
open Qcaml_particles
open Common
open Particles
type primitive = private
{

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
open Util
open Constants

View File

@ -20,7 +20,7 @@ where:
type t
open Qcaml_common
open Common
val to_string : t -> string
(** Pretty-printing of the primitive shell in a string. *)

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
open Constants

View File

@ -37,7 +37,7 @@ References:
type t
open Qcaml_common
open Common
val make : Primitive_shell.t -> Primitive_shell.t -> t
(** Creates a primitive shell pair using two primitive shells. *)

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
type t =
{

View File

@ -13,7 +13,7 @@ acting on different electrons, since they will be coupled by a two-electron oper
type t
open Qcaml_common
open Common
val make : Primitive_shell_pair.t -> Primitive_shell_pair.t -> t
(** Creates a primitive shell pair couple using two primitive shell pairs.

View File

@ -1,9 +1,9 @@
open Qcaml_common
open Qcaml_particles
open Qcaml_gaussian_basis
open Common
open Particles
open Gaussian_basis
open Alcotest
let wd = Qcaml.root ^ Filename.dir_sep ^ "test"
let wd = Common.Qcaml.root ^ Filename.dir_sep ^ "test"
let test_read () =
let oxygen = Element.of_string "O" in

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_gaussian_integrals)
(name gaussian_integrals)
(public_name qcaml.gaussian_integrals)
(libraries
str

View File

@ -1,9 +1,9 @@
(** Electron-nucleus repulsion integrals *)
include Qcaml_common
include Qcaml_particles
include Qcaml_linear_algebra
include Qcaml_gaussian_basis
include Common
include Particles
include Linear_algebra
include Gaussian_basis
open Util
open Constants

View File

@ -8,8 +8,8 @@ $$ %}
include module type of Matrix_on_basis
open Qcaml_particles
open Qcaml_gaussian_basis
open Particles
open Gaussian_basis
val of_basis_nuclei : basis:Basis.t -> Nuclei.t -> t
(** Build from a {Basis.t} and the nuclei (coordinates and charges). *)

View File

@ -1,7 +1,7 @@
(** Electron-electron repulsion integrals *)
open Qcaml_common
open Qcaml_gaussian_basis
open Common
open Gaussian_basis
module Csp = Contracted_shell_pair
module Cspc = Contracted_shell_pair_couple

View File

@ -2,9 +2,9 @@
See Eq(52) in 10.1039/b605188j
*)
open Qcaml_common
open Qcaml_gaussian_basis
open Qcaml_operators
open Common
open Gaussian_basis
open Operators
module Csp = Contracted_shell_pair
module Cspc = Contracted_shell_pair_couple

View File

@ -2,8 +2,8 @@
It is parameterized by the [zero_m] function.
*)
open Qcaml_common
open Qcaml_operators
open Common
open Operators
open Constants
let cutoff = integrals_cutoff

View File

@ -1,5 +1,5 @@
open Qcaml_common
open Qcaml_gaussian_basis
open Common
open Gaussian_basis
module Am = Angular_momentum
module Asp = Atomic_shell_pair

View File

@ -1,6 +1,6 @@
open Qcaml_common
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Common
open Linear_algebra
open Gaussian_basis
open Util
open Constants

View File

@ -1,7 +1,7 @@
(** Signature for matrices built on the {!Basis.t} *)
open Qcaml_gaussian_basis
open Qcaml_linear_algebra
open Gaussian_basis
open Linear_algebra
type t = (Basis.t, Basis.t) Matrix.t

View File

@ -1,6 +1,6 @@
open Qcaml_common
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Common
open Linear_algebra
open Gaussian_basis
open Constants
type t = (Basis.t, Basis.t) Matrix.t array

View File

@ -9,8 +9,8 @@
*)
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Linear_algebra
open Gaussian_basis
type t = (Basis.t, Basis.t) Matrix.t array

View File

@ -1,8 +1,8 @@
open Qcaml_common
open Qcaml_particles
open Common
open Particles
open Util
open Constants
open Qcaml_gaussian_basis
open Gaussian_basis
exception NullPair

View File

@ -1,6 +1,6 @@
open Qcaml_common
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Common
open Linear_algebra
open Gaussian_basis
module Am = Angular_momentum
module Bs = Basis

View File

@ -1,7 +1,7 @@
(** Orthonormalization of the basis. *)
open Qcaml_gaussian_basis
open Qcaml_linear_algebra
open Gaussian_basis
open Linear_algebra
type t = (Basis.t, Basis.t) Matrix.t

View File

@ -1,6 +1,6 @@
open Qcaml_common
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Common
open Linear_algebra
open Gaussian_basis
open Util
open Constants

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
open Util

View File

@ -1,8 +1,8 @@
(** Screened Electron-electron repulsion integrals (Yukawa potential). Required for F12/r12. *)
open Qcaml_common
open Qcaml_gaussian_basis
open Qcaml_operators
open Common
open Gaussian_basis
open Operators
module Csp = Contracted_shell_pair
module Cspc = Contracted_shell_pair_couple

View File

@ -1,10 +1,10 @@
(** Two electron integrals
*)
open Qcaml_common
open Qcaml_linear_algebra
open Qcaml_gaussian_basis
open Qcaml_operators
open Common
open Linear_algebra
open Gaussian_basis
open Operators
open Constants
let cutoff = integrals_cutoff

View File

@ -5,10 +5,10 @@
*)
open Qcaml_common
open Qcaml_gaussian_basis
open Qcaml_linear_algebra
open Qcaml_operators
open Common
open Gaussian_basis
open Linear_algebra
open Operators
module type Two_ei_structure =
sig

View File

@ -1,5 +1,5 @@
open Qcaml_common
open Qcaml_gaussian_basis
open Common
open Gaussian_basis
module Am = Angular_momentum
module Asp = Atomic_shell_pair

View File

@ -1,6 +1,6 @@
open Qcaml_common
open Qcaml_gaussian_basis
open Qcaml_linear_algebra
open Common
open Gaussian_basis
open Linear_algebra
module Am = Angular_momentum
module Co = Coordinate

View File

@ -1,5 +1,5 @@
open Qcaml_common
open Qcaml_operators
open Common
open Operators
type t =
{

View File

@ -1,9 +1,9 @@
open Qcaml_common
open Qcaml_particles
open Qcaml_gaussian_basis
open Common
open Particles
open Gaussian_basis
open Alcotest
let wd = Qcaml.root ^ Filename.dir_sep ^ "test"
let wd = Common.Qcaml.root ^ Filename.dir_sep ^ "test"
let test_read () =
let oxygen = Element.of_string "O" in

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_linear_algebra)
(name linear_algebra)
(public_name qcaml.linear_algebra)
(libraries
qcaml.common

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
let max_index = 1 lsl 14

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
module Am = Angular_momentum

View File

@ -1,6 +1,6 @@
(** Conversion from spherical coordinate to cartesian corrdinates. *)
open Qcaml_common
open Common
type num_cartesian_ao
type num_spherical_ao

View File

@ -1,4 +1,4 @@
open Qcaml_linear_algebra
open Linear_algebra
open Alcotest
open Lacaml.D

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_operators)
(name operators)
(public_name qcaml.operators)
(libraries
str

View File

@ -1,7 +1,7 @@
; name = name of the supermodule that will wrap all source files as submodules
; public_name = name of the library for ocamlfind and opam
(library
(name qcaml_particles)
(name particles)
(public_name qcaml.particles)
(libraries
str

View File

@ -1,6 +1,6 @@
(** Number of {% $\alpha$ %} and {% $\beta$ %} electrons *)
open Qcaml_common
open Common
type t = {
n_alfa : int ;

View File

@ -1,6 +1,6 @@
(** Information related to electrons. *)
open Qcaml_common
open Common
type t

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
exception ElementError of string

View File

@ -1,6 +1,6 @@
(** Chemical elements. *)
open Qcaml_common
open Common
exception ElementError of string

View File

@ -1,3 +1,3 @@
(** Atomic mass. *)
include Qcaml_common.Non_negative_float
include Common.Non_negative_float

View File

@ -1,3 +1,3 @@
(** Atomic mass. *)
include module type of Qcaml_common.Non_negative_float
include module type of Common.Non_negative_float

View File

@ -1,4 +1,4 @@
open Qcaml_common
open Common
open Xyz_ast
type t = (Element.t * Coordinate.t) array

View File

@ -2,7 +2,7 @@
of tuples ({!Element.t}, {!Coordinate.t}).
*)
open Qcaml_common
open Common
type t = (Element.t * Coordinate.t) array

View File

@ -1,7 +1,7 @@
(** When an [xyz] file is read by the [Xyz_parser.mly], it is converted into
an {!xyz_file} data structure. *)
open Qcaml_common
open Common
type nucleus =
{

View File

@ -1,7 +1,7 @@
/* Parses nuclear coordinates in xyz format */
%{
open Qcaml_common
open Common
let make_angstrom x y z =
Coordinate.(make_angstrom {

View File

@ -1,5 +1,5 @@
open Qcaml_common
open Qcaml_particles
open Common
open Particles
open Alcotest

View File

@ -1,8 +1,8 @@
open Qcaml_common
open Qcaml_particles
open Common
open Particles
open Alcotest
let wd = Qcaml.root ^ Filename.dir_sep ^ "test"
let wd = Common.Qcaml.root ^ Filename.dir_sep ^ "test"
let test_xyz molecule length repulsion charge core =
let xyz = Nuclei.of_xyz_file (wd^Filename.dir_sep^molecule^".xyz") in