(git:34ef472)
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-2024 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 input_section_types, ONLY: section_vals_type
15  USE kinds, ONLY: default_string_length,&
16  dp
17  USE qs_neighbor_list_types, ONLY: neighbor_list_set_p_type,&
19 #include "./base/base_uses.f90"
20 
21  IMPLICIT NONE
22 
23  PRIVATE
24 
25  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_dispersion_types'
26 
27 ! **************************************************************************************************
28  INTEGER, PARAMETER :: dftd2_pp = 1
29  INTEGER, PARAMETER :: dftd3_pp = 2
30 
31  TYPE qs_dispersion_type
32  INTEGER :: type
33  INTEGER :: pp_type
34  INTEGER :: nl_type
35  CHARACTER(LEN=default_string_length) :: ref_functional
36  REAL(kind=dp) :: scaling
37  REAL(kind=dp) :: rc_disp
38  REAL(kind=dp) :: exp_pre
39  TYPE(section_vals_type), POINTER :: dftd_section
40  LOGICAL :: verbose !extended output
41  CHARACTER(LEN=default_string_length) :: parameter_file_name
42  CHARACTER(LEN=default_string_length) :: kernel_file_name
43  !DFT-D3 global parameters
44  INTEGER :: max_elem !elements parametrized
45  INTEGER :: maxc !max coordination number references per element
46  REAL(kind=dp) :: k1, k2, k3 !ad hoc parameters
47  REAL(kind=dp) :: alp !ad hoc parameters
48  REAL(kind=dp) :: s6, s8, sr6 !scaling parameters
49  REAL(kind=dp) :: a1, a2 !BJ scaling parameters
50  REAL(kind=dp) :: eps_cn
51  LOGICAL :: doabc !neglect C9 terms
52  LOGICAL :: c9cnst !use constant c9 terms
53  LOGICAL :: lrc !calculate a long range correction
54  LOGICAL :: srb !calculate a short range bond correction
55  REAL(kind=dp), DIMENSION(4) :: srb_params ! parameters for SRB (s,g,t1,t2)
56  TYPE(neighbor_list_set_p_type), &
57  DIMENSION(:), POINTER :: sab_vdw, sab_cn ! neighborlists for pair interactions
58  REAL(kind=dp), DIMENSION(:, :, :, :, :), POINTER &
59  :: c6ab
60  INTEGER, DIMENSION(:), POINTER :: maxci
61  REAL(kind=dp), DIMENSION(:, :), POINTER :: r0ab
62  REAL(kind=dp), DIMENSION(:), POINTER :: rcov !covalent radii
63  REAL(kind=dp), DIMENSION(:), POINTER :: r2r4 !atomic <r^2>/<r^4> values
64  REAL(kind=dp), DIMENSION(:), POINTER :: cn !coordination numbers (defaults)
65  TYPE(cn_kind_list), DIMENSION(:), POINTER &
66  :: cnkind
67  TYPE(cn_atom_list), DIMENSION(:), POINTER &
68  :: cnlist
69  ! KG molecular corrections
70  LOGICAL :: domol
71  REAL(kind=dp) :: kgc8 !s8 scaling parameter
72  !vdW-DF variables
73  REAL(kind=dp) :: pw_cutoff
74  REAL(kind=dp) :: b_value, c_value, scale_rvv10 !parameters for the rVV10 functional
75  INTEGER :: nqs, nr_points
76  !! The number of q points and radial points
77  !! used in generating the kernel phi(q1*r, q2*r)
78  !! (see DION 14-16 and SOLER 3)
79  REAL(kind=dp) :: r_max, q_cut, q_min, dk
80  !! The maximum value of r, the maximum and minimum
81  !! values of q and the k-space spacing of grid points.
82  !! Note that, during a vdW run, values of q0 found
83  !! larger than q_cut will be saturated (SOLER 6-7) to
84  !! q_cut
85  REAL(kind=dp), DIMENSION(:), POINTER :: q_mesh !! The values of all the q points used
86  REAL(kind=dp), DIMENSION(:, :, :), POINTER &
87  :: kernel !! A matrix holding the Fourier transformed kernel function
88  !! for each pair of q values. The ordering is
89  !! kernel(k_point, q1_value, q2_value)
90  REAL(kind=dp), DIMENSION(:, :, :), POINTER &
91  :: d2phi_dk2 !! A matrix holding the second derivatives of the above
92  !! kernel matrix at each of the q points. Stored as
93  !! d2phi_dk2(k_point, q1_value, q2_value)
94  REAL(kind=dp), DIMENSION(:, :), POINTER :: d2y_dx2 !! 2nd derivatives of q_mesh for interpolation
95  INTEGER, DIMENSION(:, :), POINTER :: d3_exclude_pair
96  INTEGER :: nd3_exclude_pair
97  END TYPE qs_dispersion_type
98 
99  TYPE qs_atom_dispersion_type
100  INTEGER :: type
101  LOGICAL :: defined
102  REAL(kind=dp) :: vdw_radii !van der Waals radii
103  REAL(kind=dp) :: c6 !c6 coefficients
104  END TYPE qs_atom_dispersion_type
105 
106  TYPE cn_kind_list
107  REAL(kind=dp) :: cnum
108  INTEGER :: kind
109  END TYPE cn_kind_list
110  TYPE cn_atom_list
111  REAL(kind=dp) :: cnum
112  INTEGER :: natom
113  INTEGER, DIMENSION(:), POINTER :: atom
114  END TYPE cn_atom_list
115 
116 ! **************************************************************************************************
117 
118  PUBLIC :: qs_atom_dispersion_type, qs_dispersion_type
119  PUBLIC :: dftd2_pp, dftd3_pp
120  PUBLIC :: qs_dispersion_release
121 
122 ! **************************************************************************************************
123 CONTAINS
124 ! **************************************************************************************************
125 !> \brief ...
126 !> \param dispersion_env ...
127 ! **************************************************************************************************
128  SUBROUTINE qs_dispersion_release(dispersion_env)
129 
130  TYPE(qs_dispersion_type), POINTER :: dispersion_env
131 
132  INTEGER :: i
133 
134  IF (ASSOCIATED(dispersion_env)) THEN
135  IF (ASSOCIATED(dispersion_env%maxci)) THEN
136  ! DFT-D3 arrays
137  DEALLOCATE (dispersion_env%maxci)
138  DEALLOCATE (dispersion_env%c6ab)
139  DEALLOCATE (dispersion_env%r0ab)
140  DEALLOCATE (dispersion_env%rcov)
141  DEALLOCATE (dispersion_env%r2r4)
142  DEALLOCATE (dispersion_env%cn)
143  IF (ASSOCIATED(dispersion_env%cnkind)) THEN
144  DEALLOCATE (dispersion_env%cnkind)
145  END IF
146  IF (ASSOCIATED(dispersion_env%cnlist)) THEN
147  DO i = 1, SIZE(dispersion_env%cnlist)
148  DEALLOCATE (dispersion_env%cnlist(i)%atom)
149  END DO
150  DEALLOCATE (dispersion_env%cnlist)
151  END IF
152  END IF
153  ! vdD-DF
154  IF (ASSOCIATED(dispersion_env%q_mesh)) THEN
155  DEALLOCATE (dispersion_env%q_mesh)
156  END IF
157  IF (ASSOCIATED(dispersion_env%kernel)) THEN
158  DEALLOCATE (dispersion_env%kernel)
159  END IF
160  IF (ASSOCIATED(dispersion_env%d2phi_dk2)) THEN
161  DEALLOCATE (dispersion_env%d2phi_dk2)
162  END IF
163  IF (ASSOCIATED(dispersion_env%d2y_dx2)) THEN
164  DEALLOCATE (dispersion_env%d2y_dx2)
165  END IF
166  IF (ASSOCIATED(dispersion_env%d3_exclude_pair)) THEN
167  DEALLOCATE (dispersion_env%d3_exclude_pair)
168  END IF
169  ! neighborlists
170  CALL release_neighbor_list_sets(dispersion_env%sab_vdw)
171  CALL release_neighbor_list_sets(dispersion_env%sab_cn)
172 
173  DEALLOCATE (dispersion_env)
174 
175  END IF
176 
177  END SUBROUTINE qs_dispersion_release
178 
179 END MODULE qs_dispersion_types
180 
Definition: atom.F:9
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
Definition of disperson types for DFT calculations.
integer, parameter, public dftd2_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