Line data Source code
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 dft section of the input
10 : !> \par History
11 : !> 10.2005 moved out of input_cp2k [fawzi]
12 : !> \author fawzi
13 : ! **************************************************************************************************
14 : MODULE input_cp2k_tb
15 : USE bibliography, ONLY: Elstner1998,&
16 : Grimme2017,&
17 : Hu2007,&
18 : Porezag1995,&
19 : Seifert1996,&
20 : Zhechkov2005
21 : USE eeq_input, ONLY: create_eeq_control_section
22 : USE input_constants, ONLY: dispersion_d2,&
23 : dispersion_d3,&
24 : dispersion_d3bj,&
25 : dispersion_uff,&
26 : slater
27 : USE input_cp2k_mm, ONLY: create_GENPOT_section
28 : USE input_keyword_types, ONLY: keyword_create,&
29 : keyword_release,&
30 : keyword_type
31 : USE input_section_types, ONLY: section_add_keyword,&
32 : section_add_subsection,&
33 : section_create,&
34 : section_release,&
35 : section_type
36 : USE input_val_types, ONLY: char_t
37 : USE kinds, ONLY: dp
38 : USE string_utilities, ONLY: s2a
39 : #include "./base/base_uses.f90"
40 :
41 : IMPLICIT NONE
42 : PRIVATE
43 :
44 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_tb'
45 :
46 : PUBLIC :: create_dftb_control_section, create_xtb_control_section
47 :
48 : CONTAINS
49 :
50 : ! **************************************************************************************************
51 : !> \brief ...
52 : !> \param section ...
53 : ! **************************************************************************************************
54 8546 : SUBROUTINE create_dftb_control_section(section)
55 : TYPE(section_type), POINTER :: section
56 :
57 : TYPE(keyword_type), POINTER :: keyword
58 : TYPE(section_type), POINTER :: subsection
59 :
60 8546 : CPASSERT(.NOT. ASSOCIATED(section))
61 : CALL section_create(section, __LOCATION__, name="DFTB", &
62 : description="Parameters needed to set up the DFTB methods", &
63 : n_keywords=1, n_subsections=1, repeats=.FALSE., &
64 42730 : citations=(/Porezag1995, Seifert1996, Elstner1998, Zhechkov2005/))
65 :
66 8546 : NULLIFY (subsection)
67 8546 : CALL create_dftb_parameter_section(subsection)
68 8546 : CALL section_add_subsection(section, subsection)
69 8546 : CALL section_release(subsection)
70 :
71 8546 : NULLIFY (keyword)
72 : CALL keyword_create(keyword, __LOCATION__, name="self_consistent", &
73 : description="Use self-consistent method", &
74 : citations=(/Elstner1998/), &
75 17092 : usage="SELF_CONSISTENT", default_l_val=.TRUE.)
76 8546 : CALL section_add_keyword(section, keyword)
77 8546 : CALL keyword_release(keyword)
78 :
79 : CALL keyword_create(keyword, __LOCATION__, name="orthogonal_basis", &
80 : description="Assume orthogonal basis set", &
81 8546 : usage="ORTHOGONAL_BASIS", default_l_val=.FALSE.)
82 8546 : CALL section_add_keyword(section, keyword)
83 8546 : CALL keyword_release(keyword)
84 :
85 : CALL keyword_create(keyword, __LOCATION__, name="do_ewald", &
86 : description="Use Ewald type method instead of direct sum for Coulomb interaction", &
87 8546 : usage="DO_EWALD", default_l_val=.FALSE., lone_keyword_l_val=.TRUE.)
88 8546 : CALL section_add_keyword(section, keyword)
89 8546 : CALL keyword_release(keyword)
90 :
91 : CALL keyword_create(keyword, __LOCATION__, name="dispersion", &
92 : description="Use dispersion correction", &
93 : citations=(/Zhechkov2005/), lone_keyword_l_val=.TRUE., &
94 17092 : usage="DISPERSION", default_l_val=.FALSE.)
95 8546 : CALL section_add_keyword(section, keyword)
96 8546 : CALL keyword_release(keyword)
97 :
98 : CALL keyword_create(keyword, __LOCATION__, name="DIAGONAL_DFTB3", &
99 : description="Use a diagonal version of the 3rd order energy correction (DFTB3) ", &
100 : lone_keyword_l_val=.TRUE., &
101 8546 : usage="DIAGONAL_DFTB3", default_l_val=.FALSE.)
102 8546 : CALL section_add_keyword(section, keyword)
103 8546 : CALL keyword_release(keyword)
104 :
105 : CALL keyword_create(keyword, __LOCATION__, name="HB_SR_GAMMA", &
106 : description="Uses a modified version for the GAMMA within the SCC-DFTB scheme, "// &
107 : "specifically tuned for hydrogen bonds.", &
108 : citations=(/Hu2007/), lone_keyword_l_val=.TRUE., &
109 17092 : usage="HB_SR_GAMMA", default_l_val=.FALSE.)
110 8546 : CALL section_add_keyword(section, keyword)
111 8546 : CALL keyword_release(keyword)
112 :
113 : CALL keyword_create(keyword, __LOCATION__, name="eps_disp", &
114 : description="Define accuracy of dispersion interaction", &
115 8546 : usage="EPS_DISP", default_r_val=0.0001_dp)
116 8546 : CALL section_add_keyword(section, keyword)
117 8546 : CALL keyword_release(keyword)
118 :
119 8546 : END SUBROUTINE create_dftb_control_section
120 :
121 : ! **************************************************************************************************
122 : !> \brief ...
123 : !> \param section ...
124 : ! **************************************************************************************************
125 8546 : SUBROUTINE create_xtb_control_section(section)
126 : TYPE(section_type), POINTER :: section
127 :
128 : TYPE(keyword_type), POINTER :: keyword
129 : TYPE(section_type), POINTER :: subsection
130 :
131 8546 : CPASSERT(.NOT. ASSOCIATED(section))
132 : CALL section_create(section, __LOCATION__, name="xTB", &
133 : description="Parameters needed to set up the xTB methods", &
134 : n_keywords=1, n_subsections=1, repeats=.FALSE., &
135 17092 : citations=(/GRIMME2017/))
136 :
137 8546 : NULLIFY (subsection)
138 8546 : CALL create_xtb_parameter_section(subsection)
139 8546 : CALL section_add_subsection(section, subsection)
140 8546 : CALL section_release(subsection)
141 :
142 8546 : CALL create_xtb_nonbonded_section(subsection)
143 8546 : CALL section_add_subsection(section, subsection)
144 8546 : CALL section_release(subsection)
145 :
146 8546 : CALL create_eeq_control_section(subsection)
147 8546 : CALL section_add_subsection(section, subsection)
148 8546 : CALL section_release(subsection)
149 :
150 8546 : NULLIFY (keyword)
151 : CALL keyword_create(keyword, __LOCATION__, name="GFN_TYPE", &
152 : description="Which GFN xTB method should be used.", &
153 8546 : usage="GFN_TYPE 1", default_i_val=1)
154 8546 : CALL section_add_keyword(section, keyword)
155 8546 : CALL keyword_release(keyword)
156 :
157 : CALL keyword_create(keyword, __LOCATION__, name="DO_EWALD", &
158 : description="Use Ewald type method instead of direct sum for Coulomb interaction", &
159 8546 : usage="DO_EWALD", default_l_val=.FALSE., lone_keyword_l_val=.TRUE.)
160 8546 : CALL section_add_keyword(section, keyword)
161 8546 : CALL keyword_release(keyword)
162 :
163 : CALL keyword_create(keyword, __LOCATION__, name="STO_NG", &
164 : description="Provides the order of the Slater orbital expansion in GTOs.", &
165 8546 : usage="STO_NG 3", default_i_val=6)
166 8546 : CALL section_add_keyword(section, keyword)
167 8546 : CALL keyword_release(keyword)
168 :
169 : CALL keyword_create(keyword, __LOCATION__, name="HYDROGEN_STO_NG", &
170 : description="Number of GTOs for Hydrogen basis expansion.", &
171 8546 : usage="HYDROGEN_STO_NG 3", default_i_val=4)
172 8546 : CALL section_add_keyword(section, keyword)
173 8546 : CALL keyword_release(keyword)
174 :
175 : CALL keyword_create(keyword, __LOCATION__, name="USE_HALOGEN_CORRECTION", &
176 : description="Use XB interaction term", &
177 8546 : usage="USE_HALOGEN_CORRECTION T", default_l_val=.TRUE., lone_keyword_l_val=.TRUE.)
178 8546 : CALL section_add_keyword(section, keyword)
179 8546 : CALL keyword_release(keyword)
180 :
181 : CALL keyword_create(keyword, __LOCATION__, name="DO_NONBONDED", &
182 : description="Controls the computation of real-space "// &
183 : "(short-range) nonbonded interactions as correction to xTB.", &
184 8546 : usage="DO_NONBONDED T", default_l_val=.FALSE., lone_keyword_l_val=.TRUE.)
185 8546 : CALL section_add_keyword(section, keyword)
186 8546 : CALL keyword_release(keyword)
187 :
188 : CALL keyword_create(keyword, __LOCATION__, name="VDW_POTENTIAL", &
189 : description="vdW potential to be used: NONE, DFTD3, DFTD4. "// &
190 : "Defaults: DFTD3(gfn1), DFTD4(gfn0, gfn2).", &
191 8546 : usage="VDW_POTENTIAL type", default_c_val="")
192 8546 : CALL section_add_keyword(section, keyword)
193 8546 : CALL keyword_release(keyword)
194 :
195 : CALL keyword_create(keyword, __LOCATION__, name="COULOMB_INTERACTION", &
196 : description="Use Coulomb interaction terms (electrostatics + TB3); for debug only", &
197 8546 : usage="COULOMB_INTERACTION T", default_l_val=.TRUE., lone_keyword_l_val=.TRUE.)
198 8546 : CALL section_add_keyword(section, keyword)
199 8546 : CALL keyword_release(keyword)
200 :
201 : CALL keyword_create(keyword, __LOCATION__, name="COULOMB_LR", &
202 : description="Use Coulomb LR (1/r) interaction terms; for debug only", &
203 8546 : usage="COULOMB_LR T", default_l_val=.TRUE., lone_keyword_l_val=.TRUE.)
204 8546 : CALL section_add_keyword(section, keyword)
205 8546 : CALL keyword_release(keyword)
206 :
207 : CALL keyword_create(keyword, __LOCATION__, name="TB3_INTERACTION", &
208 : description="Use TB3 interaction terms; for debug only", &
209 8546 : usage="TB3_INTERACTION T", default_l_val=.TRUE., lone_keyword_l_val=.TRUE.)
210 8546 : CALL section_add_keyword(section, keyword)
211 8546 : CALL keyword_release(keyword)
212 :
213 : CALL keyword_create(keyword, __LOCATION__, name="CHECK_ATOMIC_CHARGES", &
214 : description="Stop calculation if atomic charges are outside chemical range.", &
215 8546 : usage="CHECK_ATOMIC_CHARGES T", default_l_val=.TRUE., lone_keyword_l_val=.TRUE.)
216 8546 : CALL section_add_keyword(section, keyword)
217 8546 : CALL keyword_release(keyword)
218 :
219 : CALL keyword_create(keyword, __LOCATION__, name="EPS_PAIRPOTENTIAL", &
220 : description="Accuracy for the repulsive pair potential.", &
221 8546 : usage="EPS_PAIRPOTENTIAL 1.0E-8", default_r_val=1.0e-10_dp)
222 8546 : CALL section_add_keyword(section, keyword)
223 8546 : CALL keyword_release(keyword)
224 :
225 : CALL keyword_create(keyword, __LOCATION__, name="EN_SHIFT_TYPE", &
226 : description="Shift function for electronegativity in EEQ method. "// &
227 : "[Select/Molecule/Crystal] Default Select from periodicity.", &
228 : usage="EN_SHIFT_TYPE [Select/Molecule/Crystal]", &
229 8546 : n_var=1, type_of_var=char_t, default_c_val="Molecule")
230 8546 : CALL section_add_keyword(section, keyword)
231 8546 : CALL keyword_release(keyword)
232 :
233 8546 : END SUBROUTINE create_xtb_control_section
234 :
235 : ! **************************************************************************************************
236 : !> \brief ...
237 : !> \param section ...
238 : ! **************************************************************************************************
239 8546 : SUBROUTINE create_dftb_parameter_section(section)
240 :
241 : TYPE(section_type), POINTER :: section
242 :
243 : TYPE(keyword_type), POINTER :: keyword
244 :
245 8546 : CPASSERT(.NOT. ASSOCIATED(section))
246 :
247 : CALL section_create(section, __LOCATION__, name="PARAMETER", &
248 : description="Information on where to find DFTB parameters", &
249 8546 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
250 :
251 8546 : NULLIFY (keyword)
252 : CALL keyword_create(keyword, __LOCATION__, name="SK_FILE", &
253 : description="Define parameter file for atom pair", &
254 : usage="SK_FILE a1 a2 filename", &
255 8546 : n_var=3, type_of_var=char_t, repeats=.TRUE.)
256 8546 : CALL section_add_keyword(section, keyword)
257 8546 : CALL keyword_release(keyword)
258 :
259 : CALL keyword_create(keyword, __LOCATION__, name="PARAM_FILE_PATH", &
260 : description="Specify the directory with the DFTB parameter files. "// &
261 : "Used in combination with the filenames specified in the file "// &
262 : "given in PARAM_FILE_NAME.", usage="PARAM_FILE_PATH pathname", &
263 8546 : n_var=1, type_of_var=char_t, default_c_val="./")
264 8546 : CALL section_add_keyword(section, keyword)
265 8546 : CALL keyword_release(keyword)
266 :
267 : CALL keyword_create(keyword, __LOCATION__, name="PARAM_FILE_NAME", &
268 : description="Specify file that contains the names of "// &
269 : "Slater-Koster tables: A plain text file, each line has the "// &
270 : 'format "ATOM1 ATOM2 filename.spl".', &
271 : usage="PARAM_FILE_NAME filename", &
272 8546 : n_var=1, type_of_var=char_t, default_c_val="")
273 8546 : CALL section_add_keyword(section, keyword)
274 8546 : CALL keyword_release(keyword)
275 :
276 : CALL keyword_create(keyword, __LOCATION__, name="DISPERSION_TYPE", &
277 : description="Use dispersion correction of the specified type."// &
278 : " Dispersion correction has to be switched on in the DFTB section.", &
279 : usage="DISPERSION_TYPE (UFF|D3|D3(BJ)|D2)", &
280 : enum_c_vals=s2a("UFF", "D3", "D3(BJ)", "D2"), &
281 : enum_i_vals=(/dispersion_uff, dispersion_d3, dispersion_d3bj, dispersion_d2/), &
282 : enum_desc=s2a("Uses the UFF force field for a pair potential dispersion correction.", &
283 : "Uses the Grimme D3 method (simplified) for a pair potential dispersion correction.", &
284 : "Uses the Grimme D3 method (simplified) with Becke-Johnson attenuation.", &
285 : "Uses the Grimme D2 method for pair potential dispersion correction."), &
286 8546 : default_i_val=dispersion_uff)
287 8546 : CALL section_add_keyword(section, keyword)
288 8546 : CALL keyword_release(keyword)
289 :
290 : CALL keyword_create(keyword, __LOCATION__, name="UFF_FORCE_FIELD", &
291 : description="Name of file with UFF parameters that will be used "// &
292 : "for the dispersion correction. Needs to be specified when "// &
293 : "DISPERSION==.TRUE., otherwise cp2k crashes with a Segmentation "// &
294 : "Fault.", usage="UFF_FORCE_FIELD filename", &
295 8546 : n_var=1, type_of_var=char_t, default_c_val="")
296 8546 : CALL section_add_keyword(section, keyword)
297 8546 : CALL keyword_release(keyword)
298 :
299 : CALL keyword_create(keyword, __LOCATION__, name="DISPERSION_PARAMETER_FILE", &
300 : description="Specify file that contains the atomic dispersion "// &
301 : "parameters for the D3 method", &
302 : usage="DISPERSION_PARAMETER_FILE filename", &
303 8546 : n_var=1, type_of_var=char_t, default_c_val="")
304 8546 : CALL section_add_keyword(section, keyword)
305 8546 : CALL keyword_release(keyword)
306 :
307 : CALL keyword_create(keyword, __LOCATION__, name="DISPERSION_RADIUS", &
308 : description="Define radius of dispersion interaction", &
309 8546 : usage="DISPERSION_RADIUS", default_r_val=15._dp)
310 8546 : CALL section_add_keyword(section, keyword)
311 8546 : CALL keyword_release(keyword)
312 :
313 : CALL keyword_create(keyword, __LOCATION__, name="COORDINATION_CUTOFF", &
314 : description="Define cutoff for coordination number calculation", &
315 8546 : usage="COORDINATION_CUTOFF", default_r_val=1.e-6_dp)
316 8546 : CALL section_add_keyword(section, keyword)
317 8546 : CALL keyword_release(keyword)
318 :
319 : CALL keyword_create(keyword, __LOCATION__, name="D3_SCALING", &
320 : description="Scaling parameters (s6,sr6,s8) for the D3 dispersion method,", &
321 8546 : usage="D3_SCALING 1.0 1.0 1.0", n_var=3, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
322 8546 : CALL section_add_keyword(section, keyword)
323 8546 : CALL keyword_release(keyword)
324 :
325 : CALL keyword_create(keyword, __LOCATION__, name="D3BJ_SCALING", &
326 : description="Scaling parameters (s6,a1,s8,a2) for the D3(BJ) dispersion method,", &
327 : usage="D3BJ_SCALING 1.0 1.0 1.0 1.0", n_var=4, &
328 8546 : default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp, 0.0_dp/))
329 8546 : CALL section_add_keyword(section, keyword)
330 8546 : CALL keyword_release(keyword)
331 :
332 : CALL keyword_create(keyword, __LOCATION__, name="D2_SCALING", &
333 : description="Scaling parameter for the D2 dispersion method,", &
334 8546 : usage="D2_SCALING 1.0", default_r_val=1.0_dp)
335 8546 : CALL section_add_keyword(section, keyword)
336 8546 : CALL keyword_release(keyword)
337 :
338 : CALL keyword_create(keyword, __LOCATION__, name="D2_EXP_PRE", &
339 : description="Exp prefactor for damping for the D2 dispersion method,", &
340 8546 : usage="EXP_PRE 2.0", default_r_val=2.0_dp)
341 8546 : CALL section_add_keyword(section, keyword)
342 8546 : CALL keyword_release(keyword)
343 :
344 : CALL keyword_create(keyword, __LOCATION__, name="HB_SR_PARAM", &
345 : description="Uses a modified version for the GAMMA within the SCC-DFTB scheme, "// &
346 : "specifically tuned for hydrogen bonds. Specify the exponent used in the exponential.", &
347 8546 : usage="HB_SR_PARAM {real}", default_r_val=4.0_dp)
348 8546 : CALL section_add_keyword(section, keyword)
349 8546 : CALL keyword_release(keyword)
350 :
351 8546 : END SUBROUTINE create_dftb_parameter_section
352 :
353 : ! **************************************************************************************************
354 : !> \brief ...
355 : !> \param section ...
356 : ! **************************************************************************************************
357 8546 : SUBROUTINE create_xtb_parameter_section(section)
358 :
359 : TYPE(section_type), POINTER :: section
360 :
361 : TYPE(keyword_type), POINTER :: keyword
362 :
363 8546 : CPASSERT(.NOT. ASSOCIATED(section))
364 :
365 : CALL section_create(section, __LOCATION__, name="PARAMETER", &
366 : description="Information on and where to find xTB parameters", &
367 8546 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
368 :
369 8546 : NULLIFY (keyword)
370 : CALL keyword_create(keyword, __LOCATION__, name="PARAM_FILE_PATH", &
371 : description="Specify the directory with the xTB parameter file. ", &
372 : usage="PARAM_FILE_PATH pathname", &
373 8546 : n_var=1, type_of_var=char_t, default_c_val="")
374 8546 : CALL section_add_keyword(section, keyword)
375 8546 : CALL keyword_release(keyword)
376 :
377 : CALL keyword_create(keyword, __LOCATION__, name="PARAM_FILE_NAME", &
378 : description="Specify file that contains all xTB default parameters. ", &
379 : usage="PARAM_FILE_NAME filename", &
380 8546 : n_var=1, type_of_var=char_t, default_c_val="xTB_parameters")
381 8546 : CALL section_add_keyword(section, keyword)
382 8546 : CALL keyword_release(keyword)
383 :
384 : CALL keyword_create(keyword, __LOCATION__, name="DISPERSION_PARAMETER_FILE", &
385 : description="Specify file that contains the atomic dispersion "// &
386 : "parameters for the D3 method", &
387 : usage="DISPERSION_PARAMETER_FILE filename", &
388 8546 : n_var=1, type_of_var=char_t, default_c_val="dftd3.dat")
389 8546 : CALL section_add_keyword(section, keyword)
390 8546 : CALL keyword_release(keyword)
391 :
392 : CALL keyword_create(keyword, __LOCATION__, name="DISPERSION_RADIUS", &
393 : description="Define radius of dispersion interaction", &
394 8546 : usage="DISPERSION_RADIUS", default_r_val=15._dp)
395 8546 : CALL section_add_keyword(section, keyword)
396 8546 : CALL keyword_release(keyword)
397 :
398 : CALL keyword_create(keyword, __LOCATION__, name="COORDINATION_CUTOFF", &
399 : description="Define cutoff for coordination number calculation", &
400 8546 : usage="COORDINATION_CUTOFF", default_r_val=1.e-6_dp)
401 8546 : CALL section_add_keyword(section, keyword)
402 8546 : CALL keyword_release(keyword)
403 :
404 : CALL keyword_create(keyword, __LOCATION__, name="D3BJ_SCALING", &
405 : description="Scaling parameters (s6,s8) for the D3 dispersion method.", &
406 8546 : usage="D3BJ_SCALING 1.0 2.4", n_var=2, default_r_vals=(/1.0_dp, 2.4_dp/))
407 8546 : CALL section_add_keyword(section, keyword)
408 8546 : CALL keyword_release(keyword)
409 :
410 : CALL keyword_create(keyword, __LOCATION__, name="D3BJ_PARAM", &
411 : description="Becke-Johnson parameters (a1, a2 for the D3 dispersion method.", &
412 8546 : usage="D3BJ_PARAM 0.63 5.0", n_var=2, default_r_vals=(/0.63_dp, 5.0_dp/))
413 8546 : CALL section_add_keyword(section, keyword)
414 8546 : CALL keyword_release(keyword)
415 :
416 : CALL keyword_create(keyword, __LOCATION__, name="HUCKEL_CONSTANTS", &
417 : description="Huckel parameters (s, p, d, sp, 2sH).", &
418 : usage="HUCKEL_CONSTANTS 1.85 2.25 2.00 2.08 2.85", n_var=5, &
419 8546 : default_r_vals=(/1.85_dp, 2.25_dp, 2.00_dp, 2.08_dp, 2.85_dp/))
420 8546 : CALL section_add_keyword(section, keyword)
421 8546 : CALL keyword_release(keyword)
422 :
423 : CALL keyword_create(keyword, __LOCATION__, name="COULOMB_CONSTANTS", &
424 : description="Scaling parameters for Coulomb interactions (electrons, nuclei).", &
425 : usage="COULOMB_CONSTANTS 2.00 1.50", n_var=2, &
426 8546 : default_r_vals=(/2.00_dp, 1.50_dp/))
427 8546 : CALL section_add_keyword(section, keyword)
428 8546 : CALL keyword_release(keyword)
429 :
430 : CALL keyword_create(keyword, __LOCATION__, name="CN_CONSTANTS", &
431 : description="Scaling parameters for Coordination number correction term.", &
432 : usage="CN_CONSTANTS 0.006 -0.003 -0.005", n_var=3, &
433 8546 : default_r_vals=(/0.006_dp, -0.003_dp, -0.005_dp/))
434 8546 : CALL section_add_keyword(section, keyword)
435 8546 : CALL keyword_release(keyword)
436 :
437 : CALL keyword_create(keyword, __LOCATION__, name="EN_CONSTANTS", &
438 : description="Scaling parameters for electronegativity correction term.", &
439 : usage="EN_CONSTANTS -0.007 0.000 0.000", n_var=3, &
440 8546 : default_r_vals=(/-0.007_dp, 0.000_dp, 0.000_dp/))
441 8546 : CALL section_add_keyword(section, keyword)
442 8546 : CALL keyword_release(keyword)
443 :
444 : CALL keyword_create(keyword, __LOCATION__, name="BEN_CONSTANT", &
445 : description="Scaling parameter for electronegativity correction term.", &
446 : usage="BEN_CONSTANT 4.0", n_var=1, &
447 8546 : default_r_val=4.0_dp)
448 8546 : CALL section_add_keyword(section, keyword)
449 8546 : CALL keyword_release(keyword)
450 :
451 : CALL keyword_create(keyword, __LOCATION__, name="ENSCALE", &
452 : description="Scaling parameter repulsive energy (dEN in exponential).", &
453 : usage="ENSCALE 0.01", n_var=1, &
454 8546 : default_r_val=0.0_dp)
455 8546 : CALL section_add_keyword(section, keyword)
456 8546 : CALL keyword_release(keyword)
457 :
458 : CALL keyword_create(keyword, __LOCATION__, name="HALOGEN_BINDING", &
459 : description="Scaling parameters for electronegativity correction term.", &
460 8546 : usage="HALOGEN_BINDING 1.30 0.44", n_var=2, default_r_vals=(/1.30_dp, 0.44_dp/))
461 8546 : CALL section_add_keyword(section, keyword)
462 8546 : CALL keyword_release(keyword)
463 :
464 : CALL keyword_create(keyword, __LOCATION__, name="KAB_PARAM", &
465 : description="Specifies the specific Kab value for types A and B.", &
466 : usage="KAB_PARAM kind1 kind2 value ", repeats=.TRUE., &
467 8546 : n_var=-1, type_of_var=char_t)
468 8546 : CALL section_add_keyword(section, keyword)
469 8546 : CALL keyword_release(keyword)
470 :
471 : CALL keyword_create(keyword, __LOCATION__, name="XB_RADIUS", &
472 : description="Specifies the radius [Bohr] of the XB pair interaction in xTB.", &
473 : usage="XB_RADIUS 20.0 ", repeats=.FALSE., &
474 8546 : n_var=1, default_r_val=20.0_dp)
475 8546 : CALL section_add_keyword(section, keyword)
476 8546 : CALL keyword_release(keyword)
477 :
478 : CALL keyword_create(keyword, __LOCATION__, name="COULOMB_SR_CUT", &
479 : description="Maximum range of short range part of Coulomb interaction.", &
480 : usage="COULOMB_SR_CUT 20.0 ", repeats=.FALSE., &
481 8546 : n_var=1, default_r_val=20.0_dp)
482 8546 : CALL section_add_keyword(section, keyword)
483 8546 : CALL keyword_release(keyword)
484 :
485 : CALL keyword_create(keyword, __LOCATION__, name="COULOMB_SR_EPS", &
486 : description="Cutoff for short range part of Coulomb interaction.", &
487 : usage="COULOMB_SR_EPS 1.E-3 ", repeats=.FALSE., &
488 8546 : n_var=1, default_r_val=1.0E-03_dp)
489 8546 : CALL section_add_keyword(section, keyword)
490 8546 : CALL keyword_release(keyword)
491 :
492 : CALL keyword_create(keyword, __LOCATION__, name="SRB_PARAMETER", &
493 : description="SRB parameters (ksrb, esrb, gscal, c1, c2, shift).", &
494 : usage="SRB_PARAMETER -0.0129 3.48 0.51 -1.71 2.11 0.0537", n_var=6, &
495 : default_r_vals=(/-0.0129_dp, 3.4847_dp, 0.5097_dp, &
496 8546 : -1.70549806_dp, 2.10878369_dp, 0.0537_dp/))
497 8546 : CALL section_add_keyword(section, keyword)
498 8546 : CALL keyword_release(keyword)
499 :
500 8546 : END SUBROUTINE create_xtb_parameter_section
501 : ! **************************************************************************************************
502 : !> \brief ...
503 : !> \param section ...
504 : ! **************************************************************************************************
505 8546 : SUBROUTINE create_xtb_nonbonded_section(section)
506 : TYPE(section_type), POINTER :: section
507 :
508 : TYPE(keyword_type), POINTER :: keyword
509 : TYPE(section_type), POINTER :: subsection
510 :
511 8546 : CPASSERT(.NOT. ASSOCIATED(section))
512 : CALL section_create(section, __LOCATION__, name="NONBONDED", &
513 : description="This section specifies the input parameters for NON-BONDED interactions.", &
514 8546 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
515 8546 : NULLIFY (subsection)
516 :
517 8546 : CALL create_GENPOT_section(subsection)
518 8546 : CALL section_add_subsection(section, subsection)
519 8546 : CALL section_release(subsection)
520 :
521 8546 : NULLIFY (keyword)
522 : CALL keyword_create(keyword, __LOCATION__, name="DX", &
523 : description="Parameter used for computing the derivative with the Ridders' method.", &
524 8546 : usage="DX <REAL>", default_r_val=0.1_dp, unit_str="bohr")
525 8546 : CALL section_add_keyword(section, keyword)
526 8546 : CALL keyword_release(keyword)
527 :
528 : CALL keyword_create(keyword, __LOCATION__, name="ERROR_LIMIT", &
529 : description="Checks that the error in computing the derivative is not larger than "// &
530 : "the value set; in case error is larger a warning message is printed.", &
531 8546 : usage="ERROR_LIMIT <REAL>", default_r_val=1.0E-12_dp)
532 8546 : CALL section_add_keyword(section, keyword)
533 8546 : CALL keyword_release(keyword)
534 :
535 8546 : END SUBROUTINE create_xtb_nonbonded_section
536 :
537 : END MODULE input_cp2k_tb
|