54#include "./base/base_uses.f90"
59 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
60 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'input_cp2k_mm'
80 cpassert(.NOT.
ASSOCIATED(section))
82 description=
"This section contains all information to run a MM calculation.", &
83 n_keywords=5, n_subsections=0, repeats=.false.)
87 CALL create_forcefield_section(subsection)
103 CALL create_print_mm_section(subsection)
114 SUBROUTINE create_print_mm_section(section)
120 cpassert(.NOT.
ASSOCIATED(section))
122 description=
"Section of possible print options in MM code.", &
123 n_keywords=0, n_subsections=1, repeats=.false.)
125 NULLIFY (print_key, keyword)
128 description=
"Controls the printing of derivatives.", &
134 description=
"Controls the printing of Ewald energy components during the "// &
135 "evaluation of the electrostatics.", &
145 description=
"Activates the printing of the neighbor lists.", &
151 description=
"Activates the printing of iteration info during the self-consistent "// &
152 "calculation of a polarizable forcefield.", &
158 description=
"Activates the printing of the subcells used for the "// &
159 "generation of neighbor lists.", &
165 description=
"Controls the printing of the banner of the MM program", &
171 description=
"Controls the printing of information regarding the run.", &
177 "Controls the printing of Force Field parameter file", &
183 "Controls the printing of information in the forcefield settings", &
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.)
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.)
203 END SUBROUTINE create_print_mm_section
211 SUBROUTINE create_forcefield_section(section)
217 cpassert(.NOT.
ASSOCIATED(section))
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.)
223 NULLIFY (subsection, keyword)
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)"), &
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)
251 description=
"Scaling factor for the VDW 1-4 ", &
252 usage=
"VDW_SCALE14 1.0", default_r_val=1.0_dp)
257 description=
"Scaling factor for the electrostatics 1-4 ", &
258 usage=
"EI_SCALE14 1.0", default_r_val=0.0_dp)
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 "// &
268 usage=
"SHIFT_CUTOFF <LOGICAL>", default_l_val=.true.)
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.)
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.)
291 CALL keyword_create(keyword, __location__, name=
"IGNORE_MISSING_CRITICAL_PARAMS", &
292 description=
"Do not abort when critical force-field parameters "// &
293 "are missing. CP2K will run as if the terms containing the "// &
294 "missing parameters are zero.", &
295 usage=
"IGNORE_MISSING_CRITICAL_PARAMS .TRUE.", default_l_val=.false., &
296 lone_keyword_l_val=.true.)
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.)
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.)
317 CALL create_spline_section(subsection)
321 CALL create_nonbonded_section(subsection)
333 CALL create_charges_section(subsection)
337 CALL create_shell_section(subsection)
341 CALL create_bond_section(subsection,
"BOND")
345 CALL create_bend_section(subsection)
349 CALL create_torsion_section(subsection)
353 CALL create_improper_section(subsection)
357 CALL create_opbend_section(subsection)
361 CALL create_dipole_section(subsection)
365 CALL create_quadrupole_section(subsection)
369 END SUBROUTINE create_forcefield_section
376 SUBROUTINE create_spline_section(section)
381 cpassert(.NOT.
ASSOCIATED(section))
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.)
390 description=
"Specify the minimum value of the distance interval "// &
391 "that brackets the value of emax_spline.", &
399 description=
"Cutoff radius for nonbonded interactions. This value overrides"// &
400 " the value specified in the potential definition and is global for all potentials.", &
402 unit_str=
"angstrom"), &
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")
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")
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")
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)
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.)
445 END SUBROUTINE create_spline_section
452 SUBROUTINE create_torsion_section(section)
457 cpassert(.NOT.
ASSOCIATED(section))
459 description=
"Specifies the torsion potential of the MM system.", &
460 n_keywords=1, n_subsections=0, repeats=.true.)
464 description=
"Defines the atomic kinds involved in the tors.", &
465 usage=
"ATOMS {KIND1} {KIND2} {KIND3} {KIND4}", type_of_var=
char_t, &
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]]"), &
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")
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)
503 description=
"Defines the multiplicity of the potential.", &
504 usage=
"M {integer}", type_of_var=
integer_t, &
509 END SUBROUTINE create_torsion_section
516 SUBROUTINE create_improper_section(section)
521 cpassert(.NOT.
ASSOCIATED(section))
523 description=
"Specifies the improper torsion potential of the MM system.", &
524 n_keywords=1, n_subsections=0, repeats=.true.)
528 description=
"Defines the atomic kinds involved in the improper tors.", &
529 usage=
"ATOMS {KIND1} {KIND2} {KIND3} {KIND4}", type_of_var=
char_t, &
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"), &
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")
558 description=
"Defines the phase of the potential.", &
559 usage=
"PHI0 {real}", type_of_var=
real_t, &
560 n_var=1, unit_str=
"rad")
564 END SUBROUTINE create_improper_section
571 SUBROUTINE create_opbend_section(section)
576 cpassert(.NOT.
ASSOCIATED(section))
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.)
585 description=
"Defines the atomic kinds involved in the opbend.", &
586 usage=
"ATOMS {KIND1} {KIND2} {KIND3} {KIND4}", type_of_var=
char_t, &
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"), &
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")
615 description=
"Defines the phase of the potential.", &
616 usage=
"PHI0 {real}", type_of_var=
real_t, &
617 n_var=1, unit_str=
"rad")
621 END SUBROUTINE create_opbend_section
628 SUBROUTINE create_bend_section(section)
634 cpassert(.NOT.
ASSOCIATED(section))
636 description=
"Specifies the bend potential of the MM system.", &
637 n_keywords=11, n_subsections=1, repeats=.true.)
639 NULLIFY (keyword, subsection)
642 description=
"Defines the atomic kinds involved in the bend.", &
643 usage=
"ATOMS {KIND1} {KIND2} {KIND3}", type_of_var=
char_t, &
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", &
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)) "), &
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")
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")
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")
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")
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")
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")
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")
725 description=
"Defines the equilibrium angle.", &
726 usage=
"THETA0 {real}", type_of_var=
real_t, &
727 n_var=1, unit_str=
'rad')
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")
742 CALL create_bond_section(subsection,
"UB")
746 END SUBROUTINE create_bend_section
754 SUBROUTINE create_bond_section(section, label)
756 CHARACTER(LEN=*),
INTENT(IN) :: label
758 CHARACTER(LEN=default_string_length) :: tag
761 cpassert(.NOT.
ASSOCIATED(section))
764 IF (trim(label) ==
"UB")
THEN
765 tag =
" Urey-Bradley "
767 description=
"Specifies the Urey-Bradley potential between the external atoms"// &
768 " defining the angle", &
769 n_keywords=1, n_subsections=0, repeats=.false.)
774 description=
"Specifies the bond potential", &
775 n_keywords=1, n_subsections=0, repeats=.true.)
778 description=
"Defines the atomic kinds involved in the bond.", &
779 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
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))"), &
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")
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")
829 description=
"Defines the equilibrium distance.", &
830 usage=
"R0 {real}", type_of_var=
real_t, &
831 n_var=1, unit_str=
"bohr")
835 END SUBROUTINE create_bond_section
842 SUBROUTINE create_charges_section(section)
847 cpassert(.NOT.
ASSOCIATED(section))
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.)
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}", &
861 END SUBROUTINE create_charges_section
873 cpassert(.NOT.
ASSOCIATED(section))
875 description=
"This section specifies the charge of the MM atoms", &
876 n_keywords=1, n_subsections=0, repeats=.true.)
881 description=
"Defines the atomic kind of the charge.", &
882 usage=
"ATOM {KIND1}", type_of_var=
char_t, &
888 description=
"Defines the charge of the MM atom in electron charge unit.", &
889 usage=
"CHARGE {real}", type_of_var=
real_t, &
901 SUBROUTINE create_quadrupole_section(section)
906 cpassert(.NOT.
ASSOCIATED(section))
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.)
916 description=
"Defines the atomic kind of the SCF quadrupole.", &
917 usage=
"ATOM {KIND1}", type_of_var=
char_t, &
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')
929 END SUBROUTINE create_quadrupole_section
936 SUBROUTINE create_dipole_section(section)
942 cpassert(.NOT.
ASSOCIATED(section))
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.)
948 NULLIFY (subsection, keyword)
951 description=
"Defines the atomic kind of the SCF dipole.", &
952 usage=
"ATOM {KIND1}", type_of_var=
char_t, &
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')
964 CALL create_damping_section(subsection)
967 END SUBROUTINE create_dipole_section
974 SUBROUTINE create_damping_section(section)
979 cpassert(.NOT.
ASSOCIATED(section))
981 description=
"This section specifies optional electric field damping for the polarizable atoms. ", &
982 n_keywords=4, n_subsections=0, repeats=.true.)
987 description=
"Defines the atomic kind for this damping function.", &
988 usage=
"ATOM {KIND1}", type_of_var=
char_t, &
994 description=
"Defines the damping type.", &
995 usage=
"TYPE {string}", type_of_var=
char_t, &
996 n_var=1, default_c_val=
"TANG-TOENNIES")
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)
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')
1015 description=
"Defines the CIJ parameter for this damping.", &
1016 usage=
"CIJ {real}", type_of_var=
real_t, &
1017 n_var=1, unit_str=
'')
1021 END SUBROUTINE create_damping_section
1028 SUBROUTINE create_shell_section(section)
1033 cpassert(.NOT.
ASSOCIATED(section))
1035 description=
"This section specifies the parameters for shell-model potentials", &
1036 n_keywords=6, n_subsections=0, repeats=.true., &
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")
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)
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)
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)
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.", &
1076 usage=
"K2_SPRING {real}", &
1077 default_r_val=-1.0_dp, &
1078 unit_str=
"hartree*bohr^-2")
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.", &
1088 usage=
"K4_SPRING {real}", &
1089 default_r_val=0.0_dp, &
1090 unit_str=
"hartree*bohr^-4")
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")
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")
1113 END SUBROUTINE create_shell_section
1126 cpassert(.NOT.
ASSOCIATED(section))
1128 description=
"This section specifies the input parameters for 1-4 NON-BONDED interactions.", &
1129 n_keywords=1, n_subsections=0, repeats=.false.)
1131 NULLIFY (subsection)
1156 SUBROUTINE create_nonbonded_section(section)
1161 cpassert(.NOT.
ASSOCIATED(section))
1163 description=
"This section specifies the input parameters for NON-BONDED interactions.", &
1164 n_keywords=1, n_subsections=0, repeats=.false.)
1166 NULLIFY (subsection)
1175 CALL create_eam_section(subsection)
1179 CALL create_quip_section(subsection)
1183 CALL create_nequip_section(subsection)
1187 CALL create_allegro_section(subsection)
1191 CALL create_ace_section(subsection)
1195 CALL create_deepmd_section(subsection)
1203 CALL create_ipbv_section(subsection)
1207 CALL create_bmhft_section(subsection)
1211 CALL create_bmhftd_section(subsection)
1215 CALL create_buck4r_section(subsection)
1219 CALL create_buckmorse_section(subsection)
1227 CALL create_tersoff_section(subsection)
1231 CALL create_siepmann_section(subsection)
1235 CALL create_gal_section(subsection)
1239 CALL create_gal21_section(subsection)
1247 END SUBROUTINE create_nonbonded_section
1261 cpassert(.NOT.
ASSOCIATED(section))
1262 CALL section_create(section, __location__, name=
"neighbor_lists", &
1263 description=
"This section specifies the input parameters for the construction of"// &
1264 " neighbor lists.", &
1265 n_keywords=1, n_subsections=0, repeats=.false.)
1268 description=
"Defines the Verlet Skin for the generation of the neighbor lists", &
1269 usage=
"VERLET_SKIN {real}", default_r_val=
cp_unit_to_cp2k(
value=1.0_dp, &
1270 unit_str=
"angstrom"), &
1271 unit_str=
"angstrom")
1275 CALL keyword_create(keyword, __location__, name=
"neighbor_lists_from_scratch", &
1276 description=
"This keyword enables the building of the neighbouring list from scratch.", &
1277 usage=
"neighbor_lists_from_scratch logical", &
1278 default_l_val=.false., lone_keyword_l_val=.true.)
1283 description=
"This keyword enables the check that two atoms are never below the minimum"// &
1284 " value used to construct the splines during the construction of the neighbouring list."// &
1285 " Disabling this keyword avoids CP2K to abort in case two atoms are below the minimum"// &
1286 " value of the radius used to generate the splines.", &
1287 usage=
"GEO_CHECK", &
1288 default_l_val=.true., lone_keyword_l_val=.true.)
1304 cpassert(.NOT.
ASSOCIATED(section))
1306 description=
"This section specifies the input parameters for a generic potential type. "// &
1307 "A functional form is specified. Mathematical Operators recognized are +, -, *, /, ** "// &
1308 "or alternatively ^, whereas symbols for brackets must be (). "// &
1309 "The function parser recognizes the (single argument) Fortran 90 intrinsic functions "// &
1310 "abs, exp, log10, log, sqrt, sinh, cosh, tanh, sin, cos, tan, asin, acos, atan, erf, erfc. "// &
1311 "Parsing for intrinsic functions is not case sensitive.", &
1312 n_keywords=1, n_subsections=0, repeats=.true.)
1317 description=
"Defines the atomic kind involved in the generic potential", &
1318 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1324 description=
"Specifies the functional form in mathematical notation.", &
1325 usage=
"FUNCTION a*EXP(-b*x^2)/x+D*log10(x)", type_of_var=
lchar_t, &
1331 description=
"Defines the variable of the functional form.", &
1332 usage=
"VARIABLES x", type_of_var=
char_t, &
1338 description=
"Defines the parameters of the functional form", &
1339 usage=
"PARAMETERS a b D", type_of_var=
char_t, &
1340 n_var=-1, repeats=.true.)
1345 description=
"Defines the values of parameter of the functional form", &
1346 usage=
"VALUES ", type_of_var=
real_t, &
1347 n_var=-1, repeats=.true., unit_str=
"internal_cp2k")
1352 description=
"Optionally, allows to define valid CP2K unit strings for each parameter value. "// &
1353 "It is assumed that the corresponding parameter value is specified in this unit.", &
1354 usage=
"UNITS angstrom eV*angstrom^-1 angstrom^1 K", type_of_var=
char_t, &
1355 n_var=-1, repeats=.true.)
1360 description=
"Defines the cutoff parameter of the generic potential", &
1362 unit_str=
"angstrom"), &
1363 unit_str=
"angstrom")
1368 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1369 " full range generate by the spline", usage=
"RMIN {real}", &
1370 type_of_var=
real_t, unit_str=
"angstrom")
1375 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1376 " full range generate by the spline", usage=
"RMAX {real}", &
1377 type_of_var=
real_t, unit_str=
"angstrom")
1388 SUBROUTINE create_eam_section(section)
1393 cpassert(.NOT.
ASSOCIATED(section))
1395 description=
"This section specifies the input parameters for EAM potential type.", &
1396 citations=(/
foiles1986/), n_keywords=1, n_subsections=0, repeats=.true.)
1401 description=
"Defines the atomic kind involved in the nonbond potential", &
1402 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1407 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
1408 variants=(/
"PARMFILE"/), &
1409 description=
"Specifies the filename that contains the tabulated EAM potential. "// &
1410 "File structure: the first line of the potential file contains a title. "// &
1411 "The second line contains: atomic number, mass and lattice constant. "// &
1412 "These information are parsed but not used in CP2K. The third line contains: "// &
1413 "dr: increment of r for the tabulated values of density and phi (assuming r starts in 0) [angstrom]; "// &
1414 "drho: increment of density for the tabulated values of the embedding function (assuming rho starts "// &
1415 "in 0) [au_c]; cutoff: cutoff of the EAM potential; npoints: number of points in tabulated. Follow "// &
1416 "in order npoints lines for rho [au_c] and its derivative [au_c*angstrom^-1]; npoints lines for "// &
1417 "PHI [ev] and its derivative [ev*angstrom^-1] and npoint lines for the embedded function [ev] "// &
1418 "and its derivative [ev*au_c^-1].", &
1419 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
" ")
1423 END SUBROUTINE create_eam_section
1430 SUBROUTINE create_quip_section(section)
1435 cpassert(.NOT.
ASSOCIATED(section))
1437 description=
"This section specifies the input parameters for QUIP potential type. "// &
1438 "Mainly intended for things like GAP corrections to DFT "// &
1439 "to achieve correlated-wavefunction-like accuracy. "// &
1440 "Requires linking with quip library from <http://www.libatoms.org>.", &
1441 citations=(/
quip_ref/), n_keywords=1, n_subsections=0, repeats=.true., &
1442 deprecation_notice=
"Support for the QUIP library is slated for removal.")
1447 description=
"Defines the atomic kinds involved in the QUIP potential. "// &
1448 "For more than 2 elements, &QUIP section must be repeated until each element "// &
1449 "has been mentioned at least once. Set IGNORE_MISSING_CRITICAL_PARAMS to T "// &
1450 "in enclosing &FORCEFIELD section to avoid having to list every pair of elements separately.", &
1451 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1456 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
1457 variants=(/
"PARMFILE"/), &
1458 description=
"Specifies the filename that contains the QUIP potential.", &
1459 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"quip_params.xml")
1464 description=
"Specifies the potential initialization arguments for the QUIP potential. "// &
1465 "If blank (default) first potential defined in QUIP parameter file will be used.", &
1466 usage=
"INIT_ARGS", default_c_vals=(/
""/), &
1467 n_var=-1, type_of_var=
char_t)
1472 description=
"Specifies the potential calculation arguments for the QUIP potential.", &
1473 usage=
"CALC_ARGS", default_c_vals=(/
""/), &
1474 n_var=-1, type_of_var=
char_t)
1478 END SUBROUTINE create_quip_section
1485 SUBROUTINE create_nequip_section(section)
1490 cpassert(.NOT.
ASSOCIATED(section))
1492 description=
"This section specifies the input parameters for NEQUIP potential type "// &
1493 "based on equivariant neural networks with message passing. Starting from the NequIP 0.6.0, "// &
1494 "one can predict stress if the config.yaml file has the StressForceOutput keyword, "// &
1495 "regardless of whether the model has been trained on the stress. "// &
1496 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1497 citations=(/
batzner2022/), n_keywords=1, n_subsections=0, repeats=.false.)
1502 description=
"Defines the atomic kinds involved in the NEQUIP potential. "// &
1503 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1504 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1505 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1506 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1511 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
1512 variants=(/
"PARMFILE"/), &
1513 description=
"Specifies the filename that contains the NEQUIP model.", &
1514 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"model.pth")
1519 description=
"Units of coordinates in the NEQUIP model.pth file. "// &
1520 "The units of positions, energies and forces must be self-consistent: "// &
1521 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1522 usage=
"UNIT_COORDS angstrom", default_c_val=
"angstrom")
1527 description=
"Units of energy in the NEQUIP model.pth file. "// &
1528 "The units of positions, energies and forces must be self-consistent: "// &
1529 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1530 usage=
"UNIT_ENERGY hartree", default_c_val=
"eV")
1535 description=
"Units of the forces in the NEQUIP model.pth file. "// &
1536 "The units of positions, energies and forces must be self-consistent: "// &
1537 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1538 usage=
"UNIT_FORCES hartree/bohr", default_c_val=
"eV/Angstrom")
1543 description=
"Units of the cell vectors in the NEQUIP model.pth file. "// &
1544 "The units of positions, energies and forces must be self-consistent: "// &
1545 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1546 usage=
"UNIT_CELL angstrom", default_c_val=
"angstrom")
1550 END SUBROUTINE create_nequip_section
1557 SUBROUTINE create_allegro_section(section)
1562 cpassert(.NOT.
ASSOCIATED(section))
1564 description=
"This section specifies the input parameters for ALLEGRO potential type "// &
1565 "based on equivariant neural network potentials. Starting from the NequIP 0.6.0, "// &
1566 "one can predict stress if the config.yaml file has the StressForceOutput keyword, "// &
1567 "regardless of whether the model has been trained on the stress. "// &
1568 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1569 citations=(/
musaelian2023/), n_keywords=1, n_subsections=0, repeats=.false.)
1574 description=
"Defines the atomic kinds involved in the ALLEGRO potential. "// &
1575 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1576 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1577 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1578 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1583 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
1584 variants=(/
"PARMFILE"/), &
1585 description=
"Specifies the filename that contains the ALLEGRO model.", &
1586 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"model.pth")
1591 description=
"Units of coordinates in the ALLEGRO model.pth file. "// &
1592 "The units of positions, energies and forces must be self-consistent: "// &
1593 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1594 usage=
"UNIT_COORDS angstrom", default_c_val=
"angstrom")
1599 description=
"Units of energy in the ALLEGRO model.pth file. "// &
1600 "The units of positions, energies and forces must be self-consistent: "// &
1601 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1602 usage=
"UNIT_ENERGY hartree", default_c_val=
"eV")
1607 description=
"Units of the forces in the ALLEGRO model.pth file. "// &
1608 "The units of positions, energies and forces must be self-consistent: "// &
1609 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1610 usage=
"UNIT_FORCES hartree/bohr", default_c_val=
"eV/Angstrom")
1615 description=
"Units of the cell vectors in the ALLEGRO model.pth file. "// &
1616 "The units of positions, energies and forces must be self-consistent: "// &
1617 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1618 usage=
"UNIT_CELL angstrom", default_c_val=
"angstrom")
1622 END SUBROUTINE create_allegro_section
1629 SUBROUTINE create_ace_section(section)
1635 description=
"This section specifies the input parameters for Atomic Cluster Expansion type. "// &
1636 "Mainly intended for accurate representation of "// &
1637 "potential energy surfaces. "// &
1638 "Requires linking with ACE library from "// &
1639 "<a href=""https://github.com/ICAMS/lammps-user-pace"" "// &
1640 "target=""_blank"">https://github.com/ICAMS/lammps-user-pace</a> .", &
1642 n_keywords=1, n_subsections=0, repeats=.false.)
1646 description=
"Defines the atomic species. "// &
1647 "Provide a list of each element, "// &
1648 "making sure that the mapping from the ATOMS list to ACE atom types is correct.", &
1649 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1653 CALL keyword_create(keyword, __location__, name=
"POT_FILE_NAME", &
1654 variants=(/
"PARMFILE"/), &
1655 description=
"Specifies the filename that contains the ACE potential parameters.", &
1656 usage=
"POT_FILE_NAME {FILENAME}", default_lc_val=
"test.yaml")
1659 END SUBROUTINE create_ace_section
1666 SUBROUTINE create_deepmd_section(section)
1672 description=
"This section specifies the input parameters for Deep Potential type. "// &
1673 "Mainly intended for things like neural network to DFT "// &
1674 "to achieve correlated-wavefunction-like accuracy. "// &
1675 "Requires linking with DeePMD-kit library from "// &
1676 "<a href=""https://docs.deepmodeling.com/projects/deepmd/en/master"" "// &
1677 "target=""_blank"">https://docs.deepmodeling.com/projects/deepmd/en/master</a> .", &
1678 citations=(/
wang2018,
zeng2023/), n_keywords=1, n_subsections=0, repeats=.false.)
1681 description=
"Defines the atomic kinds involved in the Deep Potential. "// &
1682 "Provide a list of each element, "// &
1683 "making sure that the mapping from the ATOMS list to DeePMD atom types is correct.", &
1684 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1688 CALL keyword_create(keyword, __location__, name=
"POT_FILE_NAME", &
1689 variants=(/
"PARMFILE"/), &
1690 description=
"Specifies the filename that contains the DeePMD-kit potential.", &
1691 usage=
"POT_FILE_NAME {FILENAME}", default_lc_val=
"graph.pb")
1694 CALL keyword_create(keyword, __location__, name=
"ATOMS_DEEPMD_TYPE", &
1695 description=
"Specifies the atomic TYPE for the DeePMD-kit potential. "// &
1696 "Provide a list of index, making sure that the mapping "// &
1697 "from the ATOMS list to DeePMD atom types is correct. ", &
1698 usage=
"ATOMS_DEEPMD_TYPE {TYPE INTEGER 1} {TYPE INTEGER 2} .. "// &
1699 "{TYPE INTEGER N}", type_of_var=
integer_t, &
1703 END SUBROUTINE create_deepmd_section
1715 cpassert(.NOT.
ASSOCIATED(section))
1716 CALL section_create(section, __location__, name=
"lennard-jones", &
1717 description=
"This section specifies the input parameters for LENNARD-JONES potential type. "// &
1718 "Functional form: V(r) = 4.0 * EPSILON * [(SIGMA/r)^12-(SIGMA/r)^6].", &
1719 n_keywords=1, n_subsections=0, repeats=.true.)
1724 description=
"Defines the atomic kind involved in the nonbond potential", &
1725 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1731 description=
"Defines the EPSILON parameter of the LJ potential", &
1732 usage=
"EPSILON {real}", type_of_var=
real_t, &
1733 n_var=1, unit_str=
"K_e")
1738 description=
"Defines the SIGMA parameter of the LJ potential", &
1739 usage=
"SIGMA {real}", type_of_var=
real_t, &
1740 n_var=1, unit_str=
"angstrom")
1745 description=
"Defines the cutoff parameter of the LJ potential", &
1747 unit_str=
"angstrom"), &
1748 unit_str=
"angstrom")
1753 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1754 " full range generate by the spline", usage=
"RMIN {real}", &
1755 type_of_var=
real_t, unit_str=
"angstrom")
1760 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1761 " full range generate by the spline", usage=
"RMAX {real}", &
1762 type_of_var=
real_t, unit_str=
"angstrom")
1778 cpassert(.NOT.
ASSOCIATED(section))
1780 description=
"This section specifies the input parameters for WILLIAMS potential type. "// &
1781 "Functional form: V(r) = A*EXP(-B*r) - C / r^6 .", &
1782 n_keywords=1, n_subsections=0, repeats=.true.)
1787 description=
"Defines the atomic kind involved in the nonbond potential", &
1788 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1794 description=
"Defines the A parameter of the Williams potential", &
1795 usage=
"A {real}", type_of_var=
real_t, &
1796 n_var=1, unit_str=
"K_e")
1801 description=
"Defines the B parameter of the Williams potential", &
1802 usage=
"B {real}", type_of_var=
real_t, &
1803 n_var=1, unit_str=
"angstrom^-1")
1808 description=
"Defines the C parameter of the Williams potential", &
1809 usage=
"C {real}", type_of_var=
real_t, &
1810 n_var=1, unit_str=
"K_e*angstrom^6")
1815 description=
"Defines the cutoff parameter of the Williams potential", &
1817 unit_str=
"angstrom"), &
1818 unit_str=
"angstrom")
1823 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1824 " full range generate by the spline", usage=
"RMIN {real}", &
1825 type_of_var=
real_t, unit_str=
"angstrom")
1830 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1831 " full range generate by the spline", usage=
"RMAX {real}", &
1832 type_of_var=
real_t, unit_str=
"angstrom")
1848 cpassert(.NOT.
ASSOCIATED(section))
1850 description=
"This section specifies the input parameters for GOODWIN potential type. "// &
1851 "Functional form: V(r) = EXP(M*(-(r/DC)**MC+(D/DC)**MC))*VR0*(D/r)**M.", &
1852 n_keywords=1, n_subsections=0, repeats=.true.)
1856 description=
"Defines the atomic kind involved in the nonbond potential", &
1857 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1863 description=
"Defines the VR0 parameter of the Goodwin potential", &
1864 usage=
"VR0 {real}", type_of_var=
real_t, &
1865 n_var=1, unit_str=
"K_e")
1870 description=
"Defines the D parameter of the Goodwin potential", &
1871 usage=
"D {real}", type_of_var=
real_t, &
1872 n_var=1, unit_str=
"angstrom")
1877 description=
"Defines the DC parameter of the Goodwin potential", &
1878 usage=
"DC {real}", type_of_var=
real_t, &
1879 n_var=1, unit_str=
"angstrom")
1884 description=
"Defines the M parameter of the Goodwin potential", &
1885 usage=
"M {real}", type_of_var=
integer_t, &
1891 description=
"Defines the MC parameter of the Goodwin potential", &
1892 usage=
"MC {real}", type_of_var=
integer_t, &
1898 description=
"Defines the cutoff parameter of the Goodwin potential", &
1900 unit_str=
"angstrom"), &
1901 unit_str=
"angstrom")
1906 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1907 " full range generate by the spline", usage=
"RMIN {real}", &
1908 type_of_var=
real_t, unit_str=
"angstrom")
1913 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1914 " full range generate by the spline", usage=
"RMAX {real}", &
1915 type_of_var=
real_t, unit_str=
"angstrom")
1926 SUBROUTINE create_ipbv_section(section)
1931 cpassert(.NOT.
ASSOCIATED(section))
1933 description=
"This section specifies the input parameters for IPBV potential type. "// &
1934 "Functional form: Implicit table function.", &
1935 n_keywords=1, n_subsections=0, repeats=.true.)
1940 description=
"Defines the atomic kind involved in the IPBV nonbond potential", &
1941 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1947 description=
"Defines the cutoff parameter of the IPBV potential", &
1949 unit_str=
"angstrom"), &
1950 unit_str=
"angstrom")
1955 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1956 " full range generate by the spline", usage=
"RMIN {real}", &
1957 type_of_var=
real_t, unit_str=
"angstrom")
1962 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1963 " full range generate by the spline", usage=
"RMAX {real}", &
1964 type_of_var=
real_t, unit_str=
"angstrom")
1968 END SUBROUTINE create_ipbv_section
1975 SUBROUTINE create_bmhft_section(section)
1980 cpassert(.NOT.
ASSOCIATED(section))
1982 description=
"This section specifies the input parameters for BMHFT potential type. "// &
1983 "Functional form: V(r) = A * EXP(-B*r) - C/r^6 - D/r^8. "// &
1984 "Values available inside cp2k only for the Na/Cl pair.", &
1990 description=
"Defines the atomic kind involved in the BMHFT nonbond potential", &
1991 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1997 description=
"Defines the kinds for which internally is defined the BMHFT nonbond potential"// &
1998 " at the moment only Na and Cl.", &
1999 usage=
"MAP_ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2005 description=
"Defines the cutoff parameter of the BMHFT potential", &
2006 usage=
"RCUT {real}", default_r_val=7.8_dp, &
2007 unit_str=
"angstrom")
2012 description=
"Defines the A parameter of the Fumi-Tosi Potential", &
2013 usage=
"A {real}", type_of_var=
real_t, &
2014 n_var=1, unit_str=
"hartree")
2019 description=
"Defines the B parameter of the Fumi-Tosi Potential", &
2020 usage=
"B {real}", type_of_var=
real_t, &
2021 n_var=1, unit_str=
"angstrom^-1")
2026 description=
"Defines the C parameter of the Fumi-Tosi Potential", &
2027 usage=
"C {real}", type_of_var=
real_t, &
2028 n_var=1, unit_str=
"hartree*angstrom^6")
2033 description=
"Defines the D parameter of the Fumi-Tosi Potential", &
2034 usage=
"D {real}", type_of_var=
real_t, &
2035 n_var=1, unit_str=
"hartree*angstrom^8")
2040 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2041 " full range generate by the spline", usage=
"RMIN {real}", &
2042 type_of_var=
real_t, unit_str=
"angstrom")
2047 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2048 " full range generate by the spline", usage=
"RMAX {real}", &
2049 type_of_var=
real_t, unit_str=
"angstrom")
2053 END SUBROUTINE create_bmhft_section
2062 SUBROUTINE create_bmhftd_section(section)
2067 cpassert(.NOT.
ASSOCIATED(section))
2069 description=
"This section specifies the input parameters for the BMHFTD potential type. "// &
2070 "Functional form: V(r) = A*exp(-B*r) - f_6*(r)C/r^6 - f_8(r)*D/r^8 "// &
2071 "where f_order(r) = 1 - exp(-BD*r)*\sum_{k=0}^order (BD*r)^k/k! "// &
2072 "(Tang-Toennies damping function). No pre-defined parameter values are available.", &
2078 description=
"Defines the atomic kind involved in the BMHFTD nonbond potential", &
2079 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2085 description=
"Defines the kinds for which internally is defined the BMHFTD nonbond potential"// &
2086 " at the moment no species included.", &
2087 usage=
"MAP_ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2093 description=
"Defines the cutoff parameter of the BMHFTD potential", &
2094 usage=
"RCUT {real}", default_r_val=7.8_dp, &
2095 unit_str=
"angstrom")
2100 description=
"Defines the A parameter of the dispersion-damped Fumi-Tosi potential", &
2101 usage=
"A {real}", type_of_var=
real_t, &
2102 n_var=1, unit_str=
"hartree")
2107 description=
"Defines the B parameter of the dispersion-damped Fumi-Tosi potential", &
2108 usage=
"B {real}", type_of_var=
real_t, &
2109 n_var=1, unit_str=
"angstrom^-1")
2114 description=
"Defines the C parameter of the dispersion-damped Fumi-Tosi potential", &
2115 usage=
"C {real}", type_of_var=
real_t, &
2116 n_var=1, unit_str=
"hartree*angstrom^6")
2121 description=
"Defines the D parameter of the dispersion-damped Fumi-Tosi potential", &
2122 usage=
"D {real}", type_of_var=
real_t, &
2123 n_var=1, unit_str=
"hartree*angstrom^8")
2128 description=
"Defines the BD parameters of the dispersion-damped Fumi-Tosi potential. "// &
2129 "One or two parameter values are expected. If only one value is provided, then this "// &
2130 "value will be used both for the 6th and the 8th order term.", &
2131 usage=
"BD {real} {real}", type_of_var=
real_t, &
2132 n_var=-1, unit_str=
"angstrom^-1")
2137 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2138 " full range generate by the spline", usage=
"RMIN {real}", &
2139 type_of_var=
real_t, unit_str=
"angstrom")
2144 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2145 " full range generate by the spline", usage=
"RMAX {real}", &
2146 type_of_var=
real_t, unit_str=
"angstrom")
2150 END SUBROUTINE create_bmhftd_section
2157 SUBROUTINE create_buck4r_section(section)
2162 cpassert(.NOT.
ASSOCIATED(section))
2164 description=
"This section specifies the input parameters for the Buckingham 4-ranges"// &
2165 " potential type."//
newline// &
2166 "| Range | Functional Form |"//
newline// &
2167 "| ----- | --------------- |"//
newline// &
2168 "| $ r < r_1 $ | $ V(r) = A\exp(-Br) $ |"//
newline// &
2169 "| $ r_1 \leq r < r_2 $ | $ V(r) = \sum_n \operatorname{POLY1}(n)r_n $ |"//
newline// &
2170 "| $ r_2 \leq r < r_3 $ | $ V(r) = \sum_n \operatorname{POLY2}(n)r_n $ |"//
newline// &
2171 "| $ r \geq r_3 $ | $ V(r) = -C/r_6 $ |"//
newline, &
2172 n_keywords=1, n_subsections=0, repeats=.true.)
2177 description=
"Defines the atomic kind involved in the nonbond potential", &
2178 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2184 description=
"Defines the A parameter of the Buckingham potential", &
2185 usage=
"A {real}", type_of_var=
real_t, &
2186 n_var=1, unit_str=
"K_e")
2191 description=
"Defines the B parameter of the Buckingham potential", &
2192 usage=
"B {real}", type_of_var=
real_t, &
2193 n_var=1, unit_str=
"angstrom^-1")
2198 description=
"Defines the C parameter of the Buckingham potential", &
2199 usage=
"C {real}", type_of_var=
real_t, &
2200 n_var=1, unit_str=
"K_e*angstrom^6")
2205 description=
"Defines the upper bound of the first range ", &
2206 usage=
"R1 {real}", type_of_var=
real_t, &
2207 n_var=1, unit_str=
"angstrom")
2212 description=
"Defines the upper bound of the second range ", &
2213 usage=
"R2 {real}", type_of_var=
real_t, &
2214 n_var=1, unit_str=
"angstrom")
2219 description=
"Defines the upper bound of the third range ", &
2220 usage=
"R3 {real}", type_of_var=
real_t, &
2221 n_var=1, unit_str=
"angstrom")
2226 description=
"Coefficients of the polynomial used in the second range "// &
2227 "This keyword can be repeated several times.", &
2228 usage=
"POLY1 C1 C2 C3 ..", &
2229 n_var=-1, unit_str=
"K_e", type_of_var=
real_t, repeats=.true.)
2234 description=
"Coefficients of the polynomial used in the third range "// &
2235 "This keyword can be repeated several times.", &
2236 usage=
"POLY2 C1 C2 C3 ..", &
2237 n_var=-1, unit_str=
"K_e", type_of_var=
real_t, repeats=.true.)
2242 description=
"Defines the cutoff parameter of the Buckingham potential", &
2244 unit_str=
"angstrom"), &
2245 unit_str=
"angstrom")
2250 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2251 " full range generate by the spline", usage=
"RMIN {real}", &
2252 type_of_var=
real_t, unit_str=
"angstrom")
2257 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2258 " full range generate by the spline", usage=
"RMAX {real}", &
2259 type_of_var=
real_t, unit_str=
"angstrom")
2263 END SUBROUTINE create_buck4r_section
2270 SUBROUTINE create_buckmorse_section(section)
2275 cpassert(.NOT.
ASSOCIATED(section))
2277 section, __location__, name=
"BUCKMORSE", &
2278 description=
"This section specifies the input parameters for"// &
2279 " Buckingham plus Morse potential type"// &
2280 " Functional Form: V(r) = F0*(B1+B2)*EXP([A1+A2-r]/[B1+B2])-C/r^6+D*{EXP[-2*beta*(r-R0)]-2*EXP[-beta*(r-R0)]}.", &
2281 citations=(/
yamada2000/), n_keywords=1, n_subsections=0, repeats=.true.)
2286 description=
"Defines the atomic kind involved in the nonbond potential", &
2287 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2293 description=
"Defines the f0 parameter of Buckingham+Morse potential", &
2294 usage=
"F0 {real}", type_of_var=
real_t, &
2295 n_var=1, unit_str=
"K_e*angstrom^-1")
2300 description=
"Defines the A1 parameter of Buckingham+Morse potential", &
2301 usage=
"A1 {real}", type_of_var=
real_t, &
2302 n_var=1, unit_str=
"angstrom")
2307 description=
"Defines the A2 parameter of Buckingham+Morse potential", &
2308 usage=
"A2 {real}", type_of_var=
real_t, &
2309 n_var=1, unit_str=
"angstrom")
2314 description=
"Defines the B1 parameter of Buckingham+Morse potential", &
2315 usage=
"B1 {real}", type_of_var=
real_t, &
2316 n_var=1, unit_str=
"angstrom")
2321 description=
"Defines the B2 parameter of Buckingham+Morse potential", &
2322 usage=
"B2 {real}", type_of_var=
real_t, &
2323 n_var=1, unit_str=
"angstrom")
2328 description=
"Defines the C parameter of Buckingham+Morse potential", &
2329 usage=
"C {real}", type_of_var=
real_t, &
2330 n_var=1, unit_str=
"K_e*angstrom^6")
2335 description=
"Defines the amplitude for the Morse part ", &
2336 usage=
"D {real}", type_of_var=
real_t, &
2337 n_var=1, unit_str=
"K_e")
2342 description=
"Defines the equilibrium distance for the Morse part ", &
2343 usage=
"R0 {real}", type_of_var=
real_t, &
2344 n_var=1, unit_str=
"angstrom")
2349 description=
"Defines the width for the Morse part ", &
2350 usage=
"Beta {real}", type_of_var=
real_t, &
2351 n_var=1, unit_str=
"angstrom^-1")
2356 description=
"Defines the cutoff parameter of the Buckingham potential", &
2358 unit_str=
"angstrom"), &
2359 unit_str=
"angstrom")
2364 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2365 " full range generate by the spline", usage=
"RMIN {real}", &
2366 type_of_var=
real_t, unit_str=
"angstrom")
2371 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2372 " full range generate by the spline", usage=
"RMAX {real}", &
2373 type_of_var=
real_t, unit_str=
"angstrom")
2377 END SUBROUTINE create_buckmorse_section
2384 SUBROUTINE create_tersoff_section(section)
2389 cpassert(.NOT.
ASSOCIATED(section))
2391 description=
"This section specifies the input parameters for Tersoff potential type.", &
2392 citations=(/
tersoff1988/), n_keywords=1, n_subsections=0, repeats=.true.)
2397 description=
"Defines the atomic kind involved in the nonbond potential", &
2398 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2404 description=
"Defines the A parameter of Tersoff potential", &
2405 usage=
"A {real}", type_of_var=
real_t, &
2408 n_var=1, unit_str=
"eV")
2413 description=
"Defines the B parameter of Tersoff potential", &
2414 usage=
"B {real}", type_of_var=
real_t, &
2417 n_var=1, unit_str=
"eV")
2422 description=
"Defines the lambda1 parameter of Tersoff potential", &
2423 usage=
"lambda1 {real}", type_of_var=
real_t, &
2425 unit_str=
"angstrom^-1"), &
2426 n_var=1, unit_str=
"angstrom^-1")
2431 description=
"Defines the lambda2 parameter of Tersoff potential", &
2432 usage=
"lambda2 {real}", type_of_var=
real_t, &
2434 unit_str=
"angstrom^-1"), &
2435 n_var=1, unit_str=
"angstrom^-1")
2440 description=
"Defines the alpha parameter of Tersoff potential", &
2441 usage=
"alpha {real}", type_of_var=
real_t, &
2442 default_r_val=0.0_dp, &
2448 description=
"Defines the beta parameter of Tersoff potential", &
2449 usage=
"beta {real}", type_of_var=
real_t, &
2450 default_r_val=1.0999e-6_dp, &
2451 n_var=1, unit_str=
"")
2456 description=
"Defines the n parameter of Tersoff potential", &
2457 usage=
"n {real}", type_of_var=
real_t, &
2458 default_r_val=7.8734e-1_dp, &
2459 n_var=1, unit_str=
"")
2464 description=
"Defines the c parameter of Tersoff potential", &
2465 usage=
"c {real}", type_of_var=
real_t, &
2466 default_r_val=1.0039e5_dp, &
2467 n_var=1, unit_str=
"")
2472 description=
"Defines the d parameter of Tersoff potential", &
2473 usage=
"d {real}", type_of_var=
real_t, &
2474 default_r_val=1.6218e1_dp, &
2475 n_var=1, unit_str=
"")
2480 description=
"Defines the h parameter of Tersoff potential", &
2481 usage=
"h {real}", type_of_var=
real_t, &
2482 default_r_val=-5.9826e-1_dp, &
2483 n_var=1, unit_str=
"")
2488 description=
"Defines the lambda3 parameter of Tersoff potential", &
2489 usage=
"lambda3 {real}", type_of_var=
real_t, &
2491 unit_str=
"angstrom^-1"), &
2492 n_var=1, unit_str=
"angstrom^-1")
2497 description=
"Defines the bigR parameter of Tersoff potential", &
2498 usage=
"bigR {real}", type_of_var=
real_t, &
2500 unit_str=
"angstrom"), &
2501 n_var=1, unit_str=
"angstrom")
2506 description=
"Defines the D parameter of Tersoff potential", &
2507 usage=
"bigD {real}", type_of_var=
real_t, &
2509 unit_str=
"angstrom"), &
2510 n_var=1, unit_str=
"angstrom")
2515 description=
"Defines the cutoff parameter of the tersoff potential."// &
2516 " This parameter is in principle already defined by the values of"// &
2517 " bigD and bigR. But it is necessary to define it when using the tersoff"// &
2518 " in conjunction with other potentials (for the same atomic pair) in order to have"// &
2519 " the same consistent definition of RCUT for all potentials.", &
2520 usage=
"RCUT {real}", type_of_var=
real_t, &
2521 n_var=1, unit_str=
"angstrom")
2525 END SUBROUTINE create_tersoff_section
2533 SUBROUTINE create_siepmann_section(section)
2538 cpassert(.NOT.
ASSOCIATED(section))
2540 description=
"This section specifies the input parameters for the"// &
2541 " Siepmann-Sprik potential type. Consists of 4 terms:"// &
2542 " T1+T2+T3+T4. The terms T1=A/rij^alpha and T2=-C/rij^6"// &
2543 " have to be given via the GENPOT section. The terms T3+T4"// &
2544 " are obtained from the SIEPMANN section. The Siepmann-Sprik"// &
2545 " potential is designed for water-metal chemisorption.", &
2546 citations=(/
siepmann1995/), n_keywords=1, n_subsections=0, repeats=.true.)
2551 description=
"Defines the atomic kind involved in the nonbond potential", &
2552 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2558 description=
"Defines the B parameter of Siepmann potential", &
2559 usage=
"B {real}", type_of_var=
real_t, &
2561 unit_str=
"angstrom"), &
2562 n_var=1, unit_str=
"angstrom")
2567 description=
"Defines the D parameter of Siepmann potential", &
2568 usage=
"D {real}", type_of_var=
real_t, &
2570 unit_str=
"internal_cp2k"), &
2571 n_var=1, unit_str=
"internal_cp2k")
2576 description=
"Defines the E parameter of Siepmann potential", &
2577 usage=
"E {real}", type_of_var=
real_t, &
2579 unit_str=
"internal_cp2k"), &
2580 n_var=1, unit_str=
"internal_cp2k")
2585 description=
"Defines the F parameter of Siepmann potential", &
2586 usage=
"F {real}", type_of_var=
real_t, &
2587 default_r_val=13.3_dp, n_var=1)
2592 description=
"Defines the beta parameter of Siepmann potential", &
2593 usage=
"beta {real}", type_of_var=
real_t, &
2594 default_r_val=10.0_dp, n_var=1)
2599 description=
"Defines the cutoff parameter of Siepmann potential", &
2600 usage=
"RCUT {real}", type_of_var=
real_t, &
2602 unit_str=
"angstrom"), &
2603 n_var=1, unit_str=
"angstrom")
2607 CALL keyword_create(keyword, __location__, name=
"ALLOW_OH_FORMATION", &
2608 description=
" The Siepmann-Sprik potential is actually designed for intact"// &
2609 " water molecules only. If water is treated at the QM level,"// &
2610 " water molecules can potentially dissociate, i.e."// &
2611 " some O-H bonds might be stretched leading temporarily"// &
2612 " to the formation of OH- ions. This keyword allows the"// &
2613 " the formation of such ions. The T3 term (dipole term)"// &
2614 " is then switched off for evaluating the interaction"// &
2615 " between the OH- ion and the metal.", &
2616 usage=
"ALLOW_OH_FORMATION TRUE", &
2617 default_l_val=.false., lone_keyword_l_val=.true.)
2621 CALL keyword_create(keyword, __location__, name=
"ALLOW_H3O_FORMATION", &
2622 description=
" The Siepmann-Sprik potential is designed for intact water"// &
2623 " molecules only. If water is treated at the QM level"// &
2624 " and an acid is present, hydronium ions might occur."// &
2625 " This keyword allows the formation of hydronium ions."// &
2626 " The T3 term (dipole term) is switched off for evaluating"// &
2627 " the interaction between hydronium and the metal.", &
2628 usage=
"ALLOW_H3O_FORMATION TRUE", &
2629 default_l_val=.false., lone_keyword_l_val=.true.)
2633 CALL keyword_create(keyword, __location__, name=
"ALLOW_O_FORMATION", &
2634 description=
" The Siepmann-Sprik potential is actually designed for intact"// &
2635 " water molecules only. If water is treated at the QM level,"// &
2636 " water molecules can potentially dissociate, i.e."// &
2637 " some O-H bonds might be stretched leading temporarily"// &
2638 " to the formation of O^2- ions. This keyword allows the"// &
2639 " the formation of such ions. The T3 term (dipole term)"// &
2640 " is then switched off for evaluating the interaction"// &
2641 " between the O^2- ion and the metal.", &
2642 usage=
"ALLOW_O_FORMATION .TRUE.", &
2643 default_l_val=.false., lone_keyword_l_val=.true.)
2647 END SUBROUTINE create_siepmann_section
2655 SUBROUTINE create_gal_section(section)
2661 cpassert(.NOT.
ASSOCIATED(section))
2663 description=
"Implementation of the GAL19 forcefield, see associated paper", &
2664 citations=(/
clabaut2020/), n_keywords=1, n_subsections=1, repeats=.true.)
2666 NULLIFY (keyword, subsection)
2669 description=
"Defines the atomic kind involved in the nonbond potential", &
2670 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2676 description=
"Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2677 usage=
"METALS {KIND1} {KIND2} ..", type_of_var=
char_t, &
2683 description=
"Defines the epsilon_a parameter of GAL19 potential", &
2684 usage=
"epsilon {real}", type_of_var=
real_t, &
2686 unit_str=
"kcalmol"), &
2687 n_var=1, unit_str=
"kcalmol")
2692 description=
"Defines the b perpendicular parameter of GAL19 potential", &
2693 usage=
"bxy {real}", type_of_var=
real_t, &
2695 unit_str=
"internal_cp2k"), &
2696 n_var=1, unit_str=
"angstrom^-2")
2701 description=
"Defines the b parallel parameter of GAL19 potential", &
2702 usage=
"bz {real}", type_of_var=
real_t, &
2704 unit_str=
"internal_cp2k"), &
2705 n_var=1, unit_str=
"angstrom^-2")
2710 description=
"Defines the R_0 parameters of GAL19 potential for the two METALS. "// &
2711 "This is the only parameter that is shared between the two section of the "// &
2712 "forcefield in the case of two metals (alloy). "// &
2713 "If one metal only is present, a second number should be given but won't be read", &
2714 usage=
"r {real} {real}", type_of_var=
real_t, n_var=2, unit_str=
"angstrom")
2719 description=
"Defines the a1 parameter of GAL19 potential", &
2720 usage=
"a1 {real}", type_of_var=
real_t, &
2721 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2726 description=
"Defines the a2 parameter of GAL19 potential", &
2727 usage=
"a2 {real}", type_of_var=
real_t, &
2728 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2733 description=
"Defines the a3 parameter of GAL19 potential", &
2734 usage=
"a3 {real}", type_of_var=
real_t, &
2735 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2740 description=
"Defines the a4 parameter of GAL19 potential", &
2741 usage=
"a4 {real}", type_of_var=
real_t, &
2742 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2747 description=
"Defines the A parameter of GAL19 potential", &
2748 usage=
"A {real}", type_of_var=
real_t, &
2749 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2754 description=
"Defines the B parameter of GAL19 potential", &
2755 usage=
"B {real}", type_of_var=
real_t, &
2756 default_r_val=10.0_dp, n_var=1, unit_str=
"angstrom^-1")
2761 description=
"Defines the C parameter of GAL19 potential", &
2762 usage=
"C {real}", type_of_var=
real_t, &
2763 default_r_val=10.0_dp, n_var=1, unit_str=
"angstrom^6*kcalmol")
2768 description=
"Defines the cutoff parameter of GAL19 potential", &
2769 usage=
"RCUT {real}", type_of_var=
real_t, &
2771 unit_str=
"angstrom"), &
2772 n_var=1, unit_str=
"angstrom")
2776 description=
"Demands the particular output needed to a least square fit", &
2777 usage=
"Fit_express TRUE", &
2778 default_l_val=.false., lone_keyword_l_val=.true.)
2781 CALL create_gcn_section(subsection)
2785 END SUBROUTINE create_gal_section
2793 SUBROUTINE create_gal21_section(section)
2799 cpassert(.NOT.
ASSOCIATED(section))
2801 description=
"Implementation of the GAL21 forcefield, see associated paper", &
2802 citations=(/
clabaut2021/), n_keywords=1, n_subsections=1, repeats=.true.)
2804 NULLIFY (keyword, subsection)
2807 description=
"Defines the atomic kind involved in the nonbond potential", &
2808 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2814 description=
"Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2815 usage=
"METALS {KIND1} {KIND2} ..", type_of_var=
char_t, &
2821 description=
"Defines the epsilon parameter of GAL21 potential", &
2822 usage=
"epsilon {real} {real} {real}", type_of_var=
real_t, &
2823 n_var=3, unit_str=
"kcalmol")
2828 description=
"Defines the b perpendicular parameter of GAL21 potential", &
2829 usage=
"bxy {real} {real}", type_of_var=
real_t, &
2830 n_var=2, unit_str=
"angstrom^-2")
2835 description=
"Defines the b parallel parameter of GAL21 potential", &
2836 usage=
"bz {real} {real}", type_of_var=
real_t, &
2837 n_var=2, unit_str=
"angstrom^-2")
2842 description=
"Defines the R_0 parameters of GAL21 potential for the two METALS. "// &
2843 "This is the only parameter that is shared between the two section of "// &
2844 "the forcefield in the case of two metals (alloy). "// &
2845 "If one metal only is present, a second number should be given but won't be read", &
2846 usage=
"r {real} {real}", type_of_var=
real_t, n_var=2, unit_str=
"angstrom")
2851 description=
"Defines the a1 parameter of GAL21 potential", &
2852 usage=
"a1 {real} {real} {real}", type_of_var=
real_t, &
2853 n_var=3, unit_str=
"kcalmol")
2858 description=
"Defines the a2 parameter of GAL21 potential", &
2859 usage=
"a2 {real} {real} {real}", type_of_var=
real_t, &
2860 n_var=3, unit_str=
"kcalmol")
2865 description=
"Defines the a3 parameter of GAL21 potential", &
2866 usage=
"a3 {real} {real} {real}", type_of_var=
real_t, &
2867 n_var=3, unit_str=
"kcalmol")
2872 description=
"Defines the a4 parameter of GAL21 potential", &
2873 usage=
"a4 {real} {real} {real}", type_of_var=
real_t, &
2874 n_var=3, unit_str=
"kcalmol")
2879 description=
"Defines the A parameter of GAL21 potential", &
2880 usage=
"A {real} {real}", type_of_var=
real_t, &
2881 n_var=2, unit_str=
"kcalmol")
2886 description=
"Defines the B parameter of GAL21 potential", &
2887 usage=
"B {real} {real}", type_of_var=
real_t, &
2888 n_var=2, unit_str=
"angstrom^-1")
2893 description=
"Defines the C parameter of GAL21 potential", &
2894 usage=
"C {real}", type_of_var=
real_t, &
2895 n_var=1, unit_str=
"angstrom^6*kcalmol")
2900 description=
"Defines the AH parameter of GAL21 potential", &
2901 usage=
"AH {real} {real}", type_of_var=
real_t, &
2902 n_var=2, unit_str=
"kcalmol")
2907 description=
"Defines the BH parameter of GAL21 potential", &
2908 usage=
"BH {real} {real}", type_of_var=
real_t, &
2909 n_var=2, unit_str=
"angstrom^-1")
2914 description=
"Defines the cutoff parameter of GAL21 potential", &
2915 usage=
"RCUT {real}", type_of_var=
real_t, &
2917 unit_str=
"angstrom"), &
2918 n_var=1, unit_str=
"angstrom")
2923 description=
"Demands the particular output needed to a least square fit", &
2924 usage=
"Fit_express TRUE", &
2925 default_l_val=.false., lone_keyword_l_val=.true.)
2929 CALL create_gcn_section(subsection)
2933 END SUBROUTINE create_gal21_section
2946 cpassert(.NOT.
ASSOCIATED(section))
2949 description=
"This section specifies the input parameters for TABPOT potential type.", &
2950 n_keywords=1, n_subsections=0, repeats=.true.)
2954 description=
"Defines the atomic kind involved", &
2955 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2960 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
2961 variants=(/
"PARMFILE"/), &
2962 description=
"Specifies the filename that contains the tabulated NONBONDED potential. "// &
2963 "File structure: the third line of the potential file contains a title. "// &
2964 "The 4th line contains: 'N', number of data points, 'R', lower bound of distance, distance cutoff. "// &
2966 "in order npoints lines for index, distance [A], energy [kcal/mol], and force [kcal/mol/A]", &
2967 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"")
2979 SUBROUTINE create_gcn_section(section)
2984 cpassert(.NOT.
ASSOCIATED(section))
2986 description=
"Allow to specify the generalized coordination number of the atoms. "// &
2987 "Those numbers msust be generated by another program ", &
2988 n_keywords=1, n_subsections=0, repeats=.false.)
2991 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
2992 description=
"Value of the GCN for the individual atom. Order MUST reflect"// &
2993 " the one specified for the geometry.", repeats=.true., usage=
"{Real}", &
2994 default_r_val=0.0_dp, type_of_var=
real_t)
2998 END SUBROUTINE create_gcn_section
3009 CHARACTER(LEN=*),
INTENT(IN) :: label
3010 INTEGER,
INTENT(IN) :: print_level
3014 cpassert(.NOT.
ASSOCIATED(print_key))
3016 description=
"Section controlling the calculation of "//trim(label)//
"."// &
3017 " Note that the result in the periodic case might be defined modulo a certain period,"// &
3018 " determined by the lattice vectors. During MD, this can lead to jumps.", &
3019 print_level=print_level, filename=
"__STD_OUT__")
3024 description=
"Use Berry phase formula (PERIODIC=T) or simple operator (PERIODIC=F). "// &
3025 "The latter normally requires that the CELL is periodic NONE.", &
3026 usage=
"PERIODIC {logical}", &
3029 default_l_val=.true., lone_keyword_l_val=.true.)
3034 variants=
s2a(
"REF"), &
3035 description=
"Define the reference point for the calculation of the electrostatic moment.", &
3036 usage=
"REFERENCE COM", &
3037 enum_c_vals=
s2a(
"COM",
"COAC",
"USER_DEFINED",
"ZERO"), &
3038 enum_desc=
s2a(
"Use Center of Mass", &
3039 "Use Center of Atomic Charges", &
3040 "Use User Defined Point (Keyword:REF_POINT)", &
3041 "Use Origin of Coordinate System"), &
3050 CALL keyword_create(keyword, __location__, name=
"REFERENCE_POINT", &
3051 variants=
s2a(
"REF_POINT"), &
3052 description=
"Fixed reference point for the calculations of the electrostatic moment.", &
3053 usage=
"REFERENCE_POINT x y z", &
3055 n_var=3, default_r_vals=(/0._dp, 0._dp, 0._dp/), &
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public tosi1964b
integer, save, public drautz2019
integer, save, public lysogorskiy2021
integer, save, public tersoff1988
integer, save, public quip_ref
integer, save, public dick1958
integer, save, public foiles1986
integer, save, public devynck2012
integer, save, public tosi1964a
integer, save, public bochkarev2024
integer, save, public siepmann1995
integer, save, public zeng2023
integer, save, public yamada2000
integer, save, public batzner2022
integer, save, public mitchell1993
integer, save, public musaelian2023
integer, save, public clabaut2021
integer, save, public wang2018
integer, save, public clabaut2020
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public silent_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
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
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
Utilities for string manipulations.
character(len=1), parameter, public newline