(git:374b731)
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-2024 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_BOND_PARAMS T", 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_deepmd_section(subsection)
1192 CALL section_add_subsection(section, subsection)
1193 CALL section_release(subsection)
1194
1195 CALL create_goodwin_section(subsection)
1196 CALL section_add_subsection(section, subsection)
1197 CALL section_release(subsection)
1198
1199 CALL create_ipbv_section(subsection)
1200 CALL section_add_subsection(section, subsection)
1201 CALL section_release(subsection)
1202
1203 CALL create_bmhft_section(subsection)
1204 CALL section_add_subsection(section, subsection)
1205 CALL section_release(subsection)
1206
1207 CALL create_bmhftd_section(subsection)
1208 CALL section_add_subsection(section, subsection)
1209 CALL section_release(subsection)
1210
1211 CALL create_buck4r_section(subsection)
1212 CALL section_add_subsection(section, subsection)
1213 CALL section_release(subsection)
1214
1215 CALL create_buckmorse_section(subsection)
1216 CALL section_add_subsection(section, subsection)
1217 CALL section_release(subsection)
1218
1219 CALL create_genpot_section(subsection)
1220 CALL section_add_subsection(section, subsection)
1221 CALL section_release(subsection)
1222
1223 CALL create_tersoff_section(subsection)
1224 CALL section_add_subsection(section, subsection)
1225 CALL section_release(subsection)
1226
1227 CALL create_siepmann_section(subsection)
1228 CALL section_add_subsection(section, subsection)
1229 CALL section_release(subsection)
1230
1231 CALL create_gal_section(subsection)
1232 CALL section_add_subsection(section, subsection)
1233 CALL section_release(subsection)
1234
1235 CALL create_gal21_section(subsection)
1236 CALL section_add_subsection(section, subsection)
1237 CALL section_release(subsection)
1238
1239 CALL create_tabpot_section(subsection)
1240 CALL section_add_subsection(section, subsection)
1241 CALL section_release(subsection)
1242
1243 END SUBROUTINE create_nonbonded_section
1244
1245! **************************************************************************************************
1246!> \brief This section specifies the input parameters for generation of
1247!> neighbor lists
1248!> \param section the section to create
1249!> \author teo [07.2007] - Zurich University
1250! **************************************************************************************************
1252 TYPE(section_type), POINTER :: section
1253
1254 TYPE(keyword_type), POINTER :: keyword
1255
1256 NULLIFY (keyword)
1257 cpassert(.NOT. ASSOCIATED(section))
1258 CALL section_create(section, __location__, name="neighbor_lists", &
1259 description="This section specifies the input parameters for the construction of"// &
1260 " neighbor lists.", &
1261 n_keywords=1, n_subsections=0, repeats=.false.)
1262
1263 CALL keyword_create(keyword, __location__, name="VERLET_SKIN", &
1264 description="Defines the Verlet Skin for the generation of the neighbor lists", &
1265 usage="VERLET_SKIN {real}", default_r_val=cp_unit_to_cp2k(value=1.0_dp, &
1266 unit_str="angstrom"), &
1267 unit_str="angstrom")
1268 CALL section_add_keyword(section, keyword)
1269 CALL keyword_release(keyword)
1270
1271 CALL keyword_create(keyword, __location__, name="neighbor_lists_from_scratch", &
1272 description="This keyword enables the building of the neighbouring list from scratch.", &
1273 usage="neighbor_lists_from_scratch logical", &
1274 default_l_val=.false., lone_keyword_l_val=.true.)
1275 CALL section_add_keyword(section, keyword)
1276 CALL keyword_release(keyword)
1277
1278 CALL keyword_create(keyword, __location__, name="GEO_CHECK", &
1279 description="This keyword enables the check that two atoms are never below the minimum"// &
1280 " value used to construct the splines during the construction of the neighbouring list."// &
1281 " Disabling this keyword avoids CP2K to abort in case two atoms are below the minimum"// &
1282 " value of the radius used to generate the splines.", &
1283 usage="GEO_CHECK", &
1284 default_l_val=.true., lone_keyword_l_val=.true.)
1285 CALL section_add_keyword(section, keyword)
1286 CALL keyword_release(keyword)
1287
1288 END SUBROUTINE create_neighbor_lists_section
1289
1290! **************************************************************************************************
1291!> \brief This section specifies the input parameters for a generic potential form
1292!> \param section the section to create
1293!> \author teo
1294! **************************************************************************************************
1295 SUBROUTINE create_genpot_section(section)
1296 TYPE(section_type), POINTER :: section
1297
1298 TYPE(keyword_type), POINTER :: keyword
1299
1300 cpassert(.NOT. ASSOCIATED(section))
1301 CALL section_create(section, __location__, name="GENPOT", &
1302 description="This section specifies the input parameters for a generic potential type. "// &
1303 "A functional form is specified. Mathematical Operators recognized are +, -, *, /, ** "// &
1304 "or alternatively ^, whereas symbols for brackets must be (). "// &
1305 "The function parser recognizes the (single argument) Fortran 90 intrinsic functions "// &
1306 "abs, exp, log10, log, sqrt, sinh, cosh, tanh, sin, cos, tan, asin, acos, atan, erf, erfc. "// &
1307 "Parsing for intrinsic functions is not case sensitive.", &
1308 n_keywords=1, n_subsections=0, repeats=.true.)
1309
1310 NULLIFY (keyword)
1311
1312 CALL keyword_create(keyword, __location__, name="ATOMS", &
1313 description="Defines the atomic kind involved in the generic potential", &
1314 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1315 n_var=2)
1316 CALL section_add_keyword(section, keyword)
1317 CALL keyword_release(keyword)
1318
1319 CALL keyword_create(keyword, __location__, name="FUNCTION", &
1320 description="Specifies the functional form in mathematical notation.", &
1321 usage="FUNCTION a*EXP(-b*x^2)/x+D*log10(x)", type_of_var=lchar_t, &
1322 n_var=1)
1323 CALL section_add_keyword(section, keyword)
1324 CALL keyword_release(keyword)
1325
1326 CALL keyword_create(keyword, __location__, name="VARIABLES", &
1327 description="Defines the variable of the functional form.", &
1328 usage="VARIABLES x", type_of_var=char_t, &
1329 n_var=-1)
1330 CALL section_add_keyword(section, keyword)
1331 CALL keyword_release(keyword)
1332
1333 CALL keyword_create(keyword, __location__, name="PARAMETERS", &
1334 description="Defines the parameters of the functional form", &
1335 usage="PARAMETERS a b D", type_of_var=char_t, &
1336 n_var=-1, repeats=.true.)
1337 CALL section_add_keyword(section, keyword)
1338 CALL keyword_release(keyword)
1339
1340 CALL keyword_create(keyword, __location__, name="VALUES", &
1341 description="Defines the values of parameter of the functional form", &
1342 usage="VALUES ", type_of_var=real_t, &
1343 n_var=-1, repeats=.true., unit_str="internal_cp2k")
1344 CALL section_add_keyword(section, keyword)
1345 CALL keyword_release(keyword)
1346
1347 CALL keyword_create(keyword, __location__, name="UNITS", &
1348 description="Optionally, allows to define valid CP2K unit strings for each parameter value. "// &
1349 "It is assumed that the corresponding parameter value is specified in this unit.", &
1350 usage="UNITS angstrom eV*angstrom^-1 angstrom^1 K", type_of_var=char_t, &
1351 n_var=-1, repeats=.true.)
1352 CALL section_add_keyword(section, keyword)
1353 CALL keyword_release(keyword)
1354
1355 CALL keyword_create(keyword, __location__, name="RCUT", &
1356 description="Defines the cutoff parameter of the generic potential", &
1357 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1358 unit_str="angstrom"), &
1359 unit_str="angstrom")
1360 CALL section_add_keyword(section, keyword)
1361 CALL keyword_release(keyword)
1362
1363 CALL keyword_create(keyword, __location__, name="RMIN", &
1364 description="Defines the lower bound of the potential. If not set the range is the"// &
1365 " full range generate by the spline", usage="RMIN {real}", &
1366 type_of_var=real_t, unit_str="angstrom")
1367 CALL section_add_keyword(section, keyword)
1368 CALL keyword_release(keyword)
1369
1370 CALL keyword_create(keyword, __location__, name="RMAX", &
1371 description="Defines the upper bound of the potential. If not set the range is the"// &
1372 " full range generate by the spline", usage="RMAX {real}", &
1373 type_of_var=real_t, unit_str="angstrom")
1374 CALL section_add_keyword(section, keyword)
1375 CALL keyword_release(keyword)
1376
1377 END SUBROUTINE create_genpot_section
1378
1379! **************************************************************************************************
1380!> \brief This section specifies the input parameters for EAM potential type
1381!> \param section the section to create
1382!> \author teo
1383! **************************************************************************************************
1384 SUBROUTINE create_eam_section(section)
1385 TYPE(section_type), POINTER :: section
1386
1387 TYPE(keyword_type), POINTER :: keyword
1388
1389 cpassert(.NOT. ASSOCIATED(section))
1390 CALL section_create(section, __location__, name="EAM", &
1391 description="This section specifies the input parameters for EAM potential type.", &
1392 citations=(/foiles1986/), n_keywords=1, n_subsections=0, repeats=.true.)
1393
1394 NULLIFY (keyword)
1395
1396 CALL keyword_create(keyword, __location__, name="ATOMS", &
1397 description="Defines the atomic kind involved in the nonbond potential", &
1398 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1399 n_var=2)
1400 CALL section_add_keyword(section, keyword)
1401 CALL keyword_release(keyword)
1402
1403 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1404 variants=(/"PARMFILE"/), &
1405 description="Specifies the filename that contains the tabulated EAM potential. "// &
1406 "File structure: the first line of the potential file contains a title. "// &
1407 "The second line contains: atomic number, mass and lattice constant. "// &
1408 "These information are parsed but not used in CP2K. The third line contains: "// &
1409 "dr: increment of r for the tabulated values of density and phi (assuming r starts in 0) [angstrom]; "// &
1410 "drho: increment of density for the tabulated values of the embedding function (assuming rho starts "// &
1411 "in 0) [au_c]; cutoff: cutoff of the EAM potential; npoints: number of points in tabulated. Follow "// &
1412 "in order npoints lines for rho [au_c] and its derivative [au_c*angstrom^-1]; npoints lines for "// &
1413 "PHI [ev] and its derivative [ev*angstrom^-1] and npoint lines for the embedded function [ev] "// &
1414 "and its derivative [ev*au_c^-1].", &
1415 usage="PARM_FILE_NAME {FILENAME}", default_lc_val=" ")
1416 CALL section_add_keyword(section, keyword)
1417 CALL keyword_release(keyword)
1418
1419 END SUBROUTINE create_eam_section
1420
1421! **************************************************************************************************
1422!> \brief This section specifies the input parameters for QUIP potential type
1423!> \param section the section to create
1424!> \author teo
1425! **************************************************************************************************
1426 SUBROUTINE create_quip_section(section)
1427 TYPE(section_type), POINTER :: section
1428
1429 TYPE(keyword_type), POINTER :: keyword
1430
1431 cpassert(.NOT. ASSOCIATED(section))
1432 CALL section_create(section, __location__, name="QUIP", &
1433 description="This section specifies the input parameters for QUIP potential type. "// &
1434 "Mainly intended for things like GAP corrections to DFT "// &
1435 "to achieve correlated-wavefunction-like accuracy. "// &
1436 "Requires linking with quip library from <http://www.libatoms.org>.", &
1437 citations=(/quip_ref/), n_keywords=1, n_subsections=0, repeats=.true.)
1438
1439 NULLIFY (keyword)
1440
1441 CALL keyword_create(keyword, __location__, name="ATOMS", &
1442 description="Defines the atomic kinds involved in the QUIP potential. "// &
1443 "For more than 2 elements, &QUIP section must be repeated until each element "// &
1444 "has been mentioned at least once. Set IGNORE_MISSING_CRITICAL_PARAMS to T "// &
1445 "in enclosing &FORCEFIELD section to avoid having to list every pair of elements separately.", &
1446 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1447 n_var=2)
1448 CALL section_add_keyword(section, keyword)
1449 CALL keyword_release(keyword)
1450
1451 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1452 variants=(/"PARMFILE"/), &
1453 description="Specifies the filename that contains the QUIP potential.", &
1454 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="quip_params.xml")
1455 CALL section_add_keyword(section, keyword)
1456 CALL keyword_release(keyword)
1457
1458 CALL keyword_create(keyword, __location__, name="INIT_ARGS", &
1459 description="Specifies the potential initialization arguments for the QUIP potential. "// &
1460 "If blank (default) first potential defined in QUIP parameter file will be used.", &
1461 usage="INIT_ARGS", default_c_vals=(/""/), &
1462 n_var=-1, type_of_var=char_t)
1463 CALL section_add_keyword(section, keyword)
1464 CALL keyword_release(keyword)
1465
1466 CALL keyword_create(keyword, __location__, name="CALC_ARGS", &
1467 description="Specifies the potential calculation arguments for the QUIP potential.", &
1468 usage="CALC_ARGS", default_c_vals=(/""/), &
1469 n_var=-1, type_of_var=char_t)
1470 CALL section_add_keyword(section, keyword)
1471 CALL keyword_release(keyword)
1472
1473 END SUBROUTINE create_quip_section
1474
1475! **************************************************************************************************
1476!> \brief This section specifies the input parameters for NEQUIP potential type
1477!> \param section the section to create
1478!> \author teo
1479! **************************************************************************************************
1480 SUBROUTINE create_nequip_section(section)
1481 TYPE(section_type), POINTER :: section
1482
1483 TYPE(keyword_type), POINTER :: keyword
1484
1485 cpassert(.NOT. ASSOCIATED(section))
1486 CALL section_create(section, __location__, name="NEQUIP", &
1487 description="This section specifies the input parameters for NEQUIP potential type "// &
1488 "based on equivariant neural networks with message passing. "// &
1489 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1490 citations=(/batzner2022/), n_keywords=1, n_subsections=0, repeats=.false.)
1491
1492 NULLIFY (keyword)
1493
1494 CALL keyword_create(keyword, __location__, name="ATOMS", &
1495 description="Defines the atomic kinds involved in the NEQUIP potential. "// &
1496 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1497 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1498 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1499 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1500 n_var=-1)
1501 CALL section_add_keyword(section, keyword)
1502 CALL keyword_release(keyword)
1503
1504 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1505 variants=(/"PARMFILE"/), &
1506 description="Specifies the filename that contains the NEQUIP model.", &
1507 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="model.pth")
1508 CALL section_add_keyword(section, keyword)
1509 CALL keyword_release(keyword)
1510
1511 CALL keyword_create(keyword, __location__, name="UNIT_COORDS", &
1512 description="Units of coordinates in the NEQUIP model.pth file.", &
1513 usage="UNIT angstrom", default_c_val="angstrom")
1514 CALL section_add_keyword(section, keyword)
1515 CALL keyword_release(keyword)
1516
1517 CALL keyword_create(keyword, __location__, name="UNIT_ENERGY", &
1518 description="Units of energy in the NEQUIP model.pth file.", &
1519 usage="UNIT hartree", default_c_val="hartree")
1520 CALL section_add_keyword(section, keyword)
1521 CALL keyword_release(keyword)
1522
1523 CALL keyword_create(keyword, __location__, name="UNIT_FORCES", &
1524 description="Units of the forces in the NEQUIP model.pth file.", &
1525 usage="UNIT hartree/bohr", default_c_val="hartree/bohr")
1526 CALL section_add_keyword(section, keyword)
1527 CALL keyword_release(keyword)
1528
1529 CALL keyword_create(keyword, __location__, name="UNIT_CELL", &
1530 description="Units of the cell vectors in the NEQUIP model.pth file.", &
1531 usage="UNIT angstrom", default_c_val="angstrom")
1532 CALL section_add_keyword(section, keyword)
1533 CALL keyword_release(keyword)
1534
1535 END SUBROUTINE create_nequip_section
1536
1537! **************************************************************************************************
1538!> \brief This section specifies the input parameters for ALLEGRO potential type
1539!> \param section the section to create
1540!> \author teo
1541! **************************************************************************************************
1542 SUBROUTINE create_allegro_section(section)
1543 TYPE(section_type), POINTER :: section
1544
1545 TYPE(keyword_type), POINTER :: keyword
1546
1547 cpassert(.NOT. ASSOCIATED(section))
1548 CALL section_create(section, __location__, name="ALLEGRO", &
1549 description="This section specifies the input parameters for ALLEGRO potential type "// &
1550 "based on equivariant neural network potentials. "// &
1551 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1552 citations=(/musaelian2023/), n_keywords=1, n_subsections=0, repeats=.false.)
1553
1554 NULLIFY (keyword)
1555
1556 CALL keyword_create(keyword, __location__, name="ATOMS", &
1557 description="Defines the atomic kinds involved in the ALLEGRO potential. "// &
1558 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1559 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1560 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1561 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1562 n_var=-1)
1563 CALL section_add_keyword(section, keyword)
1564 CALL keyword_release(keyword)
1565
1566 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
1567 variants=(/"PARMFILE"/), &
1568 description="Specifies the filename that contains the ALLEGRO model.", &
1569 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="model.pth")
1570 CALL section_add_keyword(section, keyword)
1571 CALL keyword_release(keyword)
1572
1573 CALL keyword_create(keyword, __location__, name="UNIT_COORDS", &
1574 description="Units of coordinates in the ALLEGRO model.pth file.", &
1575 usage="UNIT angstrom", default_c_val="angstrom")
1576 CALL section_add_keyword(section, keyword)
1577 CALL keyword_release(keyword)
1578
1579 CALL keyword_create(keyword, __location__, name="UNIT_ENERGY", &
1580 description="Units of energy in the ALLEGRO model.pth file.", &
1581 usage="UNIT hartree", default_c_val="hartree")
1582 CALL section_add_keyword(section, keyword)
1583 CALL keyword_release(keyword)
1584
1585 CALL keyword_create(keyword, __location__, name="UNIT_FORCES", &
1586 description="Units of the forces in the ALLEGRO model.pth file.", &
1587 usage="UNIT hartree/bohr", default_c_val="hartree/bohr")
1588 CALL section_add_keyword(section, keyword)
1589 CALL keyword_release(keyword)
1590
1591 CALL keyword_create(keyword, __location__, name="UNIT_CELL", &
1592 description="Units of the cell vectors in the ALLEGRO model.pth file.", &
1593 usage="UNIT angstrom", default_c_val="angstrom")
1594 CALL section_add_keyword(section, keyword)
1595 CALL keyword_release(keyword)
1596
1597 END SUBROUTINE create_allegro_section
1598
1599! **************************************************************************************************
1600!> \brief This section specifies the input parameters for DEEPMD potential type
1601!> \param section the section to create
1602!> \author ybzhuang
1603! **************************************************************************************************
1604 SUBROUTINE create_deepmd_section(section)
1605 TYPE(section_type), POINTER :: section
1606
1607 TYPE(keyword_type), POINTER :: keyword
1608
1609 CALL section_create(section, __location__, name="DEEPMD", &
1610 description="This section specifies the input parameters for Deep Potential type. "// &
1611 "Mainly intended for things like neural network to DFT "// &
1612 "to achieve correlated-wavefunction-like accuracy. "// &
1613 "Requires linking with DeePMD-kit library from "// &
1614 "<a href=""https://docs.deepmodeling.com/projects/deepmd/en/master"" "// &
1615 "target=""_blank"">https://docs.deepmodeling.com/projects/deepmd/en/master</a> .", &
1616 citations=(/wang2018, zeng2023/), n_keywords=1, n_subsections=0, repeats=.false.)
1617 NULLIFY (keyword)
1618 CALL keyword_create(keyword, __location__, name="ATOMS", &
1619 description="Defines the atomic kinds involved in the Deep Potential. "// &
1620 "Provide a list of each element, "// &
1621 "making sure that the mapping from the ATOMS list to DeePMD atom types is correct.", &
1622 usage="ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=char_t, &
1623 n_var=-1)
1624 CALL section_add_keyword(section, keyword)
1625 CALL keyword_release(keyword)
1626 CALL keyword_create(keyword, __location__, name="POT_FILE_NAME", &
1627 variants=(/"PARMFILE"/), &
1628 description="Specifies the filename that contains the DeePMD-kit potential.", &
1629 usage="POT_FILE_NAME {FILENAME}", default_lc_val="graph.pb")
1630 CALL section_add_keyword(section, keyword)
1631 CALL keyword_release(keyword)
1632 CALL keyword_create(keyword, __location__, name="ATOMS_DEEPMD_TYPE", &
1633 description="Specifies the atomic TYPE for the DeePMD-kit potential. "// &
1634 "Provide a list of index, making sure that the mapping "// &
1635 "from the ATOMS list to DeePMD atom types is correct. ", &
1636 usage="ATOMS_DEEPMD_TYPE {TYPE INTEGER 1} {TYPE INTEGER 2} .. "// &
1637 "{TYPE INTEGER N}", type_of_var=integer_t, &
1638 n_var=-1)
1639 CALL section_add_keyword(section, keyword)
1640 CALL keyword_release(keyword)
1641 END SUBROUTINE create_deepmd_section
1642
1643! **************************************************************************************************
1644!> \brief This section specifies the input parameters for Lennard-Jones potential type
1645!> \param section the section to create
1646!> \author teo
1647! **************************************************************************************************
1648 SUBROUTINE create_lj_section(section)
1649 TYPE(section_type), POINTER :: section
1650
1651 TYPE(keyword_type), POINTER :: keyword
1652
1653 cpassert(.NOT. ASSOCIATED(section))
1654 CALL section_create(section, __location__, name="lennard-jones", &
1655 description="This section specifies the input parameters for LENNARD-JONES potential type. "// &
1656 "Functional form: V(r) = 4.0 * EPSILON * [(SIGMA/r)^12-(SIGMA/r)^6].", &
1657 n_keywords=1, n_subsections=0, repeats=.true.)
1658
1659 NULLIFY (keyword)
1660
1661 CALL keyword_create(keyword, __location__, name="ATOMS", &
1662 description="Defines the atomic kind involved in the nonbond potential", &
1663 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1664 n_var=2)
1665 CALL section_add_keyword(section, keyword)
1666 CALL keyword_release(keyword)
1667
1668 CALL keyword_create(keyword, __location__, name="EPSILON", &
1669 description="Defines the EPSILON parameter of the LJ potential", &
1670 usage="EPSILON {real}", type_of_var=real_t, &
1671 n_var=1, unit_str="K_e")
1672 CALL section_add_keyword(section, keyword)
1673 CALL keyword_release(keyword)
1674
1675 CALL keyword_create(keyword, __location__, name="SIGMA", &
1676 description="Defines the SIGMA parameter of the LJ potential", &
1677 usage="SIGMA {real}", type_of_var=real_t, &
1678 n_var=1, unit_str="angstrom")
1679 CALL section_add_keyword(section, keyword)
1680 CALL keyword_release(keyword)
1681
1682 CALL keyword_create(keyword, __location__, name="RCUT", &
1683 description="Defines the cutoff parameter of the LJ potential", &
1684 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1685 unit_str="angstrom"), &
1686 unit_str="angstrom")
1687 CALL section_add_keyword(section, keyword)
1688 CALL keyword_release(keyword)
1689
1690 CALL keyword_create(keyword, __location__, name="RMIN", &
1691 description="Defines the lower bound of the potential. If not set the range is the"// &
1692 " full range generate by the spline", usage="RMIN {real}", &
1693 type_of_var=real_t, unit_str="angstrom")
1694 CALL section_add_keyword(section, keyword)
1695 CALL keyword_release(keyword)
1696
1697 CALL keyword_create(keyword, __location__, name="RMAX", &
1698 description="Defines the upper bound of the potential. If not set the range is the"// &
1699 " full range generate by the spline", usage="RMAX {real}", &
1700 type_of_var=real_t, unit_str="angstrom")
1701 CALL section_add_keyword(section, keyword)
1702 CALL keyword_release(keyword)
1703
1704 END SUBROUTINE create_lj_section
1705
1706! **************************************************************************************************
1707!> \brief This section specifies the input parameters for Williams potential type
1708!> \param section the section to create
1709!> \author teo
1710! **************************************************************************************************
1711 SUBROUTINE create_williams_section(section)
1712 TYPE(section_type), POINTER :: section
1713
1714 TYPE(keyword_type), POINTER :: keyword
1715
1716 cpassert(.NOT. ASSOCIATED(section))
1717 CALL section_create(section, __location__, name="williams", &
1718 description="This section specifies the input parameters for WILLIAMS potential type. "// &
1719 "Functional form: V(r) = A*EXP(-B*r) - C / r^6 .", &
1720 n_keywords=1, n_subsections=0, repeats=.true.)
1721
1722 NULLIFY (keyword)
1723
1724 CALL keyword_create(keyword, __location__, name="ATOMS", &
1725 description="Defines the atomic kind involved in the nonbond potential", &
1726 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1727 n_var=2)
1728 CALL section_add_keyword(section, keyword)
1729 CALL keyword_release(keyword)
1730
1731 CALL keyword_create(keyword, __location__, name="A", &
1732 description="Defines the A parameter of the Williams potential", &
1733 usage="A {real}", type_of_var=real_t, &
1734 n_var=1, unit_str="K_e")
1735 CALL section_add_keyword(section, keyword)
1736 CALL keyword_release(keyword)
1737
1738 CALL keyword_create(keyword, __location__, name="B", &
1739 description="Defines the B parameter of the Williams potential", &
1740 usage="B {real}", type_of_var=real_t, &
1741 n_var=1, unit_str="angstrom^-1")
1742 CALL section_add_keyword(section, keyword)
1743 CALL keyword_release(keyword)
1744
1745 CALL keyword_create(keyword, __location__, name="C", &
1746 description="Defines the C parameter of the Williams potential", &
1747 usage="C {real}", type_of_var=real_t, &
1748 n_var=1, unit_str="K_e*angstrom^6")
1749 CALL section_add_keyword(section, keyword)
1750 CALL keyword_release(keyword)
1751
1752 CALL keyword_create(keyword, __location__, name="RCUT", &
1753 description="Defines the cutoff parameter of the Williams potential", &
1754 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1755 unit_str="angstrom"), &
1756 unit_str="angstrom")
1757 CALL section_add_keyword(section, keyword)
1758 CALL keyword_release(keyword)
1759
1760 CALL keyword_create(keyword, __location__, name="RMIN", &
1761 description="Defines the lower bound of the potential. If not set the range is the"// &
1762 " full range generate by the spline", usage="RMIN {real}", &
1763 type_of_var=real_t, unit_str="angstrom")
1764 CALL section_add_keyword(section, keyword)
1765 CALL keyword_release(keyword)
1766
1767 CALL keyword_create(keyword, __location__, name="RMAX", &
1768 description="Defines the upper bound of the potential. If not set the range is the"// &
1769 " full range generate by the spline", usage="RMAX {real}", &
1770 type_of_var=real_t, unit_str="angstrom")
1771 CALL section_add_keyword(section, keyword)
1772 CALL keyword_release(keyword)
1773
1774 END SUBROUTINE create_williams_section
1775
1776! **************************************************************************************************
1777!> \brief This section specifies the input parameters for Goodwin potential type
1778!> \param section the section to create
1779!> \author teo
1780! **************************************************************************************************
1781 SUBROUTINE create_goodwin_section(section)
1782 TYPE(section_type), POINTER :: section
1783
1784 TYPE(keyword_type), POINTER :: keyword
1785
1786 cpassert(.NOT. ASSOCIATED(section))
1787 CALL section_create(section, __location__, name="goodwin", &
1788 description="This section specifies the input parameters for GOODWIN potential type. "// &
1789 "Functional form: V(r) = EXP(M*(-(r/DC)**MC+(D/DC)**MC))*VR0*(D/r)**M.", &
1790 n_keywords=1, n_subsections=0, repeats=.true.)
1791
1792 NULLIFY (keyword)
1793 CALL keyword_create(keyword, __location__, name="ATOMS", &
1794 description="Defines the atomic kind involved in the nonbond potential", &
1795 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1796 n_var=2)
1797 CALL section_add_keyword(section, keyword)
1798 CALL keyword_release(keyword)
1799
1800 CALL keyword_create(keyword, __location__, name="VR0", &
1801 description="Defines the VR0 parameter of the Goodwin potential", &
1802 usage="VR0 {real}", type_of_var=real_t, &
1803 n_var=1, unit_str="K_e")
1804 CALL section_add_keyword(section, keyword)
1805 CALL keyword_release(keyword)
1806
1807 CALL keyword_create(keyword, __location__, name="D", &
1808 description="Defines the D parameter of the Goodwin potential", &
1809 usage="D {real}", type_of_var=real_t, &
1810 n_var=1, unit_str="angstrom")
1811 CALL section_add_keyword(section, keyword)
1812 CALL keyword_release(keyword)
1813
1814 CALL keyword_create(keyword, __location__, name="DC", &
1815 description="Defines the DC parameter of the Goodwin potential", &
1816 usage="DC {real}", type_of_var=real_t, &
1817 n_var=1, unit_str="angstrom")
1818 CALL section_add_keyword(section, keyword)
1819 CALL keyword_release(keyword)
1820
1821 CALL keyword_create(keyword, __location__, name="M", &
1822 description="Defines the M parameter of the Goodwin potential", &
1823 usage="M {real}", type_of_var=integer_t, &
1824 n_var=1)
1825 CALL section_add_keyword(section, keyword)
1826 CALL keyword_release(keyword)
1827
1828 CALL keyword_create(keyword, __location__, name="MC", &
1829 description="Defines the MC parameter of the Goodwin potential", &
1830 usage="MC {real}", type_of_var=integer_t, &
1831 n_var=1)
1832 CALL section_add_keyword(section, keyword)
1833 CALL keyword_release(keyword)
1834
1835 CALL keyword_create(keyword, __location__, name="RCUT", &
1836 description="Defines the cutoff parameter of the Goodwin potential", &
1837 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1838 unit_str="angstrom"), &
1839 unit_str="angstrom")
1840 CALL section_add_keyword(section, keyword)
1841 CALL keyword_release(keyword)
1842
1843 CALL keyword_create(keyword, __location__, name="RMIN", &
1844 description="Defines the lower bound of the potential. If not set the range is the"// &
1845 " full range generate by the spline", usage="RMIN {real}", &
1846 type_of_var=real_t, unit_str="angstrom")
1847 CALL section_add_keyword(section, keyword)
1848 CALL keyword_release(keyword)
1849
1850 CALL keyword_create(keyword, __location__, name="RMAX", &
1851 description="Defines the upper bound of the potential. If not set the range is the"// &
1852 " full range generate by the spline", usage="RMAX {real}", &
1853 type_of_var=real_t, unit_str="angstrom")
1854 CALL section_add_keyword(section, keyword)
1855 CALL keyword_release(keyword)
1856
1857 END SUBROUTINE create_goodwin_section
1858
1859! **************************************************************************************************
1860!> \brief This section specifies the input parameters for IPBV potential type
1861!> \param section the section to create
1862!> \author teo
1863! **************************************************************************************************
1864 SUBROUTINE create_ipbv_section(section)
1865 TYPE(section_type), POINTER :: section
1866
1867 TYPE(keyword_type), POINTER :: keyword
1868
1869 cpassert(.NOT. ASSOCIATED(section))
1870 CALL section_create(section, __location__, name="ipbv", &
1871 description="This section specifies the input parameters for IPBV potential type. "// &
1872 "Functional form: Implicit table function.", &
1873 n_keywords=1, n_subsections=0, repeats=.true.)
1874
1875 NULLIFY (keyword)
1876
1877 CALL keyword_create(keyword, __location__, name="ATOMS", &
1878 description="Defines the atomic kind involved in the IPBV nonbond potential", &
1879 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1880 n_var=2)
1881 CALL section_add_keyword(section, keyword)
1882 CALL keyword_release(keyword)
1883
1884 CALL keyword_create(keyword, __location__, name="RCUT", &
1885 description="Defines the cutoff parameter of the IPBV potential", &
1886 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
1887 unit_str="angstrom"), &
1888 unit_str="angstrom")
1889 CALL section_add_keyword(section, keyword)
1890 CALL keyword_release(keyword)
1891
1892 CALL keyword_create(keyword, __location__, name="RMIN", &
1893 description="Defines the lower bound of the potential. If not set the range is the"// &
1894 " full range generate by the spline", usage="RMIN {real}", &
1895 type_of_var=real_t, unit_str="angstrom")
1896 CALL section_add_keyword(section, keyword)
1897 CALL keyword_release(keyword)
1898
1899 CALL keyword_create(keyword, __location__, name="RMAX", &
1900 description="Defines the upper bound of the potential. If not set the range is the"// &
1901 " full range generate by the spline", usage="RMAX {real}", &
1902 type_of_var=real_t, unit_str="angstrom")
1903 CALL section_add_keyword(section, keyword)
1904 CALL keyword_release(keyword)
1905
1906 END SUBROUTINE create_ipbv_section
1907
1908! **************************************************************************************************
1909!> \brief This section specifies the input parameters for BMHFT potential type
1910!> \param section the section to create
1911!> \author teo
1912! **************************************************************************************************
1913 SUBROUTINE create_bmhft_section(section)
1914 TYPE(section_type), POINTER :: section
1915
1916 TYPE(keyword_type), POINTER :: keyword
1917
1918 cpassert(.NOT. ASSOCIATED(section))
1919 CALL section_create(section, __location__, name="BMHFT", &
1920 description="This section specifies the input parameters for BMHFT potential type. "// &
1921 "Functional form: V(r) = A * EXP(-B*r) - C/r^6 - D/r^8. "// &
1922 "Values available inside cp2k only for the Na/Cl pair.", &
1923 citations=(/tosi1964a, tosi1964b/), n_keywords=1, n_subsections=0, repeats=.true.)
1924
1925 NULLIFY (keyword)
1926
1927 CALL keyword_create(keyword, __location__, name="ATOMS", &
1928 description="Defines the atomic kind involved in the BMHFT nonbond potential", &
1929 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1930 n_var=2)
1931 CALL section_add_keyword(section, keyword)
1932 CALL keyword_release(keyword)
1933
1934 CALL keyword_create(keyword, __location__, name="MAP_ATOMS", &
1935 description="Defines the kinds for which internally is defined the BMHFT nonbond potential"// &
1936 " at the moment only Na and Cl.", &
1937 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
1938 n_var=2)
1939 CALL section_add_keyword(section, keyword)
1940 CALL keyword_release(keyword)
1941
1942 CALL keyword_create(keyword, __location__, name="RCUT", &
1943 description="Defines the cutoff parameter of the BMHFT potential", &
1944 usage="RCUT {real}", default_r_val=7.8_dp, &
1945 unit_str="angstrom")
1946 CALL section_add_keyword(section, keyword)
1947 CALL keyword_release(keyword)
1948
1949 CALL keyword_create(keyword, __location__, name="A", &
1950 description="Defines the A parameter of the Fumi-Tosi Potential", &
1951 usage="A {real}", type_of_var=real_t, &
1952 n_var=1, unit_str="hartree")
1953 CALL section_add_keyword(section, keyword)
1954 CALL keyword_release(keyword)
1955
1956 CALL keyword_create(keyword, __location__, name="B", &
1957 description="Defines the B parameter of the Fumi-Tosi Potential", &
1958 usage="B {real}", type_of_var=real_t, &
1959 n_var=1, unit_str="angstrom^-1")
1960 CALL section_add_keyword(section, keyword)
1961 CALL keyword_release(keyword)
1962
1963 CALL keyword_create(keyword, __location__, name="C", &
1964 description="Defines the C parameter of the Fumi-Tosi Potential", &
1965 usage="C {real}", type_of_var=real_t, &
1966 n_var=1, unit_str="hartree*angstrom^6")
1967 CALL section_add_keyword(section, keyword)
1968 CALL keyword_release(keyword)
1969
1970 CALL keyword_create(keyword, __location__, name="D", &
1971 description="Defines the D parameter of the Fumi-Tosi Potential", &
1972 usage="D {real}", type_of_var=real_t, &
1973 n_var=1, unit_str="hartree*angstrom^8")
1974 CALL section_add_keyword(section, keyword)
1975 CALL keyword_release(keyword)
1976
1977 CALL keyword_create(keyword, __location__, name="RMIN", &
1978 description="Defines the lower bound of the potential. If not set the range is the"// &
1979 " full range generate by the spline", usage="RMIN {real}", &
1980 type_of_var=real_t, unit_str="angstrom")
1981 CALL section_add_keyword(section, keyword)
1982 CALL keyword_release(keyword)
1983
1984 CALL keyword_create(keyword, __location__, name="RMAX", &
1985 description="Defines the upper bound of the potential. If not set the range is the"// &
1986 " full range generate by the spline", usage="RMAX {real}", &
1987 type_of_var=real_t, unit_str="angstrom")
1988 CALL section_add_keyword(section, keyword)
1989 CALL keyword_release(keyword)
1990
1991 END SUBROUTINE create_bmhft_section
1992
1993! **************************************************************************************************
1994!> \brief This section specifies the input parameters for BMHFTD potential type
1995!> \param section the section to create
1996!> \par History
1997!> - Unused input keyword ORDER removed (18.10.2021, MK)
1998!> \author Mathieu Salanne 05.2010
1999! **************************************************************************************************
2000 SUBROUTINE create_bmhftd_section(section)
2001 TYPE(section_type), POINTER :: section
2002
2003 TYPE(keyword_type), POINTER :: keyword
2004
2005 cpassert(.NOT. ASSOCIATED(section))
2006 CALL section_create(section, __location__, name="BMHFTD", &
2007 description="This section specifies the input parameters for the BMHFTD potential type. "// &
2008 "Functional form: V(r) = A*exp(-B*r) - f_6*(r)C/r^6 - f_8(r)*D/r^8 "// &
2009 "where f_order(r) = 1 - exp(-BD*r)*\sum_{k=0}^order (BD*r)^k/k! "// &
2010 "(Tang-Toennies damping function). No pre-defined parameter values are available.", &
2011 citations=(/tosi1964a, tosi1964b/), n_keywords=1, n_subsections=0, repeats=.true.)
2012
2013 NULLIFY (keyword)
2014
2015 CALL keyword_create(keyword, __location__, name="ATOMS", &
2016 description="Defines the atomic kind involved in the BMHFTD nonbond potential", &
2017 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2018 n_var=2)
2019 CALL section_add_keyword(section, keyword)
2020 CALL keyword_release(keyword)
2021
2022 CALL keyword_create(keyword, __location__, name="MAP_ATOMS", &
2023 description="Defines the kinds for which internally is defined the BMHFTD nonbond potential"// &
2024 " at the moment no species included.", &
2025 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2026 n_var=2)
2027 CALL section_add_keyword(section, keyword)
2028 CALL keyword_release(keyword)
2029
2030 CALL keyword_create(keyword, __location__, name="RCUT", &
2031 description="Defines the cutoff parameter of the BMHFTD potential", &
2032 usage="RCUT {real}", default_r_val=7.8_dp, &
2033 unit_str="angstrom")
2034 CALL section_add_keyword(section, keyword)
2035 CALL keyword_release(keyword)
2036
2037 CALL keyword_create(keyword, __location__, name="A", &
2038 description="Defines the A parameter of the dispersion-damped Fumi-Tosi potential", &
2039 usage="A {real}", type_of_var=real_t, &
2040 n_var=1, unit_str="hartree")
2041 CALL section_add_keyword(section, keyword)
2042 CALL keyword_release(keyword)
2043
2044 CALL keyword_create(keyword, __location__, name="B", &
2045 description="Defines the B parameter of the dispersion-damped Fumi-Tosi potential", &
2046 usage="B {real}", type_of_var=real_t, &
2047 n_var=1, unit_str="angstrom^-1")
2048 CALL section_add_keyword(section, keyword)
2049 CALL keyword_release(keyword)
2050
2051 CALL keyword_create(keyword, __location__, name="C", &
2052 description="Defines the C parameter of the dispersion-damped Fumi-Tosi potential", &
2053 usage="C {real}", type_of_var=real_t, &
2054 n_var=1, unit_str="hartree*angstrom^6")
2055 CALL section_add_keyword(section, keyword)
2056 CALL keyword_release(keyword)
2057
2058 CALL keyword_create(keyword, __location__, name="D", &
2059 description="Defines the D parameter of the dispersion-damped Fumi-Tosi potential", &
2060 usage="D {real}", type_of_var=real_t, &
2061 n_var=1, unit_str="hartree*angstrom^8")
2062 CALL section_add_keyword(section, keyword)
2063 CALL keyword_release(keyword)
2064
2065 CALL keyword_create(keyword, __location__, name="BD", &
2066 description="Defines the BD parameters of the dispersion-damped Fumi-Tosi potential. "// &
2067 "One or two parameter values are expected. If only one value is provided, then this "// &
2068 "value will be used both for the 6th and the 8th order term.", &
2069 usage="BD {real} {real}", type_of_var=real_t, &
2070 n_var=-1, unit_str="angstrom^-1")
2071 CALL section_add_keyword(section, keyword)
2072 CALL keyword_release(keyword)
2073
2074 CALL keyword_create(keyword, __location__, name="RMIN", &
2075 description="Defines the lower bound of the potential. If not set the range is the"// &
2076 " full range generate by the spline", usage="RMIN {real}", &
2077 type_of_var=real_t, unit_str="angstrom")
2078 CALL section_add_keyword(section, keyword)
2079 CALL keyword_release(keyword)
2080
2081 CALL keyword_create(keyword, __location__, name="RMAX", &
2082 description="Defines the upper bound of the potential. If not set the range is the"// &
2083 " full range generate by the spline", usage="RMAX {real}", &
2084 type_of_var=real_t, unit_str="angstrom")
2085 CALL section_add_keyword(section, keyword)
2086 CALL keyword_release(keyword)
2087
2088 END SUBROUTINE create_bmhftd_section
2089
2090! **************************************************************************************************
2091!> \brief This section specifies the input parameters for Buckingham 4 ranges potential type
2092!> \param section the section to create
2093!> \author MI
2094! **************************************************************************************************
2095 SUBROUTINE create_buck4r_section(section)
2096 TYPE(section_type), POINTER :: section
2097
2098 TYPE(keyword_type), POINTER :: keyword
2099
2100 cpassert(.NOT. ASSOCIATED(section))
2101 CALL section_create(section, __location__, name="BUCK4RANGES", &
2102 description="This section specifies the input parameters for the Buckingham 4-ranges"// &
2103 " potential type."//newline// &
2104 "| Range | Functional Form |"//newline// &
2105 "| ----- | --------------- |"//newline// &
2106 "| $ r < r_1 $ | $ V(r) = A\exp(-Br) $ |"//newline// &
2107 "| $ r_1 \leq r < r_2 $ | $ V(r) = \sum_n \operatorname{POLY1}(n)r_n $ |"//newline// &
2108 "| $ r_2 \leq r < r_3 $ | $ V(r) = \sum_n \operatorname{POLY2}(n)r_n $ |"//newline// &
2109 "| $ r \geq r_3 $ | $ V(r) = -C/r_6 $ |"//newline, &
2110 n_keywords=1, n_subsections=0, repeats=.true.)
2111
2112 NULLIFY (keyword)
2113
2114 CALL keyword_create(keyword, __location__, name="ATOMS", &
2115 description="Defines the atomic kind involved in the nonbond potential", &
2116 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2117 n_var=2)
2118 CALL section_add_keyword(section, keyword)
2119 CALL keyword_release(keyword)
2120
2121 CALL keyword_create(keyword, __location__, name="A", &
2122 description="Defines the A parameter of the Buckingham potential", &
2123 usage="A {real}", type_of_var=real_t, &
2124 n_var=1, unit_str="K_e")
2125 CALL section_add_keyword(section, keyword)
2126 CALL keyword_release(keyword)
2127
2128 CALL keyword_create(keyword, __location__, name="B", &
2129 description="Defines the B parameter of the Buckingham potential", &
2130 usage="B {real}", type_of_var=real_t, &
2131 n_var=1, unit_str="angstrom^-1")
2132 CALL section_add_keyword(section, keyword)
2133 CALL keyword_release(keyword)
2134
2135 CALL keyword_create(keyword, __location__, name="C", &
2136 description="Defines the C parameter of the Buckingham potential", &
2137 usage="C {real}", type_of_var=real_t, &
2138 n_var=1, unit_str="K_e*angstrom^6")
2139 CALL section_add_keyword(section, keyword)
2140 CALL keyword_release(keyword)
2141
2142 CALL keyword_create(keyword, __location__, name="R1", &
2143 description="Defines the upper bound of the first range ", &
2144 usage="R1 {real}", type_of_var=real_t, &
2145 n_var=1, unit_str="angstrom")
2146 CALL section_add_keyword(section, keyword)
2147 CALL keyword_release(keyword)
2148
2149 CALL keyword_create(keyword, __location__, name="R2", &
2150 description="Defines the upper bound of the second range ", &
2151 usage="R2 {real}", type_of_var=real_t, &
2152 n_var=1, unit_str="angstrom")
2153 CALL section_add_keyword(section, keyword)
2154 CALL keyword_release(keyword)
2155
2156 CALL keyword_create(keyword, __location__, name="R3", &
2157 description="Defines the upper bound of the third range ", &
2158 usage="R3 {real}", type_of_var=real_t, &
2159 n_var=1, unit_str="angstrom")
2160 CALL section_add_keyword(section, keyword)
2161 CALL keyword_release(keyword)
2162
2163 CALL keyword_create(keyword, __location__, name="POLY1", &
2164 description="Coefficients of the polynomial used in the second range "// &
2165 "This keyword can be repeated several times.", &
2166 usage="POLY1 C1 C2 C3 ..", &
2167 n_var=-1, unit_str="K_e", type_of_var=real_t, repeats=.true.)
2168 CALL section_add_keyword(section, keyword)
2169 CALL keyword_release(keyword)
2170
2171 CALL keyword_create(keyword, __location__, name="POLY2", &
2172 description="Coefficients of the polynomial used in the third range "// &
2173 "This keyword can be repeated several times.", &
2174 usage="POLY1 C1 C2 C3 ..", &
2175 n_var=-1, unit_str="K_e", type_of_var=real_t, repeats=.true.)
2176 CALL section_add_keyword(section, keyword)
2177 CALL keyword_release(keyword)
2178
2179 CALL keyword_create(keyword, __location__, name="RCUT", &
2180 description="Defines the cutoff parameter of the Buckingham potential", &
2181 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
2182 unit_str="angstrom"), &
2183 unit_str="angstrom")
2184 CALL section_add_keyword(section, keyword)
2185 CALL keyword_release(keyword)
2186
2187 CALL keyword_create(keyword, __location__, name="RMIN", &
2188 description="Defines the lower bound of the potential. If not set the range is the"// &
2189 " full range generate by the spline", usage="RMIN {real}", &
2190 type_of_var=real_t, unit_str="angstrom")
2191 CALL section_add_keyword(section, keyword)
2192 CALL keyword_release(keyword)
2193
2194 CALL keyword_create(keyword, __location__, name="RMAX", &
2195 description="Defines the upper bound of the potential. If not set the range is the"// &
2196 " full range generate by the spline", usage="RMAX {real}", &
2197 type_of_var=real_t, unit_str="angstrom")
2198 CALL section_add_keyword(section, keyword)
2199 CALL keyword_release(keyword)
2200
2201 END SUBROUTINE create_buck4r_section
2202
2203! **************************************************************************************************
2204!> \brief This section specifies the input parameters for Buckingham + Morse potential type
2205!> \param section the section to create
2206!> \author MI
2207! **************************************************************************************************
2208 SUBROUTINE create_buckmorse_section(section)
2209 TYPE(section_type), POINTER :: section
2210
2211 TYPE(keyword_type), POINTER :: keyword
2212
2213 cpassert(.NOT. ASSOCIATED(section))
2214 CALL section_create( &
2215 section, __location__, name="BUCKMORSE", &
2216 description="This section specifies the input parameters for"// &
2217 " Buckingham plus Morse potential type"// &
2218 " 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)]}.", &
2219 citations=(/yamada2000/), n_keywords=1, n_subsections=0, repeats=.true.)
2220
2221 NULLIFY (keyword)
2222
2223 CALL keyword_create(keyword, __location__, name="ATOMS", &
2224 description="Defines the atomic kind involved in the nonbond potential", &
2225 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2226 n_var=2)
2227 CALL section_add_keyword(section, keyword)
2228 CALL keyword_release(keyword)
2229
2230 CALL keyword_create(keyword, __location__, name="F0", &
2231 description="Defines the f0 parameter of Buckingham+Morse potential", &
2232 usage="F0 {real}", type_of_var=real_t, &
2233 n_var=1, unit_str="K_e*angstrom^-1")
2234 CALL section_add_keyword(section, keyword)
2235 CALL keyword_release(keyword)
2236
2237 CALL keyword_create(keyword, __location__, name="A1", &
2238 description="Defines the A1 parameter of Buckingham+Morse potential", &
2239 usage="A1 {real}", type_of_var=real_t, &
2240 n_var=1, unit_str="angstrom")
2241 CALL section_add_keyword(section, keyword)
2242 CALL keyword_release(keyword)
2243
2244 CALL keyword_create(keyword, __location__, name="A2", &
2245 description="Defines the A2 parameter of Buckingham+Morse potential", &
2246 usage="A2 {real}", type_of_var=real_t, &
2247 n_var=1, unit_str="angstrom")
2248 CALL section_add_keyword(section, keyword)
2249 CALL keyword_release(keyword)
2250
2251 CALL keyword_create(keyword, __location__, name="B1", &
2252 description="Defines the B1 parameter of Buckingham+Morse potential", &
2253 usage="B1 {real}", type_of_var=real_t, &
2254 n_var=1, unit_str="angstrom")
2255 CALL section_add_keyword(section, keyword)
2256 CALL keyword_release(keyword)
2257
2258 CALL keyword_create(keyword, __location__, name="B2", &
2259 description="Defines the B2 parameter of Buckingham+Morse potential", &
2260 usage="B2 {real}", type_of_var=real_t, &
2261 n_var=1, unit_str="angstrom")
2262 CALL section_add_keyword(section, keyword)
2263 CALL keyword_release(keyword)
2264
2265 CALL keyword_create(keyword, __location__, name="C", &
2266 description="Defines the C parameter of Buckingham+Morse potential", &
2267 usage="C {real}", type_of_var=real_t, &
2268 n_var=1, unit_str="K_e*angstrom^6")
2269 CALL section_add_keyword(section, keyword)
2270 CALL keyword_release(keyword)
2271
2272 CALL keyword_create(keyword, __location__, name="D", &
2273 description="Defines the amplitude for the Morse part ", &
2274 usage="D {real}", type_of_var=real_t, &
2275 n_var=1, unit_str="K_e")
2276 CALL section_add_keyword(section, keyword)
2277 CALL keyword_release(keyword)
2278
2279 CALL keyword_create(keyword, __location__, name="R0", &
2280 description="Defines the equilibrium distance for the Morse part ", &
2281 usage="R0 {real}", type_of_var=real_t, &
2282 n_var=1, unit_str="angstrom")
2283 CALL section_add_keyword(section, keyword)
2284 CALL keyword_release(keyword)
2285
2286 CALL keyword_create(keyword, __location__, name="Beta", &
2287 description="Defines the width for the Morse part ", &
2288 usage="Beta {real}", type_of_var=real_t, &
2289 n_var=1, unit_str="angstrom^-1")
2290 CALL section_add_keyword(section, keyword)
2291 CALL keyword_release(keyword)
2292
2293 CALL keyword_create(keyword, __location__, name="RCUT", &
2294 description="Defines the cutoff parameter of the Buckingham potential", &
2295 usage="RCUT {real}", default_r_val=cp_unit_to_cp2k(value=10.0_dp, &
2296 unit_str="angstrom"), &
2297 unit_str="angstrom")
2298 CALL section_add_keyword(section, keyword)
2299 CALL keyword_release(keyword)
2300
2301 CALL keyword_create(keyword, __location__, name="RMIN", &
2302 description="Defines the lower bound of the potential. If not set the range is the"// &
2303 " full range generate by the spline", usage="RMIN {real}", &
2304 type_of_var=real_t, unit_str="angstrom")
2305 CALL section_add_keyword(section, keyword)
2306 CALL keyword_release(keyword)
2307
2308 CALL keyword_create(keyword, __location__, name="RMAX", &
2309 description="Defines the upper bound of the potential. If not set the range is the"// &
2310 " full range generate by the spline", usage="RMAX {real}", &
2311 type_of_var=real_t, unit_str="angstrom")
2312 CALL section_add_keyword(section, keyword)
2313 CALL keyword_release(keyword)
2314
2315 END SUBROUTINE create_buckmorse_section
2316
2317! **************************************************************************************************
2318!> \brief This section specifies the input parameters for Tersoff potential type
2319!> (Tersoff, J. PRB 39(8), 5566, 1989)
2320!> \param section ...
2321! **************************************************************************************************
2322 SUBROUTINE create_tersoff_section(section)
2323 TYPE(section_type), POINTER :: section
2324
2325 TYPE(keyword_type), POINTER :: keyword
2326
2327 cpassert(.NOT. ASSOCIATED(section))
2328 CALL section_create(section, __location__, name="TERSOFF", &
2329 description="This section specifies the input parameters for Tersoff potential type.", &
2330 citations=(/tersoff1988/), n_keywords=1, n_subsections=0, repeats=.true.)
2331
2332 NULLIFY (keyword)
2333
2334 CALL keyword_create(keyword, __location__, name="ATOMS", &
2335 description="Defines the atomic kind involved in the nonbond potential", &
2336 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2337 n_var=2)
2338 CALL section_add_keyword(section, keyword)
2339 CALL keyword_release(keyword)
2340
2341 CALL keyword_create(keyword, __location__, name="A", &
2342 description="Defines the A parameter of Tersoff potential", &
2343 usage="A {real}", type_of_var=real_t, &
2344 default_r_val=cp_unit_to_cp2k(value=1.8308e3_dp, &
2345 unit_str="eV"), &
2346 n_var=1, unit_str="eV")
2347 CALL section_add_keyword(section, keyword)
2348 CALL keyword_release(keyword)
2349
2350 CALL keyword_create(keyword, __location__, name="B", &
2351 description="Defines the B parameter of Tersoff potential", &
2352 usage="B {real}", type_of_var=real_t, &
2353 default_r_val=cp_unit_to_cp2k(value=4.7118e2_dp, &
2354 unit_str="eV"), &
2355 n_var=1, unit_str="eV")
2356 CALL section_add_keyword(section, keyword)
2357 CALL keyword_release(keyword)
2358
2359 CALL keyword_create(keyword, __location__, name="lambda1", &
2360 description="Defines the lambda1 parameter of Tersoff potential", &
2361 usage="lambda1 {real}", type_of_var=real_t, &
2362 default_r_val=cp_unit_to_cp2k(value=2.4799_dp, &
2363 unit_str="angstrom^-1"), &
2364 n_var=1, unit_str="angstrom^-1")
2365 CALL section_add_keyword(section, keyword)
2366 CALL keyword_release(keyword)
2367
2368 CALL keyword_create(keyword, __location__, name="lambda2", &
2369 description="Defines the lambda2 parameter of Tersoff potential", &
2370 usage="lambda2 {real}", type_of_var=real_t, &
2371 default_r_val=cp_unit_to_cp2k(value=1.7322_dp, &
2372 unit_str="angstrom^-1"), &
2373 n_var=1, unit_str="angstrom^-1")
2374 CALL section_add_keyword(section, keyword)
2375 CALL keyword_release(keyword)
2376
2377 CALL keyword_create(keyword, __location__, name="alpha", &
2378 description="Defines the alpha parameter of Tersoff potential", &
2379 usage="alpha {real}", type_of_var=real_t, &
2380 default_r_val=0.0_dp, &
2381 n_var=1)
2382 CALL section_add_keyword(section, keyword)
2383 CALL keyword_release(keyword)
2384
2385 CALL keyword_create(keyword, __location__, name="beta", &
2386 description="Defines the beta parameter of Tersoff potential", &
2387 usage="beta {real}", type_of_var=real_t, &
2388 default_r_val=1.0999e-6_dp, &
2389 n_var=1, unit_str="")
2390 CALL section_add_keyword(section, keyword)
2391 CALL keyword_release(keyword)
2392
2393 CALL keyword_create(keyword, __location__, name="n", &
2394 description="Defines the n parameter of Tersoff potential", &
2395 usage="n {real}", type_of_var=real_t, &
2396 default_r_val=7.8734e-1_dp, &
2397 n_var=1, unit_str="")
2398 CALL section_add_keyword(section, keyword)
2399 CALL keyword_release(keyword)
2400
2401 CALL keyword_create(keyword, __location__, name="c", &
2402 description="Defines the c parameter of Tersoff potential", &
2403 usage="c {real}", type_of_var=real_t, &
2404 default_r_val=1.0039e5_dp, &
2405 n_var=1, unit_str="")
2406 CALL section_add_keyword(section, keyword)
2407 CALL keyword_release(keyword)
2408
2409 CALL keyword_create(keyword, __location__, name="d", &
2410 description="Defines the d parameter of Tersoff potential", &
2411 usage="d {real}", type_of_var=real_t, &
2412 default_r_val=1.6218e1_dp, &
2413 n_var=1, unit_str="")
2414 CALL section_add_keyword(section, keyword)
2415 CALL keyword_release(keyword)
2416
2417 CALL keyword_create(keyword, __location__, name="h", &
2418 description="Defines the h parameter of Tersoff potential", &
2419 usage="h {real}", type_of_var=real_t, &
2420 default_r_val=-5.9826e-1_dp, &
2421 n_var=1, unit_str="")
2422 CALL section_add_keyword(section, keyword)
2423 CALL keyword_release(keyword)
2424
2425 CALL keyword_create(keyword, __location__, name="lambda3", &
2426 description="Defines the lambda3 parameter of Tersoff potential", &
2427 usage="lambda3 {real}", type_of_var=real_t, &
2428 default_r_val=cp_unit_to_cp2k(value=1.7322_dp, &
2429 unit_str="angstrom^-1"), &
2430 n_var=1, unit_str="angstrom^-1")
2431 CALL section_add_keyword(section, keyword)
2432 CALL keyword_release(keyword)
2433
2434 CALL keyword_create(keyword, __location__, name="bigR", &
2435 description="Defines the bigR parameter of Tersoff potential", &
2436 usage="bigR {real}", type_of_var=real_t, &
2437 default_r_val=cp_unit_to_cp2k(value=2.85_dp, &
2438 unit_str="angstrom"), &
2439 n_var=1, unit_str="angstrom")
2440 CALL section_add_keyword(section, keyword)
2441 CALL keyword_release(keyword)
2442
2443 CALL keyword_create(keyword, __location__, name="bigD", &
2444 description="Defines the D parameter of Tersoff potential", &
2445 usage="bigD {real}", type_of_var=real_t, &
2446 default_r_val=cp_unit_to_cp2k(value=0.15_dp, &
2447 unit_str="angstrom"), &
2448 n_var=1, unit_str="angstrom")
2449 CALL section_add_keyword(section, keyword)
2450 CALL keyword_release(keyword)
2451
2452 CALL keyword_create(keyword, __location__, name="RCUT", &
2453 description="Defines the cutoff parameter of the tersoff potential."// &
2454 " This parameter is in principle already defined by the values of"// &
2455 " bigD and bigR. But it is necessary to define it when using the tersoff"// &
2456 " in conjunction with other potentials (for the same atomic pair) in order to have"// &
2457 " the same consistent definition of RCUT for all potentials.", &
2458 usage="RCUT {real}", type_of_var=real_t, &
2459 n_var=1, unit_str="angstrom")
2460 CALL section_add_keyword(section, keyword)
2461 CALL keyword_release(keyword)
2462
2463 END SUBROUTINE create_tersoff_section
2464
2465! **************************************************************************************************
2466!> \brief This section specifies the input parameters for Siepmann-Sprik
2467!> potential type
2468!> (Siepmann and Sprik, J. Chem. Phys. 102(1) 511, 1995)
2469!> \param section ...
2470! **************************************************************************************************
2471 SUBROUTINE create_siepmann_section(section)
2472 TYPE(section_type), POINTER :: section
2473
2474 TYPE(keyword_type), POINTER :: keyword
2475
2476 cpassert(.NOT. ASSOCIATED(section))
2477 CALL section_create(section, __location__, name="SIEPMANN", &
2478 description="This section specifies the input parameters for the"// &
2479 " Siepmann-Sprik potential type. Consists of 4 terms:"// &
2480 " T1+T2+T3+T4. The terms T1=A/rij^alpha and T2=-C/rij^6"// &
2481 " have to be given via the GENPOT section. The terms T3+T4"// &
2482 " are obtained from the SIEPMANN section. The Siepmann-Sprik"// &
2483 " potential is designed for water-metal chemisorption.", &
2484 citations=(/siepmann1995/), n_keywords=1, n_subsections=0, repeats=.true.)
2485
2486 NULLIFY (keyword)
2487
2488 CALL keyword_create(keyword, __location__, name="ATOMS", &
2489 description="Defines the atomic kind involved in the nonbond potential", &
2490 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2491 n_var=2)
2492 CALL section_add_keyword(section, keyword)
2493 CALL keyword_release(keyword)
2494
2495 CALL keyword_create(keyword, __location__, name="B", &
2496 description="Defines the B parameter of Siepmann potential", &
2497 usage="B {real}", type_of_var=real_t, &
2498 default_r_val=cp_unit_to_cp2k(value=0.6_dp, &
2499 unit_str="angstrom"), &
2500 n_var=1, unit_str="angstrom")
2501 CALL section_add_keyword(section, keyword)
2502 CALL keyword_release(keyword)
2503
2504 CALL keyword_create(keyword, __location__, name="D", &
2505 description="Defines the D parameter of Siepmann potential", &
2506 usage="D {real}", type_of_var=real_t, &
2507 default_r_val=cp_unit_to_cp2k(value=3.688388_dp, &
2508 unit_str="internal_cp2k"), &
2509 n_var=1, unit_str="internal_cp2k")
2510 CALL section_add_keyword(section, keyword)
2511 CALL keyword_release(keyword)
2512
2513 CALL keyword_create(keyword, __location__, name="E", &
2514 description="Defines the E parameter of Siepmann potential", &
2515 usage="E {real}", type_of_var=real_t, &
2516 default_r_val=cp_unit_to_cp2k(value=9.069025_dp, &
2517 unit_str="internal_cp2k"), &
2518 n_var=1, unit_str="internal_cp2k")
2519 CALL section_add_keyword(section, keyword)
2520 CALL keyword_release(keyword)
2521
2522 CALL keyword_create(keyword, __location__, name="F", &
2523 description="Defines the F parameter of Siepmann potential", &
2524 usage="B {real}", type_of_var=real_t, &
2525 default_r_val=13.3_dp, n_var=1)
2526 CALL section_add_keyword(section, keyword)
2527 CALL keyword_release(keyword)
2528!
2529 CALL keyword_create(keyword, __location__, name="beta", &
2530 description="Defines the beta parameter of Siepmann potential", &
2531 usage="beta {real}", type_of_var=real_t, &
2532 default_r_val=10.0_dp, n_var=1)
2533 CALL section_add_keyword(section, keyword)
2534 CALL keyword_release(keyword)
2535!
2536 CALL keyword_create(keyword, __location__, name="RCUT", &
2537 description="Defines the cutoff parameter of Siepmann potential", &
2538 usage="RCUT {real}", type_of_var=real_t, &
2539 default_r_val=cp_unit_to_cp2k(value=3.2_dp, &
2540 unit_str="angstrom"), &
2541 n_var=1, unit_str="angstrom")
2542 CALL section_add_keyword(section, keyword)
2543 CALL keyword_release(keyword)
2544!
2545 CALL keyword_create(keyword, __location__, name="ALLOW_OH_FORMATION", &
2546 description=" The Siepmann-Sprik potential is actually designed for intact"// &
2547 " water molecules only. If water is treated at the QM level,"// &
2548 " water molecules can potentially dissociate, i.e."// &
2549 " some O-H bonds might be stretched leading temporarily"// &
2550 " to the formation of OH- ions. This keyword allows the"// &
2551 " the formation of such ions. The T3 term (dipole term)"// &
2552 " is then switched off for evaluating the interaction"// &
2553 " between the OH- ion and the metal.", &
2554 usage="ALLOW_OH_FORMATION TRUE", &
2555 default_l_val=.false., lone_keyword_l_val=.true.)
2556 CALL section_add_keyword(section, keyword)
2557 CALL keyword_release(keyword)
2558
2559 CALL keyword_create(keyword, __location__, name="ALLOW_H3O_FORMATION", &
2560 description=" The Siepmann-Sprik potential is designed for intact water"// &
2561 " molecules only. If water is treated at the QM level"// &
2562 " and an acid is present, hydronium ions might occur."// &
2563 " This keyword allows the formation of hydronium ions."// &
2564 " The T3 term (dipole term) is switched off for evaluating"// &
2565 " the interaction between hydronium and the metal.", &
2566 usage="ALLOW_H3O_FORMATION TRUE", &
2567 default_l_val=.false., lone_keyword_l_val=.true.)
2568 CALL section_add_keyword(section, keyword)
2569 CALL keyword_release(keyword)
2570
2571 CALL keyword_create(keyword, __location__, name="ALLOW_O_FORMATION", &
2572 description=" The Siepmann-Sprik potential is actually designed for intact"// &
2573 " water molecules only. If water is treated at the QM level,"// &
2574 " water molecules can potentially dissociate, i.e."// &
2575 " some O-H bonds might be stretched leading temporarily"// &
2576 " to the formation of O^2- ions. This keyword allows the"// &
2577 " the formation of such ions. The T3 term (dipole term)"// &
2578 " is then switched off for evaluating the interaction"// &
2579 " between the O^2- ion and the metal.", &
2580 usage="ALLOW_O2-_FORMATION TRUE", &
2581 default_l_val=.false., lone_keyword_l_val=.true.)
2582 CALL section_add_keyword(section, keyword)
2583 CALL keyword_release(keyword)
2584
2585 END SUBROUTINE create_siepmann_section
2586
2587! **************************************************************************************************
2588!> \brief This section specifies the input parameters for GAL19
2589!> potential type
2590!> (??)
2591!> \param section ...
2592! **************************************************************************************************
2593 SUBROUTINE create_gal_section(section)
2594 TYPE(section_type), POINTER :: section
2595
2596 TYPE(keyword_type), POINTER :: keyword
2597 TYPE(section_type), POINTER :: subsection
2598
2599 cpassert(.NOT. ASSOCIATED(section))
2600 CALL section_create(section, __location__, name="GAL19", &
2601 description="Implementation of the GAL19 forcefield, see associated paper", &
2602 citations=(/clabaut2020/), n_keywords=1, n_subsections=1, repeats=.true.)
2603
2604 NULLIFY (keyword, subsection)
2605
2606 CALL keyword_create(keyword, __location__, name="ATOMS", &
2607 description="Defines the atomic kind involved in the nonbond potential", &
2608 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2609 n_var=2)
2610 CALL section_add_keyword(section, keyword)
2611 CALL keyword_release(keyword)
2612
2613 CALL keyword_create(keyword, __location__, name="METALS", &
2614 description="Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2615 usage="METALS {KIND1} {KIND2} ..", type_of_var=char_t, &
2616 n_var=2)
2617 CALL section_add_keyword(section, keyword)
2618 CALL keyword_release(keyword)
2619
2620 CALL keyword_create(keyword, __location__, name="epsilon", &
2621 description="Defines the epsilon_a parameter of GAL19 potential", &
2622 usage="epsilon {real}", type_of_var=real_t, &
2623 default_r_val=cp_unit_to_cp2k(value=0.6_dp, &
2624 unit_str="kcalmol"), &
2625 n_var=1, unit_str="kcalmol")
2626 CALL section_add_keyword(section, keyword)
2627 CALL keyword_release(keyword)
2628
2629 CALL keyword_create(keyword, __location__, name="bxy", &
2630 description="Defines the b perpendicular parameter of GAL19 potential", &
2631 usage="bxy {real}", type_of_var=real_t, &
2632 default_r_val=cp_unit_to_cp2k(value=3.688388_dp, &
2633 unit_str="internal_cp2k"), &
2634 n_var=1, unit_str="angstrom^-2")
2635 CALL section_add_keyword(section, keyword)
2636 CALL keyword_release(keyword)
2637
2638 CALL keyword_create(keyword, __location__, name="bz", &
2639 description="Defines the b parallel parameter of GAL19 potential", &
2640 usage="bz {real}", type_of_var=real_t, &
2641 default_r_val=cp_unit_to_cp2k(value=9.069025_dp, &
2642 unit_str="internal_cp2k"), &
2643 n_var=1, unit_str="angstrom^-2")
2644 CALL section_add_keyword(section, keyword)
2645 CALL keyword_release(keyword)
2646
2647 CALL keyword_create(keyword, __location__, name="r", &
2648 description="Defines the R_0 parameters of GAL19 potential for the two METALS. "// &
2649 "This is the only parameter that is shared between the two section of the "// &
2650 "forcefield in the case of two metals (alloy). "// &
2651 "If one metal only is present, a second number should be given but won't be read", &
2652 usage="r {real} {real}", type_of_var=real_t, n_var=2, unit_str="angstrom")
2653 CALL section_add_keyword(section, keyword)
2654 CALL keyword_release(keyword)
2655
2656 CALL keyword_create(keyword, __location__, name="a1", &
2657 description="Defines the a1 parameter of GAL19 potential", &
2658 usage="a1 {real}", type_of_var=real_t, &
2659 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2660 CALL section_add_keyword(section, keyword)
2661 CALL keyword_release(keyword)
2662
2663 CALL keyword_create(keyword, __location__, name="a2", &
2664 description="Defines the a2 parameter of GAL19 potential", &
2665 usage="a2 {real}", type_of_var=real_t, &
2666 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2667 CALL section_add_keyword(section, keyword)
2668 CALL keyword_release(keyword)
2669
2670 CALL keyword_create(keyword, __location__, name="a3", &
2671 description="Defines the a3 parameter of GAL19 potential", &
2672 usage="a3 {real}", type_of_var=real_t, &
2673 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2674 CALL section_add_keyword(section, keyword)
2675 CALL keyword_release(keyword)
2676
2677 CALL keyword_create(keyword, __location__, name="a4", &
2678 description="Defines the a4 parameter of GAL19 potential", &
2679 usage="a4 {real}", type_of_var=real_t, &
2680 default_r_val=10.0_dp, n_var=1, unit_str="kcalmol")
2681 CALL section_add_keyword(section, keyword)
2682 CALL keyword_release(keyword)
2683
2684 CALL keyword_create(keyword, __location__, name="A", &
2685 description="Defines the A parameter of GAL19 potential", &
2686 usage="A {real}", type_of_var=real_t, &
2687 default_r_val=10.0_dp, 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="B", &
2692 description="Defines the B parameter of GAL19 potential", &
2693 usage="B {real}", type_of_var=real_t, &
2694 default_r_val=10.0_dp, n_var=1, unit_str="angstrom^-1")
2695 CALL section_add_keyword(section, keyword)
2696 CALL keyword_release(keyword)
2697
2698 CALL keyword_create(keyword, __location__, name="C", &
2699 description="Defines the C parameter of GAL19 potential", &
2700 usage="C {real}", type_of_var=real_t, &
2701 default_r_val=10.0_dp, n_var=1, unit_str="angstrom^6*kcalmol")
2702 CALL section_add_keyword(section, keyword)
2703 CALL keyword_release(keyword)
2704
2705 CALL keyword_create(keyword, __location__, name="RCUT", &
2706 description="Defines the cutoff parameter of GAL19 potential", &
2707 usage="RCUT {real}", type_of_var=real_t, &
2708 default_r_val=cp_unit_to_cp2k(value=3.2_dp, &
2709 unit_str="angstrom"), &
2710 n_var=1, unit_str="angstrom")
2711 CALL section_add_keyword(section, keyword)
2712 CALL keyword_release(keyword)
2713 CALL keyword_create(keyword, __location__, name="Fit_express", &
2714 description="Demands the particular output needed to a least square fit", &
2715 usage="Fit_express TRUE", &
2716 default_l_val=.false., lone_keyword_l_val=.true.)
2717 CALL section_add_keyword(section, keyword)
2718 CALL keyword_release(keyword)
2719 CALL create_gcn_section(subsection)
2720 CALL section_add_subsection(section, subsection)
2721 CALL section_release(subsection)
2722
2723 END SUBROUTINE create_gal_section
2724
2725! **************************************************************************************************
2726!> \brief This section specifies the input parameters for GAL21
2727!> potential type
2728!> (??)
2729!> \param section ...
2730! **************************************************************************************************
2731 SUBROUTINE create_gal21_section(section)
2732 TYPE(section_type), POINTER :: section
2733
2734 TYPE(keyword_type), POINTER :: keyword
2735 TYPE(section_type), POINTER :: subsection
2736
2737 cpassert(.NOT. ASSOCIATED(section))
2738 CALL section_create(section, __location__, name="GAL21", &
2739 description="Implementation of the GAL21 forcefield, see associated paper", &
2740 citations=(/clabaut2021/), n_keywords=1, n_subsections=1, repeats=.true.)
2741
2742 NULLIFY (keyword, subsection)
2743
2744 CALL keyword_create(keyword, __location__, name="ATOMS", &
2745 description="Defines the atomic kind involved in the nonbond potential", &
2746 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2747 n_var=2)
2748 CALL section_add_keyword(section, keyword)
2749 CALL keyword_release(keyword)
2750
2751 CALL keyword_create(keyword, __location__, name="METALS", &
2752 description="Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2753 usage="METALS {KIND1} {KIND2} ..", type_of_var=char_t, &
2754 n_var=2)
2755 CALL section_add_keyword(section, keyword)
2756 CALL keyword_release(keyword)
2757
2758 CALL keyword_create(keyword, __location__, name="epsilon", &
2759 description="Defines the epsilon parameter of GAL21 potential", &
2760 usage="epsilon {real} {real} {real}", type_of_var=real_t, &
2761 n_var=3, unit_str="kcalmol")
2762 CALL section_add_keyword(section, keyword)
2763 CALL keyword_release(keyword)
2764
2765 CALL keyword_create(keyword, __location__, name="bxy", &
2766 description="Defines the b perpendicular parameter of GAL21 potential", &
2767 usage="bxy {real} {real}", type_of_var=real_t, &
2768 n_var=2, unit_str="angstrom^-2")
2769 CALL section_add_keyword(section, keyword)
2770 CALL keyword_release(keyword)
2771
2772 CALL keyword_create(keyword, __location__, name="bz", &
2773 description="Defines the b parallel parameter of GAL21 potential", &
2774 usage="bz {real} {real}", type_of_var=real_t, &
2775 n_var=2, unit_str="angstrom^-2")
2776 CALL section_add_keyword(section, keyword)
2777 CALL keyword_release(keyword)
2778
2779 CALL keyword_create(keyword, __location__, name="r", &
2780 description="Defines the R_0 parameters of GAL21 potential for the two METALS. "// &
2781 "This is the only parameter that is shared between the two section of "// &
2782 "the forcefield in the case of two metals (alloy). "// &
2783 "If one metal only is present, a second number should be given but won't be read", &
2784 usage="r {real} {real}", type_of_var=real_t, n_var=2, unit_str="angstrom")
2785 CALL section_add_keyword(section, keyword)
2786 CALL keyword_release(keyword)
2787
2788 CALL keyword_create(keyword, __location__, name="a1", &
2789 description="Defines the a1 parameter of GAL21 potential", &
2790 usage="a1 {real} {real} {real}", type_of_var=real_t, &
2791 n_var=3, unit_str="kcalmol")
2792 CALL section_add_keyword(section, keyword)
2793 CALL keyword_release(keyword)
2794
2795 CALL keyword_create(keyword, __location__, name="a2", &
2796 description="Defines the a2 parameter of GAL21 potential", &
2797 usage="a2 {real} {real} {real}", type_of_var=real_t, &
2798 n_var=3, unit_str="kcalmol")
2799 CALL section_add_keyword(section, keyword)
2800 CALL keyword_release(keyword)
2801
2802 CALL keyword_create(keyword, __location__, name="a3", &
2803 description="Defines the a3 parameter of GAL21 potential", &
2804 usage="a3 {real} {real} {real}", type_of_var=real_t, &
2805 n_var=3, unit_str="kcalmol")
2806 CALL section_add_keyword(section, keyword)
2807 CALL keyword_release(keyword)
2808
2809 CALL keyword_create(keyword, __location__, name="a4", &
2810 description="Defines the a4 parameter of GAL21 potential", &
2811 usage="a4 {real} {real} {real}", type_of_var=real_t, &
2812 n_var=3, unit_str="kcalmol")
2813 CALL section_add_keyword(section, keyword)
2814 CALL keyword_release(keyword)
2815
2816 CALL keyword_create(keyword, __location__, name="A", &
2817 description="Defines the A parameter of GAL21 potential", &
2818 usage="A {real} {real}", type_of_var=real_t, &
2819 n_var=2, unit_str="kcalmol")
2820 CALL section_add_keyword(section, keyword)
2821 CALL keyword_release(keyword)
2822
2823 CALL keyword_create(keyword, __location__, name="B", &
2824 description="Defines the B parameter of GAL21 potential", &
2825 usage="B {real} {real}", type_of_var=real_t, &
2826 n_var=2, unit_str="angstrom^-1")
2827 CALL section_add_keyword(section, keyword)
2828 CALL keyword_release(keyword)
2829
2830 CALL keyword_create(keyword, __location__, name="C", &
2831 description="Defines the C parameter of GAL21 potential", &
2832 usage="C {real}", type_of_var=real_t, &
2833 n_var=1, unit_str="angstrom^6*kcalmol")
2834 CALL section_add_keyword(section, keyword)
2835 CALL keyword_release(keyword)
2836
2837 CALL keyword_create(keyword, __location__, name="AH", &
2838 description="Defines the AH parameter of GAL21 potential", &
2839 usage="AH {real} {real}", type_of_var=real_t, &
2840 n_var=2, unit_str="kcalmol")
2841 CALL section_add_keyword(section, keyword)
2842 CALL keyword_release(keyword)
2843
2844 CALL keyword_create(keyword, __location__, name="BH", &
2845 description="Defines the BH parameter of GAL21 potential", &
2846 usage="BH {real} {real}", type_of_var=real_t, &
2847 n_var=2, unit_str="angstrom^-1")
2848 CALL section_add_keyword(section, keyword)
2849 CALL keyword_release(keyword)
2850
2851 CALL keyword_create(keyword, __location__, name="RCUT", &
2852 description="Defines the cutoff parameter of GAL21 potential", &
2853 usage="RCUT {real}", type_of_var=real_t, &
2854 default_r_val=cp_unit_to_cp2k(value=3.2_dp, &
2855 unit_str="angstrom"), &
2856 n_var=1, unit_str="angstrom")
2857 CALL section_add_keyword(section, keyword)
2858 CALL keyword_release(keyword)
2859
2860 CALL keyword_create(keyword, __location__, name="Fit_express", &
2861 description="Demands the particular output needed to a least square fit", &
2862 usage="Fit_express TRUE", &
2863 default_l_val=.false., lone_keyword_l_val=.true.)
2864 CALL section_add_keyword(section, keyword)
2865 CALL keyword_release(keyword)
2866
2867 CALL create_gcn_section(subsection)
2868 CALL section_add_subsection(section, subsection)
2869 CALL section_release(subsection)
2870
2871 END SUBROUTINE create_gal21_section
2872
2873! **************************************************************************************************
2874!> \brief This section specifies the input parameters for TABPOT potential type
2875!> \param section the section to create
2876!> \author teo, Alex Mironenko, Da Teng
2877! **************************************************************************************************
2878 SUBROUTINE create_tabpot_section(section)
2879
2880 TYPE(section_type), POINTER :: section
2881
2882 TYPE(keyword_type), POINTER :: keyword
2883
2884 cpassert(.NOT. ASSOCIATED(section))
2885
2886 CALL section_create(section, __location__, name="TABPOT", &
2887 description="This section specifies the input parameters for TABPOT potential type.", &
2888 n_keywords=1, n_subsections=0, repeats=.true.)
2889
2890 NULLIFY (keyword)
2891 CALL keyword_create(keyword, __location__, name="ATOMS", &
2892 description="Defines the atomic kind involved", &
2893 usage="ATOMS {KIND1} {KIND2}", type_of_var=char_t, &
2894 n_var=2)
2895 CALL section_add_keyword(section, keyword)
2896 CALL keyword_release(keyword)
2897
2898 CALL keyword_create(keyword, __location__, name="PARM_FILE_NAME", &
2899 variants=(/"PARMFILE"/), &
2900 description="Specifies the filename that contains the tabulated NONBONDED potential. "// &
2901 "File structure: the third line of the potential file contains a title. "// &
2902 "The 4th line contains: 'N', number of data points, 'R', lower bound of distance, distance cutoff. "// &
2903 "Follow "// &
2904 "in order npoints lines for index, distance [A], energy [kcal/mol], and force [kcal/mol/A]", &
2905 usage="PARM_FILE_NAME {FILENAME}", default_lc_val="")
2906 CALL section_add_keyword(section, keyword)
2907 CALL keyword_release(keyword)
2908
2909 END SUBROUTINE create_tabpot_section
2910
2911! **************************************************************************************************
2912!> \brief This section specifies the input parameters for the subsection GCN of GAL19 and GAL21
2913!> potential type
2914!> (??)
2915!> \param section ...
2916! **************************************************************************************************
2917 SUBROUTINE create_gcn_section(section)
2918 TYPE(section_type), POINTER :: section
2919
2920 TYPE(keyword_type), POINTER :: keyword
2921
2922 cpassert(.NOT. ASSOCIATED(section))
2923 CALL section_create(section, __location__, name="GCN", &
2924 description="Allow to specify the generalized coordination number of the atoms. "// &
2925 "Those numbers msust be generated by another program ", &
2926 n_keywords=1, n_subsections=0, repeats=.false.)
2927
2928 NULLIFY (keyword)
2929 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2930 description="Value of the GCN for the individual atom. Order MUST reflect"// &
2931 " the one specified for the geometry.", repeats=.true., usage="{Real}", &
2932 default_r_val=0.0_dp, type_of_var=real_t)
2933 CALL section_add_keyword(section, keyword)
2934 CALL keyword_release(keyword)
2935
2936 END SUBROUTINE create_gcn_section
2937
2938! **************************************************************************************************
2939!> \brief creates the input section for the qs part
2940!> \param print_key ...
2941!> \param label ...
2942!> \param print_level ...
2943!> \author teo
2944! **************************************************************************************************
2945 SUBROUTINE create_dipoles_section(print_key, label, print_level)
2946 TYPE(section_type), POINTER :: print_key
2947 CHARACTER(LEN=*), INTENT(IN) :: label
2948 INTEGER, INTENT(IN) :: print_level
2949
2950 TYPE(keyword_type), POINTER :: keyword
2951
2952 cpassert(.NOT. ASSOCIATED(print_key))
2953 CALL cp_print_key_section_create(print_key, __location__, name=trim(label), &
2954 description="Section controlling the calculation of "//trim(label)//"."// &
2955 " Note that the result in the periodic case might be defined modulo a certain period,"// &
2956 " determined by the lattice vectors. During MD, this can lead to jumps.", &
2957 print_level=print_level, filename="__STD_OUT__")
2958
2959 NULLIFY (keyword)
2960 CALL keyword_create(keyword, __location__, &
2961 name="PERIODIC", &
2962 description="Use Berry phase formula (PERIODIC=T) or simple operator (PERIODIC=F). "// &
2963 "The latter normally requires that the CELL is periodic NONE.", &
2964 usage="PERIODIC {logical}", &
2965 repeats=.false., &
2966 n_var=1, &
2967 default_l_val=.true., lone_keyword_l_val=.true.)
2968 CALL section_add_keyword(print_key, keyword)
2969 CALL keyword_release(keyword)
2970
2971 CALL keyword_create(keyword, __location__, name="REFERENCE", &
2972 variants=s2a("REF"), &
2973 description="Define the reference point for the calculation of the electrostatic moment.", &
2974 usage="REFERENCE COM", &
2975 enum_c_vals=s2a("COM", "COAC", "USER_DEFINED", "ZERO"), &
2976 enum_desc=s2a("Use Center of Mass", &
2977 "Use Center of Atomic Charges", &
2978 "Use User Defined Point (Keyword:REF_POINT)", &
2979 "Use Origin of Coordinate System"), &
2980 enum_i_vals=(/use_mom_ref_com, &
2983 use_mom_ref_zero/), &
2984 default_i_val=use_mom_ref_zero)
2985 CALL section_add_keyword(print_key, keyword)
2986 CALL keyword_release(keyword)
2987
2988 CALL keyword_create(keyword, __location__, name="REFERENCE_POINT", &
2989 variants=s2a("REF_POINT"), &
2990 description="Fixed reference point for the calculations of the electrostatic moment.", &
2991 usage="REFERENCE_POINT x y z", &
2992 repeats=.false., &
2993 n_var=3, default_r_vals=(/0._dp, 0._dp, 0._dp/), &
2994 type_of_var=real_t, &
2995 unit_str='bohr')
2996 CALL section_add_keyword(print_key, keyword)
2997 CALL keyword_release(keyword)
2998 END SUBROUTINE create_dipoles_section
2999
3000END 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 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 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)
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