(git:e5b1968)
Loading...
Searching...
No Matches
input_cp2k_tb.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 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! **************************************************************************************************
15 USE bibliography, ONLY: &
23 gfn1xtb,&
24 gfn2xtb,&
25 ipea1xtb,&
26 slater
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
47
48CONTAINS
49
50! **************************************************************************************************
51!> \brief ...
52!> \param section ...
53! **************************************************************************************************
54 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 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., &
65
66 NULLIFY (subsection)
67 CALL create_dftb_parameter_section(subsection)
68 CALL section_add_subsection(section, subsection)
69 CALL section_release(subsection)
70
71 NULLIFY (keyword)
72 CALL keyword_create(keyword, __location__, name="self_consistent", &
73 description="Use self-consistent method", &
74 citations=(/elstner1998/), &
75 usage="SELF_CONSISTENT", default_l_val=.true.)
76 CALL section_add_keyword(section, keyword)
77 CALL keyword_release(keyword)
78
79 CALL keyword_create(keyword, __location__, name="orthogonal_basis", &
80 description="Assume orthogonal basis set", &
81 usage="ORTHOGONAL_BASIS", default_l_val=.false.)
82 CALL section_add_keyword(section, keyword)
83 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 usage="DO_EWALD", default_l_val=.false., lone_keyword_l_val=.true.)
88 CALL section_add_keyword(section, keyword)
89 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 usage="DISPERSION", default_l_val=.false.)
95 CALL section_add_keyword(section, keyword)
96 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 usage="DIAGONAL_DFTB3", default_l_val=.false.)
102 CALL section_add_keyword(section, keyword)
103 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 usage="HB_SR_GAMMA", default_l_val=.false.)
110 CALL section_add_keyword(section, keyword)
111 CALL keyword_release(keyword)
112
113 CALL keyword_create(keyword, __location__, name="eps_disp", &
114 description="Define accuracy of dispersion interaction", &
115 usage="EPS_DISP", default_r_val=0.0001_dp)
116 CALL section_add_keyword(section, keyword)
117 CALL keyword_release(keyword)
118
119 END SUBROUTINE create_dftb_control_section
120
121! **************************************************************************************************
122!> \brief ...
123!> \param section ...
124! **************************************************************************************************
125 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 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 citations=(/grimme2017/))
136
137 NULLIFY (subsection)
138 CALL create_xtb_parameter_section(subsection)
139 CALL section_add_subsection(section, subsection)
140 CALL section_release(subsection)
141
142 CALL create_xtb_nonbonded_section(subsection)
143 CALL section_add_subsection(section, subsection)
144 CALL section_release(subsection)
145
146 CALL create_eeq_control_section(subsection)
147 CALL section_add_subsection(section, subsection)
148 CALL section_release(subsection)
149
150 CALL create_xtb_tblite_section(subsection)
151 CALL section_add_subsection(section, subsection)
152 CALL section_release(subsection)
153
154 NULLIFY (keyword)
155 CALL keyword_create(keyword, __location__, name="GFN_TYPE", &
156 description="Which GFN xTB method should be used.", &
157 usage="GFN_TYPE 1", default_i_val=1)
158 CALL section_add_keyword(section, keyword)
159 CALL keyword_release(keyword)
160
161 CALL keyword_create(keyword, __location__, name="DO_EWALD", &
162 description="Use Ewald type method instead of direct sum for Coulomb interaction", &
163 usage="DO_EWALD", default_l_val=.false., lone_keyword_l_val=.true.)
164 CALL section_add_keyword(section, keyword)
165 CALL keyword_release(keyword)
166
167 CALL keyword_create(keyword, __location__, name="STO_NG", &
168 description="Provides the order of the Slater orbital expansion in GTOs.", &
169 usage="STO_NG 3", default_i_val=6)
170 CALL section_add_keyword(section, keyword)
171 CALL keyword_release(keyword)
172
173 CALL keyword_create(keyword, __location__, name="HYDROGEN_STO_NG", &
174 description="Number of GTOs for Hydrogen basis expansion.", &
175 usage="HYDROGEN_STO_NG 3", default_i_val=4)
176 CALL section_add_keyword(section, keyword)
177 CALL keyword_release(keyword)
178
179 CALL keyword_create(keyword, __location__, name="USE_HALOGEN_CORRECTION", &
180 description="Use XB interaction term", &
181 usage="USE_HALOGEN_CORRECTION T", default_l_val=.true., lone_keyword_l_val=.true.)
182 CALL section_add_keyword(section, keyword)
183 CALL keyword_release(keyword)
184
185 CALL keyword_create(keyword, __location__, name="DO_NONBONDED", &
186 description="Controls the computation of real-space "// &
187 "(short-range) nonbonded interactions as correction to xTB.", &
188 usage="DO_NONBONDED T", default_l_val=.false., lone_keyword_l_val=.true.)
189 CALL section_add_keyword(section, keyword)
190 CALL keyword_release(keyword)
191
192 CALL keyword_create(keyword, __location__, name="VDW_POTENTIAL", &
193 description="vdW potential to be used: NONE, DFTD3, DFTD4. "// &
194 "Defaults: DFTD3(gfn1), DFTD4(gfn0, gfn2).", &
195 usage="VDW_POTENTIAL type", default_c_val="")
196 CALL section_add_keyword(section, keyword)
197 CALL keyword_release(keyword)
198
199 CALL keyword_create(keyword, __location__, name="COULOMB_INTERACTION", &
200 description="Use Coulomb interaction terms (electrostatics + TB3); for debug only", &
201 usage="COULOMB_INTERACTION T", default_l_val=.true., lone_keyword_l_val=.true.)
202 CALL section_add_keyword(section, keyword)
203 CALL keyword_release(keyword)
204
205 CALL keyword_create(keyword, __location__, name="COULOMB_LR", &
206 description="Use Coulomb LR (1/r) interaction terms; for debug only", &
207 usage="COULOMB_LR T", default_l_val=.true., lone_keyword_l_val=.true.)
208 CALL section_add_keyword(section, keyword)
209 CALL keyword_release(keyword)
210
211 CALL keyword_create(keyword, __location__, name="TB3_INTERACTION", &
212 description="Use TB3 interaction terms; for debug only", &
213 usage="TB3_INTERACTION T", default_l_val=.true., lone_keyword_l_val=.true.)
214 CALL section_add_keyword(section, keyword)
215 CALL keyword_release(keyword)
216
217 CALL keyword_create(keyword, __location__, name="CHECK_ATOMIC_CHARGES", &
218 description="Stop calculation if atomic charges are outside chemical range.", &
219 usage="CHECK_ATOMIC_CHARGES T", default_l_val=.true., lone_keyword_l_val=.true.)
220 CALL section_add_keyword(section, keyword)
221 CALL keyword_release(keyword)
222
223 CALL keyword_create(keyword, __location__, name="VARIATIONAL_DIPOLE", &
224 description="gfn0-xTB use dipole definition from energy derivative.", &
225 usage="VARIATIONAL_DIPOLE T", default_l_val=.false., lone_keyword_l_val=.true.)
226 CALL section_add_keyword(section, keyword)
227 CALL keyword_release(keyword)
228
229 CALL keyword_create(keyword, __location__, name="EPS_PAIRPOTENTIAL", &
230 description="Accuracy for the repulsive pair potential.", &
231 usage="EPS_PAIRPOTENTIAL 1.0E-8", default_r_val=1.0e-10_dp)
232 CALL section_add_keyword(section, keyword)
233 CALL keyword_release(keyword)
234
235 CALL keyword_create(keyword, __location__, name="EN_SHIFT_TYPE", &
236 description="Shift function for electronegativity in EEQ method. "// &
237 "[Select/Molecule/Crystal] Default Select from periodicity.", &
238 usage="EN_SHIFT_TYPE [Select/Molecule/Crystal]", &
239 n_var=1, type_of_var=char_t, default_c_val="Molecule")
240 CALL section_add_keyword(section, keyword)
241 CALL keyword_release(keyword)
242
243 END SUBROUTINE create_xtb_control_section
244
245! **************************************************************************************************
246!> \brief ...
247!> \param section ...
248! **************************************************************************************************
249 SUBROUTINE create_dftb_parameter_section(section)
250
251 TYPE(section_type), POINTER :: section
252
253 TYPE(keyword_type), POINTER :: keyword
254
255 cpassert(.NOT. ASSOCIATED(section))
256
257 CALL section_create(section, __location__, name="PARAMETER", &
258 description="Information on where to find DFTB parameters", &
259 n_keywords=1, n_subsections=0, repeats=.false.)
260
261 NULLIFY (keyword)
262 CALL keyword_create(keyword, __location__, name="SK_FILE", &
263 description="Define parameter file for atom pair", &
264 usage="SK_FILE a1 a2 filename", &
265 n_var=3, type_of_var=char_t, repeats=.true.)
266 CALL section_add_keyword(section, keyword)
267 CALL keyword_release(keyword)
268
269 CALL keyword_create(keyword, __location__, name="PARAM_FILE_PATH", &
270 description="Specify the directory with the DFTB parameter files. "// &
271 "Used in combination with the filenames specified in the file "// &
272 "given in PARAM_FILE_NAME.", usage="PARAM_FILE_PATH pathname", &
273 n_var=1, type_of_var=char_t, default_c_val="./")
274 CALL section_add_keyword(section, keyword)
275 CALL keyword_release(keyword)
276
277 CALL keyword_create(keyword, __location__, name="PARAM_FILE_NAME", &
278 description="Specify file that contains the names of "// &
279 "Slater-Koster tables: A plain text file, each line has the "// &
280 'format "ATOM1 ATOM2 filename.spl".', &
281 usage="PARAM_FILE_NAME filename", &
282 n_var=1, type_of_var=char_t, default_c_val="")
283 CALL section_add_keyword(section, keyword)
284 CALL keyword_release(keyword)
285
286 CALL keyword_create(keyword, __location__, name="DISPERSION_TYPE", &
287 description="Use dispersion correction of the specified type."// &
288 " Dispersion correction has to be switched on in the DFTB section.", &
289 usage="DISPERSION_TYPE (UFF|D3|D3(BJ)|D2)", &
290 enum_c_vals=s2a("UFF", "D3", "D3(BJ)", "D2"), &
292 enum_desc=s2a("Uses the UFF force field for a pair potential dispersion correction.", &
293 "Uses the Grimme D3 method (simplified) for a pair potential dispersion correction.", &
294 "Uses the Grimme D3 method (simplified) with Becke-Johnson attenuation.", &
295 "Uses the Grimme D2 method for pair potential dispersion correction."), &
296 default_i_val=dispersion_uff)
297 CALL section_add_keyword(section, keyword)
298 CALL keyword_release(keyword)
299
300 CALL keyword_create(keyword, __location__, name="UFF_FORCE_FIELD", &
301 description="Name of file with UFF parameters that will be used "// &
302 "for the dispersion correction. Needs to be specified when "// &
303 "DISPERSION==.TRUE., otherwise cp2k crashes with a Segmentation "// &
304 "Fault.", usage="UFF_FORCE_FIELD filename", &
305 n_var=1, type_of_var=char_t, default_c_val="")
306 CALL section_add_keyword(section, keyword)
307 CALL keyword_release(keyword)
308
309 CALL keyword_create(keyword, __location__, name="DISPERSION_PARAMETER_FILE", &
310 description="Specify file that contains the atomic dispersion "// &
311 "parameters for the D3 method", &
312 usage="DISPERSION_PARAMETER_FILE filename", &
313 n_var=1, type_of_var=char_t, default_c_val="")
314 CALL section_add_keyword(section, keyword)
315 CALL keyword_release(keyword)
316
317 CALL keyword_create(keyword, __location__, name="DISPERSION_RADIUS", &
318 description="Define radius of dispersion interaction", &
319 usage="DISPERSION_RADIUS", default_r_val=15._dp)
320 CALL section_add_keyword(section, keyword)
321 CALL keyword_release(keyword)
322
323 CALL keyword_create(keyword, __location__, name="COORDINATION_CUTOFF", &
324 description="Define cutoff for coordination number calculation", &
325 usage="COORDINATION_CUTOFF", default_r_val=1.e-6_dp)
326 CALL section_add_keyword(section, keyword)
327 CALL keyword_release(keyword)
328
329 CALL keyword_create(keyword, __location__, name="D3_SCALING", &
330 description="Scaling parameters (s6,sr6,s8) for the D3 dispersion method,", &
331 usage="D3_SCALING 1.0 1.0 1.0", n_var=3, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
332 CALL section_add_keyword(section, keyword)
333 CALL keyword_release(keyword)
334
335 CALL keyword_create(keyword, __location__, name="D3BJ_SCALING", &
336 description="Scaling parameters (s6,a1,s8,a2) for the D3(BJ) dispersion method,", &
337 usage="D3BJ_SCALING 1.0 1.0 1.0 1.0", n_var=4, &
338 default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp, 0.0_dp/))
339 CALL section_add_keyword(section, keyword)
340 CALL keyword_release(keyword)
341
342 CALL keyword_create(keyword, __location__, name="D2_SCALING", &
343 description="Scaling parameter for the D2 dispersion method,", &
344 usage="D2_SCALING 1.0", default_r_val=1.0_dp)
345 CALL section_add_keyword(section, keyword)
346 CALL keyword_release(keyword)
347
348 CALL keyword_create(keyword, __location__, name="D2_EXP_PRE", &
349 description="Exp prefactor for damping for the D2 dispersion method,", &
350 usage="D2_EXP_PRE 2.0", default_r_val=2.0_dp)
351 CALL section_add_keyword(section, keyword)
352 CALL keyword_release(keyword)
353
354 CALL keyword_create(keyword, __location__, name="HB_SR_PARAM", &
355 description="Uses a modified version for the GAMMA within the SCC-DFTB scheme, "// &
356 "specifically tuned for hydrogen bonds. Specify the exponent used in the exponential.", &
357 usage="HB_SR_PARAM {real}", default_r_val=4.0_dp)
358 CALL section_add_keyword(section, keyword)
359 CALL keyword_release(keyword)
360
361 END SUBROUTINE create_dftb_parameter_section
362
363! **************************************************************************************************
364!> \brief ...
365!> \param section ...
366! **************************************************************************************************
367 SUBROUTINE create_xtb_parameter_section(section)
368
369 TYPE(section_type), POINTER :: section
370
371 TYPE(keyword_type), POINTER :: keyword
372
373 cpassert(.NOT. ASSOCIATED(section))
374
375 CALL section_create(section, __location__, name="PARAMETER", &
376 description="Information on and where to find xTB parameters", &
377 n_keywords=1, n_subsections=0, repeats=.false.)
378
379 NULLIFY (keyword)
380 CALL keyword_create(keyword, __location__, name="PARAM_FILE_PATH", &
381 description="Specify the directory with the xTB parameter file. ", &
382 usage="PARAM_FILE_PATH pathname", &
383 n_var=1, type_of_var=char_t, default_c_val="")
384 CALL section_add_keyword(section, keyword)
385 CALL keyword_release(keyword)
386
387 CALL keyword_create(keyword, __location__, name="PARAM_FILE_NAME", &
388 description="Specify file that contains all xTB default parameters. ", &
389 usage="PARAM_FILE_NAME filename", &
390 n_var=1, type_of_var=char_t, default_c_val="xTB_parameters")
391 CALL section_add_keyword(section, keyword)
392 CALL keyword_release(keyword)
393
394 CALL keyword_create(keyword, __location__, name="DISPERSION_PARAMETER_FILE", &
395 description="Specify file that contains the atomic dispersion "// &
396 "parameters for the D3 method", &
397 usage="DISPERSION_PARAMETER_FILE filename", &
398 n_var=1, type_of_var=char_t, default_c_val="dftd3.dat")
399 CALL section_add_keyword(section, keyword)
400 CALL keyword_release(keyword)
401
402 CALL keyword_create(keyword, __location__, name="DISPERSION_RADIUS", &
403 description="Define radius of dispersion interaction", &
404 usage="DISPERSION_RADIUS", default_r_val=15._dp)
405 CALL section_add_keyword(section, keyword)
406 CALL keyword_release(keyword)
407
408 CALL keyword_create(keyword, __location__, name="COORDINATION_CUTOFF", &
409 description="Define cutoff for coordination number calculation", &
410 usage="COORDINATION_CUTOFF", default_r_val=1.e-6_dp)
411 CALL section_add_keyword(section, keyword)
412 CALL keyword_release(keyword)
413
414 CALL keyword_create(keyword, __location__, name="D3BJ_SCALING", &
415 description="Scaling parameters (s6,s8) for the D3 dispersion method.", &
416 usage="D3BJ_SCALING 1.0 2.4", n_var=2, default_r_vals=(/1.0_dp, 2.4_dp/))
417 CALL section_add_keyword(section, keyword)
418 CALL keyword_release(keyword)
419
420 CALL keyword_create(keyword, __location__, name="D3BJ_PARAM", &
421 description="Becke-Johnson parameters (a1, a2 for the D3 dispersion method.", &
422 usage="D3BJ_PARAM 0.63 5.0", n_var=2, default_r_vals=(/0.63_dp, 5.0_dp/))
423 CALL section_add_keyword(section, keyword)
424 CALL keyword_release(keyword)
425
426 CALL keyword_create(keyword, __location__, name="HUCKEL_CONSTANTS", &
427 description="Huckel parameters (s, p, d, sp, 2sH).", &
428 usage="HUCKEL_CONSTANTS 1.85 2.25 2.00 2.08 2.85", n_var=5, &
429 default_r_vals=(/1.85_dp, 2.25_dp, 2.00_dp, 2.08_dp, 2.85_dp/))
430 CALL section_add_keyword(section, keyword)
431 CALL keyword_release(keyword)
432
433 CALL keyword_create(keyword, __location__, name="COULOMB_CONSTANTS", &
434 description="Scaling parameters for Coulomb interactions (electrons, nuclei).", &
435 usage="COULOMB_CONSTANTS 2.00 1.50", n_var=2, &
436 default_r_vals=(/2.00_dp, 1.50_dp/))
437 CALL section_add_keyword(section, keyword)
438 CALL keyword_release(keyword)
439
440 CALL keyword_create(keyword, __location__, name="CN_CONSTANTS", &
441 description="Scaling parameters for Coordination number correction term.", &
442 usage="CN_CONSTANTS 0.006 -0.003 -0.005", n_var=3, &
443 default_r_vals=(/0.006_dp, -0.003_dp, -0.005_dp/))
444 CALL section_add_keyword(section, keyword)
445 CALL keyword_release(keyword)
446
447 CALL keyword_create(keyword, __location__, name="EN_CONSTANTS", &
448 description="Scaling parameters for electronegativity correction term.", &
449 usage="EN_CONSTANTS -0.007 0.000 0.000", n_var=3, &
450 default_r_vals=(/-0.007_dp, 0.000_dp, 0.000_dp/))
451 CALL section_add_keyword(section, keyword)
452 CALL keyword_release(keyword)
453
454 CALL keyword_create(keyword, __location__, name="BEN_CONSTANT", &
455 description="Scaling parameter for electronegativity correction term.", &
456 usage="BEN_CONSTANT 4.0", n_var=1, &
457 default_r_val=4.0_dp)
458 CALL section_add_keyword(section, keyword)
459 CALL keyword_release(keyword)
460
461 CALL keyword_create(keyword, __location__, name="ENSCALE", &
462 description="Scaling parameter repulsive energy (dEN in exponential).", &
463 usage="ENSCALE 0.01", n_var=1, &
464 default_r_val=0.0_dp)
465 CALL section_add_keyword(section, keyword)
466 CALL keyword_release(keyword)
467
468 CALL keyword_create(keyword, __location__, name="HALOGEN_BINDING", &
469 description="Scaling parameters for electronegativity correction term.", &
470 usage="HALOGEN_BINDING 1.30 0.44", n_var=2, default_r_vals=(/1.30_dp, 0.44_dp/))
471 CALL section_add_keyword(section, keyword)
472 CALL keyword_release(keyword)
473
474 CALL keyword_create(keyword, __location__, name="KAB_PARAM", &
475 description="Specifies the specific Kab value for types A and B.", &
476 usage="KAB_PARAM kind1 kind2 value ", repeats=.true., &
477 n_var=-1, type_of_var=char_t)
478 CALL section_add_keyword(section, keyword)
479 CALL keyword_release(keyword)
480
481 CALL keyword_create(keyword, __location__, name="XB_RADIUS", &
482 description="Specifies the radius [Bohr] of the XB pair interaction in xTB.", &
483 usage="XB_RADIUS 20.0 ", repeats=.false., &
484 n_var=1, default_r_val=20.0_dp)
485 CALL section_add_keyword(section, keyword)
486 CALL keyword_release(keyword)
487
488 CALL keyword_create(keyword, __location__, name="COULOMB_SR_CUT", &
489 description="Maximum range of short range part of Coulomb interaction.", &
490 usage="COULOMB_SR_CUT 20.0 ", repeats=.false., &
491 n_var=1, default_r_val=20.0_dp)
492 CALL section_add_keyword(section, keyword)
493 CALL keyword_release(keyword)
494
495 CALL keyword_create(keyword, __location__, name="COULOMB_SR_EPS", &
496 description="Cutoff for short range part of Coulomb interaction.", &
497 usage="COULOMB_SR_EPS 1.E-3 ", repeats=.false., &
498 n_var=1, default_r_val=1.0e-03_dp)
499 CALL section_add_keyword(section, keyword)
500 CALL keyword_release(keyword)
501
502 CALL keyword_create(keyword, __location__, name="SRB_PARAMETER", &
503 description="SRB parameters (ksrb, esrb, gscal, c1, c2, shift).", &
504 usage="SRB_PARAMETER -0.0129 3.48 0.51 -1.71 2.11 0.0537", n_var=6, &
505 default_r_vals=(/-0.0129_dp, 3.4847_dp, 0.5097_dp, &
506 -1.70549806_dp, 2.10878369_dp, 0.0537_dp/))
507 CALL section_add_keyword(section, keyword)
508 CALL keyword_release(keyword)
509
510 END SUBROUTINE create_xtb_parameter_section
511! **************************************************************************************************
512!> \brief ...
513!> \param section ...
514! **************************************************************************************************
515 SUBROUTINE create_xtb_nonbonded_section(section)
516 TYPE(section_type), POINTER :: section
517
518 TYPE(keyword_type), POINTER :: keyword
519 TYPE(section_type), POINTER :: subsection
520
521 cpassert(.NOT. ASSOCIATED(section))
522 CALL section_create(section, __location__, name="NONBONDED", &
523 description="This section specifies the input parameters for NON-BONDED interactions.", &
524 n_keywords=1, n_subsections=0, repeats=.false.)
525 NULLIFY (subsection)
526
527 CALL create_genpot_section(subsection)
528 CALL section_add_subsection(section, subsection)
529 CALL section_release(subsection)
530
531 NULLIFY (keyword)
532 CALL keyword_create(keyword, __location__, name="DX", &
533 description="Parameter used for computing the derivative with the Ridders' method.", &
534 usage="DX <REAL>", default_r_val=0.1_dp, unit_str="bohr")
535 CALL section_add_keyword(section, keyword)
536 CALL keyword_release(keyword)
537
538 CALL keyword_create(keyword, __location__, name="ERROR_LIMIT", &
539 description="Checks that the error in computing the derivative is not larger than "// &
540 "the value set; in case error is larger a warning message is printed.", &
541 usage="ERROR_LIMIT <REAL>", default_r_val=1.0e-12_dp)
542 CALL section_add_keyword(section, keyword)
543 CALL keyword_release(keyword)
544
545 END SUBROUTINE create_xtb_nonbonded_section
546! **************************************************************************************************
547!> \brief Creates the &TBLITE section
548!> \param section the section to create
549!> \author JVP
550! **************************************************************************************************
551 SUBROUTINE create_xtb_tblite_section(section)
552 TYPE(section_type), POINTER :: section
553
554 TYPE(keyword_type), POINTER :: keyword
555
556 cpassert(.NOT. ASSOCIATED(section))
557 CALL section_create(section, __location__, name="TBLITE", &
558 description="Section used to specify options for an xTB computation using tblite.", &
559 n_keywords=1, n_subsections=0, repeats=.false., citations=(/caldeweyher2017, caldeweyher2020, &
561
562 NULLIFY (keyword)
563 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
564 description="activates the execution via tblite", &
565 lone_keyword_l_val=.true., default_l_val=.false.)
566 CALL section_add_keyword(section, keyword)
567 CALL keyword_release(keyword)
568
569 NULLIFY (keyword)
570 CALL keyword_create(keyword, __location__, name="METHOD", &
571 description="Selection of the method used in tblite.", &
572 usage="METHOD (GFN1|GFN2|IPEA1)", &
573 enum_c_vals=s2a("GFN1", "GFN2", "IPEA1"), &
574 enum_i_vals=(/gfn1xtb, gfn2xtb, ipea1xtb/), &
575 enum_desc=s2a("Uses the GFN1-XTB method by Grimme.", &
576 "Uses the GFN2-XTB method by Grimme.", &
577 "Uses the IEPEA1 method by Grimme."), &
578 default_i_val=gfn2xtb)
579 CALL section_add_keyword(section, keyword)
580 CALL keyword_release(keyword)
581
582 END SUBROUTINE create_xtb_tblite_section
583
584END MODULE input_cp2k_tb
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public caldeweyher2020
integer, save, public caldeweyher2017
integer, save, public grimme2017
integer, save, public elstner1998
integer, save, public hu2007
integer, save, public asgeirsson2017
integer, save, public porezag1995
integer, save, public bannwarth2019
integer, save, public seifert1996
integer, save, public zhechkov2005
Input definition and setup for EEQ model.
Definition eeq_input.F:12
subroutine, public create_eeq_control_section(section)
...
Definition eeq_input.F:50
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public dispersion_d3
integer, parameter, public gfn1xtb
integer, parameter, public dispersion_uff
integer, parameter, public ipea1xtb
integer, parameter, public dispersion_d3bj
integer, parameter, public dispersion_d2
integer, parameter, public gfn2xtb
integer, parameter, public slater
creates the mm section of the input
subroutine, public create_genpot_section(section)
This section specifies the input parameters for a generic potential form.
function that build the dft section of the input
subroutine, public create_dftb_control_section(section)
...
subroutine, public create_xtb_control_section(section)
...
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, deprecation_notice)
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 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