(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_external.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 function that build the input sections for external [potential, density VXC]
10!> \par History
11!> 10.2005 moved out of input_cp2k [fawzi]
12!> 10.2020 moved out of input_cp2k_dft [JGH]
13!> \author fawzi
14! **************************************************************************************************
16 USE bibliography, ONLY: tozer1996,&
18 USE input_constants, ONLY: use_coulomb,&
19 use_diff,&
20 use_no
29 USE input_val_types, ONLY: char_t,&
30 lchar_t,&
31 real_t
32 USE kinds, ONLY: dp
33 USE string_utilities, ONLY: s2a
34#include "./base/base_uses.f90"
35
36 IMPLICIT NONE
37 PRIVATE
38
39 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_external'
40
42
43CONTAINS
44
45! **************************************************************************************************
46!> \brief Creates the section for applying an electrostatic external potential
47!> \param section ...
48!> \date 12.2009
49!> \author teo
50! **************************************************************************************************
51 SUBROUTINE create_ext_pot_section(section)
52 TYPE(section_type), POINTER :: section
53
54 TYPE(keyword_type), POINTER :: keyword
55 TYPE(section_type), POINTER :: subsection
56
57 cpassert(.NOT. ASSOCIATED(section))
58 CALL section_create(section, __location__, name="EXTERNAL_POTENTIAL", &
59 description="Section controlling the presence of an electrostatic "// &
60 "external potential dependent on the atomic positions (X,Y,Z). "// &
61 "As the external potential is currently applied via a grid, "// &
62 "it only works with DFT based methods (GPW/GAPW) that already use "// &
63 "a grid based approach to solve the Poisson equation.", &
64 n_keywords=7, n_subsections=0, repeats=.false.)
65 NULLIFY (keyword, subsection)
66
67 CALL keyword_create(keyword, __location__, name="FUNCTION", &
68 description="Specifies the functional form in mathematical notation. Variables must be the atomic "// &
69 "coordinates (X,Y,Z) of the grid.", usage="FUNCTION X^2+Y^2+Z^2+LOG(ABS(X+Y))", &
70 type_of_var=lchar_t, n_var=1)
71 CALL section_add_keyword(section, keyword)
72 CALL keyword_release(keyword)
73
74 CALL keyword_create(keyword, __location__, name="PARAMETERS", &
75 description="Defines the parameters of the functional form", &
76 usage="PARAMETERS a b D", type_of_var=char_t, &
77 n_var=-1, repeats=.true.)
78 CALL section_add_keyword(section, keyword)
79 CALL keyword_release(keyword)
80
81 CALL keyword_create(keyword, __location__, name="VALUES", &
82 description="Defines the values of parameter of the functional form", &
83 usage="VALUES ", type_of_var=real_t, &
84 n_var=-1, repeats=.true., unit_str="internal_cp2k")
85 CALL section_add_keyword(section, keyword)
86 CALL keyword_release(keyword)
87
88 CALL keyword_create(keyword, __location__, name="UNITS", &
89 description="Optionally, allows to define valid CP2K unit strings for each parameter value. "// &
90 "It is assumed that the corresponding parameter value is specified in this unit.", &
91 usage="UNITS angstrom eV*angstrom^-1 angstrom^1 K", type_of_var=char_t, &
92 n_var=-1, repeats=.true.)
93 CALL section_add_keyword(section, keyword)
94 CALL keyword_release(keyword)
95
96 CALL keyword_create(keyword, __location__, name="STATIC", &
97 description="Specifies the external potential as STATIC or time dependent. At the moment "// &
98 "only static potentials are implemented.", &
99 usage="STATIC T", default_l_val=.true., lone_keyword_l_val=.true.)
100 CALL section_add_keyword(section, keyword)
101 CALL keyword_release(keyword)
102
103 CALL keyword_create(keyword, __location__, name="DX", &
104 description="Parameter used for computing the derivative with the Ridders' method.", &
105 usage="DX <REAL>", default_r_val=0.1_dp, unit_str="bohr")
106 CALL section_add_keyword(section, keyword)
107 CALL keyword_release(keyword)
108
109 CALL keyword_create(keyword, __location__, name="ERROR_LIMIT", &
110 description="Checks that the error in computing the derivative is not larger than "// &
111 "the value set; in case error is larger a warning message is printed.", &
112 usage="ERROR_LIMIT <REAL>", default_r_val=1.0e-12_dp)
113 CALL section_add_keyword(section, keyword)
114 CALL keyword_release(keyword)
115
116 !keyword for reading the external potential from cube file
117 CALL keyword_create(keyword, __location__, name="READ_FROM_CUBE", &
118 description="Switch for reading the external potential from file pot.cube. The values "// &
119 "of the potential must be on the grid points of the realspace grid.", &
120 usage="READ_FROM_CUBE T", default_l_val=.false., lone_keyword_l_val=.true.)
121 CALL section_add_keyword(section, keyword)
122 CALL keyword_release(keyword)
123
124 !keyword for scaling the external potential that is read from file by a constant factor
125 CALL keyword_create(keyword, __location__, name="SCALING_FACTOR", &
126 description="A factor for scaling the the external potential that is read from file. "// &
127 "The value of the potential at each grid point is multiplied by this factor.", &
128 usage="SCALING_FACTOR <REAL>", default_r_val=1.0_dp)
129 CALL section_add_keyword(section, keyword)
130 CALL keyword_release(keyword)
131
132 CALL create_maxwell_section(subsection)
133 CALL section_add_subsection(section, subsection)
134 CALL section_release(subsection)
135
136 END SUBROUTINE create_ext_pot_section
137
138! **************************************************************************************************
139!> \brief Creates the section for applying an electrostatic external potential
140!> \param section ...
141!> \date 12.2009
142!> \author teo
143! **************************************************************************************************
144 SUBROUTINE create_maxwell_section(section)
145 TYPE(section_type), POINTER :: section
146
147 TYPE(keyword_type), POINTER :: keyword
148
149 cpassert(.NOT. ASSOCIATED(section))
150 CALL section_create(section, __location__, name="MAXWELL", &
151 description="Section controlling the calculation of an electrostatic "// &
152 "external potential calculated from Maxwell equations. ", &
153 n_keywords=1, n_subsections=0, repeats=.false.)
154 NULLIFY (keyword)
155
156 CALL keyword_create(keyword, __location__, name="TEST_LOGICAL", &
157 description="Test for logical value", &
158 usage="TEST_LOGICAL T", default_l_val=.false., lone_keyword_l_val=.true.)
159 CALL section_add_keyword(section, keyword)
160 CALL keyword_release(keyword)
161
162 CALL keyword_create(keyword, __location__, name="TEST_REAL", &
163 description="TEST for Real", &
164 usage="TEST_REAL <REAL>", default_r_val=1.0_dp)
165 CALL section_add_keyword(section, keyword)
166 CALL keyword_release(keyword)
167
168 CALL keyword_create(keyword, __location__, name="TEST_INTEGER", &
169 description="TEST for Int", &
170 usage="TEST_INTEGER <INT>", default_i_val=0)
171 CALL section_add_keyword(section, keyword)
172 CALL keyword_release(keyword)
173
174 END SUBROUTINE create_maxwell_section
175
176! **************************************************************************************************
177!> \brief ZMP Creates the section for reading user supplied external density
178!> \param section ...
179!> \date 03.2011
180!> \author D. Varsano [daniele.varsano@nano.cnr.it]
181! **************************************************************************************************
182 SUBROUTINE create_ext_den_section(section)
183 TYPE(section_type), POINTER :: section
184
185 TYPE(keyword_type), POINTER :: keyword
186
187 cpassert(.NOT. ASSOCIATED(section))
188 CALL section_create(section, __location__, name="EXTERNAL_DENSITY", &
189 description="Section for the use of the ZMP technique on external densities.", &
190 n_keywords=4, n_subsections=0, repeats=.false., &
191 citations=(/zhao1994, tozer1996/))
192 NULLIFY (keyword)
193
194 CALL keyword_create(keyword, __location__, name="FILE_DENSITY", &
195 description="Specifies the filename containing the target density in *.cube format. "// &
196 "In the MGRID section it must be imposed NGRID 1, as it works with only "// &
197 "one grid. The number of points in each direction, and the spacing must "// &
198 "be previously defined choosing the plane waves cut-off in section MGRID "// &
199 "keyword CUTOFF, and the cube dimension in section SUBSYS / CELL / keyword ABC", &
200 usage="DENSITY_FILE_NAME <FILENAME>", &
201 type_of_var=char_t, default_c_val="RHO_O.dat", n_var=-1)
202 CALL section_add_keyword(section, keyword)
203 CALL keyword_release(keyword)
204
205 CALL keyword_create(keyword, __location__, name="LAMBDA", &
206 description="Lagrange multiplier defined in the constraint ZMP method. When starting, use "// &
207 "small values when starting from scratch (around 5,10). Then gradually increase "// &
208 "the values depending, restarting from the previous calculation with the smaller "// &
209 "value. To choose the progressive values of LAMBDA look at the convergence of the "// &
210 "eigenvalues.", &
211 usage="DX <REAL>", default_r_val=10.0_dp)
212 CALL section_add_keyword(section, keyword)
213 CALL keyword_release(keyword)
214
215 CALL keyword_create(keyword, __location__, name="ZMP_CONSTRAINT", &
216 description="Specify which kind of constraint to solve the ZMP equation. The COULOMB default "// &
217 "option is more stable.", &
218 usage="ZMP_CONSTRAINT <CHAR>", &
219 enum_c_vals=s2a("COULOMB", "DIFF", "NONE"), &
220 enum_i_vals=(/use_coulomb, use_diff, use_no/), &
221 enum_desc=s2a("Coulomb constraint, integral of [rho_0(r)-rho(r)]/|r-r'|", &
222 "Simple constraint, [rho_0(r)-rho(r)]", &
223 "No constrain imposed"), &
224 default_i_val=use_coulomb)
225 CALL section_add_keyword(section, keyword)
226 CALL keyword_release(keyword)
227
228 CALL keyword_create(keyword, __location__, name="FERMI_AMALDI", &
229 description="Add the Fermi-Amaldi contribution to the Hartree potential. "// &
230 "It leads to a more stable convergence.", &
231 usage="FERMI_AMALDI <LOGICAL>", &
232 repeats=.false., &
233 n_var=1, &
234 default_l_val=.true., lone_keyword_l_val=.true.)
235 CALL section_add_keyword(section, keyword)
236 CALL keyword_release(keyword)
237
238 END SUBROUTINE create_ext_den_section
239
240! **************************************************************************************************
241!> \brief ZMP Creates the section for creating the external v_xc
242!> \param section ...
243!> \date 03.2011
244!> \author D. Varsano [daniele.varsano@nano.cnr.it]
245! **************************************************************************************************
246 SUBROUTINE create_ext_vxc_section(section)
247 TYPE(section_type), POINTER :: section
248
249 TYPE(keyword_type), POINTER :: keyword
250
251 cpassert(.NOT. ASSOCIATED(section))
252 CALL section_create(section, __location__, name="EXTERNAL_VXC", &
253 description="SCF convergence with external v_xc calculated through previous ZMP "// &
254 "calculation", &
255 n_keywords=1, n_subsections=0, repeats=.false.)
256 NULLIFY (keyword)
257
258 CALL keyword_create(keyword, __location__, name="FILE_VXC", &
259 description="The *.cube filename containing the v_xc potential. This works only "// &
260 "with NGRID 1 imposed in the MGRID section. The number of points in each "// &
261 "direction, and the spacing must equal to those previously used in the ZMP "// &
262 "calculation and defined through the plane wave cut-off and the cube dimension "// &
263 "respectively set in section MGRID / keyword CUTOFF, and in section SUBSYS / "// &
264 "CELL / keyword ABC", &
265 usage="FILE_VXC <FILENAME>", &
266 type_of_var=char_t, default_c_val="VXC_O.dat", n_var=-1)
267 CALL section_add_keyword(section, keyword)
268 CALL keyword_release(keyword)
269 END SUBROUTINE create_ext_vxc_section
270
271END MODULE input_cp2k_external
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public zhao1994
integer, save, public tozer1996
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public use_coulomb
integer, parameter, public use_diff
integer, parameter, public use_no
function that build the input sections for external [potential, density VXC]
subroutine, public create_ext_pot_section(section)
Creates the section for applying an electrostatic external potential.
subroutine, public create_ext_vxc_section(section)
ZMP Creates the section for creating the external v_xc.
subroutine, public create_ext_den_section(section)
ZMP Creates the section for reading user supplied external density.
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public lchar_t
integer, parameter, public char_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file