(git:97501a3)
Loading...
Searching...
No Matches
qs_dispersion_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Definition of disperson types for DFT calculations
10!> \author JGH (20.10.2008)
11! **************************************************************************************************
13
14 USE eeq_input, ONLY: eeq_solver_type
16 USE kinds, ONLY: default_path_length,&
18 dp
21#include "./base/base_uses.f90"
22
23 IMPLICIT NONE
24
25 PRIVATE
26
27 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_dispersion_types'
28
29! **************************************************************************************************
30 INTEGER, PARAMETER :: dftd2_pp = 1
31 INTEGER, PARAMETER :: dftd3_pp = 2
32 INTEGER, PARAMETER :: dftd4_pp = 3
33
35 INTEGER :: TYPE = -1
36 INTEGER :: pp_type = -1
37 INTEGER :: nl_type = -1
38 CHARACTER(LEN=default_string_length) :: ref_functional = ""
39 REAL(kind=dp) :: scaling = -1.0_dp
40 REAL(kind=dp) :: rc_disp = -1.0_dp
41 REAL(kind=dp) :: rc_d4 = -1.0_dp
42 REAL(kind=dp) :: rc_cn = -1.0_dp
43 REAL(kind=dp) :: exp_pre = -1.0_dp
44 TYPE(section_vals_type), POINTER :: dftd_section => null()
45 LOGICAL :: verbose = .false. !extended output
46 CHARACTER(LEN=default_path_length) :: parameter_file_name = ""
47 CHARACTER(LEN=default_path_length) :: kernel_file_name = ""
48 !charges
49 LOGICAL :: ext_charges = .false.
50 REAL(kind=dp), DIMENSION(:), POINTER :: charges => null() !charges for D4
51 REAL(kind=dp), DIMENSION(:), POINTER :: dcharges => null() !derivatives of D4 energy wrt charges
52 TYPE(eeq_solver_type) :: eeq_sparam ! parameters for EEQ solver
53 !DFT-D3 global parameters
54 INTEGER :: max_elem = -1 !elements parametrized
55 INTEGER :: maxc = -1 !max coordination number references per element
56 REAL(kind=dp) :: k1 = -1.0_dp, k2 = -1.0_dp, k3 = -1.0_dp !ad hoc parameters
57 REAL(kind=dp) :: alp = -1.0_dp !ad hoc parameters
58 REAL(kind=dp) :: s6 = -1.0_dp, s8 = -1.0_dp, sr6 = -1.0_dp !scaling parameters
59 REAL(kind=dp) :: a1 = -1.0_dp, a2 = -1.0_dp !BJ scaling parameters
60 REAL(kind=dp) :: eps_cn = -1.0_dp
61 LOGICAL :: d4_reference_code = .false. !Use D4 calculation from ext. library
62 LOGICAL :: d4_debug = .false. !Output debug information for D4
63 LOGICAL :: doabc = .false. !neglect C9 terms
64 LOGICAL :: c9cnst = .false. !use constant c9 terms
65 LOGICAL :: lrc = .false. !calculate a long range correction
66 LOGICAL :: srb = .false. !calculate a short range bond correction
67 REAL(kind=dp), DIMENSION(4) :: srb_params = -1.0_dp ! parameters for SRB (s,g,t1,t2)
68 REAL(kind=dp) :: s9 = -1.0_dp !scale the many-body dispersion energy (default=1.0), dftd4
70 DIMENSION(:), POINTER :: sab_vdw => null(), sab_cn => null() ! neighborlists for pair interactions
71 REAL(kind=dp), DIMENSION(:, :, :, :, :), POINTER &
72 :: c6ab => null()
73 INTEGER, DIMENSION(:), POINTER :: maxci => null()
74 REAL(kind=dp), DIMENSION(:, :), POINTER :: r0ab => null()
75 REAL(kind=dp), DIMENSION(:), POINTER :: rcov => null() !covalent radii
76 REAL(kind=dp), DIMENSION(:), POINTER :: eneg => null() !electronegativity
77 REAL(kind=dp), DIMENSION(:), POINTER :: r2r4 => null() !atomic <r^2>/<r^4> values
78 INTEGER :: cnfun = 1 ! CN function to be used
79 REAL(kind=dp), DIMENSION(:), POINTER :: cn => null()
80 TYPE(cn_kind_list), DIMENSION(:), POINTER :: cnkind => null()
81 TYPE(cn_atom_list), DIMENSION(:), POINTER :: cnlist => null()
82 ! KG molecular corrections
83 LOGICAL :: domol = .false.
84 REAL(kind=dp) :: kgc8 = -1.0_dp !s8 scaling parameter
85 !vdW-DF variables
86 REAL(kind=dp) :: pw_cutoff = -1.0_dp
87 !parameters for the rVV10 functional
88 REAL(kind=dp) :: b_value = -1.0_dp, c_value = -1.0_dp, scale_rvv10 = -1.0_dp
89 INTEGER :: nqs = -1, nr_points = -1
90 !! The number of q points and radial points
91 !! used in generating the kernel phi(q1*r, q2*r)
92 !! (see DION 14-16 and SOLER 3)
93 REAL(kind=dp) :: r_max = -1.0_dp, q_cut = -1.0_dp, q_min = -1.0_dp, dk = -1.0_dp
94 !! The maximum value of r, the maximum and minimum
95 !! values of q and the k-space spacing of grid points.
96 !! Note that, during a vdW run, values of q0 found
97 !! larger than q_cut will be saturated (SOLER 6-7) to
98 !! q_cut
99 REAL(kind=dp), DIMENSION(:), POINTER :: q_mesh => null() !! The values of all the q points used
100 REAL(kind=dp), DIMENSION(:, :, :), POINTER &
101 :: kernel => null() !! A matrix holding the Fourier transformed kernel function
102 !! for each pair of q values. The ordering is
103 !! kernel(k_point, q1_value, q2_value)
104 REAL(kind=dp), DIMENSION(:, :, :), POINTER &
105 :: d2phi_dk2 => null() !! A matrix holding the second derivatives of the above
106 !! kernel matrix at each of the q points. Stored as
107 !! d2phi_dk2(k_point, q1_value, q2_value)
108 REAL(kind=dp), DIMENSION(:, :), POINTER :: d2y_dx2 => null() !! 2nd derivatives of q_mesh for interpolation
109 INTEGER, DIMENSION(:, :), POINTER :: d3_exclude_pair => null()
110 INTEGER :: nd3_exclude_pair = -1
111 END TYPE qs_dispersion_type
112
114 INTEGER :: TYPE = -1
115 LOGICAL :: defined = .false.
116 REAL(kind=dp) :: vdw_radii = -1.0_dp !van der Waals radii
117 REAL(kind=dp) :: c6 = -1.0_dp !c6 coefficients
119
120 TYPE cn_kind_list
121 REAL(kind=dp) :: cnum = -1.0_dp
122 INTEGER :: kind = -1
123 END TYPE cn_kind_list
124 TYPE cn_atom_list
125 REAL(kind=dp) :: cnum = -1.0_dp
126 INTEGER :: natom = -1
127 INTEGER, DIMENSION(:), POINTER :: atom => null()
128 END TYPE cn_atom_list
129
130! **************************************************************************************************
131
133 PUBLIC :: dftd2_pp, dftd3_pp, dftd4_pp
134 PUBLIC :: qs_dispersion_release
135
136! **************************************************************************************************
137CONTAINS
138! **************************************************************************************************
139!> \brief ...
140!> \param dispersion_env ...
141! **************************************************************************************************
142 SUBROUTINE qs_dispersion_release(dispersion_env)
143
144 TYPE(qs_dispersion_type), POINTER :: dispersion_env
145
146 INTEGER :: i
147
148 IF (ASSOCIATED(dispersion_env)) THEN
149 ! DFT-D3 arrays
150 IF (ASSOCIATED(dispersion_env%maxci)) THEN
151 DEALLOCATE (dispersion_env%maxci)
152 END IF
153 IF (ASSOCIATED(dispersion_env%c6ab)) THEN
154 DEALLOCATE (dispersion_env%c6ab)
155 END IF
156 IF (ASSOCIATED(dispersion_env%r0ab)) THEN
157 DEALLOCATE (dispersion_env%r0ab)
158 END IF
159 IF (ASSOCIATED(dispersion_env%rcov)) THEN
160 DEALLOCATE (dispersion_env%rcov)
161 END IF
162 IF (ASSOCIATED(dispersion_env%eneg)) THEN
163 DEALLOCATE (dispersion_env%eneg)
164 END IF
165 IF (ASSOCIATED(dispersion_env%r2r4)) THEN
166 DEALLOCATE (dispersion_env%r2r4)
167 END IF
168 IF (ASSOCIATED(dispersion_env%cn)) THEN
169 DEALLOCATE (dispersion_env%cn)
170 END IF
171 IF (ASSOCIATED(dispersion_env%cnkind)) THEN
172 DEALLOCATE (dispersion_env%cnkind)
173 END IF
174 IF (ASSOCIATED(dispersion_env%cnlist)) THEN
175 DO i = 1, SIZE(dispersion_env%cnlist)
176 DEALLOCATE (dispersion_env%cnlist(i)%atom)
177 END DO
178 DEALLOCATE (dispersion_env%cnlist)
179 END IF
180 ! vdD-DF
181 IF (ASSOCIATED(dispersion_env%q_mesh)) THEN
182 DEALLOCATE (dispersion_env%q_mesh)
183 END IF
184 IF (ASSOCIATED(dispersion_env%kernel)) THEN
185 DEALLOCATE (dispersion_env%kernel)
186 END IF
187 IF (ASSOCIATED(dispersion_env%d2phi_dk2)) THEN
188 DEALLOCATE (dispersion_env%d2phi_dk2)
189 END IF
190 IF (ASSOCIATED(dispersion_env%d2y_dx2)) THEN
191 DEALLOCATE (dispersion_env%d2y_dx2)
192 END IF
193 IF (ASSOCIATED(dispersion_env%d3_exclude_pair)) THEN
194 DEALLOCATE (dispersion_env%d3_exclude_pair)
195 END IF
196 ! neighborlists
197 CALL release_neighbor_list_sets(dispersion_env%sab_vdw)
198 CALL release_neighbor_list_sets(dispersion_env%sab_cn)
199 ! charges
200 IF (ASSOCIATED(dispersion_env%charges)) THEN
201 DEALLOCATE (dispersion_env%charges)
202 END IF
203 IF (ASSOCIATED(dispersion_env%dcharges)) THEN
204 DEALLOCATE (dispersion_env%dcharges)
205 END IF
206
207 DEALLOCATE (dispersion_env)
208
209 END IF
210
211 END SUBROUTINE qs_dispersion_release
212
213END MODULE qs_dispersion_types
214
Definition atom.F:9
Input definition and setup for EEQ model.
Definition eeq_input.F:12
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Definition of disperson types for DFT calculations.
integer, parameter, public dftd2_pp
integer, parameter, public dftd4_pp
subroutine, public qs_dispersion_release(dispersion_env)
...
integer, parameter, public dftd3_pp
Define the neighbor list data types and the corresponding functionality.
subroutine, public release_neighbor_list_sets(nlists)
releases an array of neighbor_list_sets