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_nequip_section(subsection)
1183 CALL create_allegro_section(subsection)
1187 CALL create_ace_section(subsection)
1191 CALL create_deepmd_section(subsection)
1199 CALL create_ipbv_section(subsection)
1203 CALL create_bmhft_section(subsection)
1207 CALL create_bmhftd_section(subsection)
1211 CALL create_buck4r_section(subsection)
1215 CALL create_buckmorse_section(subsection)
1223 CALL create_tersoff_section(subsection)
1227 CALL create_siepmann_section(subsection)
1231 CALL create_gal_section(subsection)
1235 CALL create_gal21_section(subsection)
1243 END SUBROUTINE create_nonbonded_section
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.)
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")
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.)
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.)
1300 cpassert(.NOT.
ASSOCIATED(section))
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.)
1313 description=
"Defines the atomic kind involved in the generic potential", &
1314 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
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, &
1327 description=
"Defines the variable of the functional form.", &
1328 usage=
"VARIABLES x", type_of_var=
char_t, &
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.)
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")
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.)
1356 description=
"Defines the cutoff parameter of the generic potential", &
1358 unit_str=
"angstrom"), &
1359 unit_str=
"angstrom")
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")
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")
1384 SUBROUTINE create_eam_section(section)
1389 cpassert(.NOT.
ASSOCIATED(section))
1391 description=
"This section specifies the input parameters for EAM potential type.", &
1392 citations=[
foiles1986], n_keywords=1, n_subsections=0, repeats=.true.)
1397 description=
"Defines the atomic kind involved in the nonbond potential", &
1398 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
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=
" ")
1419 END SUBROUTINE create_eam_section
1426 SUBROUTINE create_nequip_section(section)
1431 cpassert(.NOT.
ASSOCIATED(section))
1433 description=
"This section specifies the input parameters for NEQUIP potential type "// &
1434 "based on equivariant neural networks with message passing. Starting from the NequIP 0.6.0, "// &
1435 "one can predict stress if the config.yaml file has the StressForceOutput keyword, "// &
1436 "regardless of whether the model has been trained on the stress. "// &
1437 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1438 citations=[
batzner2022], n_keywords=1, n_subsections=0, repeats=.false.)
1443 description=
"Defines the atomic kinds involved in the NEQUIP potential. "// &
1444 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1445 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1446 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1447 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1452 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
1453 variants=[
"PARMFILE"], &
1454 description=
"Specifies the filename that contains the NEQUIP model.", &
1455 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"model.pth")
1460 description=
"Units of coordinates in the NEQUIP model.pth file. "// &
1461 "The units of positions, energies and forces must be self-consistent: "// &
1462 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1463 usage=
"UNIT_COORDS angstrom", default_c_val=
"angstrom")
1468 description=
"Units of energy in the NEQUIP model.pth file. "// &
1469 "The units of positions, energies and forces must be self-consistent: "// &
1470 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1471 usage=
"UNIT_ENERGY hartree", default_c_val=
"eV")
1476 description=
"Units of the forces in the NEQUIP model.pth file. "// &
1477 "The units of positions, energies and forces must be self-consistent: "// &
1478 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1479 usage=
"UNIT_FORCES hartree/bohr", default_c_val=
"eV/Angstrom")
1484 description=
"Units of the cell vectors in the NEQUIP model.pth file. "// &
1485 "The units of positions, energies and forces must be self-consistent: "// &
1486 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1487 usage=
"UNIT_CELL angstrom", default_c_val=
"angstrom")
1491 END SUBROUTINE create_nequip_section
1498 SUBROUTINE create_allegro_section(section)
1503 cpassert(.NOT.
ASSOCIATED(section))
1505 description=
"This section specifies the input parameters for ALLEGRO potential type "// &
1506 "based on equivariant neural network potentials. Starting from the NequIP 0.6.0, "// &
1507 "one can predict stress if the config.yaml file has the StressForceOutput keyword, "// &
1508 "regardless of whether the model has been trained on the stress. "// &
1509 "Requires linking with libtorch library from <https://pytorch.org/cppdocs/installing.html>.", &
1510 citations=[
musaelian2023], n_keywords=1, n_subsections=0, repeats=.false.)
1515 description=
"Defines the atomic kinds involved in the ALLEGRO potential. "// &
1516 "Provide a list of each element, making sure that the mapping from the ATOMS list "// &
1517 "to NequIP atom types is correct. This mapping should also be consistent for the "// &
1518 "atomic coordinates as specified in the sections COORDS or TOPOLOGY.", &
1519 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1524 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
1525 variants=[
"PARMFILE"], &
1526 description=
"Specifies the filename that contains the ALLEGRO model.", &
1527 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"model.pth")
1532 description=
"Units of coordinates in the ALLEGRO model.pth file. "// &
1533 "The units of positions, energies and forces must be self-consistent: "// &
1534 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1535 usage=
"UNIT_COORDS angstrom", default_c_val=
"angstrom")
1540 description=
"Units of energy in the ALLEGRO model.pth file. "// &
1541 "The units of positions, energies and forces must be self-consistent: "// &
1542 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1543 usage=
"UNIT_ENERGY hartree", default_c_val=
"eV")
1548 description=
"Units of the forces in the ALLEGRO model.pth file. "// &
1549 "The units of positions, energies and forces must be self-consistent: "// &
1550 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1551 usage=
"UNIT_FORCES hartree/bohr", default_c_val=
"eV/Angstrom")
1556 description=
"Units of the cell vectors in the ALLEGRO model.pth file. "// &
1557 "The units of positions, energies and forces must be self-consistent: "// &
1558 "e.g. coordinates in Angstrom, energies in eV, forces in eV/Angstrom. ", &
1559 usage=
"UNIT_CELL angstrom", default_c_val=
"angstrom")
1563 END SUBROUTINE create_allegro_section
1570 SUBROUTINE create_ace_section(section)
1576 description=
"This section specifies the input parameters for Atomic Cluster Expansion type. "// &
1577 "Mainly intended for accurate representation of "// &
1578 "potential energy surfaces. "// &
1579 "Requires linking with ACE library from "// &
1580 "<a href=""https://github.com/ICAMS/lammps-user-pace"" "// &
1581 "target=""_blank"">https://github.com/ICAMS/lammps-user-pace</a> .", &
1583 n_keywords=1, n_subsections=0, repeats=.false.)
1587 description=
"Defines the atomic species. "// &
1588 "Provide a list of each element, "// &
1589 "making sure that the mapping from the ATOMS list to ACE atom types is correct.", &
1590 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1594 CALL keyword_create(keyword, __location__, name=
"POT_FILE_NAME", &
1595 variants=[
"PARMFILE"], &
1596 description=
"Specifies the filename that contains the ACE potential parameters.", &
1597 usage=
"POT_FILE_NAME {FILENAME}", default_lc_val=
"test.yaml")
1600 END SUBROUTINE create_ace_section
1607 SUBROUTINE create_deepmd_section(section)
1613 description=
"This section specifies the input parameters for Deep Potential type. "// &
1614 "Mainly intended for things like neural network to DFT "// &
1615 "to achieve correlated-wavefunction-like accuracy. "// &
1616 "Requires linking with DeePMD-kit library from "// &
1617 "<a href=""https://docs.deepmodeling.com/projects/deepmd/en/master"" "// &
1618 "target=""_blank"">https://docs.deepmodeling.com/projects/deepmd/en/master</a> .", &
1619 citations=[
wang2018,
zeng2023], n_keywords=1, n_subsections=0, repeats=.false.)
1622 description=
"Defines the atomic kinds involved in the Deep Potential. "// &
1623 "Provide a list of each element, "// &
1624 "making sure that the mapping from the ATOMS list to DeePMD atom types is correct.", &
1625 usage=
"ATOMS {KIND 1} {KIND 2} .. {KIND N}", type_of_var=
char_t, &
1629 CALL keyword_create(keyword, __location__, name=
"POT_FILE_NAME", &
1630 variants=[
"PARMFILE"], &
1631 description=
"Specifies the filename that contains the DeePMD-kit potential.", &
1632 usage=
"POT_FILE_NAME {FILENAME}", default_lc_val=
"graph.pb")
1635 CALL keyword_create(keyword, __location__, name=
"ATOMS_DEEPMD_TYPE", &
1636 description=
"Specifies the atomic TYPE for the DeePMD-kit potential. "// &
1637 "Provide a list of index, making sure that the mapping "// &
1638 "from the ATOMS list to DeePMD atom types is correct. ", &
1639 usage=
"ATOMS_DEEPMD_TYPE {TYPE INTEGER 1} {TYPE INTEGER 2} .. "// &
1640 "{TYPE INTEGER N}", type_of_var=
integer_t, &
1644 END SUBROUTINE create_deepmd_section
1656 cpassert(.NOT.
ASSOCIATED(section))
1657 CALL section_create(section, __location__, name=
"lennard-jones", &
1658 description=
"This section specifies the input parameters for LENNARD-JONES potential type. "// &
1659 "Functional form: V(r) = 4.0 * EPSILON * [(SIGMA/r)^12-(SIGMA/r)^6].", &
1660 n_keywords=1, n_subsections=0, repeats=.true.)
1665 description=
"Defines the atomic kind involved in the nonbond potential", &
1666 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1672 description=
"Defines the EPSILON parameter of the LJ potential", &
1673 usage=
"EPSILON {real}", type_of_var=
real_t, &
1674 n_var=1, unit_str=
"K_e")
1679 description=
"Defines the SIGMA parameter of the LJ potential", &
1680 usage=
"SIGMA {real}", type_of_var=
real_t, &
1681 n_var=1, unit_str=
"angstrom")
1686 description=
"Defines the cutoff parameter of the LJ potential", &
1688 unit_str=
"angstrom"), &
1689 unit_str=
"angstrom")
1694 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1695 " full range generate by the spline", usage=
"RMIN {real}", &
1696 type_of_var=
real_t, unit_str=
"angstrom")
1701 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1702 " full range generate by the spline", usage=
"RMAX {real}", &
1703 type_of_var=
real_t, unit_str=
"angstrom")
1719 cpassert(.NOT.
ASSOCIATED(section))
1721 description=
"This section specifies the input parameters for WILLIAMS potential type. "// &
1722 "Functional form: V(r) = A*EXP(-B*r) - C / r^6 .", &
1723 n_keywords=1, n_subsections=0, repeats=.true.)
1728 description=
"Defines the atomic kind involved in the nonbond potential", &
1729 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1735 description=
"Defines the A parameter of the Williams potential", &
1736 usage=
"A {real}", type_of_var=
real_t, &
1737 n_var=1, unit_str=
"K_e")
1742 description=
"Defines the B parameter of the Williams potential", &
1743 usage=
"B {real}", type_of_var=
real_t, &
1744 n_var=1, unit_str=
"angstrom^-1")
1749 description=
"Defines the C parameter of the Williams potential", &
1750 usage=
"C {real}", type_of_var=
real_t, &
1751 n_var=1, unit_str=
"K_e*angstrom^6")
1756 description=
"Defines the cutoff parameter of the Williams potential", &
1758 unit_str=
"angstrom"), &
1759 unit_str=
"angstrom")
1764 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1765 " full range generate by the spline", usage=
"RMIN {real}", &
1766 type_of_var=
real_t, unit_str=
"angstrom")
1771 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1772 " full range generate by the spline", usage=
"RMAX {real}", &
1773 type_of_var=
real_t, unit_str=
"angstrom")
1789 cpassert(.NOT.
ASSOCIATED(section))
1791 description=
"This section specifies the input parameters for GOODWIN potential type. "// &
1792 "Functional form: V(r) = EXP(M*(-(r/DC)**MC+(D/DC)**MC))*VR0*(D/r)**M.", &
1793 n_keywords=1, n_subsections=0, repeats=.true.)
1797 description=
"Defines the atomic kind involved in the nonbond potential", &
1798 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1804 description=
"Defines the VR0 parameter of the Goodwin potential", &
1805 usage=
"VR0 {real}", type_of_var=
real_t, &
1806 n_var=1, unit_str=
"K_e")
1811 description=
"Defines the D parameter of the Goodwin potential", &
1812 usage=
"D {real}", type_of_var=
real_t, &
1813 n_var=1, unit_str=
"angstrom")
1818 description=
"Defines the DC parameter of the Goodwin potential", &
1819 usage=
"DC {real}", type_of_var=
real_t, &
1820 n_var=1, unit_str=
"angstrom")
1825 description=
"Defines the M parameter of the Goodwin potential", &
1826 usage=
"M {real}", type_of_var=
integer_t, &
1832 description=
"Defines the MC parameter of the Goodwin potential", &
1833 usage=
"MC {real}", type_of_var=
integer_t, &
1839 description=
"Defines the cutoff parameter of the Goodwin potential", &
1841 unit_str=
"angstrom"), &
1842 unit_str=
"angstrom")
1847 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1848 " full range generate by the spline", usage=
"RMIN {real}", &
1849 type_of_var=
real_t, unit_str=
"angstrom")
1854 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1855 " full range generate by the spline", usage=
"RMAX {real}", &
1856 type_of_var=
real_t, unit_str=
"angstrom")
1867 SUBROUTINE create_ipbv_section(section)
1872 cpassert(.NOT.
ASSOCIATED(section))
1874 description=
"This section specifies the input parameters for IPBV potential type. "// &
1875 "Functional form: Implicit table function.", &
1876 n_keywords=1, n_subsections=0, repeats=.true.)
1881 description=
"Defines the atomic kind involved in the IPBV nonbond potential", &
1882 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1888 description=
"Defines the cutoff parameter of the IPBV potential", &
1890 unit_str=
"angstrom"), &
1891 unit_str=
"angstrom")
1896 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1897 " full range generate by the spline", usage=
"RMIN {real}", &
1898 type_of_var=
real_t, unit_str=
"angstrom")
1903 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1904 " full range generate by the spline", usage=
"RMAX {real}", &
1905 type_of_var=
real_t, unit_str=
"angstrom")
1909 END SUBROUTINE create_ipbv_section
1916 SUBROUTINE create_bmhft_section(section)
1921 cpassert(.NOT.
ASSOCIATED(section))
1923 description=
"This section specifies the input parameters for BMHFT potential type. "// &
1924 "Functional form: V(r) = A * EXP(-B*r) - C/r^6 - D/r^8. "// &
1925 "Values available inside cp2k only for the Na/Cl pair.", &
1931 description=
"Defines the atomic kind involved in the BMHFT nonbond potential", &
1932 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1938 description=
"Defines the kinds for which internally is defined the BMHFT nonbond potential"// &
1939 " at the moment only Na and Cl.", &
1940 usage=
"MAP_ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
1946 description=
"Defines the cutoff parameter of the BMHFT potential", &
1947 usage=
"RCUT {real}", default_r_val=7.8_dp, &
1948 unit_str=
"angstrom")
1953 description=
"Defines the A parameter of the Fumi-Tosi Potential", &
1954 usage=
"A {real}", type_of_var=
real_t, &
1955 n_var=1, unit_str=
"hartree")
1960 description=
"Defines the B parameter of the Fumi-Tosi Potential", &
1961 usage=
"B {real}", type_of_var=
real_t, &
1962 n_var=1, unit_str=
"angstrom^-1")
1967 description=
"Defines the C parameter of the Fumi-Tosi Potential", &
1968 usage=
"C {real}", type_of_var=
real_t, &
1969 n_var=1, unit_str=
"hartree*angstrom^6")
1974 description=
"Defines the D parameter of the Fumi-Tosi Potential", &
1975 usage=
"D {real}", type_of_var=
real_t, &
1976 n_var=1, unit_str=
"hartree*angstrom^8")
1981 description=
"Defines the lower bound of the potential. If not set the range is the"// &
1982 " full range generate by the spline", usage=
"RMIN {real}", &
1983 type_of_var=
real_t, unit_str=
"angstrom")
1988 description=
"Defines the upper bound of the potential. If not set the range is the"// &
1989 " full range generate by the spline", usage=
"RMAX {real}", &
1990 type_of_var=
real_t, unit_str=
"angstrom")
1994 END SUBROUTINE create_bmhft_section
2003 SUBROUTINE create_bmhftd_section(section)
2008 cpassert(.NOT.
ASSOCIATED(section))
2010 description=
"This section specifies the input parameters for the BMHFTD potential type. "// &
2011 "Functional form: V(r) = A*exp(-B*r) - f_6*(r)C/r^6 - f_8(r)*D/r^8 "// &
2012 "where f_order(r) = 1 - exp(-BD*r)*\sum_{k=0}^order (BD*r)^k/k! "// &
2013 "(Tang-Toennies damping function). No pre-defined parameter values are available.", &
2019 description=
"Defines the atomic kind involved in the BMHFTD nonbond potential", &
2020 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2026 description=
"Defines the kinds for which internally is defined the BMHFTD nonbond potential"// &
2027 " at the moment no species included.", &
2028 usage=
"MAP_ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2034 description=
"Defines the cutoff parameter of the BMHFTD potential", &
2035 usage=
"RCUT {real}", default_r_val=7.8_dp, &
2036 unit_str=
"angstrom")
2041 description=
"Defines the A parameter of the dispersion-damped Fumi-Tosi potential", &
2042 usage=
"A {real}", type_of_var=
real_t, &
2043 n_var=1, unit_str=
"hartree")
2048 description=
"Defines the B parameter of the dispersion-damped Fumi-Tosi potential", &
2049 usage=
"B {real}", type_of_var=
real_t, &
2050 n_var=1, unit_str=
"angstrom^-1")
2055 description=
"Defines the C parameter of the dispersion-damped Fumi-Tosi potential", &
2056 usage=
"C {real}", type_of_var=
real_t, &
2057 n_var=1, unit_str=
"hartree*angstrom^6")
2062 description=
"Defines the D parameter of the dispersion-damped Fumi-Tosi potential", &
2063 usage=
"D {real}", type_of_var=
real_t, &
2064 n_var=1, unit_str=
"hartree*angstrom^8")
2069 description=
"Defines the BD parameters of the dispersion-damped Fumi-Tosi potential. "// &
2070 "One or two parameter values are expected. If only one value is provided, then this "// &
2071 "value will be used both for the 6th and the 8th order term.", &
2072 usage=
"BD {real} {real}", type_of_var=
real_t, &
2073 n_var=-1, unit_str=
"angstrom^-1")
2078 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2079 " full range generate by the spline", usage=
"RMIN {real}", &
2080 type_of_var=
real_t, unit_str=
"angstrom")
2085 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2086 " full range generate by the spline", usage=
"RMAX {real}", &
2087 type_of_var=
real_t, unit_str=
"angstrom")
2091 END SUBROUTINE create_bmhftd_section
2098 SUBROUTINE create_buck4r_section(section)
2103 cpassert(.NOT.
ASSOCIATED(section))
2105 description=
"This section specifies the input parameters for the Buckingham 4-ranges"// &
2106 " potential type."//
newline// &
2107 "| Range | Functional Form |"//
newline// &
2108 "| ----- | --------------- |"//
newline// &
2109 "| $ r < r_1 $ | $ V(r) = A\exp(-Br) $ |"//
newline// &
2110 "| $ r_1 \leq r < r_2 $ | $ V(r) = \sum_n \operatorname{POLY1}(n)r_n $ |"//
newline// &
2111 "| $ r_2 \leq r < r_3 $ | $ V(r) = \sum_n \operatorname{POLY2}(n)r_n $ |"//
newline// &
2112 "| $ r \geq r_3 $ | $ V(r) = -C/r_6 $ |"//
newline, &
2113 n_keywords=1, n_subsections=0, repeats=.true.)
2118 description=
"Defines the atomic kind involved in the nonbond potential", &
2119 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2125 description=
"Defines the A parameter of the Buckingham potential", &
2126 usage=
"A {real}", type_of_var=
real_t, &
2127 n_var=1, unit_str=
"K_e")
2132 description=
"Defines the B parameter of the Buckingham potential", &
2133 usage=
"B {real}", type_of_var=
real_t, &
2134 n_var=1, unit_str=
"angstrom^-1")
2139 description=
"Defines the C parameter of the Buckingham potential", &
2140 usage=
"C {real}", type_of_var=
real_t, &
2141 n_var=1, unit_str=
"K_e*angstrom^6")
2146 description=
"Defines the upper bound of the first range ", &
2147 usage=
"R1 {real}", type_of_var=
real_t, &
2148 n_var=1, unit_str=
"angstrom")
2153 description=
"Defines the upper bound of the second range ", &
2154 usage=
"R2 {real}", type_of_var=
real_t, &
2155 n_var=1, unit_str=
"angstrom")
2160 description=
"Defines the upper bound of the third range ", &
2161 usage=
"R3 {real}", type_of_var=
real_t, &
2162 n_var=1, unit_str=
"angstrom")
2167 description=
"Coefficients of the polynomial used in the second range "// &
2168 "This keyword can be repeated several times.", &
2169 usage=
"POLY1 C1 C2 C3 ..", &
2170 n_var=-1, unit_str=
"K_e", type_of_var=
real_t, repeats=.true.)
2175 description=
"Coefficients of the polynomial used in the third range "// &
2176 "This keyword can be repeated several times.", &
2177 usage=
"POLY2 C1 C2 C3 ..", &
2178 n_var=-1, unit_str=
"K_e", type_of_var=
real_t, repeats=.true.)
2183 description=
"Defines the cutoff parameter of the Buckingham potential", &
2185 unit_str=
"angstrom"), &
2186 unit_str=
"angstrom")
2191 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2192 " full range generate by the spline", usage=
"RMIN {real}", &
2193 type_of_var=
real_t, unit_str=
"angstrom")
2198 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2199 " full range generate by the spline", usage=
"RMAX {real}", &
2200 type_of_var=
real_t, unit_str=
"angstrom")
2204 END SUBROUTINE create_buck4r_section
2211 SUBROUTINE create_buckmorse_section(section)
2216 cpassert(.NOT.
ASSOCIATED(section))
2218 section, __location__, name=
"BUCKMORSE", &
2219 description=
"This section specifies the input parameters for"// &
2220 " Buckingham plus Morse potential type"// &
2221 " 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)]}.", &
2222 citations=[
yamada2000], n_keywords=1, n_subsections=0, repeats=.true.)
2227 description=
"Defines the atomic kind involved in the nonbond potential", &
2228 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2234 description=
"Defines the f0 parameter of Buckingham+Morse potential", &
2235 usage=
"F0 {real}", type_of_var=
real_t, &
2236 n_var=1, unit_str=
"K_e*angstrom^-1")
2241 description=
"Defines the A1 parameter of Buckingham+Morse potential", &
2242 usage=
"A1 {real}", type_of_var=
real_t, &
2243 n_var=1, unit_str=
"angstrom")
2248 description=
"Defines the A2 parameter of Buckingham+Morse potential", &
2249 usage=
"A2 {real}", type_of_var=
real_t, &
2250 n_var=1, unit_str=
"angstrom")
2255 description=
"Defines the B1 parameter of Buckingham+Morse potential", &
2256 usage=
"B1 {real}", type_of_var=
real_t, &
2257 n_var=1, unit_str=
"angstrom")
2262 description=
"Defines the B2 parameter of Buckingham+Morse potential", &
2263 usage=
"B2 {real}", type_of_var=
real_t, &
2264 n_var=1, unit_str=
"angstrom")
2269 description=
"Defines the C parameter of Buckingham+Morse potential", &
2270 usage=
"C {real}", type_of_var=
real_t, &
2271 n_var=1, unit_str=
"K_e*angstrom^6")
2276 description=
"Defines the amplitude for the Morse part ", &
2277 usage=
"D {real}", type_of_var=
real_t, &
2278 n_var=1, unit_str=
"K_e")
2283 description=
"Defines the equilibrium distance for the Morse part ", &
2284 usage=
"R0 {real}", type_of_var=
real_t, &
2285 n_var=1, unit_str=
"angstrom")
2290 description=
"Defines the width for the Morse part ", &
2291 usage=
"Beta {real}", type_of_var=
real_t, &
2292 n_var=1, unit_str=
"angstrom^-1")
2297 description=
"Defines the cutoff parameter of the Buckingham potential", &
2299 unit_str=
"angstrom"), &
2300 unit_str=
"angstrom")
2305 description=
"Defines the lower bound of the potential. If not set the range is the"// &
2306 " full range generate by the spline", usage=
"RMIN {real}", &
2307 type_of_var=
real_t, unit_str=
"angstrom")
2312 description=
"Defines the upper bound of the potential. If not set the range is the"// &
2313 " full range generate by the spline", usage=
"RMAX {real}", &
2314 type_of_var=
real_t, unit_str=
"angstrom")
2318 END SUBROUTINE create_buckmorse_section
2325 SUBROUTINE create_tersoff_section(section)
2330 cpassert(.NOT.
ASSOCIATED(section))
2332 description=
"This section specifies the input parameters for Tersoff potential type.", &
2333 citations=[
tersoff1988], n_keywords=1, n_subsections=0, repeats=.true.)
2338 description=
"Defines the atomic kind involved in the nonbond potential", &
2339 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2345 description=
"Defines the A parameter of Tersoff potential", &
2346 usage=
"A {real}", type_of_var=
real_t, &
2349 n_var=1, unit_str=
"eV")
2354 description=
"Defines the B parameter of Tersoff potential", &
2355 usage=
"B {real}", type_of_var=
real_t, &
2358 n_var=1, unit_str=
"eV")
2363 description=
"Defines the lambda1 parameter of Tersoff potential", &
2364 usage=
"lambda1 {real}", type_of_var=
real_t, &
2366 unit_str=
"angstrom^-1"), &
2367 n_var=1, unit_str=
"angstrom^-1")
2372 description=
"Defines the lambda2 parameter of Tersoff potential", &
2373 usage=
"lambda2 {real}", type_of_var=
real_t, &
2375 unit_str=
"angstrom^-1"), &
2376 n_var=1, unit_str=
"angstrom^-1")
2381 description=
"Defines the alpha parameter of Tersoff potential", &
2382 usage=
"alpha {real}", type_of_var=
real_t, &
2383 default_r_val=0.0_dp, &
2389 description=
"Defines the beta parameter of Tersoff potential", &
2390 usage=
"beta {real}", type_of_var=
real_t, &
2391 default_r_val=1.0999e-6_dp, &
2392 n_var=1, unit_str=
"")
2397 description=
"Defines the n parameter of Tersoff potential", &
2398 usage=
"n {real}", type_of_var=
real_t, &
2399 default_r_val=7.8734e-1_dp, &
2400 n_var=1, unit_str=
"")
2405 description=
"Defines the c parameter of Tersoff potential", &
2406 usage=
"c {real}", type_of_var=
real_t, &
2407 default_r_val=1.0039e5_dp, &
2408 n_var=1, unit_str=
"")
2413 description=
"Defines the d parameter of Tersoff potential", &
2414 usage=
"d {real}", type_of_var=
real_t, &
2415 default_r_val=1.6218e1_dp, &
2416 n_var=1, unit_str=
"")
2421 description=
"Defines the h parameter of Tersoff potential", &
2422 usage=
"h {real}", type_of_var=
real_t, &
2423 default_r_val=-5.9826e-1_dp, &
2424 n_var=1, unit_str=
"")
2429 description=
"Defines the lambda3 parameter of Tersoff potential", &
2430 usage=
"lambda3 {real}", type_of_var=
real_t, &
2432 unit_str=
"angstrom^-1"), &
2433 n_var=1, unit_str=
"angstrom^-1")
2438 description=
"Defines the bigR parameter of Tersoff potential", &
2439 usage=
"bigR {real}", type_of_var=
real_t, &
2441 unit_str=
"angstrom"), &
2442 n_var=1, unit_str=
"angstrom")
2447 description=
"Defines the D parameter of Tersoff potential", &
2448 usage=
"bigD {real}", type_of_var=
real_t, &
2450 unit_str=
"angstrom"), &
2451 n_var=1, unit_str=
"angstrom")
2456 description=
"Defines the cutoff parameter of the tersoff potential."// &
2457 " This parameter is in principle already defined by the values of"// &
2458 " bigD and bigR. But it is necessary to define it when using the tersoff"// &
2459 " in conjunction with other potentials (for the same atomic pair) in order to have"// &
2460 " the same consistent definition of RCUT for all potentials.", &
2461 usage=
"RCUT {real}", type_of_var=
real_t, &
2462 n_var=1, unit_str=
"angstrom")
2466 END SUBROUTINE create_tersoff_section
2474 SUBROUTINE create_siepmann_section(section)
2479 cpassert(.NOT.
ASSOCIATED(section))
2481 description=
"This section specifies the input parameters for the"// &
2482 " Siepmann-Sprik potential type. Consists of 4 terms:"// &
2483 " T1+T2+T3+T4. The terms T1=A/rij^alpha and T2=-C/rij^6"// &
2484 " have to be given via the GENPOT section. The terms T3+T4"// &
2485 " are obtained from the SIEPMANN section. The Siepmann-Sprik"// &
2486 " potential is designed for water-metal chemisorption.", &
2487 citations=[
siepmann1995], n_keywords=1, n_subsections=0, repeats=.true.)
2492 description=
"Defines the atomic kind involved in the nonbond potential", &
2493 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2499 description=
"Defines the B parameter of Siepmann potential", &
2500 usage=
"B {real}", type_of_var=
real_t, &
2502 unit_str=
"angstrom"), &
2503 n_var=1, unit_str=
"angstrom")
2508 description=
"Defines the D parameter of Siepmann potential", &
2509 usage=
"D {real}", type_of_var=
real_t, &
2511 unit_str=
"internal_cp2k"), &
2512 n_var=1, unit_str=
"internal_cp2k")
2517 description=
"Defines the E parameter of Siepmann potential", &
2518 usage=
"E {real}", type_of_var=
real_t, &
2520 unit_str=
"internal_cp2k"), &
2521 n_var=1, unit_str=
"internal_cp2k")
2526 description=
"Defines the F parameter of Siepmann potential", &
2527 usage=
"F {real}", type_of_var=
real_t, &
2528 default_r_val=13.3_dp, n_var=1)
2533 description=
"Defines the beta parameter of Siepmann potential", &
2534 usage=
"beta {real}", type_of_var=
real_t, &
2535 default_r_val=10.0_dp, n_var=1)
2540 description=
"Defines the cutoff parameter of Siepmann potential", &
2541 usage=
"RCUT {real}", type_of_var=
real_t, &
2543 unit_str=
"angstrom"), &
2544 n_var=1, unit_str=
"angstrom")
2548 CALL keyword_create(keyword, __location__, name=
"ALLOW_OH_FORMATION", &
2549 description=
" The Siepmann-Sprik potential is actually designed for intact"// &
2550 " water molecules only. If water is treated at the QM level,"// &
2551 " water molecules can potentially dissociate, i.e."// &
2552 " some O-H bonds might be stretched leading temporarily"// &
2553 " to the formation of OH- ions. This keyword allows the"// &
2554 " the formation of such ions. The T3 term (dipole term)"// &
2555 " is then switched off for evaluating the interaction"// &
2556 " between the OH- ion and the metal.", &
2557 usage=
"ALLOW_OH_FORMATION TRUE", &
2558 default_l_val=.false., lone_keyword_l_val=.true.)
2562 CALL keyword_create(keyword, __location__, name=
"ALLOW_H3O_FORMATION", &
2563 description=
" The Siepmann-Sprik potential is designed for intact water"// &
2564 " molecules only. If water is treated at the QM level"// &
2565 " and an acid is present, hydronium ions might occur."// &
2566 " This keyword allows the formation of hydronium ions."// &
2567 " The T3 term (dipole term) is switched off for evaluating"// &
2568 " the interaction between hydronium and the metal.", &
2569 usage=
"ALLOW_H3O_FORMATION TRUE", &
2570 default_l_val=.false., lone_keyword_l_val=.true.)
2574 CALL keyword_create(keyword, __location__, name=
"ALLOW_O_FORMATION", &
2575 description=
" The Siepmann-Sprik potential is actually designed for intact"// &
2576 " water molecules only. If water is treated at the QM level,"// &
2577 " water molecules can potentially dissociate, i.e."// &
2578 " some O-H bonds might be stretched leading temporarily"// &
2579 " to the formation of O^2- ions. This keyword allows the"// &
2580 " the formation of such ions. The T3 term (dipole term)"// &
2581 " is then switched off for evaluating the interaction"// &
2582 " between the O^2- ion and the metal.", &
2583 usage=
"ALLOW_O_FORMATION .TRUE.", &
2584 default_l_val=.false., lone_keyword_l_val=.true.)
2588 END SUBROUTINE create_siepmann_section
2596 SUBROUTINE create_gal_section(section)
2602 cpassert(.NOT.
ASSOCIATED(section))
2604 description=
"Implementation of the GAL19 forcefield, see associated paper", &
2605 citations=[
clabaut2020], n_keywords=1, n_subsections=1, repeats=.true.)
2607 NULLIFY (keyword, subsection)
2610 description=
"Defines the atomic kind involved in the nonbond potential", &
2611 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2617 description=
"Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2618 usage=
"METALS {KIND1} {KIND2} ..", type_of_var=
char_t, &
2624 description=
"Defines the epsilon_a parameter of GAL19 potential", &
2625 usage=
"epsilon {real}", type_of_var=
real_t, &
2627 unit_str=
"kcalmol"), &
2628 n_var=1, unit_str=
"kcalmol")
2633 description=
"Defines the b perpendicular parameter of GAL19 potential", &
2634 usage=
"bxy {real}", type_of_var=
real_t, &
2636 unit_str=
"internal_cp2k"), &
2637 n_var=1, unit_str=
"angstrom^-2")
2642 description=
"Defines the b parallel parameter of GAL19 potential", &
2643 usage=
"bz {real}", type_of_var=
real_t, &
2645 unit_str=
"internal_cp2k"), &
2646 n_var=1, unit_str=
"angstrom^-2")
2651 description=
"Defines the R_0 parameters of GAL19 potential for the two METALS. "// &
2652 "This is the only parameter that is shared between the two section of the "// &
2653 "forcefield in the case of two metals (alloy). "// &
2654 "If one metal only is present, a second number should be given but won't be read", &
2655 usage=
"r {real} {real}", type_of_var=
real_t, n_var=2, unit_str=
"angstrom")
2660 description=
"Defines the a1 parameter of GAL19 potential", &
2661 usage=
"a1 {real}", type_of_var=
real_t, &
2662 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2667 description=
"Defines the a2 parameter of GAL19 potential", &
2668 usage=
"a2 {real}", type_of_var=
real_t, &
2669 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2674 description=
"Defines the a3 parameter of GAL19 potential", &
2675 usage=
"a3 {real}", type_of_var=
real_t, &
2676 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2681 description=
"Defines the a4 parameter of GAL19 potential", &
2682 usage=
"a4 {real}", type_of_var=
real_t, &
2683 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2688 description=
"Defines the A parameter of GAL19 potential", &
2689 usage=
"A {real}", type_of_var=
real_t, &
2690 default_r_val=10.0_dp, n_var=1, unit_str=
"kcalmol")
2695 description=
"Defines the B parameter of GAL19 potential", &
2696 usage=
"B {real}", type_of_var=
real_t, &
2697 default_r_val=10.0_dp, n_var=1, unit_str=
"angstrom^-1")
2702 description=
"Defines the C parameter of GAL19 potential", &
2703 usage=
"C {real}", type_of_var=
real_t, &
2704 default_r_val=10.0_dp, n_var=1, unit_str=
"angstrom^6*kcalmol")
2709 description=
"Defines the cutoff parameter of GAL19 potential", &
2710 usage=
"RCUT {real}", type_of_var=
real_t, &
2712 unit_str=
"angstrom"), &
2713 n_var=1, unit_str=
"angstrom")
2717 description=
"Demands the particular output needed to a least square fit", &
2718 usage=
"Fit_express TRUE", &
2719 default_l_val=.false., lone_keyword_l_val=.true.)
2722 CALL create_gcn_section(subsection)
2726 END SUBROUTINE create_gal_section
2734 SUBROUTINE create_gal21_section(section)
2740 cpassert(.NOT.
ASSOCIATED(section))
2742 description=
"Implementation of the GAL21 forcefield, see associated paper", &
2743 citations=[
clabaut2021], n_keywords=1, n_subsections=1, repeats=.true.)
2745 NULLIFY (keyword, subsection)
2748 description=
"Defines the atomic kind involved in the nonbond potential", &
2749 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2755 description=
"Defines the two atomic kinds to be considered as part of the metallic phase in the system", &
2756 usage=
"METALS {KIND1} {KIND2} ..", type_of_var=
char_t, &
2762 description=
"Defines the epsilon parameter of GAL21 potential", &
2763 usage=
"epsilon {real} {real} {real}", type_of_var=
real_t, &
2764 n_var=3, unit_str=
"kcalmol")
2769 description=
"Defines the b perpendicular parameter of GAL21 potential", &
2770 usage=
"bxy {real} {real}", type_of_var=
real_t, &
2771 n_var=2, unit_str=
"angstrom^-2")
2776 description=
"Defines the b parallel parameter of GAL21 potential", &
2777 usage=
"bz {real} {real}", type_of_var=
real_t, &
2778 n_var=2, unit_str=
"angstrom^-2")
2783 description=
"Defines the R_0 parameters of GAL21 potential for the two METALS. "// &
2784 "This is the only parameter that is shared between the two section of "// &
2785 "the forcefield in the case of two metals (alloy). "// &
2786 "If one metal only is present, a second number should be given but won't be read", &
2787 usage=
"r {real} {real}", type_of_var=
real_t, n_var=2, unit_str=
"angstrom")
2792 description=
"Defines the a1 parameter of GAL21 potential", &
2793 usage=
"a1 {real} {real} {real}", type_of_var=
real_t, &
2794 n_var=3, unit_str=
"kcalmol")
2799 description=
"Defines the a2 parameter of GAL21 potential", &
2800 usage=
"a2 {real} {real} {real}", type_of_var=
real_t, &
2801 n_var=3, unit_str=
"kcalmol")
2806 description=
"Defines the a3 parameter of GAL21 potential", &
2807 usage=
"a3 {real} {real} {real}", type_of_var=
real_t, &
2808 n_var=3, unit_str=
"kcalmol")
2813 description=
"Defines the a4 parameter of GAL21 potential", &
2814 usage=
"a4 {real} {real} {real}", type_of_var=
real_t, &
2815 n_var=3, unit_str=
"kcalmol")
2820 description=
"Defines the A parameter of GAL21 potential", &
2821 usage=
"A {real} {real}", type_of_var=
real_t, &
2822 n_var=2, unit_str=
"kcalmol")
2827 description=
"Defines the B parameter of GAL21 potential", &
2828 usage=
"B {real} {real}", type_of_var=
real_t, &
2829 n_var=2, unit_str=
"angstrom^-1")
2834 description=
"Defines the C parameter of GAL21 potential", &
2835 usage=
"C {real}", type_of_var=
real_t, &
2836 n_var=1, unit_str=
"angstrom^6*kcalmol")
2841 description=
"Defines the AH parameter of GAL21 potential", &
2842 usage=
"AH {real} {real}", type_of_var=
real_t, &
2843 n_var=2, unit_str=
"kcalmol")
2848 description=
"Defines the BH parameter of GAL21 potential", &
2849 usage=
"BH {real} {real}", type_of_var=
real_t, &
2850 n_var=2, unit_str=
"angstrom^-1")
2855 description=
"Defines the cutoff parameter of GAL21 potential", &
2856 usage=
"RCUT {real}", type_of_var=
real_t, &
2858 unit_str=
"angstrom"), &
2859 n_var=1, unit_str=
"angstrom")
2864 description=
"Demands the particular output needed to a least square fit", &
2865 usage=
"Fit_express TRUE", &
2866 default_l_val=.false., lone_keyword_l_val=.true.)
2870 CALL create_gcn_section(subsection)
2874 END SUBROUTINE create_gal21_section
2887 cpassert(.NOT.
ASSOCIATED(section))
2890 description=
"This section specifies the input parameters for TABPOT potential type.", &
2891 n_keywords=1, n_subsections=0, repeats=.true.)
2895 description=
"Defines the atomic kind involved", &
2896 usage=
"ATOMS {KIND1} {KIND2}", type_of_var=
char_t, &
2901 CALL keyword_create(keyword, __location__, name=
"PARM_FILE_NAME", &
2902 variants=[
"PARMFILE"], &
2903 description=
"Specifies the filename that contains the tabulated NONBONDED potential. "// &
2904 "File structure: the third line of the potential file contains a title. "// &
2905 "The 4th line contains: 'N', number of data points, 'R', lower bound of distance, distance cutoff. "// &
2907 "in order npoints lines for index, distance [A], energy [kcal/mol], and force [kcal/mol/A]", &
2908 usage=
"PARM_FILE_NAME {FILENAME}", default_lc_val=
"")
2920 SUBROUTINE create_gcn_section(section)
2925 cpassert(.NOT.
ASSOCIATED(section))
2927 description=
"Allow to specify the generalized coordination number of the atoms. "// &
2928 "Those numbers msust be generated by another program ", &
2929 n_keywords=1, n_subsections=0, repeats=.false.)
2932 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
2933 description=
"Value of the GCN for the individual atom. Order MUST reflect"// &
2934 " the one specified for the geometry.", repeats=.true., usage=
"{Real}", &
2935 default_r_val=0.0_dp, type_of_var=
real_t)
2939 END SUBROUTINE create_gcn_section
2950 CHARACTER(LEN=*),
INTENT(IN) :: label
2951 INTEGER,
INTENT(IN) :: print_level
2955 cpassert(.NOT.
ASSOCIATED(print_key))
2957 description=
"Section controlling the calculation of "//trim(label)//
"."// &
2958 " Note that the result in the periodic case might be defined modulo a certain period,"// &
2959 " determined by the lattice vectors. During MD, this can lead to jumps.", &
2960 print_level=print_level, filename=
"__STD_OUT__")
2965 description=
"Use Berry phase formula (PERIODIC=T) or simple operator (PERIODIC=F). "// &
2966 "The latter normally requires that the CELL is periodic NONE.", &
2967 usage=
"PERIODIC {logical}", &
2970 default_l_val=.true., lone_keyword_l_val=.true.)
2975 variants=
s2a(
"REF"), &
2976 description=
"Define the reference point for the calculation of the electrostatic moment.", &
2977 usage=
"REFERENCE COM", &
2978 enum_c_vals=
s2a(
"COM",
"COAC",
"USER_DEFINED",
"ZERO"), &
2979 enum_desc=
s2a(
"Use Center of Mass", &
2980 "Use Center of Atomic Charges", &
2981 "Use User Defined Point (Keyword:REF_POINT)", &
2982 "Use Origin of Coordinate System"), &
2991 CALL keyword_create(keyword, __location__, name=
"REFERENCE_POINT", &
2992 variants=
s2a(
"REF_POINT"), &
2993 description=
"Fixed reference point for the calculations of the electrostatic moment.", &
2994 usage=
"REFERENCE_POINT x y z", &
2996 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 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