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