42#include "./base/base_uses.f90"
47 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .false.
48 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'input_cp2k_colvar'
64 LOGICAL,
OPTIONAL :: skip_recursive_colvar
70 IF (
PRESENT(skip_recursive_colvar)) skip = skip_recursive_colvar
71 cpassert(.NOT.
ASSOCIATED(section))
73 description=
"This section specifies the nature of the collective variables.", &
74 n_keywords=1, n_subsections=1, repeats=.true.)
75 NULLIFY (subsection, print_key)
77 CALL create_colvar_var_section(subsection=subsection, &
78 section=section, skip_recursive_colvar=skip)
81 description=
"Controls the printing of the colvar specifications", &
82 n_keywords=0, n_subsections=1, repeats=.true.)
85 description=
"Controls the printing of basic information during colvar setup.", &
92 CALL create_clv_info_section(subsection)
105 SUBROUTINE create_clv_info_section(section)
110 cpassert(.NOT.
ASSOCIATED(section))
112 CALL section_create(section, __location__, name=
"COLVAR_FUNC_INFO", &
113 description=
"Specify further data possibly used by colvars, depending "// &
114 "on the starting geometry, for computing the functions value.", &
115 n_subsections=0, repeats=.false.)
117 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
118 description=
"Colvar function data."// &
119 " The order is an internal order. So if you decide to edit/modify/add these values by hand"// &
120 " you should know very well what you are doing.!", repeats=.true., &
121 usage=
"{Real} ...", type_of_var=
real_t, n_var=-1)
125 END SUBROUTINE create_clv_info_section
134 RECURSIVE SUBROUTINE create_colvar_var_section(subsection, section, skip_recursive_colvar)
136 LOGICAL,
INTENT(IN) :: skip_recursive_colvar
138 cpassert(.NOT.
ASSOCIATED(subsection))
139 cpassert(
ASSOCIATED(section))
141 CALL create_colvar_dist_section(subsection)
145 CALL create_colvar_angle_section(subsection)
149 CALL create_colvar_torsion_section(subsection)
153 CALL create_colvar_coord_section(subsection)
157 CALL create_colvar_pop_section(subsection)
161 CALL create_colvar_gyr_section(subsection)
165 CALL create_colvar_d_pl_section(subsection)
169 CALL create_colvar_a_pl_section(subsection)
173 CALL create_colvar_rot_section(subsection)
177 CALL create_colvar_dfunct_section(subsection)
181 CALL create_colvar_qparm_section(subsection)
185 CALL create_colvar_hydronium_shell_section(subsection)
189 CALL create_colvar_hydronium_dist_section(subsection)
193 CALL create_colvar_acid_hyd_dist_section(subsection)
197 CALL create_colvar_acid_hyd_shell_section(subsection)
201 CALL create_colvar_rmsd_section(subsection)
213 CALL create_colvar_u_section(subsection)
217 CALL create_colvar_wc_section(subsection)
221 CALL create_colvar_hbp_section(subsection)
225 CALL create_colvar_ring_puckering_section(subsection)
229 CALL create_colvar_cond_dist_section(subsection)
233 IF (.NOT. skip_recursive_colvar)
THEN
234 CALL create_colvar_rpath_section(subsection)
238 CALL create_colvar_dpath_section(subsection)
242 CALL create_colvar_comb_section(subsection)
247 END SUBROUTINE create_colvar_var_section
254 SUBROUTINE create_colvar_coord_section(section)
260 cpassert(.NOT.
ASSOCIATED(section))
262 description=
"Section to define the coordination number as a collective variable.", &
263 n_keywords=1, n_subsections=0, repeats=.false.)
265 NULLIFY (subsection, keyword)
268 variants=(/
"POINTS_FROM"/), &
269 description=
"Specify indexes of atoms/points building the coordination variable. ", &
270 usage=
"ATOMS_FROM {integer} {integer} ..", repeats=.true., &
276 variants=(/
"POINTS_TO"/), &
277 description=
"Specify indexes of atoms/points building the coordination variable. ", &
278 usage=
"ATOMS_TO {integer} {integer} ..", repeats=.true., &
284 variants=(/
"POINTS_TO_B"/), &
285 description=
"For the CV given by the multiplication of two coorination numbers,"// &
286 " here specify indexes of the third set of atoms/points. ", &
287 usage=
"ATOMS_TO_B {integer} {integer} ..", repeats=.true., &
293 description=
"Specify alternatively kinds of atoms building the coordination variable.", &
294 usage=
"KINDS_FROM {CHAR} {CHAR} ..", repeats=.true., &
295 n_var=-1, type_of_var=
char_t)
300 description=
"Specify alternatively kinds of atoms building the coordination variable.", &
301 usage=
"KINDS_TO {CHAR} {CHAR} ..", repeats=.true., &
302 n_var=-1, type_of_var=
char_t)
307 description=
"For the CV given by the multiplication of two coorination numbers,"// &
308 " here specify alternatively kinds of atoms building the coordination variable.", &
309 usage=
"KINDS_TO_B {CHAR} {CHAR} ..", repeats=.true., &
310 n_var=-1, type_of_var=
char_t)
315 CALL create_point_section(subsection)
320 variants=(/
"R_0"/), &
321 description=
"Specify the R0 parameter in the coordination function.", &
322 usage=
"R0 {real}", default_r_val=3.0_dp, &
323 unit_str=
"bohr", n_var=1)
328 variants=(/
"EXPON_NUMERATOR"/), &
329 description=
"Sets the value of the numerator of the exponential factor"// &
330 " in the coordination FUNCTION.", &
331 usage=
"NN {integer}", default_i_val=6, &
337 variants=(/
"EXPON_DENOMINATOR"/), &
338 description=
"Sets the value of the denominator of the exponential factor"// &
339 " in the coordination FUNCTION.", &
340 usage=
"ND {integer}", default_i_val=12, &
346 variants=(/
"R_0_B"/), &
347 description=
"For the CV given by the multiplication of two coorination numbers,"// &
348 " specify the R0 parameter in the second coordination function.", &
349 usage=
"R0_B {real}", default_r_val=3.0_dp, &
350 unit_str=
"bohr", n_var=1)
355 variants=(/
"EXPON_NUMERATOR_B"/), &
356 description=
"For the CV given by the multiplication of two coorination numbers,"// &
357 " Sets the value of the numerator of the exponential factor"// &
358 " in the coordination FUNCTION.", &
359 usage=
"NN_B {integer}", default_i_val=6, &
365 variants=(/
"EXPON_DENOMINATOR_B"/), &
366 description=
"For the CV given by the multiplication of two coorination numbers,"// &
367 " Sets the value of the denominator of the exponential factor"// &
368 " in the coordination FUNCTION.", &
369 usage=
"ND_B {integer}", default_i_val=12, &
374 END SUBROUTINE create_colvar_coord_section
380 SUBROUTINE create_colvar_cond_dist_section(section)
386 cpassert(.NOT.
ASSOCIATED(section))
387 CALL section_create(section, __location__, name=
"CONDITIONED_DISTANCE", &
388 description=
"Section to define the conditioned distance as a collective variable.", &
389 n_keywords=1, n_subsections=0, repeats=.false.)
391 NULLIFY (subsection, keyword)
393 CALL keyword_create(keyword, __location__, name=
"ATOMS_DISTANCE", &
394 description=
"Specify indexes of atoms/points from which the distance is computed. ", &
395 usage=
"ATOMS_DISTANCE {integer} {integer} ..", repeats=.true., &
401 variants=(/
"POINTS_FROM"/), &
402 description=
"Specify indexes of atoms/points building the coordination variable. ", &
403 usage=
"ATOMS_FROM {integer} {integer} ..", repeats=.true., &
409 variants=(/
"POINTS_TO"/), &
410 description=
"Specify indexes of atoms/points building the coordination variable. ", &
411 usage=
"ATOMS_TO {integer} {integer} ..", repeats=.true., &
417 description=
"Specify alternatively kinds of atoms building the coordination variable.", &
418 usage=
"KINDS_FROM {CHAR} {CHAR} ..", repeats=.true., &
419 n_var=-1, type_of_var=
char_t)
424 description=
"Specify alternatively kinds of atoms building the coordination variable.", &
425 usage=
"KINDS_TO {CHAR} {CHAR} ..", repeats=.true., &
426 n_var=-1, type_of_var=
char_t)
431 CALL create_point_section(subsection)
436 variants=(/
"R_0"/), &
437 description=
"Specify the R0 parameter in the coordination function.", &
438 usage=
"R0 {real}", default_r_val=3.0_dp, &
439 unit_str=
"bohr", n_var=1)
444 variants=(/
"EXPON_NUMERATOR"/), &
445 description=
"Sets the value of the numerator of the exponential factor"// &
446 " in the coordination FUNCTION.", &
447 usage=
"NN {integer}", default_i_val=6, &
453 variants=(/
"EXPON_DENOMINATOR"/), &
454 description=
"Sets the value of the denominator of the exponential factor"// &
455 " in the coordination FUNCTION.", &
456 usage=
"ND {integer}", default_i_val=12, &
462 description=
"Specify the lambda parameter at the exponent of the conditioned distance function.", &
463 usage=
"LAMBDA {real}", default_r_val=3.0_dp, &
464 unit_str=
"bohr", n_var=1)
468 END SUBROUTINE create_colvar_cond_dist_section
476 SUBROUTINE create_colvar_pop_section(section)
482 cpassert(.NOT.
ASSOCIATED(section))
484 description=
"Section to define the population of specie as a collective variable. "// &
485 "See also <https://doi.org/10.1021/jp3019588>.", &
486 n_keywords=1, n_subsections=0, repeats=.false.)
488 NULLIFY (subsection, keyword)
491 variants=(/
"POINTS_FROM"/), &
492 description=
"Specify indexes of atoms/points building the coordination variable. ", &
493 usage=
"ATOMS_FROM {integer} {integer} ..", repeats=.true., &
499 variants=(/
"POINTS_TO"/), &
500 description=
"Specify indexes of atoms/points building the coordination variable. ", &
501 usage=
"ATOMS_TO {integer} {integer} ..", repeats=.true., &
507 description=
"Specify alternatively kinds of atoms building the coordination variable.", &
508 usage=
"KINDS_FROM {CHAR} {CHAR} ..", repeats=.true., &
509 n_var=-1, type_of_var=
char_t)
514 description=
"Specify alternatively kinds of atoms building the coordination variable.", &
515 usage=
"KINDS_TO {CHAR} {CHAR} ..", repeats=.true., &
516 n_var=-1, type_of_var=
char_t)
521 CALL create_point_section(subsection)
526 variants=(/
"R_0"/), &
527 description=
"Specify the R0 parameter in the coordination function.", &
528 usage=
"R0 {real}", default_r_val=3.0_dp, &
534 variants=(/
"EXPON_NUMERATOR"/), &
535 description=
"Sets the value of the numerator of the exponential factor"// &
536 " in the coordination FUNCTION.", &
537 usage=
"NN {integer}", default_i_val=6, &
543 variants=(/
"EXPON_DENOMINATOR"/), &
544 description=
"Sets the value of the denominator of the exponential factor"// &
545 " in the coordination FUNCTION.", &
546 usage=
"ND {integer}", default_i_val=12, &
552 variants=(/
"n_0"/), &
553 description=
"Specify the n0 parameter that sets the coordination of the species.", &
554 usage=
"n0 {integer}", default_i_val=4, &
560 description=
"Specify the gaussian width of used to build the population istogram.", &
561 usage=
"SIGMA {real}", default_r_val=0.5_dp, &
566 END SUBROUTINE create_colvar_pop_section
572 SUBROUTINE create_colvar_gyr_section(section)
578 cpassert(.NOT.
ASSOCIATED(section))
579 CALL section_create(section, __location__, name=
"GYRATION_RADIUS", &
580 description=
"Section to define the gyration radius as a collective variable.", &
581 n_keywords=1, n_subsections=0, repeats=.false.)
583 NULLIFY (subsection, keyword)
586 variants=(/
"POINTS"/), &
587 description=
"Specify indexes of atoms/points defyining the gyration radius variable. ", &
588 usage=
"ATOMS {integer} {integer} ..", repeats=.true., &
594 description=
"Specify alternatively kinds of atoms defining the gyration radius.", &
595 usage=
"KINDS {CHAR} {CHAR} ..", repeats=.true., &
596 n_var=-1, type_of_var=
char_t)
601 CALL create_point_section(subsection)
605 END SUBROUTINE create_colvar_gyr_section
612 SUBROUTINE create_colvar_dfunct_section(section)
618 cpassert(.NOT.
ASSOCIATED(section))
619 CALL section_create(section, __location__, name=
"DISTANCE_FUNCTION", &
620 description=
"Section to define functions between two distances as collective variables."// &
621 " The function is defined as d1+coeff*d2", &
622 n_keywords=1, n_subsections=0, repeats=.false.)
624 NULLIFY (keyword, subsection)
627 variants=(/
"POINTS"/), &
628 description=
"Specifies the indexes of atoms/points for the two bonds d1=(1-2) d2=(3-4).", &
629 usage=
"ATOMS {integer} {integer} {integer} {integer}", &
635 description=
"Specifies the coefficient in the function for the constraint."// &
636 " -1.0 has to be used for distance difference, 1.0 for distance addition", &
637 usage=
"COEFFICIENT {real}", &
643 description=
"Whether periodic boundary conditions should be applied on the "// &
644 "atomic position before computing the colvar or not.", &
646 default_l_val=.true., lone_keyword_l_val=.true.)
651 CALL create_point_section(subsection)
655 END SUBROUTINE create_colvar_dfunct_section
662 SUBROUTINE create_colvar_torsion_section(section)
668 cpassert(.NOT.
ASSOCIATED(section))
670 description=
"Section to define the torsion as a collective variables.", &
671 n_keywords=1, n_subsections=0, repeats=.false.)
673 NULLIFY (keyword, subsection)
676 variants=(/
"POINTS"/), &
677 description=
"Specifies the indexes of atoms/points defining the torsion.", &
678 usage=
"ATOMS {integer} {integer} {integer} {integer}", &
684 CALL create_point_section(subsection)
688 END SUBROUTINE create_colvar_torsion_section
695 SUBROUTINE create_colvar_rot_section(section)
701 cpassert(.NOT.
ASSOCIATED(section))
702 CALL section_create(section, __location__, name=
"bond_rotation", &
703 description=
"Section to define the rotation of a bond/line with respect to"// &
704 " another bond/line", &
705 n_keywords=1, n_subsections=0, repeats=.false.)
707 NULLIFY (keyword, subsection)
710 description=
"Specifies the index of atom/point defining the first point"// &
711 " of the first bond/line.", &
712 usage=
"P1_BOND1 {integer}", &
718 description=
"Specifies the index of atom/point defining the second point"// &
719 " of the first bond/line.", &
720 usage=
"P2_BOND1 {integer}", &
726 description=
"Specifies the index of atom/point defining the first point"// &
727 " of the second bond/line.", &
728 usage=
"P1_BOND2 {integer}", &
734 description=
"Specifies the index of atom/point defining the second point"// &
735 " of the second bond/line.", &
736 usage=
"P2_BOND2 {integer}", &
742 CALL create_point_section(subsection)
746 END SUBROUTINE create_colvar_rot_section
753 SUBROUTINE create_colvar_angle_section(section)
759 cpassert(.NOT.
ASSOCIATED(section))
761 description=
"Section to define the angle as a collective variables.", &
762 n_keywords=1, n_subsections=0, repeats=.false.)
763 NULLIFY (keyword, subsection)
766 variants=(/
"POINTS"/), &
767 description=
"Specifies the indexes of atoms/points defining the angle.", &
768 usage=
"ATOMS {integer} {integer} {integer}", &
774 CALL create_point_section(subsection)
778 END SUBROUTINE create_colvar_angle_section
785 SUBROUTINE create_colvar_dist_section(section)
791 cpassert(.NOT.
ASSOCIATED(section))
793 description=
"Section to define the distance as a collective variables.", &
794 n_keywords=1, n_subsections=0, repeats=.false.)
795 NULLIFY (keyword, subsection)
798 variants=(/
"POINTS"/), &
799 description=
"Specifies the indexes of atoms/points defining the distance.", &
800 usage=
"ATOMS {integer} {integer}", &
805 description=
"Define the axes along which the colvar should be evaluated", &
806 usage=
"AXIS (XYZ | X | Y | Z | XY| XZ | YZ)", &
807 enum_c_vals=
s2a(
"XYZ",
"X",
"Y",
"Z",
"XY",
"XZ",
"YZ"), &
814 description=
"Whether the distance along one Cartesian axis has to be considered with sign."// &
815 " This option is valid if only one dimension is selected.", &
817 default_l_val=.false., lone_keyword_l_val=.true.)
822 CALL create_point_section(subsection)
826 END SUBROUTINE create_colvar_dist_section
839 cpassert(.NOT.
ASSOCIATED(section))
841 description=
"Section to define the distance of an atom from its starting "// &
842 "position ((X-X(0))^2+(Y-Y(0))^2+(Z-Z(0))^2) or part of its components as a collective variable. "// &
843 "If absolute_position is specified, instead the CV is represented by the "// &
844 "instantaneous position of the atom (only available for X, Y or Z components).", &
845 n_keywords=1, n_subsections=0, repeats=.false.)
846 NULLIFY (keyword, subsection)
849 variants=(/
"POINT"/), &
850 description=
"Specifies the index of the atom/point.", &
851 usage=
"ATOM {integer}", &
857 description=
"Define the component of the position vector which will be used "// &
859 usage=
"COMPONENT (XYZ | X | Y | Z | XY| XZ | YZ)", &
860 enum_c_vals=
s2a(
"XYZ",
"X",
"Y",
"Z",
"XY",
"XZ",
"YZ"), &
867 description=
"Whether periodic boundary conditions should be applied on the "// &
868 "atomic position before computing the colvar or not.", &
870 default_l_val=.true., lone_keyword_l_val=.true.)
874 CALL keyword_create(keyword, __location__, name=
"ABSOLUTE_POSITION", &
875 description=
"If enabled, the absolute position of the atoms will be used. ", &
876 usage=
"ABSOLUTE_POSITION", &
877 default_l_val=.false., lone_keyword_l_val=.true.)
882 CALL create_point_section(subsection)
899 cpassert(.NOT.
ASSOCIATED(section))
900 CALL section_create(section, __location__, name=
"XYZ_OUTERDIAG", &
901 description=
"Section to define the cross term (XA-XA(0))*(XB-XB(0))+(XA-XA(0))*(YB-YB(0))"// &
902 " or part of its components as a collective variable. The final term is given by the product"// &
903 " of the components of A with the components of B.", &
904 n_keywords=1, n_subsections=0, repeats=.false.)
905 NULLIFY (keyword, subsection)
908 variants=(/
"POINTS"/), &
909 description=
"Specifies the index of the atoms/points A and B.", &
910 usage=
"ATOMS {integer} {integer}", &
916 description=
"Define the component of the position vector which will be used "// &
917 "as a colvar for atom A.", &
918 usage=
"COMPONENT_A (XYZ | X | Y | Z | XY| XZ | YZ)", &
919 enum_c_vals=
s2a(
"XYZ",
"X",
"Y",
"Z",
"XY",
"XZ",
"YZ"), &
926 description=
"Define the component of the position vector which will be used "// &
927 "as a colvar for atom B.", &
928 usage=
"COMPONENT_B (XYZ | X | Y | Z | XY| XZ | YZ)", &
929 enum_c_vals=
s2a(
"XYZ",
"X",
"Y",
"Z",
"XY",
"XZ",
"YZ"), &
936 description=
"Whether periodic boundary conditions should be applied on the "// &
937 "atomic position before computing the colvar or not.", &
939 default_l_val=.true., lone_keyword_l_val=.true.)
944 CALL create_point_section(subsection)
955 SUBROUTINE create_colvar_u_section(section)
961 cpassert(.NOT.
ASSOCIATED(section))
963 description=
"Section to define the energy as a generalized collective variable.", &
964 n_keywords=0, n_subsections=0, repeats=.false.)
966 NULLIFY (subsection, keyword)
968 description=
"This section allows to use any function of the energy subsystems"// &
969 " in a mixed_env calculation as a collective variable.", &
970 n_keywords=1, n_subsections=0, repeats=.false.)
972 CALL keyword_create(keyword, __location__, name=
"ENERGY_FUNCTION", &
973 description=
"Specifies the functional form of the collective variable in mathematical notation.", &
974 usage=
"ENERGY_FUNCTION (E1+E2-LOG(E1/E2))", type_of_var=
lchar_t, &
980 description=
"Defines the variables of the functional form. To allow an efficient"// &
981 " mapping the order of the energy variables will be considered identical to the"// &
982 " order of the force_eval in the force_eval_order list.", &
983 usage=
"VARIABLES x", type_of_var=
char_t, &
989 description=
"Defines the parameters of the functional form", &
990 usage=
"PARAMETERS a b D", type_of_var=
char_t, &
991 n_var=-1, repeats=.true.)
996 description=
"Defines the values of parameter of the functional form", &
997 usage=
"VALUES ", type_of_var=
real_t, &
998 n_var=-1, repeats=.true., unit_str=
"internal_cp2k")
1003 description=
"Optionally, allows to define valid CP2K unit strings for each parameter value. "// &
1004 "It is assumed that the corresponding parameter value is specified in this unit.", &
1005 usage=
"UNITS angstrom eV*angstrom^-1 angstrom^1 K", type_of_var=
char_t, &
1006 n_var=-1, repeats=.true.)
1011 description=
"Parameter used for computing the derivative with the Ridders' method.", &
1012 usage=
"DX <REAL>", default_r_val=0.1_dp, unit_str=
"bohr")
1017 description=
"Checks that the error in computing the derivative is not larger than "// &
1018 "the value set; in case error is larger a warning message is printed.", &
1019 usage=
"ERROR_LIMIT <REAL>", default_r_val=1.0e-12_dp)
1026 END SUBROUTINE create_colvar_u_section
1034 SUBROUTINE create_colvar_d_pl_section(section)
1040 cpassert(.NOT.
ASSOCIATED(section))
1041 CALL section_create(section, __location__, name=
"distance_point_plane", &
1042 description=
"Section to define the distance of a point from a plane "// &
1043 "as a collective variables.", &
1044 n_keywords=1, n_subsections=0, repeats=.false.)
1045 NULLIFY (keyword, subsection)
1048 description=
"Whether periodic boundary conditions should be applied on the "// &
1049 "atomic position before computing the colvar or not.", &
1051 default_l_val=.true., lone_keyword_l_val=.true.)
1056 variants=(/
"POINTS_PLANE"/), &
1057 description=
"Specifies the indexes of atoms/points defining the plane.", &
1058 usage=
"ATOMS_PLANE <INTEGER> <INTEGER> <INTEGER>", &
1064 variants=(/
"POINT_POINT"/), &
1065 description=
"Specifies the atom/point index defining the point.", &
1066 usage=
"ATOM_POINT <INTEGER>", &
1072 CALL create_point_section(subsection)
1076 END SUBROUTINE create_colvar_d_pl_section
1084 SUBROUTINE create_colvar_a_pl_section(section)
1090 cpassert(.NOT.
ASSOCIATED(section))
1091 CALL section_create(section, __location__, name=
"angle_plane_plane", &
1092 description=
"This section defines the angle between two planes "// &
1093 "as a collective variables.", &
1094 n_keywords=1, n_subsections=0, repeats=.false.)
1095 NULLIFY (keyword, subsection)
1098 description=
"This section defines the plane. When using this colvar, "// &
1099 "two plane section must be defined!", &
1100 n_keywords=1, n_subsections=0, repeats=.true.)
1103 description=
"Specify how the plane is defined: either by 3 atoms or by a fixed normal "// &
1104 "vector. At least one plane must be defined through atoms.", &
1105 usage=
"DEF_TYPE ATOMS", &
1107 enum_c_vals=
s2a(
"ATOMS",
"VECTOR"), &
1108 enum_desc=
s2a(
"Plane defined by the position of 3 atoms", &
1109 "Plane defined by a fixed normal vector"), &
1115 description=
"Specifies the indexes of 3 atoms/points defining the plane.", &
1116 usage=
"ATOMS <INTEGER> <INTEGER> <INTEGER>", &
1121 CALL keyword_create(keyword, __location__, name=
"NORMAL_VECTOR", &
1122 description=
"Alternatively to 3 atoms/points one can define one of the two, "// &
1123 "planes by defining its NORMAL vector.", &
1124 usage=
"NORMAL_VECTOR 0.0 1.0 0.0", &
1125 n_var=3, type_of_var=
real_t)
1132 CALL create_point_section(subsection)
1135 END SUBROUTINE create_colvar_a_pl_section
1142 SUBROUTINE create_point_section(section)
1147 cpassert(.NOT.
ASSOCIATED(section))
1149 description=
"Enables the possibility to use geometrical centers instead of single atoms"// &
1150 " to define colvars", &
1151 n_keywords=1, n_subsections=0, repeats=.true.)
1156 description=
"Chooses the type of geometrical point", &
1157 usage=
"type (GEO_CENTER|FIX_POINT)", &
1158 enum_c_vals=
s2a(
"GEO_CENTER",
"FIX_POINT"), &
1159 enum_desc=
s2a(
"Computes the geometrical center of the listed atoms", &
1160 "Defines a fixed point in space"), &
1167 description=
"Specifies the indexes of atoms defining the geometrical center", &
1168 usage=
"ATOMS {integer} {integer} {integer} {integer}", &
1169 n_var=-1, type_of_var=
integer_t, repeats=.true.)
1174 keyword, __location__, name=
"WEIGHTS", &
1175 description=
"Specifies the weights for a weighted geometrical center. Default is 1/natoms for every atom", &
1176 usage=
"WEIGHTS {real} {real} {real} {real}", &
1177 n_var=-1, type_of_var=
real_t, repeats=.true.)
1182 description=
"Specifies the xyz of the fixed point (if the case)", &
1183 usage=
"XYZ {real} {real} {real}", &
1184 n_var=3, type_of_var=
real_t, unit_str=
"bohr", &
1189 END SUBROUTINE create_point_section
1196 SUBROUTINE create_colvar_qparm_section(section)
1202 cpassert(.NOT.
ASSOCIATED(section))
1204 description=
"Section to define the Q parameter (crystalline order parameter) as a collective variable.", &
1205 n_keywords=1, n_subsections=0, repeats=.false.)
1207 NULLIFY (keyword, subsection)
1210 variants=(/
"POINTS_FROM"/), &
1211 description=
"Specify indexes of atoms/points building the coordination variable. ", &
1212 usage=
"ATOMS_FROM {integer} {integer} ..", repeats=.true., &
1218 variants=(/
"POINTS_TO"/), &
1219 description=
"Specify indexes of atoms/points building the coordination variable. ", &
1220 usage=
"ATOMS_TO {integer} {integer} ..", repeats=.true., &
1226 description=
"Specifies the distance cutoff for neighbors. "// &
1227 "Cutoff function is exactly zero for all neighbors beyond RCUT.", &
1228 usage=
"RCUT {real}", &
1229 n_var=1, unit_str=
"angstrom", type_of_var=
real_t)
1233 CALL keyword_create(keyword, __location__, name=
"INCLUDE_IMAGES", &
1234 description=
"Whether to include periodic images of ATOMS_TO into the neighbor list.", &
1235 usage=
"INCLUDE_IMAGES", &
1236 default_l_val=.false., lone_keyword_l_val=.true.)
1241 description=
"Specifies the distance cutoff for neighbors. "// &
1242 "Cutoff function is exactly 1 for all neighbors closer than RSTART.", &
1243 usage=
"RSTART {real}", &
1244 n_var=1, unit_str=
"angstrom", type_of_var=
real_t)
1249 description=
"Specifies the L spherical harmonics from Ylm.", &
1250 usage=
"L {integer}", &
1262 CALL create_point_section(subsection)
1266 END SUBROUTINE create_colvar_qparm_section
1273 SUBROUTINE create_colvar_hydronium_shell_section(section)
1278 cpassert(.NOT.
ASSOCIATED(section))
1279 CALL section_create(section, __location__, name=
"HYDRONIUM_SHELL", &
1280 description=
"Section to define the formation of a hydronium as a"// &
1281 " collective variable. Number of oxygens in the 1st shell of the"// &
1282 " hydronium. Adapted from Equation (3) in Supplementary Info of"// &
1283 " J. Am. Chem. Soc.,128, 2006, 11318, i.e. omitting the cutoff function"// &
1284 " and summing only over the oxygens of water.", &
1285 n_keywords=1, n_subsections=0, repeats=.false.)
1290 description=
"Specifies indexes of atoms building the coordination variable."// &
1291 " Oxygens of the water molecules.", &
1292 usage=
"OXYGENS {integer} {integer} ..", repeats=.true., &
1298 description=
"Specifies indexes of atoms building the coordination variable."// &
1299 " Hydrogens of the water molecules.", &
1300 usage=
"HYDROGENS {integer} {integer} ..", repeats=.true., &
1306 description=
"Specifies the rc parameter in the coordination function:"// &
1307 " number of oxygens per water oxygen.", &
1309 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1314 variants=(/
"EXPON_NUMERATORA"/), &
1315 description=
"Sets the value of the numerator of the exponential factor"// &
1316 " in the coordination function: number of oxygens per water oxygen.", &
1317 usage=
"pOO {integer}", default_i_val=6, &
1323 variants=(/
"EXPON_DENOMINATORA"/), &
1324 description=
"Sets the value of the denominator of the exponential factor"// &
1325 " in the coordination function: number of oxygens per water oxygen.", &
1326 usage=
"qOO {integer}", default_i_val=12, &
1332 description=
"Specifies the rc parameter in the coordination function:"// &
1333 " number of hydrogens per water molecule.", &
1335 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1340 variants=(/
"EXPON_NUMERATORB"/), &
1341 description=
"Sets the value of the numerator of the exponential factor"// &
1342 " in the coordination function: number of hydrogens per water molecule.", &
1343 usage=
"pOH {integer}", default_i_val=6, &
1349 variants=(/
"EXPON_DENOMINATORB"/), &
1350 description=
"Sets the value of the denominator of the exponential factor"// &
1351 " in the coordination function: number of hydrogens per water molecule.", &
1352 usage=
"qOH {integer}", default_i_val=12, &
1358 description=
"Specifies the NH parameter in the M function.", &
1359 usage=
"NH {real}", default_r_val=3.0_dp, &
1365 variants=(/
"EXPON_NUMERATOR"/), &
1366 description=
"Sets the value of the numerator of the exponential factor"// &
1367 " in the M function.", &
1368 usage=
"pM {integer}", default_i_val=8, &
1374 variants=(/
"EXPON_DENOMINATOR"/), &
1375 description=
"Sets the value of the denominator of the exponential factor"// &
1376 " in the M function.", &
1377 usage=
"qM {integer}", default_i_val=16, &
1383 description=
"Specify the LAMBDA parameter in the hydronium function.", &
1384 usage=
"LAMBDA {real}", default_r_val=10.0_dp, &
1389 END SUBROUTINE create_colvar_hydronium_shell_section
1396 SUBROUTINE create_colvar_hydronium_dist_section(section)
1401 cpassert(.NOT.
ASSOCIATED(section))
1402 CALL section_create(section, __location__, name=
"HYDRONIUM_DISTANCE", &
1403 description=
"Section to define the formation of a hydronium as a"// &
1404 " collective variable. Distance between hydronium and hydroxide ion"// &
1405 " Experimental at this point, i.e. not proved to be an effective"// &
1406 " collective variable.", &
1407 n_keywords=1, n_subsections=0, repeats=.false.)
1412 description=
"Specifies indexes of atoms building the coordination variable."// &
1413 " Oxygens of the water molecules.", &
1414 usage=
"OXYGENS {integer} {integer} ..", repeats=.true., &
1420 description=
"Specifies indexes of atoms building the coordination variable."// &
1421 " Hydrogens of the water molecules.", &
1422 usage=
"HYDROGENS {integer} {integer} ..", repeats=.true., &
1428 description=
"Specifies the rc parameter in the coordination function:"// &
1429 " number of hydrogens per water molecule.", &
1431 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1436 description=
"Sets the value of the numerator of the exponential factor"// &
1437 " in the coordination function: number of hydrogens per water molecule.", &
1438 usage=
"pOH {integer}", default_i_val=6, &
1444 description=
"Sets the value of the denominator of the exponential factor"// &
1445 " in the coordination function: number of hydrogens per water molecule.", &
1446 usage=
"qOH {integer}", default_i_val=12, &
1452 description=
"Specifies the NH parameter in the M function.", &
1453 usage=
"NH {real}", default_r_val=2.2_dp, &
1459 description=
"Sets the value of the numerator of the exponential factor"// &
1460 " in the M function.", &
1461 usage=
"pM {integer}", default_i_val=8, &
1467 description=
"Sets the value of the denominator of the exponential factor"// &
1468 " in the M function.", &
1469 usage=
"qM {integer}", default_i_val=16, &
1475 description=
"Specifies the NN parameter in the F function.", &
1476 usage=
"NN {real}", default_r_val=1.5_dp, &
1482 description=
"Sets the value of the numerator of the exponential factor"// &
1483 " in the F function.", &
1484 usage=
"pF {integer}", default_i_val=8, &
1490 description=
"Sets the value of the denominator of the exponential factor"// &
1491 " in the F function.", &
1492 usage=
"qF {integer}", default_i_val=16, &
1498 description=
"Specify the LAMBDA parameter in the hydronium function.", &
1499 usage=
"LAMBDA {real}", default_r_val=20.0_dp, &
1504 END SUBROUTINE create_colvar_hydronium_dist_section
1513 SUBROUTINE create_colvar_acid_hyd_dist_section(section)
1518 cpassert(.NOT.
ASSOCIATED(section))
1519 CALL section_create(section, __location__, name=
"ACID_HYDRONIUM_DISTANCE", &
1520 description=
"Section to define the dissociation of a carboxylic acid in"// &
1521 " water. Distance between hydronium ion and acetate ion. Equation (2)"// &
1522 " in Supplementary Info of J. Am. Chem. Soc.,128, 2006, 11318.", &
1523 n_keywords=1, n_subsections=0, repeats=.false.)
1527 CALL keyword_create(keyword, __location__, name=
"OXYGENS_WATER", &
1528 description=
"Specifies indexes of atoms building the coordination variable."// &
1529 " Oxygens of the water molecules. ", &
1530 usage=
"OXYGENS_WATER {integer} {integer} ..", repeats=.true., &
1535 CALL keyword_create(keyword, __location__, name=
"OXYGENS_ACID", &
1536 description=
"Specifies indexes of atoms building the coordination variable."// &
1537 " Oxygens of the carboxyl groups.", &
1538 usage=
"OXYGENS_ACID {integer} {integer} ..", repeats=.true., &
1544 description=
"Specifies indexes of atoms building the coordination variable."// &
1545 " Hydrogens of the water molecules and of the carboxyl groups.", &
1546 usage=
"HYDROGENS {integer} {integer} ..", repeats=.true., &
1552 description=
"Sets the value of the numerator of the exponential factor"// &
1553 " in the coordination function: number of hydrogens per water molecule.", &
1554 usage=
"pWOH {integer}", default_i_val=8, &
1560 description=
"Sets the value of the denominator of the exponential factor"// &
1561 " in the coordination function: number of hydrogens per water molecule.", &
1562 usage=
"qWOH {integer}", default_i_val=16, &
1568 description=
"Specify the rc parameter in the coordination function:"// &
1569 " number of hydrogens per water molecule.", &
1571 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1576 description=
"Sets the value of the numerator of the exponential factor"// &
1577 " in the coordination function: number of hydrogens per carboxyl group.", &
1578 usage=
"pAOH {integer}", default_i_val=6, &
1584 description=
"Sets the value of the denominator of the exponential factor"// &
1585 " in the coordination function: number of hydrogens per carboxyl group.", &
1586 usage=
"qAOH {integer}", default_i_val=14, &
1592 description=
"Specify the rc parameter in the coordination function:"// &
1593 " number of hydrogens per carboxyl group.", &
1595 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1600 description=
"Sets the value of the numerator of the exponential factor"// &
1601 " in the cutoff function.", &
1602 usage=
"pCUT {integer}", default_i_val=6, &
1608 description=
"Sets the value of the denominator of the exponential factor"// &
1609 " in the cutoff function.", &
1610 usage=
"qCUT {integer}", default_i_val=12, &
1616 description=
"Specifies the NC parameter in the cutoff function.", &
1617 usage=
"NC {real}", default_r_val=0.56_dp, &
1623 variants=(/
"LAMBDA"/), &
1624 description=
"Specifies the LAMBDA parameter carboxylic acid function.", &
1625 usage=
"LAMBDA {real}", default_r_val=20.0_dp, &
1630 END SUBROUTINE create_colvar_acid_hyd_dist_section
1639 SUBROUTINE create_colvar_acid_hyd_shell_section(section)
1644 cpassert(.NOT.
ASSOCIATED(section))
1645 CALL section_create(section, __location__, name=
"ACID_HYDRONIUM_SHELL", &
1646 description=
"Section to define the dissociation of a carboxylic acid in"// &
1647 " water. Number of oxygens in the 1st shell of the hydronium. Equation (3)"// &
1648 " in Supplementary Info of J. Am. Chem. Soc.,128, 2006, 11318. Similar to"// &
1649 " the HYDRONIUM colvar, but with modification for the acid.", &
1650 n_keywords=1, n_subsections=0, repeats=.false.)
1654 CALL keyword_create(keyword, __location__, name=
"OXYGENS_WATER", &
1655 description=
"Specifies indexes of atoms building the coordination variable."// &
1656 " Oxygens of the water molecules. ", &
1657 usage=
"OXYGENS_WATER {integer} {integer} ..", repeats=.true., &
1662 CALL keyword_create(keyword, __location__, name=
"OXYGENS_ACID", &
1663 description=
"Specifies indexes of atoms building the coordination variable."// &
1664 " Oxygens of the carboxyl groups.", &
1665 usage=
"OXYGENS_ACID {integer} {integer} ..", repeats=.true., &
1671 description=
"Specifies indexes of atoms building the coordination variable."// &
1672 " Hydrogens of the water molecules and of the carboxyl groups.", &
1673 usage=
"HYDROGENS {integer} {integer} ..", repeats=.true., &
1679 description=
"Sets the value of the numerator of the exponential factor"// &
1680 " in the coordination function: number of hydrogens per water molecule.", &
1681 usage=
"pWOH {integer}", default_i_val=8, &
1687 description=
"Sets the value of the denominator of the exponential factor"// &
1688 " in the coordination function: number of hydrogens per water molecule.", &
1689 usage=
"qWOH {integer}", default_i_val=16, &
1695 description=
"Specifies the rc parameter in the coordination function:"// &
1696 " number of hydrogens per water molecule.", &
1698 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1703 description=
"Sets the value of the numerator of the exponential factor"// &
1704 " in the coordination function: number of hydrogens per carboxyl group.", &
1705 usage=
"pAOH {integer}", default_i_val=6, &
1711 description=
"Sets the value of the denominator of the exponential factor"// &
1712 " in the coordination function: number of hydrogens per carboxyl group.", &
1713 usage=
"qAOH {integer}", default_i_val=14, &
1719 description=
"Specifies the rc parameter in the coordination function:"// &
1720 " number of hydrogens per carboxyl group.", &
1722 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1727 description=
"Sets the value of the numerator of the exponential factor"// &
1728 " in the coordination function: number of oxygens per water oxygen.", &
1729 usage=
"pOO {integer}", default_i_val=6, &
1735 description=
"Sets the value of the denominator of the exponential factor"// &
1736 " in the coordination function: number of oxygens per water oxygen.", &
1737 usage=
"qOO {integer}", default_i_val=12, &
1743 description=
"Specifies the rc parameter in the coordination function:"// &
1744 " number of oxygens per water oxygen.", &
1746 unit_str=
"bohr"), unit_str=
"bohr", n_var=1)
1751 description=
"Sets the value of the numerator of the exponential factor"// &
1752 " in the M function.", &
1753 usage=
"pM {integer}", default_i_val=8, &
1759 description=
"Sets the value of the denominator of the exponential factor"// &
1760 " in the M function.", &
1761 usage=
"qM {integer}", default_i_val=16, &
1767 description=
"Specifies the NH parameter in the M function.", &
1768 usage=
"NH {real}", default_r_val=2.2_dp, &
1774 description=
"Sets the value of the numerator of the exponential factor"// &
1775 " in the cutoff function.", &
1776 usage=
"pCUT {integer}", default_i_val=6, &
1782 description=
"Sets the value of the denominator of the exponential factor"// &
1783 " in the cutoff function.", &
1784 usage=
"qCUT {integer}", default_i_val=12, &
1790 description=
"Specifies the NC parameter in the cutoff function.", &
1791 usage=
"NC {real}", default_r_val=0.9_dp, &
1797 variants=(/
"LAMBDA"/), &
1798 description=
"Specifies the LAMBDA parameter carboxylic acid function.", &
1799 usage=
"LAMBDA {real}", default_r_val=10.0_dp, &
1804 END SUBROUTINE create_colvar_acid_hyd_shell_section
1810 SUBROUTINE create_colvar_rmsd_section(section)
1814 TYPE(
section_type),
POINTER :: subsection, subsubsection
1816 cpassert(.NOT.
ASSOCIATED(section))
1818 description=
"Section to define a CV as function of RMSD computed with respect to"// &
1819 " given reference configurations. For 2 configurations the colvar is equal to:"// &
1820 " ss = (RMSDA-RMSDB)/(RMSDA+RMSDB), while if only 1 configuration is given, then the"// &
1821 " colvar is just the RMSD from that frame.", &
1822 n_keywords=1, n_subsections=0, repeats=.false.)
1824 NULLIFY (keyword, subsection, subsubsection)
1826 description=
"Define the subsytem used to compute the RMSD. With ALL the displacements"// &
1827 " are mass-weighted, with LIST all weights are set to 1,"// &
1828 " with WEIGHT_LIST a list of weights is expected from input.", &
1829 usage=
"SUBSET_TYPE ALL", &
1830 enum_c_vals=
s2a(
"ALL",
"LIST",
"WEIGHT_LIST"), &
1836 CALL keyword_create(keyword, __location__, name=
"ALIGN_FRAMES", &
1837 description=
"Whether the reference frames should be aligned to minimize the RMSD", &
1838 usage=
"ALIGN_FRAMES", &
1839 default_l_val=.false., lone_keyword_l_val=.true.)
1844 description=
"Specify indexes of atoms building the subset. ", &
1845 usage=
"ATOMS {integer} {integer} ..", repeats=.true., &
1851 description=
"Specify weights of atoms building the subset. It is used only with WEIGHT_LIST ", &
1852 usage=
"weightS {real} {real} ..", repeats=.true., &
1853 n_var=-1, type_of_var=
real_t)
1858 description=
"Specify coordinates of the frame (number of frames can be either 1 or 2)", &
1861 CALL keyword_create(keyword, __location__, name=
"COORD_FILE_NAME", &
1862 description=
"Name of the xyz file with coordinates (alternative to &COORD section)", &
1863 usage=
"COORD_FILE_NAME <CHAR>", &
1868 CALL create_coord_section_cv(subsubsection,
"RMSD")
1875 END SUBROUTINE create_colvar_rmsd_section
1883 SUBROUTINE create_colvar_rpath_section(section)
1886 cpassert(.NOT.
ASSOCIATED(section))
1887 CALL section_create(section, __location__, name=
"REACTION_PATH", &
1888 description=
"Section defining a one dimensional reaction path in an Q-dimensional space of colvars. "// &
1889 "Constraining this colvar, allows to sample the space orthogonal to the reaction path, "// &
1890 "both in the Q-dimensional colvar and 3N-Q remaining coordinates. "// &
1891 "For the details of the function see cited literature.", &
1892 n_keywords=1, n_subsections=0, repeats=.false., &
1895 CALL keywords_colvar_path(section)
1896 END SUBROUTINE create_colvar_rpath_section
1903 SUBROUTINE create_colvar_dpath_section(section)
1906 cpassert(.NOT.
ASSOCIATED(section))
1907 CALL section_create(section, __location__, name=
"DISTANCE_FROM_PATH", &
1908 description=
"Section defining the distance from a one dimensional reaction "// &
1909 "path in an Q-dimensional space of colvars. "// &
1910 "Constraining this colvar, allows to sample the space equidistant to the reaction path, "// &
1911 "both in the Q-dimensional colvar and 3N-Q remaining coordinates. "// &
1912 "For the details of the function see cited literature.", &
1913 n_keywords=1, n_subsections=0, repeats=.false., &
1916 CALL keywords_colvar_path(section)
1917 END SUBROUTINE create_colvar_dpath_section
1924 SUBROUTINE keywords_colvar_path(section)
1929 TYPE(
section_type),
POINTER :: print_key, subsection, subsubsection
1931 NULLIFY (keyword, subsection, subsubsection, print_key)
1936 CALL keyword_create(keyword, __location__, name=
"DISTANCES_RMSD", &
1938 usage=
"DISTANCES_RMSD T", &
1939 default_l_val=.false., lone_keyword_l_val=.true.)
1946 default_l_val=.false., lone_keyword_l_val=.true.)
1951 description=
"Define the subsytem used to compute the RMSD", &
1952 usage=
"SUBSET_TYPE ALL", &
1953 enum_c_vals=
s2a(
"ALL",
"LIST"), &
1959 CALL keyword_create(keyword, __location__, name=
"ALIGN_FRAMES", &
1960 description=
"Whether the reference frames should be aligned to minimize the RMSD", &
1961 usage=
"ALIGN_FRAMES", &
1962 default_l_val=.false., lone_keyword_l_val=.true.)
1967 description=
"Specify indexes of atoms building the subset. ", &
1968 usage=
"ATOMS {integer} {integer} ..", repeats=.true., &
1974 description=
"Specify coordinates of the frame", &
1977 CALL keyword_create(keyword, __location__, name=
"COORD_FILE_NAME", &
1978 description=
"Name of the xyz file with coordinates (alternative to &COORD section)", &
1979 usage=
"COORD_FILE_NAME <CHAR>", &
1984 CALL create_coord_section_cv(subsubsection,
"RMSD")
1992 description=
"Specifies the ith element of the vector valued function that defines the reaction path. "// &
1993 "This keyword needs to repeat exactly Q times, and the order must match the order of the colvars. "// &
1994 "The VARIABLE (e.g. T) which parametrises the curve can be used as the target of a constraint.", &
1995 usage=
"FUNCTION (sin(T+2)+2*T)", type_of_var=
lchar_t, &
1996 n_var=1, default_lc_val=
"0", repeats=.true.)
2001 description=
"Specifies the name of the variable that parametrises the FUNCTION "// &
2002 "defining the reaction path.", &
2003 usage=
"VARIABLE T", type_of_var=
char_t, &
2004 n_var=1, repeats=.false.)
2009 keyword, __location__, name=
"LAMBDA", &
2010 description=
"Specifies the exponent of the Gaussian used in the integral representation of the colvar. "// &
2011 "The shape of the space orthogonal to the reaction path is defined by this choice. "// &
2012 "In the limit of large values, it is given by the plane orthogonal to the path. "// &
2013 "In practice, modest values are required for stable numerical integration.", &
2014 usage=
"LAMBDA {real}", &
2015 type_of_var=
real_t, default_r_val=5.0_dp)
2020 description=
"Step size in the numerical integration, "// &
2021 "a few thousand points are common, and the proper number also depends on LAMBDA.", &
2022 usage=
"STEP_SIZE {real}", &
2023 type_of_var=
real_t, default_r_val=0.01_dp)
2028 description=
"The range of VARIABLE used for the parametrisation.", &
2029 usage=
"RANGE <REAL> <REAL>", &
2030 n_var=2, type_of_var=
real_t)
2035 print_key, __location__, name=
"MAP", &
2036 description=
"Activating this print key will print once a file with the values of the FUNCTION on a grid "// &
2037 "of COLVAR values in a specified range. "// &
2038 "GRID_SPACING and RANGE for every COLVAR has to be specified again in the same order as they are in the input.", &
2042 description=
"The range of of the grid of the COLVAR.", &
2043 usage=
"RANGE <REAL> <REAL>", &
2044 n_var=2, type_of_var=
real_t, repeats=.true.)
2048 CALL keyword_create(keyword, __location__, name=
"GRID_SPACING", &
2049 description=
"Distance between two gridpoints for the grid on the COLVAR", &
2050 usage=
"GRID_SPACING {real}", repeats=.true., &
2051 type_of_var=
real_t, default_r_val=0.01_dp)
2058 END SUBROUTINE keywords_colvar_path
2065 SUBROUTINE create_colvar_comb_section(section)
2071 cpassert(.NOT.
ASSOCIATED(section))
2072 CALL section_create(section, __location__, name=
"COMBINE_COLVAR", &
2073 description=
"Allows the possibility to combine several COLVARs into one COLVAR "// &
2074 "with a generic function.", &
2075 n_keywords=1, n_subsections=0, repeats=.false.)
2077 NULLIFY (keyword, subsection)
2083 description=
"Specifies the function used to combine different COLVARs into one.", &
2093 usage=
"FUNCTION SQRT(CV1^2+CV2^2)", type_of_var=
lchar_t, &
2099 description=
"Specifies the name of the variable that parametrises the FUNCTION "// &
2100 "defining how COLVARS should be combined. The matching follows the same order of the "// &
2101 "COLVARS definition in the input file.", &
2102 usage=
"VARIABLES CV1 CV2 CV3", type_of_var=
char_t, n_var=-1, repeats=.false.)
2107 description=
"Defines the parameters of the functional form", &
2108 usage=
"PARAMETERS a b D", type_of_var=
char_t, &
2109 n_var=-1, repeats=.true.)
2114 description=
"Defines the values of parameter of the functional form", &
2115 usage=
"VALUES ", type_of_var=
real_t, &
2116 n_var=-1, repeats=.true., unit_str=
"internal_cp2k")
2121 description=
"Parameter used for computing the derivative of the combination "// &
2122 "of COLVARs with the Ridders' method.", &
2123 usage=
"DX <REAL>", default_r_val=0.1_dp, unit_str=
"bohr")
2128 description=
"Checks that the error in computing the derivative is not larger than "// &
2129 "the value set; in case error is larger a warning message is printed.", &
2130 usage=
"ERROR_LIMIT <REAL>", default_r_val=1.0e-12_dp)
2134 END SUBROUTINE create_colvar_comb_section
2142 SUBROUTINE create_coord_section_cv(section, name)
2144 CHARACTER(LEN=*),
INTENT(IN) :: name
2148 cpassert(.NOT.
ASSOCIATED(section))
2150 description=
"The positions for "//trim(name)//
" used for restart", &
2151 n_keywords=1, n_subsections=0, repeats=.false.)
2154 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
2155 description=
"Specify positions of the system", repeats=.true., &
2156 usage=
"{Real} ...", type_of_var=
real_t, n_var=-1)
2160 END SUBROUTINE create_coord_section_cv
2167 SUBROUTINE create_colvar_wc_section(section)
2173 cpassert(.NOT.
ASSOCIATED(section))
2175 description=
"Section to define the hbond wannier centre as a collective variables.", &
2176 n_keywords=1, n_subsections=0, repeats=.false.)
2177 NULLIFY (keyword, subsection)
2180 description=
"Parameter used for computing the cutoff radius for searching "// &
2181 "the wannier centres around an atom", &
2182 usage=
"RCUT <REAL>", default_r_val=0.529177208590000_dp, unit_str=
"angstrom", &
2183 type_of_var=
real_t, repeats=.false.)
2188 variants=(/
"POINTS"/), &
2189 description=
"Specifies the indexes of atoms/points defining the bond (Od, H, Oa).", &
2190 usage=
"ATOMS {integer} {integer} {integer}", &
2191 n_var=3, type_of_var=
integer_t, repeats=.true.)
2196 CALL create_point_section(subsection)
2200 END SUBROUTINE create_colvar_wc_section
2207 SUBROUTINE create_colvar_hbp_section(section)
2213 cpassert(.NOT.
ASSOCIATED(section))
2215 description=
"Section to define the hbond wannier centre as a collective variables.", &
2216 n_keywords=1, n_subsections=0, repeats=.false.)
2217 NULLIFY (keyword, subsection)
2220 description=
"Parameter used for computing the cutoff radius for searching "// &
2221 "the wannier centres around an atom", &
2222 usage=
"RCUT <REAL>", default_r_val=0.529177208590000_dp, unit_str=
"angstrom", &
2223 type_of_var=
real_t, repeats=.false.)
2228 description=
"Parameter used for shifting each term in the sum ", &
2229 usage=
"SHIFT <REAL>", default_r_val=0.5_dp, &
2230 type_of_var=
real_t, repeats=.false.)
2235 description=
"The number of points in the path", &
2236 usage=
"NPOINTS {integer}", default_i_val=-1, &
2237 n_var=1, type_of_var=
integer_t, repeats=.false.)
2242 variants=(/
"POINTS"/), &
2243 description=
"Specifies the indexes of atoms/points defining the bond (Od, H, Oa).", &
2244 usage=
"ATOMS {integer} {integer} {integer}", &
2245 n_var=3, type_of_var=
integer_t, repeats=.true.)
2250 CALL create_point_section(subsection)
2254 END SUBROUTINE create_colvar_hbp_section
2262 SUBROUTINE create_colvar_ring_puckering_section(section)
2268 cpassert(.NOT.
ASSOCIATED(section))
2269 CALL section_create(section, __location__, name=
"RING_PUCKERING", &
2270 description=
"Section to define general ring puckering collective variables.", &
2271 n_keywords=1, n_subsections=0, repeats=.false.)
2273 NULLIFY (keyword, subsection)
2276 variants=(/
"POINTS"/), &
2277 description=
"Specifies the indexes of atoms/points defining the ring. "// &
2278 "At least 4 Atoms are needed.", &
2279 usage=
"ATOMS {integer} {integer} {integer} ..", &
2285 description=
"Indicate the coordinate to be used. Follow the Cremer-Pople definition for a N ring. "// &
2286 "0 is the total puckering variable Q, "// &
2287 "2..[N/2] are puckering coordinates. "// &
2288 "-2..-[N/2-1] are puckering angles.", &
2289 usage=
"COORDINATE {integer}", default_i_val=0, &
2295 CALL create_point_section(subsection)
2299 END SUBROUTINE create_colvar_ring_puckering_section
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public branduardi2007
Initialize the collective variables types.
integer, parameter, public do_clv_geo_center
integer, parameter, public do_clv_xyz
integer, parameter, public do_clv_xz
integer, parameter, public do_clv_fix_point
integer, parameter, public do_clv_z
integer, parameter, public plane_def_atoms
integer, parameter, public do_clv_yz
integer, parameter, public do_clv_xy
integer, parameter, public do_clv_y
integer, parameter, public plane_def_vec
integer, parameter, public do_clv_x
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public low_print_level
integer, parameter, public high_print_level
integer, parameter, public add_last_numeric
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
Defines the basic variable types.
integer, parameter, public dp
Utilities for string manipulations.