(git:e5b1968)
Loading...
Searching...
No Matches
input_cp2k_mm.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 creates the mm section of the input
10!> \note
11!> moved out of input_cp2k
12!> \par History
13!> 04.2004 created
14!> \author fawzi
15! **************************************************************************************************
17 USE bibliography, ONLY: &
27 USE cp_units, ONLY: cp_unit_to_cp2k
28 USE force_field_kind_types, ONLY: &
46 USE input_val_types, ONLY: char_t,&
47 integer_t,&
48 lchar_t,&
49 real_t
50 USE kinds, ONLY: default_string_length,&
51 dp
52 USE string_utilities, ONLY: newline,&
53 s2a
54#include "./base/base_uses.f90"
55
56 IMPLICIT NONE
57 PRIVATE
58
59 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
60 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_mm'
61
66 PUBLIC :: create_charge_section
67!***
68CONTAINS
69
70! **************************************************************************************************
71!> \brief Create the input section for FIST.. Come on.. Let's get woohooo
72!> \param section the section to create
73!> \author teo
74! **************************************************************************************************
75 SUBROUTINE create_mm_section(section)
76 TYPE(section_type), POINTER :: section
77
78 TYPE(section_type), POINTER :: subsection
79
80 cpassert(.NOT. ASSOCIATED(section))
81 CALL section_create(section, __location__, name="mm", &
82 description="This section contains all information to run a MM calculation.", &
83 n_keywords=5, n_subsections=0, repeats=.false.)
84
85 NULLIFY (subsection)
86
87 CALL create_forcefield_section(subsection)
88 CALL section_add_subsection(section, subsection)
89 CALL section_release(subsection)
90
91 CALL create_neighbor_lists_section(subsection)
92 CALL section_add_subsection(section, subsection)
93 CALL section_release(subsection)
94
95 CALL create_poisson_section(subsection)
96 CALL section_add_subsection(section, subsection)
97 CALL section_release(subsection)
98
99 CALL create_per_efield_section(subsection)
100 CALL section_add_subsection(section, subsection)
101 CALL section_release(subsection)
102
103 CALL create_print_mm_section(subsection)
104 CALL section_add_subsection(section, subsection)
105 CALL section_release(subsection)
106
107 END SUBROUTINE create_mm_section
108
109! **************************************************************************************************
110!> \brief Create the print mm section
111!> \param section the section to create
112!> \author teo
113! **************************************************************************************************
114 SUBROUTINE create_print_mm_section(section)
115 TYPE(section_type), POINTER :: section
116
117 TYPE(keyword_type), POINTER :: keyword
118 TYPE(section_type), POINTER :: print_key
119
120 cpassert(.NOT. ASSOCIATED(section))
121 CALL section_create(section, __location__, name="print", &
122 description="Section of possible print options in MM code.", &
123 n_keywords=0, n_subsections=1, repeats=.false.)
124
125 NULLIFY (print_key, keyword)
126
127 CALL cp_print_key_section_create(print_key, __location__, "DERIVATIVES", &
128 description="Controls the printing of derivatives.", &
129 print_level=high_print_level, filename="__STD_OUT__")
130 CALL section_add_subsection(section, print_key)
131 CALL section_release(print_key)
132
133 CALL cp_print_key_section_create(print_key, __location__, "EWALD_INFO", &
134 description="Controls the printing of Ewald energy components during the "// &
135 "evaluation of the electrostatics.", &
136 print_level=high_print_level, filename="__STD_OUT__")
137 CALL section_add_subsection(section, print_key)
138 CALL section_release(print_key)
139
140 CALL create_dipoles_section(print_key, "DIPOLE", medium_print_level)
141 CALL section_add_subsection(section, print_key)
142 CALL section_release(print_key)
143
144 CALL cp_print_key_section_create(print_key, __location__, "NEIGHBOR_LISTS", &
145 description="Activates the printing of the neighbor lists.", &
146 print_level=high_print_level, filename="", unit_str="angstrom")
147 CALL section_add_subsection(section, print_key)
148 CALL section_release(print_key)
149
150 CALL cp_print_key_section_create(print_key, __location__, "ITER_INFO", &
151 description="Activates the printing of iteration info during the self-consistent "// &
152 "calculation of a polarizable forcefield.", &
153 print_level=medium_print_level, filename="__STD_OUT__")
154 CALL section_add_subsection(section, print_key)
155 CALL section_release(print_key)
156
157 CALL cp_print_key_section_create(print_key, __location__, "SUBCELL", &
158 description="Activates the printing of the subcells used for the "// &
159 "generation of neighbor lists.", &
160 print_level=high_print_level, filename="__STD_OUT__")
161 CALL section_add_subsection(section, print_key)
162 CALL section_release(print_key)
163
164 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_BANNER", &
165 description="Controls the printing of the banner of the MM program", &
166 print_level=silent_print_level, filename="__STD_OUT__")
167 CALL section_add_subsection(section, print_key)
168 CALL section_release(print_key)
169
170 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
171 description="Controls the printing of information regarding the run.", &
172 print_level=low_print_level, filename="__STD_OUT__")
173 CALL section_add_subsection(section, print_key)
174 CALL section_release(print_key)
175
176 CALL cp_print_key_section_create(print_key, __location__, "FF_PARAMETER_FILE", description= &
177 "Controls the printing of Force Field parameter file", &
178 print_level=debug_print_level + 1, filename="", common_iter_levels=2)
179 CALL section_add_subsection(section, print_key)
180 CALL section_release(print_key)
181
182 CALL cp_print_key_section_create(print_key, __location__, "FF_INFO", description= &
183 "Controls the printing of information in the forcefield settings", &
184 print_level=high_print_level, filename="__STD_OUT__")
185
186 CALL keyword_create(keyword, __location__, name="spline_info", &
187 description="if the printkey is active prints information regarding the splines"// &
188 " used in the nonbonded interactions", &
189 default_l_val=.true., lone_keyword_l_val=.true.)
190 CALL section_add_keyword(print_key, keyword)
191 CALL keyword_release(keyword)
192
193 CALL keyword_create(keyword, __location__, name="spline_data", &
194 description="if the printkey is active prints on separated files the splined function"// &
195 " together with the reference one. Useful to check the spline behavior.", &
196 default_l_val=.false., lone_keyword_l_val=.true.)
197 CALL section_add_keyword(print_key, keyword)
198 CALL keyword_release(keyword)
199
200 CALL section_add_subsection(section, print_key)
201 CALL section_release(print_key)
202
203 END SUBROUTINE create_print_mm_section
204
205! **************************************************************************************************
206!> \brief Create the forcefield section. This section is useful to set up the
207!> proper force_field for FIST calculations
208!> \param section the section to create
209!> \author teo
210! **************************************************************************************************
211 SUBROUTINE create_forcefield_section(section)
212 TYPE(section_type), POINTER :: section
213
214 TYPE(keyword_type), POINTER :: keyword
215 TYPE(section_type), POINTER :: subsection
216
217 cpassert(.NOT. ASSOCIATED(section))
218 CALL section_create(section, __location__, name="FORCEFIELD", &
219 description="Section specifying information regarding how to set up properly"// &
220 " a force_field for the classical calculations.", &
221 n_keywords=2, n_subsections=2, repeats=.false.)
222
223 NULLIFY (subsection, keyword)
224
225 CALL keyword_create( &
226 keyword, __location__, name="PARMTYPE", &
227 description="Define the kind of torsion potential", &
228 usage="PARMTYPE {OFF,CHM,G87,G96}", &
229 enum_c_vals=s2a("OFF", "CHM", "G87", "G96", "AMBER"), &
230 enum_desc=s2a("Provides force field parameters through the input file", &
231 "Provides force field parameters through an external file with CHARMM format", &
232 "Provides force field parameters through an external file with GROMOS 87 format", &
233 "Provides force field parameters through an external file with GROMOS 96 format", &
234 "Provides force field parameters through an external file with AMBER format (from v.8 on)"), &
235 enum_i_vals=(/do_ff_undef, &
236 do_ff_charmm, &
237 do_ff_g87, &
238 do_ff_g96, &
239 do_ff_amber/), &
240 default_i_val=do_ff_undef)
241 CALL section_add_keyword(section, keyword)
242 CALL keyword_release(keyword)
243
244 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
245 description="Specifies the filename that contains the parameters of the FF.", &
246 usage="PARM_FILE_NAME {FILENAME}", type_of_var=lchar_t)
247 CALL section_add_keyword(section, keyword)
248 CALL keyword_release(keyword)
249
250 CALL keyword_create(keyword, __location__, name="VDW_SCALE14", &
251 description="Scaling factor for the VDW 1-4 ", &
252 usage="VDW_SCALE14 1.0", default_r_val=1.0_dp)
253 CALL section_add_keyword(section, keyword)
254 CALL keyword_release(keyword)
255
256 CALL keyword_create(keyword, __location__, name="EI_SCALE14", &
257 description="Scaling factor for the electrostatics 1-4 ", &
258 usage="EI_SCALE14 1.0", default_r_val=0.0_dp)
259 CALL section_add_keyword(section, keyword)
260 CALL keyword_release(keyword)
261
262 CALL keyword_create(keyword, __location__, name="SHIFT_CUTOFF", &
263 description="Add a constant energy shift to the real-space "// &
264 "non-bonding interactions (both Van der Waals and "// &
265 "electrostatic) such that the energy at the cutoff radius is "// &
266 "zero. This makes the non-bonding interactions continuous at "// &
267 "the cutoff.", &
268 usage="SHIFT_CUTOFF <LOGICAL>", default_l_val=.true.)
269 CALL section_add_keyword(section, keyword)
270 CALL keyword_release(keyword)
271
272 CALL keyword_create(keyword, __location__, name="DO_NONBONDED", &
273 description="Controls the computation of all the real-space "// &
274 "(short-range) nonbonded interactions. This also "// &
275 "includes the real-space corrections for excluded "// &
276 "or scaled 1-2, 1-3 and 1-4 interactions. When set "// &
277 "to F, the neighborlists are not created and all "// &
278 "interactions that depend on them are not computed.", &
279 usage="DO_NONBONDED T", default_l_val=.true., lone_keyword_l_val=.true.)
280 CALL section_add_keyword(section, keyword)
281 CALL keyword_release(keyword)
282
283 CALL keyword_create(keyword, __location__, name="DO_ELECTROSTATICS", &
284 description="Controls the computation of all the real-space "// &
285 "(short-range) electrostatics interactions. This does not "// &
286 "affect the QM/MM electrostatic coupling when turned off.", &
287 usage="DO_ELECTROSTATICS T", default_l_val=.true., lone_keyword_l_val=.true.)
288 CALL section_add_keyword(section, keyword)
289 CALL keyword_release(keyword)
290
291 CALL keyword_create(keyword, __location__, name="IGNORE_MISSING_CRITICAL_PARAMS", &
292 description="Do not abort when critical force-field parameters "// &
293 "are missing. CP2K will run as if the terms containing the "// &
294 "missing parameters are zero.", &
295 usage="IGNORE_MISSING_CRITICAL_PARAMS .TRUE.", default_l_val=.false., &
296 lone_keyword_l_val=.true.)
297 CALL section_add_keyword(section, keyword)
298 CALL keyword_release(keyword)
299
300 CALL keyword_create(keyword, __location__, name="MULTIPLE_POTENTIAL", &
301 description="Enables the possibility to define NONBONDED and NONBONDED14 as a"// &
302 " sum of different kinds of potential. Useful for piecewise defined potentials.", &
303 usage="MULTIPLE_POTENTIAL T", default_l_val=.false., lone_keyword_l_val=.true.)
304 CALL section_add_keyword(section, keyword)
305 CALL keyword_release(keyword)
306 !Universal scattering potential at very short distances
307 CALL keyword_create(keyword, __location__, name="ZBL_SCATTERING", &
308 description="A short range repulsive potential is added, to simulate "// &
309 "collisions and scattering.", &
310 usage="ZBL_SCATTERING T", default_l_val=.false., lone_keyword_l_val=.true.)
311 CALL section_add_keyword(section, keyword)
312 CALL keyword_release(keyword)
313
314 !
315 ! subsections
316 !
317 CALL create_spline_section(subsection)
318 CALL section_add_subsection(section, subsection)
319 CALL section_release(subsection)
320
321 CALL create_nonbonded_section(subsection)
322 CALL section_add_subsection(section, subsection)
323 CALL section_release(subsection)
324
325 CALL create_nonbonded14_section(subsection)
326 CALL section_add_subsection(section, subsection)
327 CALL section_release(subsection)
328
329 CALL create_charge_section(subsection)
330 CALL section_add_subsection(section, subsection)
331 CALL section_release(subsection)
332
333 CALL create_charges_section(subsection)
334 CALL section_add_subsection(section, subsection)
335 CALL section_release(subsection)
336
337 CALL create_shell_section(subsection)
338 CALL section_add_subsection(section, subsection)
339 CALL section_release(subsection)
340
341 CALL create_bond_section(subsection, "BOND")
342 CALL section_add_subsection(section, subsection)
343 CALL section_release(subsection)
344
345 CALL create_bend_section(subsection)
346 CALL section_add_subsection(section, subsection)
347 CALL section_release(subsection)
348
349 CALL create_torsion_section(subsection)
350 CALL section_add_subsection(section, subsection)
351 CALL section_release(subsection)
352
353 CALL create_improper_section(subsection)
354 CALL section_add_subsection(section, subsection)
355 CALL section_release(subsection)
356
357 CALL create_opbend_section(subsection)
358 CALL section_add_subsection(section, subsection)
359 CALL section_release(subsection)
360
361 CALL create_dipole_section(subsection)
362 CALL section_add_subsection(section, subsection)
363 CALL section_release(subsection)
364
365 CALL create_quadrupole_section(subsection)
366 CALL section_add_subsection(section, subsection)
367 CALL section_release(subsection)
368
369 END SUBROUTINE create_forcefield_section
370
371! **************************************************************************************************
372!> \brief This section specifies the parameters for the splines
373!> \param section the section to create
374!> \author teo
375! **************************************************************************************************
376 SUBROUTINE create_spline_section(section)
377 TYPE(section_type), POINTER :: section
378
379 TYPE(keyword_type), POINTER :: keyword
380
381 cpassert(.NOT. ASSOCIATED(section))
382 CALL section_create(section, __location__, name="SPLINE", &
383 description="specifies parameters to set up the splines used in the"// &
384 " nonboned interactions (both pair body potential and many body potential)", &
385 n_keywords=1, n_subsections=0, repeats=.true.)
386
387 NULLIFY (keyword)
388
389 CALL keyword_create(keyword, __location__, name="R0_NB", &
390 description="Specify the minimum value of the distance interval "// &
391 "that brackets the value of emax_spline.", &
392 usage="R0_NB <REAL>", default_r_val=cp_unit_to_cp2k(value=0.9_dp, &
393 unit_str="bohr"), &
394 unit_str="angstrom")
395 CALL section_add_keyword(section, keyword)
396 CALL keyword_release(keyword)
397
398 CALL keyword_create(keyword, __location__, name="RCUT_NB", &
399 description="Cutoff radius for nonbonded interactions. This value overrides"// &
400 " the value specified in the potential definition and is global for all potentials.", &
401 usage="RCUT_NB {real}", default_r_val=cp_unit_to_cp2k(value=-1.0_dp, &
402 unit_str="angstrom"), &
403 unit_str="angstrom")
404 CALL section_add_keyword(section, keyword)
405 CALL keyword_release(keyword)
406
407 CALL keyword_create(keyword, __location__, name="EMAX_SPLINE", &
408 description="Specify the maximum value of the potential up to which"// &
409 " splines will be constructed", &
410 usage="EMAX_SPLINE <REAL>", &
411 default_r_val=0.5_dp, unit_str="hartree")
412 CALL section_add_keyword(section, keyword)
413 CALL keyword_release(keyword)
414
415 CALL keyword_create(keyword, __location__, name="EMAX_ACCURACY", &
416 description="Specify the maximum value of energy used to check the accuracy"// &
417 " requested through EPS_SPLINE. Energy values larger than EMAX_ACCURACY"// &
418 " generally do not satisfy the requested accuracy", &
419 usage="EMAX_ACCURACY <REAL>", default_r_val=0.02_dp, unit_str="hartree")
420 CALL section_add_keyword(section, keyword)
421 CALL keyword_release(keyword)
422
423 CALL keyword_create(keyword, __location__, name="EPS_SPLINE", &
424 description="Specify the threshold for the choice of the number of"// &
425 " points used in the splines (comparing the splined value with the"// &
426 " analytically evaluated one)", &
427 usage="EPS_SPLINE <REAL>", default_r_val=1.0e-7_dp, unit_str="hartree")
428 CALL section_add_keyword(section, keyword)
429 CALL keyword_release(keyword)
430
431 CALL keyword_create( &
432 keyword, __location__, name="NPOINTS", &
433 description="Override the default search for an accurate spline by specifying a fixed number of spline points.", &
434 usage="NPOINTS 1024", default_i_val=-1)
435 CALL section_add_keyword(section, keyword)
436 CALL keyword_release(keyword)
437
438 CALL keyword_create(keyword, __location__, name="UNIQUE_SPLINE", &
439 description="For few potentials (Lennard-Jones) one global optimal spline is generated instead"// &
440 " of different optimal splines for each kind of potential", &
441 usage="UNIQUE_SPLINE <LOGICAL>", lone_keyword_l_val=.true., default_l_val=.false.)
442 CALL section_add_keyword(section, keyword)
443 CALL keyword_release(keyword)
444
445 END SUBROUTINE create_spline_section
446
447! **************************************************************************************************
448!> \brief This section specifies the torsion of the MM atoms
449!> \param section the section to create
450!> \author teo
451! **************************************************************************************************
452 SUBROUTINE create_torsion_section(section)
453 TYPE(section_type), POINTER :: section
454
455 TYPE(keyword_type), POINTER :: keyword
456
457 cpassert(.NOT. ASSOCIATED(section))
458 CALL section_create(section, __location__, name="TORSION", &
459 description="Specifies the torsion potential of the MM system.", &
460 n_keywords=1, n_subsections=0, repeats=.true.)
461
462 NULLIFY (keyword)
463 CALL keyword_create(keyword, __location__, name="ATOMS", &
464 description="Defines the atomic kinds involved in the tors.", &
465 usage="ATOMS {KIND1} {KIND2} {KIND3} {KIND4}", type_of_var=char_t, &
466 n_var=4)
467 CALL section_add_keyword(section, keyword)
468 CALL keyword_release(keyword)
469
470 CALL keyword_create(keyword, __location__, name="KIND", &
471 description="Define the kind of torsion potential", &
472 usage="KIND CHARMM", &
473 enum_c_vals=s2a("CHARMM", "G87", "G96", "AMBER", "OPLS"), &
474 enum_desc=s2a("Functional Form (CHARMM|G87|G96|AMBER): K * [ 1 + cos[M*PHI - PHI0]]", &
475 "Functional Form (CHARMM|G87|G96|AMBER): K * [ 1 + cos[M*PHI - PHI0]]", &
476 "Functional Form (CHARMM|G87|G96|AMBER): K * [ 1 + cos[M*PHI - PHI0]]", &
477 "Functional Form (CHARMM|G87|G96|AMBER): K * [ 1 + cos[M*PHI - PHI0]]", &
478 "Functional Form: K / 2 * [ 1 + (-1)^(M-1) * cos[M*PHI]]"), &
479 enum_i_vals=(/do_ff_charmm, &
480 do_ff_g87, &
481 do_ff_g96, &
482 do_ff_amber, &
483 do_ff_opls/), &
484 default_i_val=do_ff_charmm)
485 CALL section_add_keyword(section, keyword)
486 CALL keyword_release(keyword)
487
488 CALL keyword_create(keyword, __location__, name="K", &
489 description="Defines the force constant of the potential", &
490 usage="K {real}", type_of_var=real_t, &
491 n_var=1, unit_str="hartree")
492 CALL section_add_keyword(section, keyword)
493 CALL keyword_release(keyword)
494
495 CALL keyword_create(keyword, __location__, name="PHI0", &
496 description="Defines the phase of the potential.", &
497 usage="PHI0 {real}", type_of_var=real_t, &
498 n_var=1, unit_str="rad", default_r_val=0.0_dp)
499 CALL section_add_keyword(section, keyword)
500 CALL keyword_release(keyword)
501
502 CALL keyword_create(keyword, __location__, name="M", &
503 description="Defines the multiplicity of the potential.", &
504 usage="M {integer}", type_of_var=integer_t, &
505 n_var=1)
506 CALL section_add_keyword(section, keyword)
507 CALL keyword_release(keyword)
508
509 END SUBROUTINE create_torsion_section
510
511! **************************************************************************************************
512!> \brief This section specifies the improper torsion of the MM atoms
513!> \param section the section to create
514!> \author louis vanduyfhuys
515! **************************************************************************************************
516 SUBROUTINE create_improper_section(section)
517 TYPE(section_type), POINTER :: section
518
519 TYPE(keyword_type), POINTER :: keyword
520
521 cpassert(.NOT. ASSOCIATED(section))
522 CALL section_create(section, __location__, name="IMPROPER", &
523 description="Specifies the improper torsion potential of the MM system.", &
524 n_keywords=1, n_subsections=0, repeats=.true.)
525
526 NULLIFY (keyword)
527 CALL keyword_create(keyword, __location__, name="ATOMS", &
528 description="Defines the atomic kinds involved in the improper tors.", &
529 usage="ATOMS {KIND1} {KIND2} {KIND3} {KIND4}", type_of_var=char_t, &
530 n_var=4)
531 CALL section_add_keyword(section, keyword)
532 CALL keyword_release(keyword)
533
534 CALL keyword_create(keyword, __location__, name="KIND", &
535 description="Define the kind of improper torsion potential", &
536 usage="KIND CHARMM", &
537 enum_c_vals=s2a("CHARMM", "G87", "G96", "HARMONIC"), &
538 enum_desc=s2a("Functional Form (CHARMM): K * [ PHI - PHI0 ]**2", &
539 "Functional Form (G87|G96|HARMONIC): 0.5 * K * [ PHI - PHI0 ]**2", &
540 "Functional Form (G87|G96|HARMONIC): 0.5 * K * [ PHI - PHI0 ]**2", &
541 "Functional Form (G87|G96|HARMONIC): 0.5 * K * [ PHI - PHI0 ]**2"), &
542 enum_i_vals=(/do_ff_charmm, &
543 do_ff_g87, &
544 do_ff_g96, &
545 do_ff_harmonic/), &
546 default_i_val=do_ff_charmm)
547 CALL section_add_keyword(section, keyword)
548 CALL keyword_release(keyword)
549
550 CALL keyword_create(keyword, __location__, name="K", &
551 description="Defines the force constant of the potential", &
552 usage="K {real}", type_of_var=real_t, &
553 n_var=1, unit_str="hartree*rad^-2")
554 CALL section_add_keyword(section, keyword)
555 CALL keyword_release(keyword)
556
557 CALL keyword_create(keyword, __location__, name="PHI0", &
558 description="Defines the phase of the potential.", &
559 usage="PHI0 {real}", type_of_var=real_t, &
560 n_var=1, unit_str="rad")
561 CALL section_add_keyword(section, keyword)
562 CALL keyword_release(keyword)
563
564 END SUBROUTINE create_improper_section
565
566! **************************************************************************************************
567!> \brief This section specifies the out of plane bend of the MM atoms
568!> \param section the section to create
569!> \author louis vanduyfhuys
570! **************************************************************************************************
571 SUBROUTINE create_opbend_section(section)
572 TYPE(section_type), POINTER :: section
573
574 TYPE(keyword_type), POINTER :: keyword
575
576 cpassert(.NOT. ASSOCIATED(section))
577 CALL section_create(section, __location__, name="OPBEND", &
578 description="Specifies the out of plane bend potential of the MM system."// &
579 " (Only defined for atom quadruples which are also defined as an improper"// &
580 " pattern in the topology.)", &
581 n_keywords=1, n_subsections=0, repeats=.true.)
582
583 NULLIFY (keyword)
584 CALL keyword_create(keyword, __location__, name="ATOMS", &
585 description="Defines the atomic kinds involved in the opbend.", &
586 usage="ATOMS {KIND1} {KIND2} {KIND3} {KIND4}", type_of_var=char_t, &
587 n_var=4)
588 CALL section_add_keyword(section, keyword)
589 CALL keyword_release(keyword)
590
591 CALL keyword_create(keyword, __location__, name="KIND", &
592 description="Define the kind of out of plane bend potential", &
593 usage="KIND HARMONIC", &
594 enum_c_vals=s2a("HARMONIC", "MM2", "MM3", "MM4"), &
595 enum_desc=s2a("Functional Form (HARMONIC): 0.5 * K * [ PHI - PHI0 ]**2", &
596 "Functional Form (MM2|MM3|MM4): K * [ PHI - PHI0 ]**2", &
597 "Functional Form (MM2|MM3|MM4): K * [ PHI - PHI0 ]**2", &
598 "Functional Form (MM2|MM3|MM4): K * [ PHI - PHI0 ]**2"), &
599 enum_i_vals=(/do_ff_harmonic, &
600 do_ff_mm2, &
601 do_ff_mm3, &
602 do_ff_mm4/), &
603 default_i_val=do_ff_harmonic)
604 CALL section_add_keyword(section, keyword)
605 CALL keyword_release(keyword)
606
607 CALL keyword_create(keyword, __location__, name="K", &
608 description="Defines the force constant of the potential", &
609 usage="K {real}", type_of_var=real_t, &
610 n_var=1, unit_str="hartree*rad^-2")
611 CALL section_add_keyword(section, keyword)
612 CALL keyword_release(keyword)
613
614 CALL keyword_create(keyword, __location__, name="PHI0", &
615 description="Defines the phase of the potential.", &
616 usage="PHI0 {real}", type_of_var=real_t, &
617 n_var=1, unit_str="rad")
618 CALL section_add_keyword(section, keyword)
619 CALL keyword_release(keyword)
620
621 END SUBROUTINE create_opbend_section
622
623! **************************************************************************************************
624!> \brief This section specifies the bend of the MM atoms
625!> \param section the section to create
626!> \author teo
627! **************************************************************************************************
628 SUBROUTINE create_bend_section(section)
629 TYPE(section_type), POINTER :: section
630
631 TYPE(keyword_type), POINTER :: keyword
632 TYPE(section_type), POINTER :: subsection
633
634 cpassert(.NOT. ASSOCIATED(section))
635 CALL section_create(section, __location__, name="BEND", &
636 description="Specifies the bend potential of the MM system.", &
637 n_keywords=11, n_subsections=1, repeats=.true.)
638
639 NULLIFY (keyword, subsection)
640
641 CALL keyword_create(keyword, __location__, name="ATOMS", &
642 description="Defines the atomic kinds involved in the bend.", &
643 usage="ATOMS {KIND1} {KIND2} {KIND3}", type_of_var=char_t, &
644 n_var=3)
645 CALL section_add_keyword(section, keyword)
646 CALL keyword_release(keyword)
647
648 CALL keyword_create( &
649 keyword, __location__, name="KIND", &
650 description="Define the kind of bend potential", &
651 usage="KIND HARMONIC", &
652 enum_c_vals=s2a("HARMONIC", "CHARMM", "AMBER", "G87", "G96", "CUBIC", "MIXED_BEND_STRETCH", "MM3", &
653 "LEGENDRE"), &
654 enum_desc=s2a("Functional Form (HARMONIC|G87): 1/2*K*(THETA-THETA0)^2", &
655 "Functional Form (CHARMM|AMBER): K*(THETA-THETA0)^2", &
656 "Functional Form (CHARMM|AMBER): K*(THETA-THETA0)^2", &
657 "Functional Form (HARMONIC|G87): 1/2*K*(THETA-THETA0)^2", &
658 "Functional Form (G96): 1/2*K*(COS(THETA)-THETA0)^2", &
659 "Functional Form (CUBIC): K*(THETA-THETA0)**2*(1+CB*(THETA-THETA0))", &
660 "Functional Form (MIXED_BEND_STRETCH): K*(THETA-THETA0)**2*(1+CB*(THETA-THETA0))+"// &
661 " KSS*(R12-R012)*(R32-R032)+KBS12*(R12-R012)*(THETA-THETA0)+KBS32*(R32-R032)*(THETA-THETA0)", &
662 "Functional Form (MM3): 1/2*K*(THETA-THETA0)**2*(1-0.014*(THETA-THETA0)+5.6E-5*(THETA-THETA0)**2"// &
663 " -7.0E-7*(THETA-THETA0)**3+9.0E-10*(THETA-THETA0)**4)+KBS12*(R12-R012)*(THETA-THETA0)+"// &
664 " KBS32*(R32-R032)*(THETA-THETA0)", &
665 "Functional Form (LEGENDRE): sum_{i=0}^N c_i*P_i(COS(THETA)) "), &
666 enum_i_vals=(/do_ff_harmonic, &
667 do_ff_charmm, &
668 do_ff_amber, &
669 do_ff_g87, &
670 do_ff_g96, &
671 do_ff_cubic, &
673 do_ff_mm3, &
674 do_ff_legendre/), &
675 default_i_val=do_ff_charmm)
676 CALL section_add_keyword(section, keyword)
677 CALL keyword_release(keyword)
678
679 CALL keyword_create(keyword, __location__, name="K", &
680 description="Defines the force constant of the potential", &
681 usage="K {real}", type_of_var=real_t, &
682 n_var=1, unit_str="hartree*rad^-2")
683 CALL section_add_keyword(section, keyword)
684 CALL keyword_release(keyword)
685
686 CALL keyword_create(keyword, __location__, name="CB", &
687 description="Defines the the cubic force constant of the bend", &
688 usage="CB {real}", default_r_val=0.0_dp, type_of_var=real_t, &
689 n_var=1, unit_str="rad^-1")
690 CALL section_add_keyword(section, keyword)
691 CALL keyword_release(keyword)
692
693 CALL keyword_create(keyword, __location__, name="R012", &
694 description="Mixed bend stretch parameter", &
695 usage="R012 {real}", default_r_val=0.0_dp, type_of_var=real_t, &
696 n_var=1, unit_str="bohr")
697 CALL section_add_keyword(section, keyword)
698 CALL keyword_release(keyword)
699 CALL keyword_create(keyword, __location__, name="R032", &
700 description="Mixed bend stretch parameter", &
701 usage="R032 {real}", default_r_val=0.0_dp, type_of_var=real_t, &
702 n_var=1, unit_str="bohr")
703 CALL section_add_keyword(section, keyword)
704 CALL keyword_release(keyword)
705 CALL keyword_create(keyword, __location__, name="KBS12", &
706 description="Mixed bend stretch parameter", &
707 usage="KBS12 {real}", default_r_val=0.0_dp, type_of_var=real_t, &
708 n_var=1, unit_str="hartree*bohr^-1*rad^-1")
709 CALL section_add_keyword(section, keyword)
710 CALL keyword_release(keyword)
711 CALL keyword_create(keyword, __location__, name="KBS32", &
712 description="Mixed bend stretch parameter", &
713 usage="KBS32 {real}", default_r_val=0.0_dp, type_of_var=real_t, &
714 n_var=1, unit_str="hartree*bohr^-1*rad^-1")
715 CALL section_add_keyword(section, keyword)
716 CALL keyword_release(keyword)
717 CALL keyword_create(keyword, __location__, name="KSS", &
718 description="Mixed bend stretch parameter", &
719 usage="KSS {real}", default_r_val=0.0_dp, type_of_var=real_t, &
720 n_var=1, unit_str="hartree*bohr^-2")
721 CALL section_add_keyword(section, keyword)
722 CALL keyword_release(keyword)
723
724 CALL keyword_create(keyword, __location__, name="THETA0", &
725 description="Defines the equilibrium angle.", &
726 usage="THETA0 {real}", type_of_var=real_t, &
727 n_var=1, unit_str='rad')
728 CALL section_add_keyword(section, keyword)
729 CALL keyword_release(keyword)
730
731 CALL keyword_create(keyword, __location__, name="LEGENDRE", &
732 description="Specifies the coefficients for the legendre"// &
733 " expansion of the bending potential."// &
734 " 'THETA0' and 'K' are not used, but need to be specified."// &
735 " Use an arbitrary value.", usage="LEGENDRE {REAL} {REAL} ...", &
736 default_r_val=0.0d0, type_of_var=real_t, &
737 n_var=-1, unit_str="hartree")
738 CALL section_add_keyword(section, keyword)
739 CALL keyword_release(keyword)
740
741 ! Create the Urey-Bradley section
742 CALL create_bond_section(subsection, "UB")
743 CALL section_add_subsection(section, subsection)
744 CALL section_release(subsection)
745
746 END SUBROUTINE create_bend_section
747
748! **************************************************************************************************
749!> \brief This section specifies the bond of the MM atoms
750!> \param section the section to create
751!> \param label ...
752!> \author teo
753! **************************************************************************************************
754 SUBROUTINE create_bond_section(section, label)
755 TYPE(section_type), POINTER :: section
756 CHARACTER(LEN=*), INTENT(IN) :: label
757
758 CHARACTER(LEN=default_string_length) :: tag
759 TYPE(keyword_type), POINTER :: keyword
760
761 cpassert(.NOT. ASSOCIATED(section))
762 NULLIFY (keyword)
763
764 IF (trim(label) == "UB") THEN
765 tag = " Urey-Bradley "
766 CALL section_create(section, __location__, name=trim(label), &
767 description="Specifies the Urey-Bradley potential between the external atoms"// &
768 " defining the angle", &
769 n_keywords=1, n_subsections=0, repeats=.false.)
770
771 ELSE
772 tag = " Bond "
773 CALL section_create(section, __location__, name=trim(label), &
774 description="Specifies the bond potential", &
775 n_keywords=1, n_subsections=0, repeats=.true.)
776
777 CALL keyword_create(keyword, __location__, name="ATOMS", &
778 description="Defines the atomic kinds involved in the bond.", &
779 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
780 n_var=2)
781 CALL section_add_keyword(section, keyword)
782 CALL keyword_release(keyword)
783 END IF
784
785 CALL keyword_create(keyword, __location__, name="KIND", &
786 description="Define the kind of"//trim(tag)//"potential.", &
787 usage="KIND HARMONIC", &
788 enum_c_vals=s2a("HARMONIC", "CHARMM", "AMBER", "G87", "G96", "QUARTIC", &
789 "MORSE", "CUBIC", "FUES"), &
790 enum_desc=s2a("Functional Form (HARMONIC|G87): 1/2*K*(R-R0)^2", &
791 "Functional Form (CHARMM|AMBER): K*(R-R0)^2", &
792 "Functional Form (CHARMM|AMBER): K*(R-R0)^2", &
793 "Functional Form (HARMONIC|G87): 1/2*K*(R-R0)^2", &
794 "Functional Form (G96): 1/4*K*(R^2-R0^2)^2", &
795 "Functional Form (QUARTIC): (1/2*K1+[1/3*K2+1/4*K3*|R-R0|]*|R-R0|)(R-R0)^2", &
796 "Functional Form (MORSE): K1*[(1-exp(-K2*(R-R0)))^2-1])", &
797 "Functional Form (CUBIC): K*(R-R0)^2*(1+cs*(R-R0)+7/12*(cs^2*(R-R0)^2))", &
798 "Functional Form (FUES): 1/2*K*R0^2*(1+R0/R*(R0/R-2))"), &
799 enum_i_vals=(/do_ff_harmonic, &
800 do_ff_charmm, &
801 do_ff_amber, &
802 do_ff_g87, &
803 do_ff_g96, &
805 do_ff_morse, &
806 do_ff_cubic, &
807 do_ff_fues/), &
808 default_i_val=do_ff_charmm)
809 CALL section_add_keyword(section, keyword)
810 CALL keyword_release(keyword)
811
812 CALL keyword_create(keyword, __location__, name="K", &
813 description="Defines the force constant of the potential. "// &
814 "For MORSE potentials 2 numbers are expected. "// &
815 "For QUARTIC potentials 3 numbers are expected.", &
816 usage="K {real}", type_of_var=real_t, &
817 n_var=-1, unit_str="internal_cp2k")
818 CALL section_add_keyword(section, keyword)
819 CALL keyword_release(keyword)
820
821 CALL keyword_create(keyword, __location__, name="CS", &
822 description="Defines the cubic stretch term.", &
823 usage="CS {real}", default_r_val=0.0_dp, type_of_var=real_t, &
824 n_var=1, unit_str="bohr^-1")
825 CALL section_add_keyword(section, keyword)
826 CALL keyword_release(keyword)
827
828 CALL keyword_create(keyword, __location__, name="R0", &
829 description="Defines the equilibrium distance.", &
830 usage="R0 {real}", type_of_var=real_t, &
831 n_var=1, unit_str="bohr")
832 CALL section_add_keyword(section, keyword)
833 CALL keyword_release(keyword)
834
835 END SUBROUTINE create_bond_section
836
837! **************************************************************************************************
838!> \brief This section specifies the charge of the MM atoms
839!> \param section the section to create
840!> \author teo
841! **************************************************************************************************
842 SUBROUTINE create_charges_section(section)
843 TYPE(section_type), POINTER :: section
844
845 TYPE(keyword_type), POINTER :: keyword
846
847 cpassert(.NOT. ASSOCIATED(section))
848 CALL section_create(section, __location__, name="charges", &
849 description="Allow to specify an array of classical charges, thus avoiding the"// &
850 " packing and permitting the usage of different charges for same atomic types.", &
851 n_keywords=1, n_subsections=0, repeats=.false.)
852
853 NULLIFY (keyword)
854 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
855 description="Value of the charge for the individual atom. Order MUST reflect"// &
856 " the one specified for the geometry.", repeats=.true., usage="{Real}", &
857 type_of_var=real_t)
858 CALL section_add_keyword(section, keyword)
859 CALL keyword_release(keyword)
860
861 END SUBROUTINE create_charges_section
862
863! **************************************************************************************************
864!> \brief This section specifies the charge of the MM atoms
865!> \param section the section to create
866!> \author teo
867! **************************************************************************************************
868 SUBROUTINE create_charge_section(section)
869 TYPE(section_type), POINTER :: section
870
871 TYPE(keyword_type), POINTER :: keyword
872
873 cpassert(.NOT. ASSOCIATED(section))
874 CALL section_create(section, __location__, name="charge", &
875 description="This section specifies the charge of the MM atoms", &
876 n_keywords=1, n_subsections=0, repeats=.true.)
877
878 NULLIFY (keyword)
879
880 CALL keyword_create(keyword, __location__, name="ATOM", &
881 description="Defines the atomic kind of the charge.", &
882 usage="ATOM {KIND1}", type_of_var=char_t, &
883 n_var=1)
884 CALL section_add_keyword(section, keyword)
885 CALL keyword_release(keyword)
886
887 CALL keyword_create(keyword, __location__, name="CHARGE", &
888 description="Defines the charge of the MM atom in electron charge unit.", &
889 usage="CHARGE {real}", type_of_var=real_t, &
890 n_var=1)
891 CALL section_add_keyword(section, keyword)
892 CALL keyword_release(keyword)
893
894 END SUBROUTINE create_charge_section
895
896! **************************************************************************************************
897!> \brief This section specifies the isotropic polarizability of the MM atoms
898!> \param section the section to create
899!> \author Marcel Baer
900! **************************************************************************************************
901 SUBROUTINE create_quadrupole_section(section)
902 TYPE(section_type), POINTER :: section
903
904 TYPE(keyword_type), POINTER :: keyword
905
906 cpassert(.NOT. ASSOCIATED(section))
907 CALL section_create( &
908 section, __location__, name="QUADRUPOLE", &
909 description="This section specifies that we will perform an SCF quadrupole calculation of the MM atoms. "// &
910 "Needs KEYWORD POL_SCF in POISSON secton", &
911 n_keywords=1, n_subsections=0, repeats=.true.)
912
913 NULLIFY (keyword)
914
915 CALL keyword_create(keyword, __location__, name="ATOM", &
916 description="Defines the atomic kind of the SCF quadrupole.", &
917 usage="ATOM {KIND1}", type_of_var=char_t, &
918 n_var=1)
919 CALL section_add_keyword(section, keyword)
920 CALL keyword_release(keyword)
921
922 CALL keyword_create(keyword, __location__, name="CPOL", &
923 description="Defines the isotropic polarizability of the MM atom.", &
924 usage="CPOL {real}", type_of_var=real_t, &
925 n_var=1, unit_str='internal_cp2k')
926 CALL section_add_keyword(section, keyword)
927 CALL keyword_release(keyword)
928
929 END SUBROUTINE create_quadrupole_section
930
931! **************************************************************************************************
932!> \brief This section specifies the isotropic polarizability of the MM atoms
933!> \param section the section to create
934!> \author Marcel Baer
935! **************************************************************************************************
936 SUBROUTINE create_dipole_section(section)
937 TYPE(section_type), POINTER :: section
938
939 TYPE(keyword_type), POINTER :: keyword
940 TYPE(section_type), POINTER :: subsection
941
942 cpassert(.NOT. ASSOCIATED(section))
943 CALL section_create(section, __location__, name="DIPOLE", &
944 description="This section specifies that we will perform an SCF dipole calculation of the MM atoms. "// &
945 "Needs KEYWORD POL_SCF in POISSON secton", &
946 n_keywords=1, n_subsections=1, repeats=.true.)
947
948 NULLIFY (subsection, keyword)
949
950 CALL keyword_create(keyword, __location__, name="ATOM", &
951 description="Defines the atomic kind of the SCF dipole.", &
952 usage="ATOM {KIND1}", type_of_var=char_t, &
953 n_var=1)
954 CALL section_add_keyword(section, keyword)
955 CALL keyword_release(keyword)
956
957 CALL keyword_create(keyword, __location__, name="APOL", &
958 description="Defines the isotropic polarizability of the MM atom.", &
959 usage="APOL {real}", type_of_var=real_t, &
960 n_var=1, unit_str='angstrom^3')
961 CALL section_add_keyword(section, keyword)
962 CALL keyword_release(keyword)
963
964 CALL create_damping_section(subsection)
965 CALL section_add_subsection(section, subsection)
966 CALL section_release(subsection)
967 END SUBROUTINE create_dipole_section
968
969! **************************************************************************************************
970!> \brief This section specifies the idamping parameters for polarizable atoms
971!> \param section the section to create
972!> \author Rodolphe Vuilleumier
973! **************************************************************************************************
974 SUBROUTINE create_damping_section(section)
975 TYPE(section_type), POINTER :: section
976
977 TYPE(keyword_type), POINTER :: keyword
978
979 cpassert(.NOT. ASSOCIATED(section))
980 CALL section_create(section, __location__, name="DAMPING", &
981 description="This section specifies optional electric field damping for the polarizable atoms. ", &
982 n_keywords=4, n_subsections=0, repeats=.true.)
983
984 NULLIFY (keyword)
985
986 CALL keyword_create(keyword, __location__, name="ATOM", &
987 description="Defines the atomic kind for this damping function.", &
988 usage="ATOM {KIND1}", type_of_var=char_t, &
989 n_var=1)
990 CALL section_add_keyword(section, keyword)
991 CALL keyword_release(keyword)
992
993 CALL keyword_create(keyword, __location__, name="TYPE", &
994 description="Defines the damping type.", &
995 usage="TYPE {string}", type_of_var=char_t, &
996 n_var=1, default_c_val="TANG-TOENNIES")
997 CALL section_add_keyword(section, keyword)
998 CALL keyword_release(keyword)
999
1000 CALL keyword_create(keyword, __location__, name="ORDER", &
1001 description="Defines the order for this damping.", &
1002 usage="ORDER {integer}", type_of_var=integer_t, &
1003 n_var=1, default_i_val=3)
1004 CALL section_add_keyword(section, keyword)
1005 CALL keyword_release(keyword)
1006
1007 CALL keyword_create(keyword, __location__, name="BIJ", &
1008 description="Defines the BIJ parameter for this damping.", &
1009 usage="BIJ {real}", type_of_var=real_t, &
1010 n_var=1, unit_str='angstrom^-1')
1011 CALL section_add_keyword(section, keyword)
1012 CALL keyword_release(keyword)
1013
1014 CALL keyword_create(keyword, __location__, name="CIJ", &
1015 description="Defines the CIJ parameter for this damping.", &
1016 usage="CIJ {real}", type_of_var=real_t, &
1017 n_var=1, unit_str='')
1018 CALL section_add_keyword(section, keyword)
1019 CALL keyword_release(keyword)
1020
1021 END SUBROUTINE create_damping_section
1022
1023! **************************************************************************************************
1024!> \brief This section specifies the charge of the MM atoms
1025!> \param section the section to create
1026!> \author teo
1027! **************************************************************************************************
1028 SUBROUTINE create_shell_section(section)
1029 TYPE(section_type), POINTER :: section
1030
1031 TYPE(keyword_type), POINTER :: keyword
1032
1033 cpassert(.NOT. ASSOCIATED(section))
1034 CALL section_create(section, __location__, name="SHELL", &
1035 description="This section specifies the parameters for shell-model potentials", &
1036 n_keywords=6, n_subsections=0, repeats=.true., &
1037 citations=(/dick1958, mitchell1993, devynck2012/))
1038
1039 NULLIFY (keyword)
1040
1041 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
1042 description="The kind for which the shell potential parameters are given ", &
1043 usage="H", default_c_val="DEFAULT")
1044 CALL section_add_keyword(section, keyword)
1045 CALL keyword_release(keyword)
1046
1047 CALL keyword_create(keyword, __location__, name="CORE_CHARGE", &
1048 variants=(/"CORE"/), &
1049 description="Partial charge assigned to the core (electron charge units)", &
1050 usage="CORE_CHARGE {real}", &
1051 default_r_val=0.0_dp)
1052 CALL section_add_keyword(section, keyword)
1053 CALL keyword_release(keyword)
1054
1055 CALL keyword_create(keyword, __location__, name="SHELL_CHARGE", &
1056 variants=(/"SHELL"/), &
1057 description="Partial charge assigned to the shell (electron charge units)", &
1058 usage="SHELL_CHARGE {real}", &
1059 default_r_val=0.0_dp)
1060 CALL section_add_keyword(section, keyword)
1061 CALL keyword_release(keyword)
1062
1063 CALL keyword_create(keyword, __location__, name="MASS_FRACTION", &
1064 variants=(/"MASS"/), &
1065 description="Fraction of the mass of the atom to be assigned to the shell", &
1066 usage="MASS_FRACTION {real}", &
1067 default_r_val=0.1_dp)
1068 CALL section_add_keyword(section, keyword)
1069 CALL keyword_release(keyword)
1070
1071 CALL keyword_create(keyword, __location__, name="K2_SPRING", &
1072 variants=s2a("K2", "SPRING"), &
1073 description="Force constant k2 of the spring potential 1/2*k2*r^2 + 1/24*k4*r^4 "// &
1074 "binding a core-shell pair when a core-shell potential is employed.", &
1075 repeats=.false., &
1076 usage="K2_SPRING {real}", &
1077 default_r_val=-1.0_dp, &
1078 unit_str="hartree*bohr^-2")
1079 CALL section_add_keyword(section, keyword)
1080 CALL keyword_release(keyword)
1081
1082 CALL keyword_create(keyword, __location__, name="K4_SPRING", &
1083 variants=s2a("K4"), &
1084 description="Force constant k4 of the spring potential 1/2*k2*r^2 + 1/24*k4*r^4 "// &
1085 "binding a core-shell pair when a core-shell potential is employed. "// &
1086 "By default a harmonic spring potential is used, i.e. k4 is zero.", &
1087 repeats=.false., &
1088 usage="K4_SPRING {real}", &
1089 default_r_val=0.0_dp, &
1090 unit_str="hartree*bohr^-4")
1091 CALL section_add_keyword(section, keyword)
1092 CALL keyword_release(keyword)
1093
1094 CALL keyword_create(keyword, __location__, name="MAX_DISTANCE", &
1095 description="Assign a maximum elongation of the spring, "// &
1096 "if negative no limit is imposed", &
1097 usage="MAX_DISTANCE 0.0", &
1098 default_r_val=-1.0_dp, &
1099 unit_str="angstrom")
1100 CALL section_add_keyword(section, keyword)
1101 CALL keyword_release(keyword)
1102
1103 CALL keyword_create(keyword, __location__, name="SHELL_CUTOFF", &
1104 description="Define a screening function to exclude some neighbors "// &
1105 "of the shell when electrostatic interaction are considered, "// &
1106 "if negative no screening is operated", &
1107 usage="SHELL_CUTOFF -1.0", &
1108 default_r_val=-1.0_dp, &
1109 unit_str="angstrom")
1110 CALL section_add_keyword(section, keyword)
1111 CALL keyword_release(keyword)
1112
1113 END SUBROUTINE create_shell_section
1114
1115! **************************************************************************************************
1116!> \brief This section specifies the input parameters for 1-4 NON-BONDED
1117!> Interactions
1118!> \param section the section to create
1119!> \author teo
1120! **************************************************************************************************
1121 SUBROUTINE create_nonbonded14_section(section)
1122 TYPE(section_type), POINTER :: section
1123
1124 TYPE(section_type), POINTER :: subsection
1125
1126 cpassert(.NOT. ASSOCIATED(section))
1127 CALL section_create(section, __location__, name="nonbonded14", &
1128 description="This section specifies the input parameters for 1-4 NON-BONDED interactions.", &
1129 n_keywords=1, n_subsections=0, repeats=.false.)
1130
1131 NULLIFY (subsection)
1132 CALL create_lj_section(subsection)
1133 CALL section_add_subsection(section, subsection)
1134 CALL section_release(subsection)
1135
1136 CALL create_williams_section(subsection)
1137 CALL section_add_subsection(section, subsection)
1138 CALL section_release(subsection)
1139
1140 CALL create_goodwin_section(subsection)
1141 CALL section_add_subsection(section, subsection)
1142 CALL section_release(subsection)
1143
1144 CALL create_genpot_section(subsection)
1145 CALL section_add_subsection(section, subsection)
1146 CALL section_release(subsection)
1147
1148 END SUBROUTINE create_nonbonded14_section
1149
1150! **************************************************************************************************
1151!> \brief This section specifies the input parameters for 1-4 NON-BONDED
1152!> Interactions
1153!> \param section the section to create
1154!> \author teo
1155! **************************************************************************************************
1156 SUBROUTINE create_nonbonded_section(section)
1157 TYPE(section_type), POINTER :: section
1158
1159 TYPE(section_type), POINTER :: subsection
1160
1161 cpassert(.NOT. ASSOCIATED(section))
1162 CALL section_create(section, __location__, name="nonbonded", &
1163 description="This section specifies the input parameters for NON-BONDED interactions.", &
1164 n_keywords=1, n_subsections=0, repeats=.false.)
1165
1166 NULLIFY (subsection)
1167 CALL create_lj_section(subsection)
1168 CALL section_add_subsection(section, subsection)
1169 CALL section_release(subsection)
1170
1171 CALL create_williams_section(subsection)
1172 CALL section_add_subsection(section, subsection)
1173 CALL section_release(subsection)
1174
1175 CALL create_eam_section(subsection)
1176 CALL section_add_subsection(section, subsection)
1177 CALL section_release(subsection)
1178
1179 CALL create_quip_section(subsection)
1180 CALL section_add_subsection(section, subsection)
1181 CALL section_release(subsection)
1182
1183 CALL create_nequip_section(subsection)
1184 CALL section_add_subsection(section, subsection)
1185 CALL section_release(subsection)
1186
1187 CALL create_allegro_section(subsection)
1188 CALL section_add_subsection(section, subsection)
1189 CALL section_release(subsection)
1190
1191 CALL create_ace_section(subsection)
1192 CALL section_add_subsection(section, subsection)
1193 CALL section_release(subsection)
1194
1195 CALL create_deepmd_section(subsection)
1196 CALL section_add_subsection(section, subsection)
1197 CALL section_release(subsection)
1198
1199 CALL create_goodwin_section(subsection)
1200 CALL section_add_subsection(section, subsection)
1201 CALL section_release(subsection)
1202
1203 CALL create_ipbv_section(subsection)
1204 CALL section_add_subsection(section, subsection)
1205 CALL section_release(subsection)
1206
1207 CALL create_bmhft_section(subsection)
1208 CALL section_add_subsection(section, subsection)
1209 CALL section_release(subsection)
1210
1211 CALL create_bmhftd_section(subsection)
1212 CALL section_add_subsection(section, subsection)
1213 CALL section_release(subsection)
1214
1215 CALL create_buck4r_section(subsection)
1216 CALL section_add_subsection(section, subsection)
1217 CALL section_release(subsection)
1218
1219 CALL create_buckmorse_section(subsection)
1220 CALL section_add_subsection(section, subsection)
1221 CALL section_release(subsection)
1222
1223 CALL create_genpot_section(subsection)
1224 CALL section_add_subsection(section, subsection)
1225 CALL section_release(subsection)
1226
1227 CALL create_tersoff_section(subsection)
1228 CALL section_add_subsection(section, subsection)
1229 CALL section_release(subsection)
1230
1231 CALL create_siepmann_section(subsection)
1232 CALL section_add_subsection(section, subsection)
1233 CALL section_release(subsection)
1234
1235 CALL create_gal_section(subsection)
1236 CALL section_add_subsection(section, subsection)
1237 CALL section_release(subsection)
1238
1239 CALL create_gal21_section(subsection)
1240 CALL section_add_subsection(section, subsection)
1241 CALL section_release(subsection)
1242
1243 CALL create_tabpot_section(subsection)
1244 CALL section_add_subsection(section, subsection)
1245 CALL section_release(subsection)
1246
1247 END SUBROUTINE create_nonbonded_section
1248
1249! **************************************************************************************************
1250!> \brief This section specifies the input parameters for generation of
1251!> neighbor lists
1252!> \param section the section to create
1253!> \author teo [07.2007] - Zurich University
1254! **************************************************************************************************
1256 TYPE(section_type), POINTER :: section
1257
1258 TYPE(keyword_type), POINTER :: keyword
1259
1260 NULLIFY (keyword)
1261 cpassert(.NOT. ASSOCIATED(section))
1262 CALL section_create(section, __location__, name="neighbor_lists", &
1263 description="This section specifies the input parameters for the construction of"// &
1264 " neighbor lists.", &
1265 n_keywords=1, n_subsections=0, repeats=.false.)
1266
1267 CALL keyword_create(keyword, __location__, name="VERLET_SKIN", &
1268 description="Defines the Verlet Skin for the generation of the neighbor lists", &
1269 usage="VERLET_SKIN {real}", default_r_val=cp_unit_to_cp2k(value=1.0_dp, &
1270 unit_str="angstrom"), &
1271 unit_str="angstrom")
1272 CALL section_add_keyword(section, keyword)
1273 CALL keyword_release(keyword)
1274
1275 CALL keyword_create(keyword, __location__, name="neighbor_lists_from_scratch", &
1276 description="This keyword enables the building of the neighbouring list from scratch.", &
1277 usage="neighbor_lists_from_scratch logical", &
1278 default_l_val=.false., lone_keyword_l_val=.true.)
1279 CALL section_add_keyword(section, keyword)
1280 CALL keyword_release(keyword)
1281
1282 CALL keyword_create(keyword, __location__, name="GEO_CHECK", &
1283 description="This keyword enables the check that two atoms are never below the minimum"// &
1284 " value used to construct the splines during the construction of the neighbouring list."// &
1285 " Disabling this keyword avoids CP2K to abort in case two atoms are below the minimum"// &
1286 " value of the radius used to generate the splines.", &
1287 usage="GEO_CHECK", &
1288 default_l_val=.true., lone_keyword_l_val=.true.)
1289 CALL section_add_keyword(section, keyword)
1290 CALL keyword_release(keyword)
1291
1292 END SUBROUTINE create_neighbor_lists_section
1293
1294! **************************************************************************************************
1295!> \brief This section specifies the input parameters for a generic potential form
1296!> \param section the section to create
1297!> \author teo
1298! **************************************************************************************************
1299 SUBROUTINE create_genpot_section(section)
1300 TYPE(section_type), POINTER :: section
1301
1302 TYPE(keyword_type), POINTER :: keyword
1303
1304 cpassert(.NOT. ASSOCIATED(section))
1305 CALL section_create(section, __location__, name="GENPOT", &
1306 description="This section specifies the input parameters for a generic potential type. "// &
1307 "A functional form is specified. Mathematical Operators recognized are +, -, *, /, ** "// &
1308 "or alternatively ^, whereas symbols for brackets must be (). "// &
1309 "The function parser recognizes the (single argument) Fortran 90 intrinsic functions "// &
1310 "abs, exp, log10, log, sqrt, sinh, cosh, tanh, sin, cos, tan, asin, acos, atan, erf, erfc. "// &
1311 "Parsing for intrinsic functions is not case sensitive.", &
1312 n_keywords=1, n_subsections=0, repeats=.true.)
1313
1314 NULLIFY (keyword)
1315
1316 CALL keyword_create(keyword, __location__, name="ATOMS", &
1317 description="Defines the atomic kind involved in the generic potential", &
1318 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1319 n_var=2)
1320 CALL section_add_keyword(section, keyword)
1321 CALL keyword_release(keyword)
1322
1323 CALL keyword_create(keyword, __location__, name="FUNCTION", &
1324 description="Specifies the functional form in mathematical notation.", &
1325 usage="FUNCTION a*EXP(-b*x^2)/x+D*log10(x)", type_of_var=lchar_t, &
1326 n_var=1)
1327 CALL section_add_keyword(section, keyword)
1328 CALL keyword_release(keyword)
1329
1330 CALL keyword_create(keyword, __location__, name="VARIABLES", &
1331 description="Defines the variable of the functional form.", &
1332 usage="VARIABLES x", type_of_var=char_t, &
1333 n_var=-1)
1334 CALL section_add_keyword(section, keyword)
1335 CALL keyword_release(keyword)
1336
1337 CALL keyword_create(keyword, __location__, name="PARAMETERS", &
1338 description="Defines the parameters of the functional form", &
1339 usage="PARAMETERS a b D", type_of_var=char_t, &
1340 n_var=-1, repeats=.true.)
1341 CALL section_add_keyword(section, keyword)
1342 CALL keyword_release(keyword)
1343
1344 CALL keyword_create(keyword, __location__, name="VALUES", &
1345 description="Defines the values of parameter of the functional form", &
1346 usage="VALUES ", type_of_var=real_t, &
1347 n_var=-1, repeats=.true., unit_str="internal_cp2k")
1348 CALL section_add_keyword(section, keyword)
1349 CALL keyword_release(keyword)
1350
1351 CALL keyword_create(keyword, __location__, name="UNITS", &
1352 description="Optionally, allows to define valid CP2K unit strings for each parameter value. "// &
1353 "It is assumed that the corresponding parameter value is specified in this unit.", &
1354 usage="UNITS angstrom eV*angstrom^-1 angstrom^1 K", type_of_var=char_t, &
1355 n_var=-1, repeats=.true.)
1356 CALL section_add_keyword(section, keyword)
1357 CALL keyword_release(keyword)
1358
1359 CALL keyword_create(keyword, __location__, name="RCUT", &
1360 description="Defines the cutoff parameter of the generic potential", &
1361 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1362 unit_str="angstrom"), &
1363 unit_str="angstrom")
1364 CALL section_add_keyword(section, keyword)
1365 CALL keyword_release(keyword)
1366
1367 CALL keyword_create(keyword, __location__, name="RMIN", &
1368 description="Defines the lower bound of the potential. If not set the range is the"// &
1369 " full range generate by the spline", usage="RMIN {real}", &
1370 type_of_var=real_t, unit_str="angstrom")
1371 CALL section_add_keyword(section, keyword)
1372 CALL keyword_release(keyword)
1373
1374 CALL keyword_create(keyword, __location__, name="RMAX", &
1375 description="Defines the upper bound of the potential. If not set the range is the"// &
1376 " full range generate by the spline", usage="RMAX {real}", &
1377 type_of_var=real_t, unit_str="angstrom")
1378 CALL section_add_keyword(section, keyword)
1379 CALL keyword_release(keyword)
1380
1381 END SUBROUTINE create_genpot_section
1382
1383! **************************************************************************************************
1384!> \brief This section specifies the input parameters for EAM potential type
1385!> \param section the section to create
1386!> \author teo
1387! **************************************************************************************************
1388 SUBROUTINE create_eam_section(section)
1389 TYPE(section_type), POINTER :: section
1390
1391 TYPE(keyword_type), POINTER :: keyword
1392
1393 cpassert(.NOT. ASSOCIATED(section))
1394 CALL section_create(section, __location__, name="EAM", &
1395 description="This section specifies the input parameters for EAM potential type.", &
1396 citations=(/foiles1986/), n_keywords=1, n_subsections=0, repeats=.true.)
1397
1398 NULLIFY (keyword)
1399
1400 CALL keyword_create(keyword, __location__, name="ATOMS", &
1401 description="Defines the atomic kind involved in the nonbond potential", &
1402 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1403 n_var=2)
1404 CALL section_add_keyword(section, keyword)
1405 CALL keyword_release(keyword)
1406
1407 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1408 variants=(/"PARMFILE"/), &
1409 description="Specifies the filename that contains the tabulated EAM potential. "// &
1410 "File structure: the first line of the potential file contains a title. "// &
1411 "The second line contains: atomic number, mass and lattice constant. "// &
1412 "These information are parsed but not used in CP2K. The third line contains: "// &
1413 "dr: increment of r for the tabulated values of density and phi (assuming r starts in 0) [angstrom]; "// &
1414 "drho: increment of density for the tabulated values of the embedding function (assuming rho starts "// &
1415 "in 0) [au_c]; cutoff: cutoff of the EAM potential; npoints: number of points in tabulated. Follow "// &
1416 "in order npoints lines for rho [au_c] and its derivative [au_c*angstrom^-1]; npoints lines for "// &
1417 "PHI [ev] and its derivative [ev*angstrom^-1] and npoint lines for the embedded function [ev] "// &
1418 "and its derivative [ev*au_c^-1].", &
1419 usage="PARM_FILE_NAME {FILENAME}", default_lc_val=" ")
1420 CALL section_add_keyword(section, keyword)
1421 CALL keyword_release(keyword)
1422
1423 END SUBROUTINE create_eam_section
1424
1425! **************************************************************************************************
1426!> \brief This section specifies the input parameters for QUIP potential type
1427!> \param section the section to create
1428!> \author teo
1429! **************************************************************************************************
1430 SUBROUTINE create_quip_section(section)
1431 TYPE(section_type), POINTER :: section
1432
1433 TYPE(keyword_type), POINTER :: keyword
1434
1435 cpassert(.NOT. ASSOCIATED(section))
1436 CALL section_create(section, __location__, name="QUIP", &
1437 description="This section specifies the input parameters for QUIP potential type. "// &
1438 "Mainly intended for things like GAP corrections to DFT "// &
1439 "to achieve correlated-wavefunction-like accuracy. "// &
1440 "Requires linking with quip library from <http://www.libatoms.org>.", &
1441 citations=(/quip_ref/), n_keywords=1, n_subsections=0, repeats=.true., &
1442 deprecation_notice="Support for the QUIP library is slated for removal.")
1443
1444 NULLIFY (keyword)
1445
1446 CALL keyword_create(keyword, __location__, name="ATOMS", &
1447 description="Defines the atomic kinds involved in the QUIP potential. "// &
1448 "For more than 2 elements, &QUIP section must be repeated until each element "// &
1449 "has been mentioned at least once. Set IGNORE_MISSING_CRITICAL_PARAMS to T "// &
1450 "in enclosing &FORCEFIELD section to avoid having to list every pair of elements separately.", &
1451 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1452 n_var=2)
1453 CALL section_add_keyword(section, keyword)
1454 CALL keyword_release(keyword)
1455
1456 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1457 variants=(/"PARMFILE"/), &
1458 description="Specifies the filename that contains the QUIP potential.", &
1459 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="quip_params.xml")
1460 CALL section_add_keyword(section, keyword)
1461 CALL keyword_release(keyword)
1462
1463 CALL keyword_create(keyword, __location__, name="INIT_ARGS", &
1464 description="Specifies the potential initialization arguments for the QUIP potential. "// &
1465 "If blank (default) first potential defined in QUIP parameter file will be used.", &
1466 usage="INIT_ARGS", default_c_vals=(/""/), &
1467 n_var=-1, type_of_var=char_t)
1468 CALL section_add_keyword(section, keyword)
1469 CALL keyword_release(keyword)
1470
1471 CALL keyword_create(keyword, __location__, name="CALC_ARGS", &
1472 description="Specifies the potential calculation arguments for the QUIP potential.", &
1473 usage="CALC_ARGS", default_c_vals=(/""/), &
1474 n_var=-1, type_of_var=char_t)
1475 CALL section_add_keyword(section, keyword)
1476 CALL keyword_release(keyword)
1477
1478 END SUBROUTINE create_quip_section
1479
1480! **************************************************************************************************
1481!> \brief This section specifies the input parameters for NEQUIP potential type
1482!> \param section the section to create
1483!> \author teo
1484! **************************************************************************************************
1485 SUBROUTINE create_nequip_section(section)
1486 TYPE(section_type), POINTER :: section
1487
1488 TYPE(keyword_type), POINTER :: keyword
1489
1490 cpassert(.NOT. ASSOCIATED(section))
1491 CALL section_create(section, __location__, name="NEQUIP", &
1492 description="This section specifies the input parameters for NEQUIP potential type "// &
1493 "based on equivariant neural networks with message passing. Starting from the NequIP 0.6.0, "// &
1494 "one can predict stress if the config.yaml file has the StressForceOutput keyword, "// &
1495 "regardless of whether the model has been trained on the stress. "// &
1496 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1497 citations=(/batzner2022/), n_keywords=1, n_subsections=0, repeats=.false.)
1498
1499 NULLIFY (keyword)
1500
1501 CALL keyword_create(keyword, __location__, name="ATOMS", &
1502 description="Defines the atomic kinds involved in the NEQUIP potential. "// &
1503 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1504 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1505 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1506 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1507 n_var=-1)
1508 CALL section_add_keyword(section, keyword)
1509 CALL keyword_release(keyword)
1510
1511 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1512 variants=(/"PARMFILE"/), &
1513 description="Specifies the filename that contains the NEQUIP model.", &
1514 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="model.pth")
1515 CALL section_add_keyword(section, keyword)
1516 CALL keyword_release(keyword)
1517
1518 CALL keyword_create(keyword, __location__, name="UNIT_COORDS", &
1519 description="Units of coordinates in the NEQUIP model.pth file. "// &
1520 "The units of positions, energies and forces must be self-consistent: "// &
1521 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1522 usage="UNIT_COORDS angstrom", default_c_val="angstrom")
1523 CALL section_add_keyword(section, keyword)
1524 CALL keyword_release(keyword)
1525
1526 CALL keyword_create(keyword, __location__, name="UNIT_ENERGY", &
1527 description="Units of energy in the NEQUIP model.pth file. "// &
1528 "The units of positions, energies and forces must be self-consistent: "// &
1529 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1530 usage="UNIT_ENERGY hartree", default_c_val="eV")
1531 CALL section_add_keyword(section, keyword)
1532 CALL keyword_release(keyword)
1533
1534 CALL keyword_create(keyword, __location__, name="UNIT_FORCES", &
1535 description="Units of the forces in the NEQUIP model.pth file. "// &
1536 "The units of positions, energies and forces must be self-consistent: "// &
1537 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1538 usage="UNIT_FORCES hartree/bohr", default_c_val="eV/Angstrom")
1539 CALL section_add_keyword(section, keyword)
1540 CALL keyword_release(keyword)
1541
1542 CALL keyword_create(keyword, __location__, name="UNIT_CELL", &
1543 description="Units of the cell vectors in the NEQUIP model.pth file. "// &
1544 "The units of positions, energies and forces must be self-consistent: "// &
1545 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1546 usage="UNIT_CELL angstrom", default_c_val="angstrom")
1547 CALL section_add_keyword(section, keyword)
1548 CALL keyword_release(keyword)
1549
1550 END SUBROUTINE create_nequip_section
1551
1552! **************************************************************************************************
1553!> \brief This section specifies the input parameters for ALLEGRO potential type
1554!> \param section the section to create
1555!> \author teo
1556! **************************************************************************************************
1557 SUBROUTINE create_allegro_section(section)
1558 TYPE(section_type), POINTER :: section
1559
1560 TYPE(keyword_type), POINTER :: keyword
1561
1562 cpassert(.NOT. ASSOCIATED(section))
1563 CALL section_create(section, __location__, name="ALLEGRO", &
1564 description="This section specifies the input parameters for ALLEGRO potential type "// &
1565 "based on equivariant neural network potentials. Starting from the NequIP 0.6.0, "// &
1566 "one can predict stress if the config.yaml file has the StressForceOutput keyword, "// &
1567 "regardless of whether the model has been trained on the stress. "// &
1568 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1569 citations=(/musaelian2023/), n_keywords=1, n_subsections=0, repeats=.false.)
1570
1571 NULLIFY (keyword)
1572
1573 CALL keyword_create(keyword, __location__, name="ATOMS", &
1574 description="Defines the atomic kinds involved in the ALLEGRO potential. "// &
1575 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1576 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1577 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1578 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1579 n_var=-1)
1580 CALL section_add_keyword(section, keyword)
1581 CALL keyword_release(keyword)
1582
1583 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1584 variants=(/"PARMFILE"/), &
1585 description="Specifies the filename that contains the ALLEGRO model.", &
1586 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="model.pth")
1587 CALL section_add_keyword(section, keyword)
1588 CALL keyword_release(keyword)
1589
1590 CALL keyword_create(keyword, __location__, name="UNIT_COORDS", &
1591 description="Units of coordinates in the ALLEGRO model.pth file. "// &
1592 "The units of positions, energies and forces must be self-consistent: "// &
1593 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1594 usage="UNIT_COORDS angstrom", default_c_val="angstrom")
1595 CALL section_add_keyword(section, keyword)
1596 CALL keyword_release(keyword)
1597
1598 CALL keyword_create(keyword, __location__, name="UNIT_ENERGY", &
1599 description="Units of energy in the ALLEGRO model.pth file. "// &
1600 "The units of positions, energies and forces must be self-consistent: "// &
1601 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1602 usage="UNIT_ENERGY hartree", default_c_val="eV")
1603 CALL section_add_keyword(section, keyword)
1604 CALL keyword_release(keyword)
1605
1606 CALL keyword_create(keyword, __location__, name="UNIT_FORCES", &
1607 description="Units of the forces in the ALLEGRO model.pth file. "// &
1608 "The units of positions, energies and forces must be self-consistent: "// &
1609 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1610 usage="UNIT_FORCES hartree/bohr", default_c_val="eV/Angstrom")
1611 CALL section_add_keyword(section, keyword)
1612 CALL keyword_release(keyword)
1613
1614 CALL keyword_create(keyword, __location__, name="UNIT_CELL", &
1615 description="Units of the cell vectors in the ALLEGRO model.pth file. "// &
1616 "The units of positions, energies and forces must be self-consistent: "// &
1617 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1618 usage="UNIT_CELL angstrom", default_c_val="angstrom")
1619 CALL section_add_keyword(section, keyword)
1620 CALL keyword_release(keyword)
1621
1622 END SUBROUTINE create_allegro_section
1623
1624! **************************************************************************************************
1625!> \brief This section specifies the input parameters for ACE potential type
1626!> \param section the section to create
1627!> \author
1628! **************************************************************************************************
1629 SUBROUTINE create_ace_section(section)
1630 TYPE(section_type), POINTER :: section
1631
1632 TYPE(keyword_type), POINTER :: keyword
1633
1634 CALL section_create(section, __location__, name="ACE", &
1635 description="This section specifies the input parameters for Atomic Cluster Expansion type. "// &
1636 "Mainly intended for accurate representation of "// &
1637 "potential energy surfaces. "// &
1638 "Requires linking with ACE library from "// &
1639 "<a href=""https://github.com/ICAMS/lammps-user-pace"" "// &
1640 "target=""_blank"">https://github.com/ICAMS/lammps-user-pace</a> .", &
1641 citations=(/drautz2019, lysogorskiy2021, bochkarev2024/), &
1642 n_keywords=1, n_subsections=0, repeats=.false.)
1643 NULLIFY (keyword)
1644
1645 CALL keyword_create(keyword, __location__, name="ATOMS", &
1646 description="Defines the atomic species. "// &
1647 "Provide a list of each element, "// &
1648 "making sure that the mapping from the ATOMS list to ACE atom types is correct.", &
1649 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1650 n_var=-1)
1651 CALL section_add_keyword(section, keyword)
1652 CALL keyword_release(keyword)
1653 CALL keyword_create(keyword, __location__, name="POT_FILE_NAME", &
1654 variants=(/"PARMFILE"/), &
1655 description="Specifies the filename that contains the ACE potential parameters.", &
1656 usage="POT_FILE_NAME {FILENAME}", default_lc_val="test.yaml")
1657 CALL section_add_keyword(section, keyword)
1658 CALL keyword_release(keyword)
1659 END SUBROUTINE create_ace_section
1660
1661! **************************************************************************************************
1662!> \brief This section specifies the input parameters for DEEPMD potential type
1663!> \param section the section to create
1664!> \author ybzhuang
1665! **************************************************************************************************
1666 SUBROUTINE create_deepmd_section(section)
1667 TYPE(section_type), POINTER :: section
1668
1669 TYPE(keyword_type), POINTER :: keyword
1670
1671 CALL section_create(section, __location__, name="DEEPMD", &
1672 description="This section specifies the input parameters for Deep Potential type. "// &
1673 "Mainly intended for things like neural network to DFT "// &
1674 "to achieve correlated-wavefunction-like accuracy. "// &
1675 "Requires linking with DeePMD-kit library from "// &
1676 "<a href=""https://docs.deepmodeling.com/projects/deepmd/en/master"" "// &
1677 "target=""_blank"">https://docs.deepmodeling.com/projects/deepmd/en/master</a> .", &
1678 citations=(/wang2018, zeng2023/), n_keywords=1, n_subsections=0, repeats=.false.)
1679 NULLIFY (keyword)
1680 CALL keyword_create(keyword, __location__, name="ATOMS", &
1681 description="Defines the atomic kinds involved in the Deep Potential. "// &
1682 "Provide a list of each element, "// &
1683 "making sure that the mapping from the ATOMS list to DeePMD atom types is correct.", &
1684 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1685 n_var=-1)
1686 CALL section_add_keyword(section, keyword)
1687 CALL keyword_release(keyword)
1688 CALL keyword_create(keyword, __location__, name="POT_FILE_NAME", &
1689 variants=(/"PARMFILE"/), &
1690 description="Specifies the filename that contains the DeePMD-kit potential.", &
1691 usage="POT_FILE_NAME {FILENAME}", default_lc_val="graph.pb")
1692 CALL section_add_keyword(section, keyword)
1693 CALL keyword_release(keyword)
1694 CALL keyword_create(keyword, __location__, name="ATOMS_DEEPMD_TYPE", &
1695 description="Specifies the atomic TYPE for the DeePMD-kit potential. "// &
1696 "Provide a list of index, making sure that the mapping "// &
1697 "from the ATOMS list to DeePMD atom types is correct. ", &
1698 usage="ATOMS_DEEPMD_TYPE {TYPE INTEGER 1} {TYPE INTEGER 2} .. "// &
1699 "{TYPE INTEGER N}", type_of_var=integer_t, &
1700 n_var=-1)
1701 CALL section_add_keyword(section, keyword)
1702 CALL keyword_release(keyword)
1703 END SUBROUTINE create_deepmd_section
1704
1705! **************************************************************************************************
1706!> \brief This section specifies the input parameters for Lennard-Jones potential type
1707!> \param section the section to create
1708!> \author teo
1709! **************************************************************************************************
1710 SUBROUTINE create_lj_section(section)
1711 TYPE(section_type), POINTER :: section
1712
1713 TYPE(keyword_type), POINTER :: keyword
1714
1715 cpassert(.NOT. ASSOCIATED(section))
1716 CALL section_create(section, __location__, name="lennard-jones", &
1717 description="This section specifies the input parameters for LENNARD-JONES potential type. "// &
1718 "Functional form: V(r) = 4.0 * EPSILON * [(SIGMA/r)^12-(SIGMA/r)^6].", &
1719 n_keywords=1, n_subsections=0, repeats=.true.)
1720
1721 NULLIFY (keyword)
1722
1723 CALL keyword_create(keyword, __location__, name="ATOMS", &
1724 description="Defines the atomic kind involved in the nonbond potential", &
1725 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1726 n_var=2)
1727 CALL section_add_keyword(section, keyword)
1728 CALL keyword_release(keyword)
1729
1730 CALL keyword_create(keyword, __location__, name="EPSILON", &
1731 description="Defines the EPSILON parameter of the LJ potential", &
1732 usage="EPSILON {real}", type_of_var=real_t, &
1733 n_var=1, unit_str="K_e")
1734 CALL section_add_keyword(section, keyword)
1735 CALL keyword_release(keyword)
1736
1737 CALL keyword_create(keyword, __location__, name="SIGMA", &
1738 description="Defines the SIGMA parameter of the LJ potential", &
1739 usage="SIGMA {real}", type_of_var=real_t, &
1740 n_var=1, unit_str="angstrom")
1741 CALL section_add_keyword(section, keyword)
1742 CALL keyword_release(keyword)
1743
1744 CALL keyword_create(keyword, __location__, name="RCUT", &
1745 description="Defines the cutoff parameter of the LJ potential", &
1746 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1747 unit_str="angstrom"), &
1748 unit_str="angstrom")
1749 CALL section_add_keyword(section, keyword)
1750 CALL keyword_release(keyword)
1751
1752 CALL keyword_create(keyword, __location__, name="RMIN", &
1753 description="Defines the lower bound of the potential. If not set the range is the"// &
1754 " full range generate by the spline", usage="RMIN {real}", &
1755 type_of_var=real_t, unit_str="angstrom")
1756 CALL section_add_keyword(section, keyword)
1757 CALL keyword_release(keyword)
1758
1759 CALL keyword_create(keyword, __location__, name="RMAX", &
1760 description="Defines the upper bound of the potential. If not set the range is the"// &
1761 " full range generate by the spline", usage="RMAX {real}", &
1762 type_of_var=real_t, unit_str="angstrom")
1763 CALL section_add_keyword(section, keyword)
1764 CALL keyword_release(keyword)
1765
1766 END SUBROUTINE create_lj_section
1767
1768! **************************************************************************************************
1769!> \brief This section specifies the input parameters for Williams potential type
1770!> \param section the section to create
1771!> \author teo
1772! **************************************************************************************************
1773 SUBROUTINE create_williams_section(section)
1774 TYPE(section_type), POINTER :: section
1775
1776 TYPE(keyword_type), POINTER :: keyword
1777
1778 cpassert(.NOT. ASSOCIATED(section))
1779 CALL section_create(section, __location__, name="williams", &
1780 description="This section specifies the input parameters for WILLIAMS potential type. "// &
1781 "Functional form: V(r) = A*EXP(-B*r) - C / r^6 .", &
1782 n_keywords=1, n_subsections=0, repeats=.true.)
1783
1784 NULLIFY (keyword)
1785
1786 CALL keyword_create(keyword, __location__, name="ATOMS", &
1787 description="Defines the atomic kind involved in the nonbond potential", &
1788 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1789 n_var=2)
1790 CALL section_add_keyword(section, keyword)
1791 CALL keyword_release(keyword)
1792
1793 CALL keyword_create(keyword, __location__, name="A", &
1794 description="Defines the A parameter of the Williams potential", &
1795 usage="A {real}", type_of_var=real_t, &
1796 n_var=1, unit_str="K_e")
1797 CALL section_add_keyword(section, keyword)
1798 CALL keyword_release(keyword)
1799
1800 CALL keyword_create(keyword, __location__, name="B", &
1801 description="Defines the B parameter of the Williams potential", &
1802 usage="B {real}", type_of_var=real_t, &
1803 n_var=1, unit_str="angstrom^-1")
1804 CALL section_add_keyword(section, keyword)
1805 CALL keyword_release(keyword)
1806
1807 CALL keyword_create(keyword, __location__, name="C", &
1808 description="Defines the C parameter of the Williams potential", &
1809 usage="C {real}", type_of_var=real_t, &
1810 n_var=1, unit_str="K_e*angstrom^6")
1811 CALL section_add_keyword(section, keyword)
1812 CALL keyword_release(keyword)
1813
1814 CALL keyword_create(keyword, __location__, name="RCUT", &
1815 description="Defines the cutoff parameter of the Williams potential", &
1816 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1817 unit_str="angstrom"), &
1818 unit_str="angstrom")
1819 CALL section_add_keyword(section, keyword)
1820 CALL keyword_release(keyword)
1821
1822 CALL keyword_create(keyword, __location__, name="RMIN", &
1823 description="Defines the lower bound of the potential. If not set the range is the"// &
1824 " full range generate by the spline", usage="RMIN {real}", &
1825 type_of_var=real_t, unit_str="angstrom")
1826 CALL section_add_keyword(section, keyword)
1827 CALL keyword_release(keyword)
1828
1829 CALL keyword_create(keyword, __location__, name="RMAX", &
1830 description="Defines the upper bound of the potential. If not set the range is the"// &
1831 " full range generate by the spline", usage="RMAX {real}", &
1832 type_of_var=real_t, unit_str="angstrom")
1833 CALL section_add_keyword(section, keyword)
1834 CALL keyword_release(keyword)
1835
1836 END SUBROUTINE create_williams_section
1837
1838! **************************************************************************************************
1839!> \brief This section specifies the input parameters for Goodwin potential type
1840!> \param section the section to create
1841!> \author teo
1842! **************************************************************************************************
1843 SUBROUTINE create_goodwin_section(section)
1844 TYPE(section_type), POINTER :: section
1845
1846 TYPE(keyword_type), POINTER :: keyword
1847
1848 cpassert(.NOT. ASSOCIATED(section))
1849 CALL section_create(section, __location__, name="goodwin", &
1850 description="This section specifies the input parameters for GOODWIN potential type. "// &
1851 "Functional form: V(r) = EXP(M*(-(r/DC)**MC+(D/DC)**MC))*VR0*(D/r)**M.", &
1852 n_keywords=1, n_subsections=0, repeats=.true.)
1853
1854 NULLIFY (keyword)
1855 CALL keyword_create(keyword, __location__, name="ATOMS", &
1856 description="Defines the atomic kind involved in the nonbond potential", &
1857 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1858 n_var=2)
1859 CALL section_add_keyword(section, keyword)
1860 CALL keyword_release(keyword)
1861
1862 CALL keyword_create(keyword, __location__, name="VR0", &
1863 description="Defines the VR0 parameter of the Goodwin potential", &
1864 usage="VR0 {real}", type_of_var=real_t, &
1865 n_var=1, unit_str="K_e")
1866 CALL section_add_keyword(section, keyword)
1867 CALL keyword_release(keyword)
1868
1869 CALL keyword_create(keyword, __location__, name="D", &
1870 description="Defines the D parameter of the Goodwin potential", &
1871 usage="D {real}", type_of_var=real_t, &
1872 n_var=1, unit_str="angstrom")
1873 CALL section_add_keyword(section, keyword)
1874 CALL keyword_release(keyword)
1875
1876 CALL keyword_create(keyword, __location__, name="DC", &
1877 description="Defines the DC parameter of the Goodwin potential", &
1878 usage="DC {real}", type_of_var=real_t, &
1879 n_var=1, unit_str="angstrom")
1880 CALL section_add_keyword(section, keyword)
1881 CALL keyword_release(keyword)
1882
1883 CALL keyword_create(keyword, __location__, name="M", &
1884 description="Defines the M parameter of the Goodwin potential", &
1885 usage="M {real}", type_of_var=integer_t, &
1886 n_var=1)
1887 CALL section_add_keyword(section, keyword)
1888 CALL keyword_release(keyword)
1889
1890 CALL keyword_create(keyword, __location__, name="MC", &
1891 description="Defines the MC parameter of the Goodwin potential", &
1892 usage="MC {real}", type_of_var=integer_t, &
1893 n_var=1)
1894 CALL section_add_keyword(section, keyword)
1895 CALL keyword_release(keyword)
1896
1897 CALL keyword_create(keyword, __location__, name="RCUT", &
1898 description="Defines the cutoff parameter of the Goodwin potential", &
1899 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1900 unit_str="angstrom"), &
1901 unit_str="angstrom")
1902 CALL section_add_keyword(section, keyword)
1903 CALL keyword_release(keyword)
1904
1905 CALL keyword_create(keyword, __location__, name="RMIN", &
1906 description="Defines the lower bound of the potential. If not set the range is the"// &
1907 " full range generate by the spline", usage="RMIN {real}", &
1908 type_of_var=real_t, unit_str="angstrom")
1909 CALL section_add_keyword(section, keyword)
1910 CALL keyword_release(keyword)
1911
1912 CALL keyword_create(keyword, __location__, name="RMAX", &
1913 description="Defines the upper bound of the potential. If not set the range is the"// &
1914 " full range generate by the spline", usage="RMAX {real}", &
1915 type_of_var=real_t, unit_str="angstrom")
1916 CALL section_add_keyword(section, keyword)
1917 CALL keyword_release(keyword)
1918
1919 END SUBROUTINE create_goodwin_section
1920
1921! **************************************************************************************************
1922!> \brief This section specifies the input parameters for IPBV potential type
1923!> \param section the section to create
1924!> \author teo
1925! **************************************************************************************************
1926 SUBROUTINE create_ipbv_section(section)
1927 TYPE(section_type), POINTER :: section
1928
1929 TYPE(keyword_type), POINTER :: keyword
1930
1931 cpassert(.NOT. ASSOCIATED(section))
1932 CALL section_create(section, __location__, name="ipbv", &
1933 description="This section specifies the input parameters for IPBV potential type. "// &
1934 "Functional form: Implicit table function.", &
1935 n_keywords=1, n_subsections=0, repeats=.true.)
1936
1937 NULLIFY (keyword)
1938
1939 CALL keyword_create(keyword, __location__, name="ATOMS", &
1940 description="Defines the atomic kind involved in the IPBV nonbond potential", &
1941 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1942 n_var=2)
1943 CALL section_add_keyword(section, keyword)
1944 CALL keyword_release(keyword)
1945
1946 CALL keyword_create(keyword, __location__, name="RCUT", &
1947 description="Defines the cutoff parameter of the IPBV potential", &
1948 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1949 unit_str="angstrom"), &
1950 unit_str="angstrom")
1951 CALL section_add_keyword(section, keyword)
1952 CALL keyword_release(keyword)
1953
1954 CALL keyword_create(keyword, __location__, name="RMIN", &
1955 description="Defines the lower bound of the potential. If not set the range is the"// &
1956 " full range generate by the spline", usage="RMIN {real}", &
1957 type_of_var=real_t, unit_str="angstrom")
1958 CALL section_add_keyword(section, keyword)
1959 CALL keyword_release(keyword)
1960
1961 CALL keyword_create(keyword, __location__, name="RMAX", &
1962 description="Defines the upper bound of the potential. If not set the range is the"// &
1963 " full range generate by the spline", usage="RMAX {real}", &
1964 type_of_var=real_t, unit_str="angstrom")
1965 CALL section_add_keyword(section, keyword)
1966 CALL keyword_release(keyword)
1967
1968 END SUBROUTINE create_ipbv_section
1969
1970! **************************************************************************************************
1971!> \brief This section specifies the input parameters for BMHFT potential type
1972!> \param section the section to create
1973!> \author teo
1974! **************************************************************************************************
1975 SUBROUTINE create_bmhft_section(section)
1976 TYPE(section_type), POINTER :: section
1977
1978 TYPE(keyword_type), POINTER :: keyword
1979
1980 cpassert(.NOT. ASSOCIATED(section))
1981 CALL section_create(section, __location__, name="BMHFT", &
1982 description="This section specifies the input parameters for BMHFT potential type. "// &
1983 "Functional form: V(r) = A * EXP(-B*r) - C/r^6 - D/r^8. "// &
1984 "Values available inside cp2k only for the Na/Cl pair.", &
1985 citations=(/tosi1964a, tosi1964b/), n_keywords=1, n_subsections=0, repeats=.true.)
1986
1987 NULLIFY (keyword)
1988
1989 CALL keyword_create(keyword, __location__, name="ATOMS", &
1990 description="Defines the atomic kind involved in the BMHFT nonbond potential", &
1991 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1992 n_var=2)
1993 CALL section_add_keyword(section, keyword)
1994 CALL keyword_release(keyword)
1995
1996 CALL keyword_create(keyword, __location__, name="MAP_ATOMS", &
1997 description="Defines the kinds for which internally is defined the BMHFT nonbond potential"// &
1998 " at the moment only Na and Cl.", &
1999 usage="MAP_ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2000 n_var=2)
2001 CALL section_add_keyword(section, keyword)
2002 CALL keyword_release(keyword)
2003
2004 CALL keyword_create(keyword, __location__, name="RCUT", &
2005 description="Defines the cutoff parameter of the BMHFT potential", &
2006 usage="RCUT {real}", default_r_val=7.8_dp, &
2007 unit_str="angstrom")
2008 CALL section_add_keyword(section, keyword)
2009 CALL keyword_release(keyword)
2010
2011 CALL keyword_create(keyword, __location__, name="A", &
2012 description="Defines the A parameter of the Fumi-Tosi Potential", &
2013 usage="A {real}", type_of_var=real_t, &
2014 n_var=1, unit_str="hartree")
2015 CALL section_add_keyword(section, keyword)
2016 CALL keyword_release(keyword)
2017
2018 CALL keyword_create(keyword, __location__, name="B", &
2019 description="Defines the B parameter of the Fumi-Tosi Potential", &
2020 usage="B {real}", type_of_var=real_t, &
2021 n_var=1, unit_str="angstrom^-1")
2022 CALL section_add_keyword(section, keyword)
2023 CALL keyword_release(keyword)
2024
2025 CALL keyword_create(keyword, __location__, name="C", &
2026 description="Defines the C parameter of the Fumi-Tosi Potential", &
2027 usage="C {real}", type_of_var=real_t, &
2028 n_var=1, unit_str="hartree*angstrom^6")
2029 CALL section_add_keyword(section, keyword)
2030 CALL keyword_release(keyword)
2031
2032 CALL keyword_create(keyword, __location__, name="D", &
2033 description="Defines the D parameter of the Fumi-Tosi Potential", &
2034 usage="D {real}", type_of_var=real_t, &
2035 n_var=1, unit_str="hartree*angstrom^8")
2036 CALL section_add_keyword(section, keyword)
2037 CALL keyword_release(keyword)
2038
2039 CALL keyword_create(keyword, __location__, name="RMIN", &
2040 description="Defines the lower bound of the potential. If not set the range is the"// &
2041 " full range generate by the spline", usage="RMIN {real}", &
2042 type_of_var=real_t, unit_str="angstrom")
2043 CALL section_add_keyword(section, keyword)
2044 CALL keyword_release(keyword)
2045
2046 CALL keyword_create(keyword, __location__, name="RMAX", &
2047 description="Defines the upper bound of the potential. If not set the range is the"// &
2048 " full range generate by the spline", usage="RMAX {real}", &
2049 type_of_var=real_t, unit_str="angstrom")
2050 CALL section_add_keyword(section, keyword)
2051 CALL keyword_release(keyword)
2052
2053 END SUBROUTINE create_bmhft_section
2054
2055! **************************************************************************************************
2056!> \brief This section specifies the input parameters for BMHFTD potential type
2057!> \param section the section to create
2058!> \par History
2059!> - Unused input keyword ORDER removed (18.10.2021, MK)
2060!> \author Mathieu Salanne 05.2010
2061! **************************************************************************************************
2062 SUBROUTINE create_bmhftd_section(section)
2063 TYPE(section_type), POINTER :: section
2064
2065 TYPE(keyword_type), POINTER :: keyword
2066
2067 cpassert(.NOT. ASSOCIATED(section))
2068 CALL section_create(section, __location__, name="BMHFTD", &
2069 description="This section specifies the input parameters for the BMHFTD potential type. "// &
2070 "Functional form: V(r) = A*exp(-B*r) - f_6*(r)C/r^6 - f_8(r)*D/r^8 "// &
2071 "where f_order(r) = 1 - exp(-BD*r)*\sum_{k=0}^order (BD*r)^k/k! "// &
2072 "(Tang-Toennies damping function). No pre-defined parameter values are available.", &
2073 citations=(/tosi1964a, tosi1964b/), n_keywords=1, n_subsections=0, repeats=.true.)
2074
2075 NULLIFY (keyword)
2076
2077 CALL keyword_create(keyword, __location__, name="ATOMS", &
2078 description="Defines the atomic kind involved in the BMHFTD nonbond potential", &
2079 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2080 n_var=2)
2081 CALL section_add_keyword(section, keyword)
2082 CALL keyword_release(keyword)
2083
2084 CALL keyword_create(keyword, __location__, name="MAP_ATOMS", &
2085 description="Defines the kinds for which internally is defined the BMHFTD nonbond potential"// &
2086 " at the moment no species included.", &
2087 usage="MAP_ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2088 n_var=2)
2089 CALL section_add_keyword(section, keyword)
2090 CALL keyword_release(keyword)
2091
2092 CALL keyword_create(keyword, __location__, name="RCUT", &
2093 description="Defines the cutoff parameter of the BMHFTD potential", &
2094 usage="RCUT {real}", default_r_val=7.8_dp, &
2095 unit_str="angstrom")
2096 CALL section_add_keyword(section, keyword)
2097 CALL keyword_release(keyword)
2098
2099 CALL keyword_create(keyword, __location__, name="A", &
2100 description="Defines the A parameter of the dispersion-damped Fumi-Tosi potential", &
2101 usage="A {real}", type_of_var=real_t, &
2102 n_var=1, unit_str="hartree")
2103 CALL section_add_keyword(section, keyword)
2104 CALL keyword_release(keyword)
2105
2106 CALL keyword_create(keyword, __location__, name="B", &
2107 description="Defines the B parameter of the dispersion-damped Fumi-Tosi potential", &
2108 usage="B {real}", type_of_var=real_t, &
2109 n_var=1, unit_str="angstrom^-1")
2110 CALL section_add_keyword(section, keyword)
2111 CALL keyword_release(keyword)
2112
2113 CALL keyword_create(keyword, __location__, name="C", &
2114 description="Defines the C parameter of the dispersion-damped Fumi-Tosi potential", &
2115 usage="C {real}", type_of_var=real_t, &
2116 n_var=1, unit_str="hartree*angstrom^6")
2117 CALL section_add_keyword(section, keyword)
2118 CALL keyword_release(keyword)
2119
2120 CALL keyword_create(keyword, __location__, name="D", &
2121 description="Defines the D parameter of the dispersion-damped Fumi-Tosi potential", &
2122 usage="D {real}", type_of_var=real_t, &
2123 n_var=1, unit_str="hartree*angstrom^8")
2124 CALL section_add_keyword(section, keyword)
2125 CALL keyword_release(keyword)
2126
2127 CALL keyword_create(keyword, __location__, name="BD", &
2128 description="Defines the BD parameters of the dispersion-damped Fumi-Tosi potential. "// &
2129 "One or two parameter values are expected. If only one value is provided, then this "// &
2130 "value will be used both for the 6th and the 8th order term.", &
2131 usage="BD {real} {real}", type_of_var=real_t, &
2132 n_var=-1, unit_str="angstrom^-1")
2133 CALL section_add_keyword(section, keyword)
2134 CALL keyword_release(keyword)
2135
2136 CALL keyword_create(keyword, __location__, name="RMIN", &
2137 description="Defines the lower bound of the potential. If not set the range is the"// &
2138 " full range generate by the spline", usage="RMIN {real}", &
2139 type_of_var=real_t, unit_str="angstrom")
2140 CALL section_add_keyword(section, keyword)
2141 CALL keyword_release(keyword)
2142
2143 CALL keyword_create(keyword, __location__, name="RMAX", &
2144 description="Defines the upper bound of the potential. If not set the range is the"// &
2145 " full range generate by the spline", usage="RMAX {real}", &
2146 type_of_var=real_t, unit_str="angstrom")
2147 CALL section_add_keyword(section, keyword)
2148 CALL keyword_release(keyword)
2149
2150 END SUBROUTINE create_bmhftd_section
2151
2152! **************************************************************************************************
2153!> \brief This section specifies the input parameters for Buckingham 4 ranges potential type
2154!> \param section the section to create
2155!> \author MI
2156! **************************************************************************************************
2157 SUBROUTINE create_buck4r_section(section)
2158 TYPE(section_type), POINTER :: section
2159
2160 TYPE(keyword_type), POINTER :: keyword
2161
2162 cpassert(.NOT. ASSOCIATED(section))
2163 CALL section_create(section, __location__, name="BUCK4RANGES", &
2164 description="This section specifies the input parameters for the Buckingham 4-ranges"// &
2165 " potential type."//newline// &
2166 "| Range | Functional Form |"//newline// &
2167 "| ----- | --------------- |"//newline// &
2168 "| $ r < r_1 $ | $ V(r) = A\exp(-Br) $ |"//newline// &
2169 "| $ r_1 \leq r < r_2 $ | $ V(r) = \sum_n \operatorname{POLY1}(n)r_n $ |"//newline// &
2170 "| $ r_2 \leq r < r_3 $ | $ V(r) = \sum_n \operatorname{POLY2}(n)r_n $ |"//newline// &
2171 "| $ r \geq r_3 $ | $ V(r) = -C/r_6 $ |"//newline, &
2172 n_keywords=1, n_subsections=0, repeats=.true.)
2173
2174 NULLIFY (keyword)
2175
2176 CALL keyword_create(keyword, __location__, name="ATOMS", &
2177 description="Defines the atomic kind involved in the nonbond potential", &
2178 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2179 n_var=2)
2180 CALL section_add_keyword(section, keyword)
2181 CALL keyword_release(keyword)
2182
2183 CALL keyword_create(keyword, __location__, name="A", &
2184 description="Defines the A parameter of the Buckingham potential", &
2185 usage="A {real}", type_of_var=real_t, &
2186 n_var=1, unit_str="K_e")
2187 CALL section_add_keyword(section, keyword)
2188 CALL keyword_release(keyword)
2189
2190 CALL keyword_create(keyword, __location__, name="B", &
2191 description="Defines the B parameter of the Buckingham potential", &
2192 usage="B {real}", type_of_var=real_t, &
2193 n_var=1, unit_str="angstrom^-1")
2194 CALL section_add_keyword(section, keyword)
2195 CALL keyword_release(keyword)
2196
2197 CALL keyword_create(keyword, __location__, name="C", &
2198 description="Defines the C parameter of the Buckingham potential", &
2199 usage="C {real}", type_of_var=real_t, &
2200 n_var=1, unit_str="K_e*angstrom^6")
2201 CALL section_add_keyword(section, keyword)
2202 CALL keyword_release(keyword)
2203
2204 CALL keyword_create(keyword, __location__, name="R1", &
2205 description="Defines the upper bound of the first range ", &
2206 usage="R1 {real}", type_of_var=real_t, &
2207 n_var=1, unit_str="angstrom")
2208 CALL section_add_keyword(section, keyword)
2209 CALL keyword_release(keyword)
2210
2211 CALL keyword_create(keyword, __location__, name="R2", &
2212 description="Defines the upper bound of the second range ", &
2213 usage="R2 {real}", type_of_var=real_t, &
2214 n_var=1, unit_str="angstrom")
2215 CALL section_add_keyword(section, keyword)
2216 CALL keyword_release(keyword)
2217
2218 CALL keyword_create(keyword, __location__, name="R3", &
2219 description="Defines the upper bound of the third range ", &
2220 usage="R3 {real}", type_of_var=real_t, &
2221 n_var=1, unit_str="angstrom")
2222 CALL section_add_keyword(section, keyword)
2223 CALL keyword_release(keyword)
2224
2225 CALL keyword_create(keyword, __location__, name="POLY1", &
2226 description="Coefficients of the polynomial used in the second range "// &
2227 "This keyword can be repeated several times.", &
2228 usage="POLY1 C1 C2 C3 ..", &
2229 n_var=-1, unit_str="K_e", type_of_var=real_t, repeats=.true.)
2230 CALL section_add_keyword(section, keyword)
2231 CALL keyword_release(keyword)
2232
2233 CALL keyword_create(keyword, __location__, name="POLY2", &
2234 description="Coefficients of the polynomial used in the third range "// &
2235 "This keyword can be repeated several times.", &
2236 usage="POLY2 C1 C2 C3 ..", &
2237 n_var=-1, unit_str="K_e", type_of_var=real_t, repeats=.true.)
2238 CALL section_add_keyword(section, keyword)
2239 CALL keyword_release(keyword)
2240
2241 CALL keyword_create(keyword, __location__, name="RCUT", &
2242 description="Defines the cutoff parameter of the Buckingham potential", &
2243 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
2244 unit_str="angstrom"), &
2245 unit_str="angstrom")
2246 CALL section_add_keyword(section, keyword)
2247 CALL keyword_release(keyword)
2248
2249 CALL keyword_create(keyword, __location__, name="RMIN", &
2250 description="Defines the lower bound of the potential. If not set the range is the"// &
2251 " full range generate by the spline", usage="RMIN {real}", &
2252 type_of_var=real_t, unit_str="angstrom")
2253 CALL section_add_keyword(section, keyword)
2254 CALL keyword_release(keyword)
2255
2256 CALL keyword_create(keyword, __location__, name="RMAX", &
2257 description="Defines the upper bound of the potential. If not set the range is the"// &
2258 " full range generate by the spline", usage="RMAX {real}", &
2259 type_of_var=real_t, unit_str="angstrom")
2260 CALL section_add_keyword(section, keyword)
2261 CALL keyword_release(keyword)
2262
2263 END SUBROUTINE create_buck4r_section
2264
2265! **************************************************************************************************
2266!> \brief This section specifies the input parameters for Buckingham + Morse potential type
2267!> \param section the section to create
2268!> \author MI
2269! **************************************************************************************************
2270 SUBROUTINE create_buckmorse_section(section)
2271 TYPE(section_type), POINTER :: section
2272
2273 TYPE(keyword_type), POINTER :: keyword
2274
2275 cpassert(.NOT. ASSOCIATED(section))
2276 CALL section_create( &
2277 section, __location__, name="BUCKMORSE", &
2278 description="This section specifies the input parameters for"// &
2279 " Buckingham plus Morse potential type"// &
2280 " Functional Form: V(r) = F0*(B1+B2)*EXP([A1+A2-r]/[B1+B2])-C/r^6+D*{EXP[-2*beta*(r-R0)]-2*EXP[-beta*(r-R0)]}.", &
2281 citations=(/yamada2000/), n_keywords=1, n_subsections=0, repeats=.true.)
2282
2283 NULLIFY (keyword)
2284
2285 CALL keyword_create(keyword, __location__, name="ATOMS", &
2286 description="Defines the atomic kind involved in the nonbond potential", &
2287 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2288 n_var=2)
2289 CALL section_add_keyword(section, keyword)
2290 CALL keyword_release(keyword)
2291
2292 CALL keyword_create(keyword, __location__, name="F0", &
2293 description="Defines the f0 parameter of Buckingham+Morse potential", &
2294 usage="F0 {real}", type_of_var=real_t, &
2295 n_var=1, unit_str="K_e*angstrom^-1")
2296 CALL section_add_keyword(section, keyword)
2297 CALL keyword_release(keyword)
2298
2299 CALL keyword_create(keyword, __location__, name="A1", &
2300 description="Defines the A1 parameter of Buckingham+Morse potential", &
2301 usage="A1 {real}", type_of_var=real_t, &
2302 n_var=1, unit_str="angstrom")
2303 CALL section_add_keyword(section, keyword)
2304 CALL keyword_release(keyword)
2305
2306 CALL keyword_create(keyword, __location__, name="A2", &
2307 description="Defines the A2 parameter of Buckingham+Morse potential", &
2308 usage="A2 {real}", type_of_var=real_t, &
2309 n_var=1, unit_str="angstrom")
2310 CALL section_add_keyword(section, keyword)
2311 CALL keyword_release(keyword)
2312
2313 CALL keyword_create(keyword, __location__, name="B1", &
2314 description="Defines the B1 parameter of Buckingham+Morse potential", &
2315 usage="B1 {real}", type_of_var=real_t, &
2316 n_var=1, unit_str="angstrom")
2317 CALL section_add_keyword(section, keyword)
2318 CALL keyword_release(keyword)
2319
2320 CALL keyword_create(keyword, __location__, name="B2", &
2321 description="Defines the B2 parameter of Buckingham+Morse potential", &
2322 usage="B2 {real}", type_of_var=real_t, &
2323 n_var=1, unit_str="angstrom")
2324 CALL section_add_keyword(section, keyword)
2325 CALL keyword_release(keyword)
2326
2327 CALL keyword_create(keyword, __location__, name="C", &
2328 description="Defines the C parameter of Buckingham+Morse potential", &
2329 usage="C {real}", type_of_var=real_t, &
2330 n_var=1, unit_str="K_e*angstrom^6")
2331 CALL section_add_keyword(section, keyword)
2332 CALL keyword_release(keyword)
2333
2334 CALL keyword_create(keyword, __location__, name="D", &
2335 description="Defines the amplitude for the Morse part ", &
2336 usage="D {real}", type_of_var=real_t, &
2337 n_var=1, unit_str="K_e")
2338 CALL section_add_keyword(section, keyword)
2339 CALL keyword_release(keyword)
2340
2341 CALL keyword_create(keyword, __location__, name="R0", &
2342 description="Defines the equilibrium distance for the Morse part ", &
2343 usage="R0 {real}", type_of_var=real_t, &
2344 n_var=1, unit_str="angstrom")
2345 CALL section_add_keyword(section, keyword)
2346 CALL keyword_release(keyword)
2347
2348 CALL keyword_create(keyword, __location__, name="Beta", &
2349 description="Defines the width for the Morse part ", &
2350 usage="Beta {real}", type_of_var=real_t, &
2351 n_var=1, unit_str="angstrom^-1")
2352 CALL section_add_keyword(section, keyword)
2353 CALL keyword_release(keyword)
2354
2355 CALL keyword_create(keyword, __location__, name="RCUT", &
2356 description="Defines the cutoff parameter of the Buckingham potential", &
2357 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
2358 unit_str="angstrom"), &
2359 unit_str="angstrom")
2360 CALL section_add_keyword(section, keyword)
2361 CALL keyword_release(keyword)
2362
2363 CALL keyword_create(keyword, __location__, name="RMIN", &
2364 description="Defines the lower bound of the potential. If not set the range is the"// &
2365 " full range generate by the spline", usage="RMIN {real}", &
2366 type_of_var=real_t, unit_str="angstrom")
2367 CALL section_add_keyword(section, keyword)
2368 CALL keyword_release(keyword)
2369
2370 CALL keyword_create(keyword, __location__, name="RMAX", &
2371 description="Defines the upper bound of the potential. If not set the range is the"// &
2372 " full range generate by the spline", usage="RMAX {real}", &
2373 type_of_var=real_t, unit_str="angstrom")
2374 CALL section_add_keyword(section, keyword)
2375 CALL keyword_release(keyword)
2376
2377 END SUBROUTINE create_buckmorse_section
2378
2379! **************************************************************************************************
2380!> \brief This section specifies the input parameters for Tersoff potential type
2381!> (Tersoff, J. PRB 39(8), 5566, 1989)
2382!> \param section ...
2383! **************************************************************************************************
2384 SUBROUTINE create_tersoff_section(section)
2385 TYPE(section_type), POINTER :: section
2386
2387 TYPE(keyword_type), POINTER :: keyword
2388
2389 cpassert(.NOT. ASSOCIATED(section))
2390 CALL section_create(section, __location__, name="TERSOFF", &
2391 description="This section specifies the input parameters for Tersoff potential type.", &
2392 citations=(/tersoff1988/), n_keywords=1, n_subsections=0, repeats=.true.)
2393
2394 NULLIFY (keyword)
2395
2396 CALL keyword_create(keyword, __location__, name="ATOMS", &
2397 description="Defines the atomic kind involved in the nonbond potential", &
2398 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2399 n_var=2)
2400 CALL section_add_keyword(section, keyword)
2401 CALL keyword_release(keyword)
2402
2403 CALL keyword_create(keyword, __location__, name="A", &
2404 description="Defines the A parameter of Tersoff potential", &
2405 usage="A {real}", type_of_var=real_t, &
2406 default_r_val=cp_unit_to_cp2k(value=1.8308e3_dp, &
2407 unit_str="eV"), &
2408 n_var=1, unit_str="eV")
2409 CALL section_add_keyword(section, keyword)
2410 CALL keyword_release(keyword)
2411
2412 CALL keyword_create(keyword, __location__, name="B", &
2413 description="Defines the B parameter of Tersoff potential", &
2414 usage="B {real}", type_of_var=real_t, &
2415 default_r_val=cp_unit_to_cp2k(value=4.7118e2_dp, &
2416 unit_str="eV"), &
2417 n_var=1, unit_str="eV")
2418 CALL section_add_keyword(section, keyword)
2419 CALL keyword_release(keyword)
2420
2421 CALL keyword_create(keyword, __location__, name="lambda1", &
2422 description="Defines the lambda1 parameter of Tersoff potential", &
2423 usage="lambda1 {real}", type_of_var=real_t, &
2424 default_r_val=cp_unit_to_cp2k(value=2.4799_dp, &
2425 unit_str="angstrom^-1"), &
2426 n_var=1, unit_str="angstrom^-1")
2427 CALL section_add_keyword(section, keyword)
2428 CALL keyword_release(keyword)
2429
2430 CALL keyword_create(keyword, __location__, name="lambda2", &
2431 description="Defines the lambda2 parameter of Tersoff potential", &
2432 usage="lambda2 {real}", type_of_var=real_t, &
2433 default_r_val=cp_unit_to_cp2k(value=1.7322_dp, &
2434 unit_str="angstrom^-1"), &
2435 n_var=1, unit_str="angstrom^-1")
2436 CALL section_add_keyword(section, keyword)
2437 CALL keyword_release(keyword)
2438
2439 CALL keyword_create(keyword, __location__, name="alpha", &
2440 description="Defines the alpha parameter of Tersoff potential", &
2441 usage="alpha {real}", type_of_var=real_t, &
2442 default_r_val=0.0_dp, &
2443 n_var=1)
2444 CALL section_add_keyword(section, keyword)
2445 CALL keyword_release(keyword)
2446
2447 CALL keyword_create(keyword, __location__, name="beta", &
2448 description="Defines the beta parameter of Tersoff potential", &
2449 usage="beta {real}", type_of_var=real_t, &
2450 default_r_val=1.0999e-6_dp, &
2451 n_var=1, unit_str="")
2452 CALL section_add_keyword(section, keyword)
2453 CALL keyword_release(keyword)
2454
2455 CALL keyword_create(keyword, __location__, name="n", &
2456 description="Defines the n parameter of Tersoff potential", &
2457 usage="n {real}", type_of_var=real_t, &
2458 default_r_val=7.8734e-1_dp, &
2459 n_var=1, unit_str="")
2460 CALL section_add_keyword(section, keyword)
2461 CALL keyword_release(keyword)
2462
2463 CALL keyword_create(keyword, __location__, name="c", &
2464 description="Defines the c parameter of Tersoff potential", &
2465 usage="c {real}", type_of_var=real_t, &
2466 default_r_val=1.0039e5_dp, &
2467 n_var=1, unit_str="")
2468 CALL section_add_keyword(section, keyword)
2469 CALL keyword_release(keyword)
2470
2471 CALL keyword_create(keyword, __location__, name="d", &
2472 description="Defines the d parameter of Tersoff potential", &
2473 usage="d {real}", type_of_var=real_t, &
2474 default_r_val=1.6218e1_dp, &
2475 n_var=1, unit_str="")
2476 CALL section_add_keyword(section, keyword)
2477 CALL keyword_release(keyword)
2478
2479 CALL keyword_create(keyword, __location__, name="h", &
2480 description="Defines the h parameter of Tersoff potential", &
2481 usage="h {real}", type_of_var=real_t, &
2482 default_r_val=-5.9826e-1_dp, &
2483 n_var=1, unit_str="")
2484 CALL section_add_keyword(section, keyword)
2485 CALL keyword_release(keyword)
2486
2487 CALL keyword_create(keyword, __location__, name="lambda3", &
2488 description="Defines the lambda3 parameter of Tersoff potential", &
2489 usage="lambda3 {real}", type_of_var=real_t, &
2490 default_r_val=cp_unit_to_cp2k(value=1.7322_dp, &
2491 unit_str="angstrom^-1"), &
2492 n_var=1, unit_str="angstrom^-1")
2493 CALL section_add_keyword(section, keyword)
2494 CALL keyword_release(keyword)
2495
2496 CALL keyword_create(keyword, __location__, name="bigR", &
2497 description="Defines the bigR parameter of Tersoff potential", &
2498 usage="bigR {real}", type_of_var=real_t, &
2499 default_r_val=cp_unit_to_cp2k(value=2.85_dp, &
2500 unit_str="angstrom"), &
2501 n_var=1, unit_str="angstrom")
2502 CALL section_add_keyword(section, keyword)
2503 CALL keyword_release(keyword)
2504
2505 CALL keyword_create(keyword, __location__, name="bigD", &
2506 description="Defines the D parameter of Tersoff potential", &
2507 usage="bigD {real}", type_of_var=real_t, &
2508 default_r_val=cp_unit_to_cp2k(value=0.15_dp, &
2509 unit_str="angstrom"), &
2510 n_var=1, unit_str="angstrom")
2511 CALL section_add_keyword(section, keyword)
2512 CALL keyword_release(keyword)
2513
2514 CALL keyword_create(keyword, __location__, name="RCUT", &
2515 description="Defines the cutoff parameter of the tersoff potential."// &
2516 " This parameter is in principle already defined by the values of"// &
2517 " bigD and bigR. But it is necessary to define it when using the tersoff"// &
2518 " in conjunction with other potentials (for the same atomic pair) in order to have"// &
2519 " the same consistent definition of RCUT for all potentials.", &
2520 usage="RCUT {real}", type_of_var=real_t, &
2521 n_var=1, unit_str="angstrom")
2522 CALL section_add_keyword(section, keyword)
2523 CALL keyword_release(keyword)
2524
2525 END SUBROUTINE create_tersoff_section
2526
2527! **************************************************************************************************
2528!> \brief This section specifies the input parameters for Siepmann-Sprik
2529!> potential type
2530!> (Siepmann and Sprik, J. Chem. Phys. 102(1) 511, 1995)
2531!> \param section ...
2532! **************************************************************************************************
2533 SUBROUTINE create_siepmann_section(section)
2534 TYPE(section_type), POINTER :: section
2535
2536 TYPE(keyword_type), POINTER :: keyword
2537
2538 cpassert(.NOT. ASSOCIATED(section))
2539 CALL section_create(section, __location__, name="SIEPMANN", &
2540 description="This section specifies the input parameters for the"// &
2541 " Siepmann-Sprik potential type. Consists of 4 terms:"// &
2542 " T1+T2+T3+T4. The terms T1=A/rij^alpha and T2=-C/rij^6"// &
2543 " have to be given via the GENPOT section. The terms T3+T4"// &
2544 " are obtained from the SIEPMANN section. The Siepmann-Sprik"// &
2545 " potential is designed for water-metal chemisorption.", &
2546 citations=(/siepmann1995/), n_keywords=1, n_subsections=0, repeats=.true.)
2547
2548 NULLIFY (keyword)
2549
2550 CALL keyword_create(keyword, __location__, name="ATOMS", &
2551 description="Defines the atomic kind involved in the nonbond potential", &
2552 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2553 n_var=2)
2554 CALL section_add_keyword(section, keyword)
2555 CALL keyword_release(keyword)
2556
2557 CALL keyword_create(keyword, __location__, name="B", &
2558 description="Defines the B parameter of Siepmann potential", &
2559 usage="B {real}", type_of_var=real_t, &
2560 default_r_val=cp_unit_to_cp2k(value=0.6_dp, &
2561 unit_str="angstrom"), &
2562 n_var=1, unit_str="angstrom")
2563 CALL section_add_keyword(section, keyword)
2564 CALL keyword_release(keyword)
2565
2566 CALL keyword_create(keyword, __location__, name="D", &
2567 description="Defines the D parameter of Siepmann potential", &
2568 usage="D {real}", type_of_var=real_t, &
2569 default_r_val=cp_unit_to_cp2k(value=3.688388_dp, &
2570 unit_str="internal_cp2k"), &
2571 n_var=1, unit_str="internal_cp2k")
2572 CALL section_add_keyword(section, keyword)
2573 CALL keyword_release(keyword)
2574
2575 CALL keyword_create(keyword, __location__, name="E", &
2576 description="Defines the E parameter of Siepmann potential", &
2577 usage="E {real}", type_of_var=real_t, &
2578 default_r_val=cp_unit_to_cp2k(value=9.069025_dp, &
2579 unit_str="internal_cp2k"), &
2580 n_var=1, unit_str="internal_cp2k")
2581 CALL section_add_keyword(section, keyword)
2582 CALL keyword_release(keyword)
2583
2584 CALL keyword_create(keyword, __location__, name="F", &
2585 description="Defines the F parameter of Siepmann potential", &
2586 usage="F {real}", type_of_var=real_t, &
2587 default_r_val=13.3_dp, n_var=1)
2588 CALL section_add_keyword(section, keyword)
2589 CALL keyword_release(keyword)
2590!
2591 CALL keyword_create(keyword, __location__, name="beta", &
2592 description="Defines the beta parameter of Siepmann potential", &
2593 usage="beta {real}", type_of_var=real_t, &
2594 default_r_val=10.0_dp, n_var=1)
2595 CALL section_add_keyword(section, keyword)
2596 CALL keyword_release(keyword)
2597!
2598 CALL keyword_create(keyword, __location__, name="RCUT", &
2599 description="Defines the cutoff parameter of Siepmann potential", &
2600 usage="RCUT {real}", type_of_var=real_t, &
2601 default_r_val=cp_unit_to_cp2k(value=3.2_dp, &
2602 unit_str="angstrom"), &
2603 n_var=1, unit_str="angstrom")
2604 CALL section_add_keyword(section, keyword)
2605 CALL keyword_release(keyword)
2606!
2607 CALL keyword_create(keyword, __location__, name="ALLOW_OH_FORMATION", &
2608 description=" The Siepmann-Sprik potential is actually designed for intact"// &
2609 " water molecules only. If water is treated at the QM level,"// &
2610 " water molecules can potentially dissociate, i.e."// &
2611 " some O-H bonds might be stretched leading temporarily"// &
2612 " to the formation of OH- ions. This keyword allows the"// &
2613 " the formation of such ions. The T3 term (dipole term)"// &
2614 " is then switched off for evaluating the interaction"// &
2615 " between the OH- ion and the metal.", &
2616 usage="ALLOW_OH_FORMATION TRUE", &
2617 default_l_val=.false., lone_keyword_l_val=.true.)
2618 CALL section_add_keyword(section, keyword)
2619 CALL keyword_release(keyword)
2620
2621 CALL keyword_create(keyword, __location__, name="ALLOW_H3O_FORMATION", &
2622 description=" The Siepmann-Sprik potential is designed for intact water"// &
2623 " molecules only. If water is treated at the QM level"// &
2624 " and an acid is present, hydronium ions might occur."// &
2625 " This keyword allows the formation of hydronium ions."// &
2626 " The T3 term (dipole term) is switched off for evaluating"// &
2627 " the interaction between hydronium and the metal.", &
2628 usage="ALLOW_H3O_FORMATION TRUE", &
2629 default_l_val=.false., lone_keyword_l_val=.true.)
2630 CALL section_add_keyword(section, keyword)
2631 CALL keyword_release(keyword)
2632
2633 CALL keyword_create(keyword, __location__, name="ALLOW_O_FORMATION", &
2634 description=" The Siepmann-Sprik potential is actually designed for intact"// &
2635 " water molecules only. If water is treated at the QM level,"// &
2636 " water molecules can potentially dissociate, i.e."// &
2637 " some O-H bonds might be stretched leading temporarily"// &
2638 " to the formation of O^2- ions. This keyword allows the"// &
2639 " the formation of such ions. The T3 term (dipole term)"// &
2640 " is then switched off for evaluating the interaction"// &
2641 " between the O^2- ion and the metal.", &
2642 usage="ALLOW_O_FORMATION .TRUE.", &
2643 default_l_val=.false., lone_keyword_l_val=.true.)
2644 CALL section_add_keyword(section, keyword)
2645 CALL keyword_release(keyword)
2646
2647 END SUBROUTINE create_siepmann_section
2648
2649! **************************************************************************************************
2650!> \brief This section specifies the input parameters for GAL19
2651!> potential type
2652!> (??)
2653!> \param section ...
2654! **************************************************************************************************
2655 SUBROUTINE create_gal_section(section)
2656 TYPE(section_type), POINTER :: section
2657
2658 TYPE(keyword_type), POINTER :: keyword
2659 TYPE(section_type), POINTER :: subsection
2660
2661 cpassert(.NOT. ASSOCIATED(section))
2662 CALL section_create(section, __location__, name="GAL19", &
2663 description="Implementation of the GAL19 forcefield, see associated paper", &
2664 citations=(/clabaut2020/), n_keywords=1, n_subsections=1, repeats=.true.)
2665
2666 NULLIFY (keyword, subsection)
2667
2668 CALL keyword_create(keyword, __location__, name="ATOMS", &
2669 description="Defines the atomic kind involved in the nonbond potential", &
2670 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2671 n_var=2)
2672 CALL section_add_keyword(section, keyword)
2673 CALL keyword_release(keyword)
2674
2675 CALL keyword_create(keyword, __location__, name="METALS", &
2676 description="Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2677 usage="METALS {KIND1} {KIND2} ..", type_of_var=char_t, &
2678 n_var=2)
2679 CALL section_add_keyword(section, keyword)
2680 CALL keyword_release(keyword)
2681
2682 CALL keyword_create(keyword, __location__, name="epsilon", &
2683 description="Defines the epsilon_a parameter of GAL19 potential", &
2684 usage="epsilon {real}", type_of_var=real_t, &
2685 default_r_val=cp_unit_to_cp2k(value=0.6_dp, &
2686 unit_str="kcalmol"), &
2687 n_var=1, unit_str="kcalmol")
2688 CALL section_add_keyword(section, keyword)
2689 CALL keyword_release(keyword)
2690
2691 CALL keyword_create(keyword, __location__, name="bxy", &
2692 description="Defines the b perpendicular parameter of GAL19 potential", &
2693 usage="bxy {real}", type_of_var=real_t, &
2694 default_r_val=cp_unit_to_cp2k(value=3.688388_dp, &
2695 unit_str="internal_cp2k"), &
2696 n_var=1, unit_str="angstrom^-2")
2697 CALL section_add_keyword(section, keyword)
2698 CALL keyword_release(keyword)
2699
2700 CALL keyword_create(keyword, __location__, name="bz", &
2701 description="Defines the b parallel parameter of GAL19 potential", &
2702 usage="bz {real}", type_of_var=real_t, &
2703 default_r_val=cp_unit_to_cp2k(value=9.069025_dp, &
2704 unit_str="internal_cp2k"), &
2705 n_var=1, unit_str="angstrom^-2")
2706 CALL section_add_keyword(section, keyword)
2707 CALL keyword_release(keyword)
2708
2709 CALL keyword_create(keyword, __location__, name="r", &
2710 description="Defines the R_0 parameters of GAL19 potential for the two METALS. "// &
2711 "This is the only parameter that is shared between the two section of the "// &
2712 "forcefield in the case of two metals (alloy). "// &
2713 "If one metal only is present, a second number should be given but won't be read", &
2714 usage="r {real} {real}", type_of_var=real_t, n_var=2, unit_str="angstrom")
2715 CALL section_add_keyword(section, keyword)
2716 CALL keyword_release(keyword)
2717
2718 CALL keyword_create(keyword, __location__, name="a1", &
2719 description="Defines the a1 parameter of GAL19 potential", &
2720 usage="a1 {real}", type_of_var=real_t, &
2721 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2722 CALL section_add_keyword(section, keyword)
2723 CALL keyword_release(keyword)
2724
2725 CALL keyword_create(keyword, __location__, name="a2", &
2726 description="Defines the a2 parameter of GAL19 potential", &
2727 usage="a2 {real}", type_of_var=real_t, &
2728 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2729 CALL section_add_keyword(section, keyword)
2730 CALL keyword_release(keyword)
2731
2732 CALL keyword_create(keyword, __location__, name="a3", &
2733 description="Defines the a3 parameter of GAL19 potential", &
2734 usage="a3 {real}", type_of_var=real_t, &
2735 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2736 CALL section_add_keyword(section, keyword)
2737 CALL keyword_release(keyword)
2738
2739 CALL keyword_create(keyword, __location__, name="a4", &
2740 description="Defines the a4 parameter of GAL19 potential", &
2741 usage="a4 {real}", type_of_var=real_t, &
2742 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2743 CALL section_add_keyword(section, keyword)
2744 CALL keyword_release(keyword)
2745
2746 CALL keyword_create(keyword, __location__, name="A", &
2747 description="Defines the A parameter of GAL19 potential", &
2748 usage="A {real}", type_of_var=real_t, &
2749 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2750 CALL section_add_keyword(section, keyword)
2751 CALL keyword_release(keyword)
2752
2753 CALL keyword_create(keyword, __location__, name="B", &
2754 description="Defines the B parameter of GAL19 potential", &
2755 usage="B {real}", type_of_var=real_t, &
2756 default_r_val=10.0_dp, n_var=1, unit_str="angstrom^-1")
2757 CALL section_add_keyword(section, keyword)
2758 CALL keyword_release(keyword)
2759
2760 CALL keyword_create(keyword, __location__, name="C", &
2761 description="Defines the C parameter of GAL19 potential", &
2762 usage="C {real}", type_of_var=real_t, &
2763 default_r_val=10.0_dp, n_var=1, unit_str="angstrom^6*kcalmol")
2764 CALL section_add_keyword(section, keyword)
2765 CALL keyword_release(keyword)
2766
2767 CALL keyword_create(keyword, __location__, name="RCUT", &
2768 description="Defines the cutoff parameter of GAL19 potential", &
2769 usage="RCUT {real}", type_of_var=real_t, &
2770 default_r_val=cp_unit_to_cp2k(value=3.2_dp, &
2771 unit_str="angstrom"), &
2772 n_var=1, unit_str="angstrom")
2773 CALL section_add_keyword(section, keyword)
2774 CALL keyword_release(keyword)
2775 CALL keyword_create(keyword, __location__, name="Fit_express", &
2776 description="Demands the particular output needed to a least square fit", &
2777 usage="Fit_express TRUE", &
2778 default_l_val=.false., lone_keyword_l_val=.true.)
2779 CALL section_add_keyword(section, keyword)
2780 CALL keyword_release(keyword)
2781 CALL create_gcn_section(subsection)
2782 CALL section_add_subsection(section, subsection)
2783 CALL section_release(subsection)
2784
2785 END SUBROUTINE create_gal_section
2786
2787! **************************************************************************************************
2788!> \brief This section specifies the input parameters for GAL21
2789!> potential type
2790!> (??)
2791!> \param section ...
2792! **************************************************************************************************
2793 SUBROUTINE create_gal21_section(section)
2794 TYPE(section_type), POINTER :: section
2795
2796 TYPE(keyword_type), POINTER :: keyword
2797 TYPE(section_type), POINTER :: subsection
2798
2799 cpassert(.NOT. ASSOCIATED(section))
2800 CALL section_create(section, __location__, name="GAL21", &
2801 description="Implementation of the GAL21 forcefield, see associated paper", &
2802 citations=(/clabaut2021/), n_keywords=1, n_subsections=1, repeats=.true.)
2803
2804 NULLIFY (keyword, subsection)
2805
2806 CALL keyword_create(keyword, __location__, name="ATOMS", &
2807 description="Defines the atomic kind involved in the nonbond potential", &
2808 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2809 n_var=2)
2810 CALL section_add_keyword(section, keyword)
2811 CALL keyword_release(keyword)
2812
2813 CALL keyword_create(keyword, __location__, name="METALS", &
2814 description="Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2815 usage="METALS {KIND1} {KIND2} ..", type_of_var=char_t, &
2816 n_var=2)
2817 CALL section_add_keyword(section, keyword)
2818 CALL keyword_release(keyword)
2819
2820 CALL keyword_create(keyword, __location__, name="epsilon", &
2821 description="Defines the epsilon parameter of GAL21 potential", &
2822 usage="epsilon {real} {real} {real}", type_of_var=real_t, &
2823 n_var=3, unit_str="kcalmol")
2824 CALL section_add_keyword(section, keyword)
2825 CALL keyword_release(keyword)
2826
2827 CALL keyword_create(keyword, __location__, name="bxy", &
2828 description="Defines the b perpendicular parameter of GAL21 potential", &
2829 usage="bxy {real} {real}", type_of_var=real_t, &
2830 n_var=2, unit_str="angstrom^-2")
2831 CALL section_add_keyword(section, keyword)
2832 CALL keyword_release(keyword)
2833
2834 CALL keyword_create(keyword, __location__, name="bz", &
2835 description="Defines the b parallel parameter of GAL21 potential", &
2836 usage="bz {real} {real}", type_of_var=real_t, &
2837 n_var=2, unit_str="angstrom^-2")
2838 CALL section_add_keyword(section, keyword)
2839 CALL keyword_release(keyword)
2840
2841 CALL keyword_create(keyword, __location__, name="r", &
2842 description="Defines the R_0 parameters of GAL21 potential for the two METALS. "// &
2843 "This is the only parameter that is shared between the two section of "// &
2844 "the forcefield in the case of two metals (alloy). "// &
2845 "If one metal only is present, a second number should be given but won't be read", &
2846 usage="r {real} {real}", type_of_var=real_t, n_var=2, unit_str="angstrom")
2847 CALL section_add_keyword(section, keyword)
2848 CALL keyword_release(keyword)
2849
2850 CALL keyword_create(keyword, __location__, name="a1", &
2851 description="Defines the a1 parameter of GAL21 potential", &
2852 usage="a1 {real} {real} {real}", type_of_var=real_t, &
2853 n_var=3, unit_str="kcalmol")
2854 CALL section_add_keyword(section, keyword)
2855 CALL keyword_release(keyword)
2856
2857 CALL keyword_create(keyword, __location__, name="a2", &
2858 description="Defines the a2 parameter of GAL21 potential", &
2859 usage="a2 {real} {real} {real}", type_of_var=real_t, &
2860 n_var=3, unit_str="kcalmol")
2861 CALL section_add_keyword(section, keyword)
2862 CALL keyword_release(keyword)
2863
2864 CALL keyword_create(keyword, __location__, name="a3", &
2865 description="Defines the a3 parameter of GAL21 potential", &
2866 usage="a3 {real} {real} {real}", type_of_var=real_t, &
2867 n_var=3, unit_str="kcalmol")
2868 CALL section_add_keyword(section, keyword)
2869 CALL keyword_release(keyword)
2870
2871 CALL keyword_create(keyword, __location__, name="a4", &
2872 description="Defines the a4 parameter of GAL21 potential", &
2873 usage="a4 {real} {real} {real}", type_of_var=real_t, &
2874 n_var=3, unit_str="kcalmol")
2875 CALL section_add_keyword(section, keyword)
2876 CALL keyword_release(keyword)
2877
2878 CALL keyword_create(keyword, __location__, name="A", &
2879 description="Defines the A parameter of GAL21 potential", &
2880 usage="A {real} {real}", type_of_var=real_t, &
2881 n_var=2, unit_str="kcalmol")
2882 CALL section_add_keyword(section, keyword)
2883 CALL keyword_release(keyword)
2884
2885 CALL keyword_create(keyword, __location__, name="B", &
2886 description="Defines the B parameter of GAL21 potential", &
2887 usage="B {real} {real}", type_of_var=real_t, &
2888 n_var=2, unit_str="angstrom^-1")
2889 CALL section_add_keyword(section, keyword)
2890 CALL keyword_release(keyword)
2891
2892 CALL keyword_create(keyword, __location__, name="C", &
2893 description="Defines the C parameter of GAL21 potential", &
2894 usage="C {real}", type_of_var=real_t, &
2895 n_var=1, unit_str="angstrom^6*kcalmol")
2896 CALL section_add_keyword(section, keyword)
2897 CALL keyword_release(keyword)
2898
2899 CALL keyword_create(keyword, __location__, name="AH", &
2900 description="Defines the AH parameter of GAL21 potential", &
2901 usage="AH {real} {real}", type_of_var=real_t, &
2902 n_var=2, unit_str="kcalmol")
2903 CALL section_add_keyword(section, keyword)
2904 CALL keyword_release(keyword)
2905
2906 CALL keyword_create(keyword, __location__, name="BH", &
2907 description="Defines the BH parameter of GAL21 potential", &
2908 usage="BH {real} {real}", type_of_var=real_t, &
2909 n_var=2, unit_str="angstrom^-1")
2910 CALL section_add_keyword(section, keyword)
2911 CALL keyword_release(keyword)
2912
2913 CALL keyword_create(keyword, __location__, name="RCUT", &
2914 description="Defines the cutoff parameter of GAL21 potential", &
2915 usage="RCUT {real}", type_of_var=real_t, &
2916 default_r_val=cp_unit_to_cp2k(value=3.2_dp, &
2917 unit_str="angstrom"), &
2918 n_var=1, unit_str="angstrom")
2919 CALL section_add_keyword(section, keyword)
2920 CALL keyword_release(keyword)
2921
2922 CALL keyword_create(keyword, __location__, name="Fit_express", &
2923 description="Demands the particular output needed to a least square fit", &
2924 usage="Fit_express TRUE", &
2925 default_l_val=.false., lone_keyword_l_val=.true.)
2926 CALL section_add_keyword(section, keyword)
2927 CALL keyword_release(keyword)
2928
2929 CALL create_gcn_section(subsection)
2930 CALL section_add_subsection(section, subsection)
2931 CALL section_release(subsection)
2932
2933 END SUBROUTINE create_gal21_section
2934
2935! **************************************************************************************************
2936!> \brief This section specifies the input parameters for TABPOT potential type
2937!> \param section the section to create
2938!> \author teo, Alex Mironenko, Da Teng
2939! **************************************************************************************************
2940 SUBROUTINE create_tabpot_section(section)
2941
2942 TYPE(section_type), POINTER :: section
2943
2944 TYPE(keyword_type), POINTER :: keyword
2945
2946 cpassert(.NOT. ASSOCIATED(section))
2947
2948 CALL section_create(section, __location__, name="TABPOT", &
2949 description="This section specifies the input parameters for TABPOT potential type.", &
2950 n_keywords=1, n_subsections=0, repeats=.true.)
2951
2952 NULLIFY (keyword)
2953 CALL keyword_create(keyword, __location__, name="ATOMS", &
2954 description="Defines the atomic kind involved", &
2955 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2956 n_var=2)
2957 CALL section_add_keyword(section, keyword)
2958 CALL keyword_release(keyword)
2959
2960 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
2961 variants=(/"PARMFILE"/), &
2962 description="Specifies the filename that contains the tabulated NONBONDED potential. "// &
2963 "File structure: the third line of the potential file contains a title. "// &
2964 "The 4th line contains: 'N', number of data points, 'R', lower bound of distance, distance cutoff. "// &
2965 "Follow "// &
2966 "in order npoints lines for index, distance [A], energy [kcal/mol], and force [kcal/mol/A]", &
2967 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="")
2968 CALL section_add_keyword(section, keyword)
2969 CALL keyword_release(keyword)
2970
2971 END SUBROUTINE create_tabpot_section
2972
2973! **************************************************************************************************
2974!> \brief This section specifies the input parameters for the subsection GCN of GAL19 and GAL21
2975!> potential type
2976!> (??)
2977!> \param section ...
2978! **************************************************************************************************
2979 SUBROUTINE create_gcn_section(section)
2980 TYPE(section_type), POINTER :: section
2981
2982 TYPE(keyword_type), POINTER :: keyword
2983
2984 cpassert(.NOT. ASSOCIATED(section))
2985 CALL section_create(section, __location__, name="GCN", &
2986 description="Allow to specify the generalized coordination number of the atoms. "// &
2987 "Those numbers msust be generated by another program ", &
2988 n_keywords=1, n_subsections=0, repeats=.false.)
2989
2990 NULLIFY (keyword)
2991 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2992 description="Value of the GCN for the individual atom. Order MUST reflect"// &
2993 " the one specified for the geometry.", repeats=.true., usage="{Real}", &
2994 default_r_val=0.0_dp, type_of_var=real_t)
2995 CALL section_add_keyword(section, keyword)
2996 CALL keyword_release(keyword)
2997
2998 END SUBROUTINE create_gcn_section
2999
3000! **************************************************************************************************
3001!> \brief creates the input section for the qs part
3002!> \param print_key ...
3003!> \param label ...
3004!> \param print_level ...
3005!> \author teo
3006! **************************************************************************************************
3007 SUBROUTINE create_dipoles_section(print_key, label, print_level)
3008 TYPE(section_type), POINTER :: print_key
3009 CHARACTER(LEN=*), INTENT(IN) :: label
3010 INTEGER, INTENT(IN) :: print_level
3011
3012 TYPE(keyword_type), POINTER :: keyword
3013
3014 cpassert(.NOT. ASSOCIATED(print_key))
3015 CALL cp_print_key_section_create(print_key, __location__, name=trim(label), &
3016 description="Section controlling the calculation of "//trim(label)//"."// &
3017 " Note that the result in the periodic case might be defined modulo a certain period,"// &
3018 " determined by the lattice vectors. During MD, this can lead to jumps.", &
3019 print_level=print_level, filename="__STD_OUT__")
3020
3021 NULLIFY (keyword)
3022 CALL keyword_create(keyword, __location__, &
3023 name="PERIODIC", &
3024 description="Use Berry phase formula (PERIODIC=T) or simple operator (PERIODIC=F). "// &
3025 "The latter normally requires that the CELL is periodic NONE.", &
3026 usage="PERIODIC {logical}", &
3027 repeats=.false., &
3028 n_var=1, &
3029 default_l_val=.true., lone_keyword_l_val=.true.)
3030 CALL section_add_keyword(print_key, keyword)
3031 CALL keyword_release(keyword)
3032
3033 CALL keyword_create(keyword, __location__, name="REFERENCE", &
3034 variants=s2a("REF"), &
3035 description="Define the reference point for the calculation of the electrostatic moment.", &
3036 usage="REFERENCE COM", &
3037 enum_c_vals=s2a("COM", "COAC", "USER_DEFINED", "ZERO"), &
3038 enum_desc=s2a("Use Center of Mass", &
3039 "Use Center of Atomic Charges", &
3040 "Use User Defined Point (Keyword:REF_POINT)", &
3041 "Use Origin of Coordinate System"), &
3042 enum_i_vals=(/use_mom_ref_com, &
3045 use_mom_ref_zero/), &
3046 default_i_val=use_mom_ref_zero)
3047 CALL section_add_keyword(print_key, keyword)
3048 CALL keyword_release(keyword)
3049
3050 CALL keyword_create(keyword, __location__, name="REFERENCE_POINT", &
3051 variants=s2a("REF_POINT"), &
3052 description="Fixed reference point for the calculations of the electrostatic moment.", &
3053 usage="REFERENCE_POINT x y z", &
3054 repeats=.false., &
3055 n_var=3, default_r_vals=(/0._dp, 0._dp, 0._dp/), &
3056 type_of_var=real_t, &
3057 unit_str='bohr')
3058 CALL section_add_keyword(print_key, keyword)
3059 CALL keyword_release(keyword)
3060 END SUBROUTINE create_dipoles_section
3061
3062END MODULE input_cp2k_mm
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public tosi1964b
integer, save, public drautz2019
integer, save, public lysogorskiy2021
integer, save, public tersoff1988
integer, save, public quip_ref
integer, save, public dick1958
integer, save, public foiles1986
integer, save, public devynck2012
integer, save, public tosi1964a
integer, save, public bochkarev2024
integer, save, public siepmann1995
integer, save, public zeng2023
integer, save, public yamada2000
integer, save, public batzner2022
integer, save, public mitchell1993
integer, save, public musaelian2023
integer, save, public clabaut2021
integer, save, public wang2018
integer, save, public clabaut2020
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public silent_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition cp_units.F:1150
Define all structure types related to force field kinds.
integer, parameter, public do_ff_legendre
integer, parameter, public do_ff_undef
integer, parameter, public do_ff_mm4
integer, parameter, public do_ff_charmm
integer, parameter, public do_ff_mm3
integer, parameter, public do_ff_g87
integer, parameter, public do_ff_g96
integer, parameter, public do_ff_morse
integer, parameter, public do_ff_mm2
integer, parameter, public do_ff_harmonic
integer, parameter, public do_ff_amber
integer, parameter, public do_ff_mixed_bend_stretch
integer, parameter, public do_ff_cubic
integer, parameter, public do_ff_quartic
integer, parameter, public do_ff_fues
integer, parameter, public do_ff_opls
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public use_mom_ref_coac
integer, parameter, public use_mom_ref_user
integer, parameter, public use_mom_ref_com
integer, parameter, public use_mom_ref_zero
function that build the field section of the input
subroutine, public create_per_efield_section(section)
creates the section for static periodic fields
creates the mm section of the input
subroutine, public create_genpot_section(section)
This section specifies the input parameters for a generic potential form.
subroutine, public create_williams_section(section)
This section specifies the input parameters for Williams potential type.
subroutine, public create_goodwin_section(section)
This section specifies the input parameters for Goodwin potential type.
subroutine, public create_dipoles_section(print_key, label, print_level)
creates the input section for the qs part
subroutine, public create_charge_section(section)
This section specifies the charge of the MM atoms.
subroutine, public create_nonbonded14_section(section)
This section specifies the input parameters for 1-4 NON-BONDED Interactions.
subroutine, public create_mm_section(section)
Create the input section for FIST.. Come on.. Let's get woohooo.
subroutine, public create_lj_section(section)
This section specifies the input parameters for Lennard-Jones potential type.
subroutine, public create_neighbor_lists_section(section)
This section specifies the input parameters for generation of neighbor lists.
subroutine, public create_tabpot_section(section)
This section specifies the input parameters for TABPOT potential type.
function that build the poisson section of the input
subroutine, public create_poisson_section(section)
Creates the Poisson 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 real_t
integer, parameter, public lchar_t
integer, parameter, public char_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
Utilities for string manipulations.
character(len=1), parameter, public newline
represent a keyword in the input
represent a section of the input file