52 create_velocity_section
68#include "../base/base_uses.f90"
73 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
74 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'input_cp2k_motion'
90 cpassert(.NOT.
ASSOCIATED(section))
92 description=
"This section defines a set of tool connected with the motion of the nuclei.", &
93 n_keywords=1, n_subsections=1, repeats=.false.)
97 CALL create_geoopt_section(subsection, __location__, label=
"GEO_OPT", &
98 description=
"This section sets the environment of the geometry optimizer.", &
99 just_optimizers=.false., &
100 use_model_hessian=.true.)
104 CALL create_cell_opt_section(subsection)
108 CALL create_shellcore_opt_section(subsection)
116 CALL create_driver_section(subsection)
128 CALL create_fp_section(subsection)
132 CALL create_mc_section(subsection)
140 CALL create_pint_section(subsection)
159 SUBROUTINE create_mc_section(section)
165 cpassert(.NOT.
ASSOCIATED(section))
167 description=
"This section sets parameters to set up a MonteCarlo calculation.", &
168 n_keywords=10, n_subsections=2, repeats=.false.)
170 NULLIFY (keyword, subsection)
173 description=
"Specifies the number of MC cycles.", &
174 usage=
"NSTEP {integer}", &
180 description=
"Prints coordinate/cell/etc information every IPRINT steps.", &
181 usage=
"IPRINT {integer}", &
187 description=
"Specifies the number of classical moves between energy evaluations. ", &
188 usage=
"NMOVES {integer}", &
194 description=
"How many insertions to try per swap move.", &
195 usage=
"NSWAPMOVES {integer}", &
201 description=
"Dictates if we presample moves with a different potential.", &
202 usage=
"LBIAS {logical}", &
203 default_l_val=.false.)
208 description=
"Makes nstep in terms of steps, instead of cycles.", &
209 usage=
"LSTOP {logical}", &
210 default_l_val=.false.)
215 description=
"Changes the volume of the box in discrete steps, one side at a time.", &
216 usage=
"LDISCRETE {logical}", &
217 default_l_val=.false.)
222 description=
"The cluster cut off radius in angstroms.", &
223 usage=
"RCLUS {real}", &
224 default_r_val=1.0e0_dp)
229 description=
"Read initial configuration from restart file.", &
230 usage=
"RESTART {logical}", &
231 default_l_val=.false.)
236 keyword, __location__, name=
"NVIRIAL", &
237 description=
"Use this many random orientations to compute the second virial coefficient (ENSEMBLE=VIRIAL)", &
238 usage=
"NVIRIAL {integer}", &
244 description=
"Specify the type of simulation", &
245 usage=
"ENSEMBLE (TRADITIONAL|GEMC_NVT|GEMC_NPT|VIRIAL)", &
246 enum_c_vals=
s2a(
"TRADITIONAL",
"GEMC_NVT",
"GEMC_NPT",
"VIRIAL"), &
252 CALL keyword_create(keyword, __location__, name=
"RESTART_FILE_NAME", &
253 description=
"Name of the restart file for MC information.", &
254 usage=
"RESTART_FILE_NAME {filename}", &
259 CALL keyword_create(keyword, __location__, name=
"MOVES_FILE_NAME", &
260 description=
"The file to print the move statistics to.", &
261 usage=
"MOVES_FILE_NAME {filename}", &
266 CALL keyword_create(keyword, __location__, name=
"MOLECULES_FILE_NAME", &
267 description=
"The file to print the number of molecules to.", &
268 usage=
"MOLECULES_FILE_NAME {filename}", &
273 CALL keyword_create(keyword, __location__, name=
"COORDINATE_FILE_NAME", &
274 description=
"The file to print the current coordinates to.", &
275 usage=
"COORDINATE_FILE_NAME {filename}", &
280 CALL keyword_create(keyword, __location__, name=
"ENERGY_FILE_NAME", &
281 description=
"The file to print current energies to.", &
282 usage=
"ENERGY_FILE_NAME {filename}", &
287 CALL keyword_create(keyword, __location__, name=
"DATA_FILE_NAME", &
288 description=
"The file to print current configurational info to.", &
289 usage=
"DATA_FILE_NAME {filename}", &
294 CALL keyword_create(keyword, __location__, name=
"CELL_FILE_NAME", &
295 description=
"The file to print current cell length info to.", &
296 usage=
"CELL_FILE_NAME {filename}", &
301 CALL keyword_create(keyword, __location__, name=
"MAX_DISP_FILE_NAME", &
302 description=
"The file to print current maximum displacement info to.", &
303 usage=
"MAX_DISP_FILE_NAME {filename}", &
308 CALL keyword_create(keyword, __location__, name=
"BOX2_FILE_NAME", &
309 description=
"For GEMC, the name of the input file for the other box.", &
310 usage=
"BOX2_FILE_NAME {filename}", &
316 description=
"The pressure for NpT simulations, in bar.", &
317 usage=
"PRESSURE {real}", &
323 description=
"The temperature of the simulation, in Kelvin.", &
324 usage=
"TEMPERATURE {real}", &
330 keyword, __location__, name=
"VIRIAL_TEMPS", &
331 description=
"The temperatures you wish to compute the virial coefficient for. Only used if ensemble=VIRIAL.", &
332 usage=
"VIRIAL_TEMPS {real} {real} ... ", &
333 n_var=-1, type_of_var=
real_t)
337 CALL keyword_create(keyword, __location__, name=
"DISCRETE_STEP", &
338 description=
"The size of the discrete volume move step, in angstroms.", &
339 usage=
"DISCRETE_STEP {real}", &
340 default_r_val=1.0e0_dp)
345 description=
"The free energy bias (in Kelvin) for swapping a molecule of each type into this box.", &
346 usage=
"ETA {real} {real} ... ", &
347 n_var=-1, type_of_var=
real_t)
352 description=
"Number of random numbers from the acceptance/rejection stream to skip", &
353 usage=
"RANDOMTOSKIP {integer}", &
358 CALL create_avbmc_section(subsection)
362 CALL create_move_prob_section(subsection)
366 CALL create_update_section(subsection)
370 CALL create_max_disp_section(subsection)
374 END SUBROUTINE create_mc_section
381 SUBROUTINE create_avbmc_section(section)
386 cpassert(.NOT.
ASSOCIATED(section))
389 description=
"Parameters for Aggregation Volume Bias Monte Carlo (AVBMC) "// &
390 "which explores cluster formation and destruction. "// &
391 "Chen and Siepmann, J. Phys. Chem. B 105, 11275-11282 (2001).", &
392 n_keywords=5, n_subsections=0, repeats=.false.)
397 keyword, __location__, name=
"PBIAS", &
398 description=
"The probability of swapping to an inner region in an AVBMC swap move for each molecule type.", &
399 usage=
"PBIAS {real} {real} ... ", &
400 n_var=-1, type_of_var=
real_t)
405 description=
"The target atom for an AVBMC swap move for each molecule type.", &
406 usage=
"AVBMC_ATOM {integer} {integer} ... ", &
412 description=
"The inner radius for an AVBMC swap move, in angstroms for every molecule type.", &
413 usage=
"AVBMC_RMIN {real} {real} ... ", &
414 n_var=-1, type_of_var=
real_t)
419 description=
"The outer radius for an AVBMC swap move, in angstroms, for every molecule type.", &
420 usage=
"AVBMC_RMAX {real} {real} ... ", &
421 n_var=-1, type_of_var=
real_t)
425 END SUBROUTINE create_avbmc_section
433 SUBROUTINE create_move_prob_section(section)
439 cpassert(.NOT.
ASSOCIATED(section))
441 CALL section_create(section, __location__, name=
"move_probabilities", &
442 description=
"Parameters for fraction of moves performed for each move type.", &
443 n_keywords=5, n_subsections=2, repeats=.false.)
445 NULLIFY (keyword, subsection)
448 description=
"The probability of attempting a hybrid MC move.", &
449 usage=
"PMHMC {real}", &
450 type_of_var=
real_t, default_r_val=0.0e0_dp)
455 description=
"The probability of attempting a molecule translation.", &
456 usage=
"PMTRANS {real}", &
462 description=
"The probability of attempting a cluster translation.", &
463 usage=
"PMCLTRANS {real}", &
464 type_of_var=
real_t, default_r_val=0.0e0_dp)
469 description=
"The probability of attempting an AVBMC swap move.", &
470 usage=
"PMAVBMC {real}", &
471 default_r_val=0.0e0_dp)
476 description=
"The probability of attempting a conformational change.", &
477 usage=
"PMTRAION {real}", &
483 description=
"The probability of attempting a swap move.", &
484 usage=
"PMSWAP {real}", &
485 type_of_var=
real_t, default_r_val=0.0e0_dp)
490 description=
"The probability of attempting a volume move.", &
491 usage=
"PMVOLUME {real}", &
492 type_of_var=
real_t, default_r_val=0.0e0_dp)
496 CALL create_mol_prob_section(subsection)
500 CALL create_box_prob_section(subsection)
504 END SUBROUTINE create_move_prob_section
512 SUBROUTINE create_mol_prob_section(section)
517 cpassert(.NOT.
ASSOCIATED(section))
519 CALL section_create(section, __location__, name=
"mol_probabilities", &
520 description=
"Probabilities of attempting various moves types on "// &
521 "the various molecular types present in the simulation.", &
522 n_keywords=5, n_subsections=0, repeats=.false.)
527 description=
"The probability of attempting an AVBMC swap move on each molecule type.", &
528 usage=
"PMAVBMC_MOL {real} {real} ... ", &
529 n_var=-1, type_of_var=
real_t)
534 description=
"The probability of attempting a molecule swap of a given molecule type.", &
535 usage=
"PMSWAP_MOL {real} {real} ... ", &
536 n_var=-1, type_of_var=
real_t)
541 description=
"The probability of attempting a molecule rotation of a given molecule type.", &
542 usage=
"PMROT_MOL {real} {real} ... ", &
543 n_var=-1, type_of_var=
real_t)
548 description=
"The probability of attempting a conformational change of a given molecule type.", &
549 usage=
"PMTRAION_MOL {real} {real} ... ", &
550 n_var=-1, type_of_var=
real_t)
555 description=
"The probability of attempting a molecule translation of a given molecule type.", &
556 usage=
"PMTRANS_MOL {real} {real} ... ", &
557 n_var=-1, type_of_var=
real_t)
561 END SUBROUTINE create_mol_prob_section
569 SUBROUTINE create_box_prob_section(section)
574 cpassert(.NOT.
ASSOCIATED(section))
576 CALL section_create(section, __location__, name=
"BOX_PROBABILITIES", &
577 description=
"Probabilities of attempting various moves types on "// &
579 n_keywords=2, n_subsections=0, repeats=.false.)
584 description=
"The probability of attempting a HMC move on this box.", &
585 usage=
"PMHMC_BOX {real}", &
586 type_of_var=
real_t, default_r_val=1.0e0_dp)
591 description=
"The probability of attempting a volume move on this box (GEMC_NpT).", &
592 usage=
"PMVOL_BOX {real}", &
593 type_of_var=
real_t, default_r_val=1.0e0_dp)
598 description=
"The probability of attempting a cluster move in this box", &
599 usage=
"PMCLUS_BOX {real}", &
600 type_of_var=
real_t, default_r_val=1.0e0_dp)
604 END SUBROUTINE create_box_prob_section
612 SUBROUTINE create_update_section(section)
617 cpassert(.NOT.
ASSOCIATED(section))
620 description=
"Frequency for updating move maximum displacements.", &
621 n_keywords=2, n_subsections=0, repeats=.false.)
626 description=
"Every iupvolume steps update maximum volume displacement.", &
627 usage=
"IUPVOLUME {integer}", &
633 description=
"Every iuptrans steps update maximum "// &
634 "translation/rotation/configurational changes.", &
635 usage=
"IUPTRANS {integer}", &
641 description=
"Every iupcltrans steps update maximum cluster translation.", &
642 usage=
"IUPCLTRANS {integer}", &
647 END SUBROUTINE create_update_section
654 SUBROUTINE create_max_disp_section(section)
659 cpassert(.NOT.
ASSOCIATED(section))
661 CALL section_create(section, __location__, name=
"max_displacements", &
662 description=
"The maximum displacements for all attempted moves.", &
663 n_keywords=1, n_subsections=2, repeats=.false.)
667 CALL create_mol_disp_section(subsection)
671 CALL create_box_disp_section(subsection)
675 END SUBROUTINE create_max_disp_section
683 SUBROUTINE create_mol_disp_section(section)
688 cpassert(.NOT.
ASSOCIATED(section))
690 CALL section_create(section, __location__, name=
"mol_displacements", &
691 description=
"Maximum displacements for every move type that requires "// &
692 "a value for each molecular type in the simulation.", &
693 n_keywords=5, n_subsections=0, repeats=.false.)
698 description=
"Maximum bond length displacement, in angstroms, for each molecule type.", &
699 usage=
"RMBOND {real} {real} ... ", &
700 n_var=-1, type_of_var=
real_t)
705 description=
"Maximum bond angle displacement, in degrees, for each molecule type.", &
706 usage=
"RMANGLE {real} {real} ...", &
707 n_var=-1, type_of_var=
real_t)
712 description=
"Maximum dihedral angle distplacement, in degrees, for each molecule type.", &
713 usage=
"RMDIHEDRAL {real} {real} ... ", &
714 n_var=-1, type_of_var=
real_t)
719 description=
"Maximum rotational displacement, in degrees, for each molecule type.", &
720 usage=
"RMROT {real} {real} ... ", &
721 n_var=-1, type_of_var=
real_t)
726 description=
"Maximum translational displacement, in angstroms, for each molecule type.", &
727 usage=
"RMTRANS {real} {real} ...", &
728 n_var=-1, type_of_var=
real_t)
732 END SUBROUTINE create_mol_disp_section
740 SUBROUTINE create_box_disp_section(section)
745 cpassert(.NOT.
ASSOCIATED(section))
747 CALL section_create(section, __location__, name=
"BOX_DISPLACEMENTS", &
748 description=
"Maximum displacements for any move that is performed on each"// &
749 " simulation box.", &
750 n_keywords=1, n_subsections=0, repeats=.false.)
755 description=
"Maximum volume displacement, in angstrom**3.", &
756 usage=
"RMVOLUME {real}", &
762 description=
"Maximum translational displacement, in angstroms, for each cluster.", &
763 usage=
"RMCLTRANS {real}", &
764 default_r_val=1.0e0_dp)
768 END SUBROUTINE create_box_disp_section
782 RECURSIVE SUBROUTINE create_geoopt_section(section, location, label, description, just_optimizers, use_model_hessian)
784 CHARACTER(LEN=*),
INTENT(IN) :: location, label, description
785 LOGICAL,
INTENT(IN) :: just_optimizers, use_model_hessian
790 cpassert(.NOT.
ASSOCIATED(section))
791 CALL section_create(section, location=location, name=label, description=description, &
792 n_keywords=1, n_subsections=1, repeats=.false.)
795 IF (.NOT. just_optimizers)
THEN
797 description=
"Specify which kind of geometry optimization to perform", &
798 usage=
"TYPE (MINIMIZATION|TRANSITION_STATE)", &
799 enum_c_vals=
s2a(
"MINIMIZATION",
"TRANSITION_STATE"), &
800 enum_desc=
s2a(
"Performs a geometry minimization.", &
801 "Performs a transition state optimization."), &
809 keyword, __location__, name=
"OPTIMIZER", &
810 variants=[
"MINIMIZER"], &
812 description=
"Specify which method to use to perform a geometry optimization.", &
813 usage=
"OPTIMIZER {BFGS|LBFGS|CG}", &
814 enum_c_vals=
s2a(
"BFGS",
"LBFGS",
"CG"), &
815 enum_desc=
s2a(
"Most efficient minimizer, but only for 'small' systems, "// &
816 "as it relies on diagonalization of a full Hessian matrix", &
817 "Limited-memory variant of BFGS suitable for large systems. "// &
818 "Not as well fine-tuned but can be more robust.", &
819 "conjugate gradients, robust minimizer (depending on the line search) also OK for large systems"), &
826 description=
"Specifies the maximum number of geometry optimization steps. "// &
827 "One step might imply several force evaluations for the CG and LBFGS optimizers.", &
828 usage=
"MAX_ITER {integer}", &
834 description=
"Convergence criterion for the maximum geometry change "// &
835 "between the current and the last optimizer iteration.", &
836 usage=
"MAX_DR {real}", &
837 default_r_val=0.0030_dp, unit_str=
"bohr")
842 description=
"Convergence criterion for the maximum force component of the current configuration.", &
843 usage=
"MAX_FORCE {real}", &
844 default_r_val=0.00045_dp, unit_str=
"hartree/bohr")
849 description=
"Convergence criterion for the root mean square (RMS) geometry"// &
850 " change between the current and the last optimizer iteration.", &
851 usage=
"RMS_DR {real}", unit_str=
"bohr", &
852 default_r_val=0.0015_dp)
857 description=
"Convergence criterion for the root mean square (RMS) force of the current configuration.", &
858 usage=
"RMS_FORCE {real}", unit_str=
"hartree/bohr", &
859 default_r_val=0.00030_dp)
863 CALL keyword_create(keyword, __location__, name=
"step_start_val", &
864 description=
"The starting step value for the "//trim(label)//
" module.", &
865 usage=
"step_start_val <integer>", default_i_val=0)
871 keyword, __location__, name=
"KEEP_SPACE_GROUP", &
872 description=
"Detect space group of the system and preserve it during optimization. "// &
873 "The space group symmetry is applied to coordinates, forces, and the stress tensor. "// &
874 "It works for supercell. It does not affect/reduce computational cost. "// &
875 "Use EPS_SYMMETRY to adjust the detection threshold.", &
876 usage=
"KEEP_SPACE_GROUP .TRUE.", &
877 default_l_val=.false., lone_keyword_l_val=.true., repeats=.false.)
883 keyword, __location__, name=
"SHOW_SPACE_GROUP", &
884 description=
"Detect and show space group of the system after optimization. "// &
885 "It works for supercell. It does not affect/reduce computational cost. "// &
886 "Use EPS_SYMMETRY to adjust the detection threshold.", &
887 usage=
"SHOW_SPACE_GROUP .TRUE.", &
888 default_l_val=.false., lone_keyword_l_val=.true., repeats=.false.)
894 keyword, __location__, name=
"EPS_SYMMETRY", &
895 description=
"Accuracy for space group determination. EPS_SYMMETRY is dimensionless. "// &
896 "Roughly speaking, two scaled (fractional) atomic positions v1, v2 are considered identical if |v1 - v2| < EPS_SYMMETRY. ", &
897 usage=
"EPS_SYMMETRY {REAL}", &
898 default_r_val=1.e-4_dp, repeats=.false.)
904 keyword, __location__, name=
"SYMM_REDUCTION", &
905 description=
"Direction of the external static electric field. "// &
906 "Some symmetry operations are not compatible with the direction of an electric field. "// &
907 "These operations are used when enforcing the space group.", &
908 usage=
"SYMM_REDUCTION 0.0 0.0 0.0", &
909 repeats=.false., n_var=3, &
910 type_of_var=
real_t, default_r_vals=[0.0_dp, 0.0_dp, 0.0_dp])
916 keyword, __location__, name=
"SYMM_EXCLUDE_RANGE", &
917 description=
"Range of atoms to exclude from space group symmetry. "// &
918 "These atoms are excluded from both identification and enforcement. "// &
919 "This keyword can be repeated.", &
920 repeats=.true., usage=
"SYMM_EXCLUDE_RANGE {Int} {Int}", type_of_var=
integer_t, n_var=2)
925 keyword, __location__, name=
"SPGR_PRINT_ATOMS", &
926 description=
"Print equivalent atoms list for each space group symmetry operation.", &
927 default_l_val=.false., lone_keyword_l_val=.true.)
931 CALL create_lbfgs_section(subsection)
935 CALL create_cg_section(subsection)
939 CALL create_bfgs_section(subsection, use_model_hessian)
943 IF (.NOT. just_optimizers)
THEN
945 CALL create_ts_section(subsection)
952 description=
"Controls the printing properties during a geometry optimization run", &
953 n_keywords=0, n_subsections=1, repeats=.true.)
956 print_key, __location__,
"program_run_info", &
957 description=
"Controls the printing of basic information during the Geometry Optimization", &
965 END SUBROUTINE create_geoopt_section
972 SUBROUTINE create_shellcore_opt_section(section)
977 CALL create_geoopt_section( &
978 section, __location__, label=
"SHELL_OPT", &
979 description=
"This section sets the environment for the optimization of the shell-core distances"// &
980 " that might turn to be necessary along a MD run using a shell-model potential."// &
981 " The optimization procedure is activated when at least one of the shell-core"// &
982 " pairs becomes too elongated, i.e. when the assumption of point dipole is not longer valid.", &
983 just_optimizers=.true., &
984 use_model_hessian=.false.)
986 NULLIFY (print_key, subsection)
991 description=
"Controls the printing properties during a shell-core optimization procedure", &
992 n_keywords=0, n_subsections=1, repeats=.true.)
995 description=
"Controls the printing of basic information during the Optimization", &
1002 END SUBROUTINE create_shellcore_opt_section
1009 SUBROUTINE create_cell_opt_section(section)
1015 CALL create_geoopt_section(section, __location__, label=
"CELL_OPT", &
1016 description=
"This section sets the environment for the optimization of the simulation cell."// &
1017 " Two possible schemes are available: (1) Zero temperature optimization;"// &
1018 " (2) Finite temperature optimization.", &
1019 just_optimizers=.true., &
1020 use_model_hessian=.false.)
1022 NULLIFY (keyword, print_key, subsection)
1024 keyword, __location__, name=
"TYPE", &
1025 description=
"Specify which kind of method to use for the optimization of the simulation cell", &
1026 usage=
"TYPE (GEO_OPT|MD|DIRECT_CELL_OPT)", &
1027 enum_c_vals=
s2a(
"GEO_OPT",
"MD",
"DIRECT_CELL_OPT"), &
1029 "Performs a geometry optimization (the GEO_OPT section must be defined) between cell optimization steps."// &
1030 " The stress tensor is computed at the optimized geometry.", &
1031 "Performs a molecular dynamics run (the MD section needs must defined) for computing the stress tensor"// &
1032 " used for the cell optimization.", &
1033 "Performs a geometry and cell optimization at the same time."// &
1034 " The stress tensor is computed at every step"), &
1041 keyword, __location__, name=
"EXTERNAL_PRESSURE", &
1042 description=
"Specifies the external pressure (1 value or the full 9 components of the pressure tensor) "// &
1043 "applied during the cell optimization.", &
1044 usage=
"EXTERNAL_PRESSURE {REAL} .. {REAL}", unit_str=
"bar", &
1052 keyword, __location__, name=
"KEEP_ANGLES", &
1053 description=
"Keep angles between the cell vectors constant, but allow the lengths of the"// &
1054 " cell vectors to change independently."// &
1055 " Albeit general, this is most useful for triclinic cells, to enforce higher symmetry, see KEEP_SYMMETRY.", &
1056 usage=
"KEEP_ANGLES TRUE", default_l_val=.false., lone_keyword_l_val=.true.)
1060 CALL keyword_create(keyword, __location__, name=
"KEEP_SYMMETRY", &
1061 description=
"Keep the requested initial cell symmetry (e.g. during a cell optimisation). "// &
1062 "The initial symmetry must be specified in the &CELL section.", &
1063 usage=
"KEEP_SYMMETRY yes", default_l_val=.false., lone_keyword_l_val=.true.)
1068 keyword, __location__, name=
"CONSTRAINT", &
1069 description=
"Imposes a constraint on the pressure tensor by fixing the specified cell components.", &
1070 usage=
"CONSTRAINT (none|x|y|z|xy|xz|yz)", &
1071 enum_desc=
s2a(
"Fix nothing", &
1072 "Fix only x component", &
1073 "Fix only y component", &
1074 "Fix only z component", &
1075 "Fix x and y component", &
1076 "Fix x and z component", &
1077 "Fix y and z component"), &
1078 enum_c_vals=
s2a(
"NONE",
"X",
"Y",
"Z",
"XY",
"XZ",
"YZ"), &
1084 CALL keyword_create(keyword, __location__, name=
"PRESSURE_TOLERANCE", &
1085 description=
"Specifies the Pressure tolerance (compared to the external pressure) to achieve "// &
1086 "during the cell optimization.", &
1087 usage=
"PRESSURE_TOLERANCE {REAL}", unit_str=
"bar", &
1093 NULLIFY (subsection)
1095 description=
"Controls the printing properties during a geometry optimization run", &
1096 n_keywords=0, n_subsections=1, repeats=.true.)
1099 description=
"Controls the printing of basic information during the Geometry Optimization", &
1104 description=
"Controls the printing of the cell eveytime a calculation using a new cell is started.", &
1106 unit_str=
"angstrom")
1112 END SUBROUTINE create_cell_opt_section
1119 SUBROUTINE create_ts_section(section)
1123 TYPE(
section_type),
POINTER :: print_key, subsection, subsection2, &
1128 NULLIFY (section, keyword, subsection, subsection2)
1129 CALL section_create(section, __location__, name=
"TRANSITION_STATE", &
1130 description=
"Specifies parameters to perform a transition state search", &
1131 n_keywords=0, n_subsections=1, repeats=.false.)
1134 description=
"Specify which kind of method to use for locating transition states", &
1136 usage=
"METHOD (DIMER)", &
1137 enum_c_vals=
s2a(
"DIMER"), &
1138 enum_desc=
s2a(
"Uses the dimer method to optimize transition states."), &
1145 description=
"Specifies parameters for Dimer Method", &
1146 n_keywords=0, n_subsections=1, repeats=.false.)
1149 description=
"This keyword sets the value for the DR parameter.", &
1150 usage=
"DR {real}", unit_str=
'angstrom', &
1155 CALL keyword_create(keyword, __location__, name=
"INTERPOLATE_GRADIENT", &
1156 description=
"This keyword controls the interpolation of the gradient whenever possible"// &
1157 " during the optimization of the Dimer. The use of this keywords saves 1 evaluation"// &
1158 " of energy/forces.", usage=
"INTERPOLATE_GRADIENT {logical}", default_l_val=.true., &
1159 lone_keyword_l_val=.true.)
1163 CALL keyword_create(keyword, __location__, name=
"ANGLE_TOLERANCE", &
1164 description=
"This keyword sets the value of the tolerance angle for the line search"// &
1165 " performed to optimize the orientation of the dimer.", &
1166 usage=
"ANGLE_TOLERANCE {real}", unit_str=
'rad', &
1172 description=
"This keyword activates the constrained k-dimer translation"// &
1173 " J. Chem. Phys. 141, 164111 (2014).", &
1175 usage=
"K-DIMER {logica}", &
1176 default_l_val=.false., &
1177 lone_keyword_l_val=.false.)
1182 description=
"Exponential factor for the switching function used in K-DIMER", &
1183 usage=
"BETA {real}", &
1184 default_r_val=5.0_dp, &
1185 lone_keyword_r_val=5.0_dp)
1189 CALL create_geoopt_section( &
1190 subsection2, __location__, label=
"ROT_OPT", &
1191 description=
"This section sets the environment for the optimization of the rotation of the Dimer.", &
1192 just_optimizers=.true., &
1193 use_model_hessian=.false.)
1194 NULLIFY (subsection3)
1196 description=
"Controls the printing properties during the dimer rotation optimization run", &
1197 n_keywords=0, n_subsections=1, repeats=.true.)
1201 description=
"Controls the printing of basic information during the Geometry Optimization", &
1207 description=
"Controls the printing basic info during the cleaning of the "// &
1211 description=
"Prints atomic coordinates after rotation", &
1212 default_l_val=.false., lone_keyword_l_val=.true.)
1223 CALL section_create(subsection2, __location__, name=
"DIMER_VECTOR", &
1224 description=
"Specifies the initial dimer vector (used frequently to restart DIMER calculations)."// &
1225 " If not provided the starting orientation of the dimer is chosen randomly.", &
1226 n_keywords=0, n_subsections=1, repeats=.false.)
1227 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
1228 description=
"Specify on each line the components of the dimer vector.", repeats=.true., &
1229 usage=
"{Real} {Real} {Real}", type_of_var=
real_t, n_var=-1)
1238 END SUBROUTINE create_ts_section
1246 SUBROUTINE create_bfgs_section(section, use_model_hessian)
1248 LOGICAL,
INTENT(IN) :: use_model_hessian
1255 NULLIFY (section, keyword, print_key)
1257 description=
"Provides parameters to tune the BFGS optimization", &
1258 n_keywords=0, n_subsections=1, repeats=.false.)
1260 CALL keyword_create(keyword, __location__, name=
"TRUST_RADIUS", &
1261 description=
"Trust radius used in BFGS. Previously set to 0.1. "// &
1262 "Large values can lead to instabilities", &
1263 usage=
"TRUST_RADIUS {real}", unit_str=
'angstrom', &
1268 CALL keyword_create(keyword, __location__, name=
"USE_MODEL_HESSIAN", &
1269 description=
"Uses a model Hessian as initial guess instead of a unit matrix."// &
1270 " Should lead in general to improved convergence might be switched off for exotic cases", &
1271 usage=
"USE_MODEL_HESSIAN", &
1272 default_l_val=use_model_hessian, lone_keyword_l_val=.true.)
1276 CALL keyword_create(keyword, __location__, name=
"USE_RAT_FUN_OPT", &
1277 description=
"Includes a rational function optimization to determine the step."// &
1278 " Previously default but did not improve convergence in many cases", &
1279 usage=
"USE_RAT_FUN_OPT", &
1280 default_l_val=.false., lone_keyword_l_val=.true.)
1284 CALL keyword_create(keyword, __location__, name=
"RESTART_HESSIAN", &
1285 description=
"Controls the reading of the initial Hessian from file.", &
1286 usage=
"RESTART_HESSIAN", &
1287 default_l_val=.false., lone_keyword_l_val=.true.)
1291 CALL keyword_create(keyword, __location__, name=
"RESTART_FILE_NAME", &
1292 description=
"Specifies the name of the file used to read the initial Hessian.", &
1293 usage=
"RESTART_FILE_NAME {filename}", &
1299 description=
"Controls the printing of Hessian Restart file", &
1301 common_iter_levels=2)
1305 END SUBROUTINE create_bfgs_section
1312 SUBROUTINE create_cg_section(section)
1316 TYPE(
section_type),
POINTER :: subsection, subsubsection
1320 NULLIFY (section, subsection, subsubsection, keyword)
1322 description=
"Provides parameters to tune the conjugate gradient optimization", &
1323 n_keywords=0, n_subsections=1, repeats=.false.)
1325 CALL keyword_create(keyword, __location__, name=
"MAX_STEEP_STEPS", &
1326 description=
"Maximum number of steepest descent steps before starting the"// &
1327 " conjugate gradients optimization.", &
1328 usage=
"MAX_STEEP_STEPS {integer}", &
1333 CALL keyword_create(keyword, __location__, name=
"RESTART_LIMIT", &
1334 description=
"Cosine of the angle between two consecutive searching directions."// &
1335 " If the angle during a CG optimization is less than the one corresponding to"// &
1336 " to the RESTART_LIMIT the CG is reset and one step of steepest descent is"// &
1338 usage=
"RESTART_LIMIT {real}", &
1339 default_r_val=0.9_dp)
1343 CALL keyword_create(keyword, __location__, name=
"FLETCHER_REEVES", &
1344 description=
"Uses FLETCHER-REEVES instead of POLAK-RIBIERE when using Conjugate Gradients", &
1345 usage=
"FLETCHER_REEVES", &
1346 default_l_val=.false., lone_keyword_l_val=.true.)
1351 CALL section_create(subsection, __location__, name=
"LINE_SEARCH", &
1352 description=
"Provides parameters to tune the line search during the conjugate gradient optimization", &
1353 n_keywords=0, n_subsections=1, repeats=.false.)
1356 description=
"1D line search algorithm to be used with the CG optimizer,"// &
1357 " in increasing order of robustness and cost. ", &
1358 usage=
"TYPE GOLD", &
1360 enum_c_vals=
s2a(
"2PNT",
"GOLD",
"FIT"), &
1361 enum_desc=
s2a(
"extrapolate based on 2 points", &
1362 "perform 1D golden section search of the minimum (very expensive)", &
1363 "perform 1D fit of a parabola on several evaluation of energy "// &
1364 "(very expensive and more robust vs numerical noise)"), &
1370 NULLIFY (subsubsection)
1372 description=
"Provides parameters to tune the line search for the two point based line search.", &
1373 n_keywords=0, n_subsections=1, repeats=.false.)
1375 CALL keyword_create(keyword, __location__, name=
"MAX_ALLOWED_STEP", &
1376 description=
"Max allowed value for the line search step.", &
1377 usage=
"MAX_ALLOWED_STEP {real}", unit_str=
"internal_cp2k", &
1378 default_r_val=0.25_dp)
1383 keyword, __location__, name=
"LINMIN_GRAD_ONLY", &
1384 description=
"Use only the gradient, not the energy for line minimizations (e.g. in conjugate gradients).", &
1385 usage=
"LINMIN_GRAD_ONLY T", &
1386 default_l_val=.false., lone_keyword_l_val=.true.)
1394 NULLIFY (subsubsection)
1396 description=
"Provides parameters to tune the line search for the gold search.", &
1397 n_keywords=0, n_subsections=1, repeats=.false.)
1399 CALL keyword_create(keyword, __location__, name=
"INITIAL_STEP", &
1400 description=
"Initial step size used, e.g. for bracketing or minimizers. "// &
1401 "Might need to be reduced for systems with close contacts", &
1402 usage=
"INITIAL_STEP {real}", unit_str=
"internal_cp2k", &
1403 default_r_val=0.2_dp)
1408 description=
"Limit in 1D bracketing during line search in Conjugate Gradients Optimization.", &
1409 usage=
"BRACK_LIMIT {real}", unit_str=
"internal_cp2k", &
1410 default_r_val=100.0_dp)
1415 description=
"Tolerance requested during Brent line search in Conjugate Gradients Optimization.", &
1416 usage=
"BRENT_TOL {real}", unit_str=
"internal_cp2k", &
1417 default_r_val=0.01_dp)
1421 CALL keyword_create(keyword, __location__, name=
"BRENT_MAX_ITER", &
1422 description=
"Maximum number of iterations in brent algorithm "// &
1423 "(used for the line search in Conjugated Gradients Optimization)", &
1424 usage=
"BRENT_MAX_ITER {integer}", &
1433 END SUBROUTINE create_cg_section
1440 SUBROUTINE create_lbfgs_section(section)
1447 NULLIFY (section, keyword)
1449 description=
"Provides parameters to tune the limited memory BFGS (LBFGS) optimization", &
1450 n_keywords=0, n_subsections=1, repeats=.false., &
1454 description=
"Maximum rank (and consequently size) of the "// &
1455 "approximate Hessian matrix used by the LBFGS optimizer. "// &
1456 "Larger values (e.g. 30) will accelerate the convergence behaviour "// &
1457 "at the cost of a larger memory consumption.", &
1458 usage=
"MAX_H_RANK {integer}", &
1463 CALL keyword_create(keyword, __location__, name=
"MAX_F_PER_ITER", &
1464 description=
"Maximum number of force evaluations per iteration"// &
1465 " (used for the line search)", &
1466 usage=
"MAX_F_PER_ITER {integer}", &
1471 CALL keyword_create(keyword, __location__, name=
"WANTED_PROJ_GRADIENT", &
1472 description=
"Convergence criterion (overrides the general ones):"// &
1473 " Requested norm threshold of the gradient multiplied"// &
1474 " by the approximate Hessian.", &
1475 usage=
"WANTED_PROJ_GRADIENT {real}", unit_str=
"internal_cp2k", &
1476 default_r_val=1.0e-16_dp)
1480 CALL keyword_create(keyword, __location__, name=
"WANTED_REL_F_ERROR", &
1481 description=
"Convergence criterion (overrides the general ones):"// &
1482 " Requested relative error on the objective function"// &
1483 " of the optimizer (the energy)", &
1484 usage=
"WANTED_REL_F_ERROR {real}", unit_str=
"internal_cp2k", &
1485 default_r_val=1.0e-16_dp)
1490 keyword, __location__, name=
"TRUST_RADIUS", &
1491 description=
"Trust radius used in LBFGS. Not completely in depth tested. Negativ values means no trust radius is used.", &
1492 usage=
"TRUST_RADIUS {real}", unit_str=
'angstrom', &
1493 default_r_val=-1.0_dp)
1497 END SUBROUTINE create_lbfgs_section
1504 SUBROUTINE create_fp_section(section)
1510 cpassert(.NOT.
ASSOCIATED(section))
1511 CALL section_create(section, __location__, name=
"FLEXIBLE_PARTITIONING", &
1512 description=
"This section sets up flexible_partitioning", &
1513 n_keywords=1, n_subsections=1, repeats=.false.)
1515 NULLIFY (keyword, print_key)
1517 CALL keyword_create(keyword, __location__, name=
"CENTRAL_ATOM", &
1518 description=
"Specifies the central atom.", &
1519 usage=
"CENTRAL_ATOM {integer}", &
1525 description=
"Specifies the list of atoms that should remain close to the central atom.", &
1526 usage=
"INNER_ATOMS {integer} {integer} .. {integer}", &
1532 description=
"Specifies the list of atoms that should remain far from the central atom.", &
1533 usage=
"OUTER_ATOMS {integer} {integer} .. {integer}", &
1538 CALL keyword_create(keyword, __location__, name=
"INNER_RADIUS", &
1539 description=
"radius of the inner wall", &
1540 usage=
"INNER_RADIUS {real} ", type_of_var=
real_t, &
1541 n_var=1, unit_str=
"angstrom")
1545 CALL keyword_create(keyword, __location__, name=
"OUTER_RADIUS", &
1546 description=
"radius of the outer wall", &
1547 usage=
"OUTER_RADIUS {real} ", type_of_var=
real_t, &
1548 n_var=1, unit_str=
"angstrom")
1553 description=
"Sets the force constant of the repulsive harmonic potential", &
1554 usage=
"STRENGTH 1.0", default_r_val=1.0_dp)
1559 description=
"If a bias potential counter-acting the weight term should be applied (recommended).", &
1560 usage=
"BIAS F", default_l_val=.true., lone_keyword_l_val=.true.)
1565 description=
"Sets the temperature parameter that is used in the baising potential."// &
1566 " It is recommended to use the actual simulation temperature", &
1567 usage=
"TEMPERATURE 300", default_r_val=300.0_dp, unit_str=
'K')
1571 CALL keyword_create(keyword, __location__, name=
"SMOOTH_WIDTH", &
1572 description=
"Sets the width of the smooth counting function.", &
1573 usage=
"SMOOTH_WIDTH 0.2", default_r_val=0.02_dp, unit_str=
'angstrom')
1578 description=
"Controls the printing of FP info during flexible partitioning simulations.", &
1580 filename=
"FLEXIBLE_PARTIONING")
1585 description=
"Controls the printing of FP info at startup", &
1587 filename=
"__STD_OUT__")
1591 END SUBROUTINE create_fp_section
1598 SUBROUTINE create_driver_section(section)
1603 cpassert(.NOT.
ASSOCIATED(section))
1605 description=
"This section defines the parameters needed to run in i-PI driver mode.", &
1607 n_keywords=3, n_subsections=0, repeats=.false.)
1611 description=
"Use a UNIX socket rather than an INET socket.", &
1612 usage=
"unix LOGICAL", &
1613 default_l_val=.false., lone_keyword_l_val=.true.)
1618 description=
"Port number for the i-PI server.", &
1619 usage=
"port <INTEGER>", &
1620 default_i_val=12345)
1625 description=
"Host name for the i-PI server.", &
1626 usage=
"host <HOSTNAME>", &
1627 default_c_val=
"localhost")
1632 description=
"Sleeping time while waiting for for driver commands [s].", &
1633 usage=
"SLEEP_TIME 0.1", &
1634 default_r_val=0.01_dp)
1638 END SUBROUTINE create_driver_section
1645 SUBROUTINE create_pint_section(section)
1649 TYPE(
section_type),
POINTER :: print_key, subsection, subsubsection
1651 cpassert(.NOT.
ASSOCIATED(section))
1653 description=
"The section that controls a path integral run", &
1654 n_keywords=13, n_subsections=9, repeats=.false.)
1658 description=
"Specify number beads to use", repeats=.false., &
1662 CALL keyword_create(keyword, __location__, name=
"proc_per_replica", &
1663 description=
"Specify number of processors to use for each replica", &
1664 repeats=.false., default_i_val=0)
1668 description=
"Number of steps (if MAX_STEP is not explicitly given"// &
1669 " the program will perform this number of steps)", repeats=.false., &
1674 description=
"Maximum step number (the program will stop if"// &
1675 " ITERATION >= MAX_STEP even if NUM_STEPS has not been reached)", &
1676 repeats=.false., default_i_val=10)
1680 description=
"Specify the iteration number from which it should be "// &
1681 "counted", default_i_val=0)
1685 description=
"The temperature you want to simulate", &
1690 CALL keyword_create(keyword, __location__, name=
"kT_CORRECTION", &
1691 description=
"Corrects for the loss of temperature due to constrained "// &
1692 "degrees of freedom for Nose-Hover chains and numeric integration", &
1693 repeats=.false., default_l_val=.false.)
1696 CALL keyword_create(keyword, __location__, name=
"T_tol", variants=[
"temp_to"], &
1697 description=
"threshold for the oscillations of the temperature "// &
1698 "excedeed which the temperature is rescaled. 0 means no rescaling.", &
1699 default_r_val=0._dp, unit_str=
"K")
1703 description=
"timestep (might be subdivised in nrespa subtimesteps", &
1706 usage=
"dt 1.0", unit_str=
"fs")
1710 description=
"integrator scheme for integrating the harmonic bead springs.", &
1711 usage=
"HARM_INT (NUMERIC|EXACT)", &
1713 enum_c_vals=
s2a(
"NUMERIC",
"EXACT"), &
1718 description=
"number of respa steps for the bead for each md step", &
1719 repeats=.false., default_i_val=5)
1723 CALL keyword_create(keyword, __location__, name=
"transformation", &
1724 description=
"Specifies the coordinate transformation to use", &
1725 usage=
"TRANSFORMATION (NORMAL|STAGE)", &
1727 enum_c_vals=
s2a(
"NORMAL",
"STAGE"), &
1733 description=
"Specifies the real time propagator to use", &
1734 usage=
"PROPAGATOR (PIMD|RPMD|CMD)", &
1736 enum_c_vals=
s2a(
"PIMD",
"RPMD",
"CMD"), &
1740 CALL keyword_create(keyword, __location__, name=
"FIX_CENTROID_POS", &
1741 description=
"Propagate all DOF but the centroid - "// &
1742 "useful for equilibration of the non-centroid modes "// &
1743 "(activated only if TRANSFORMATION==NORMAL)", &
1744 repeats=.false., default_l_val=.false., &
1745 lone_keyword_l_val=.true.)
1749 NULLIFY (subsection, subsubsection)
1750 CALL section_create(subsection, __location__, name=
"NORMALMODE", &
1751 description=
"Controls the normal mode transformation", &
1752 n_keywords=3, n_subsections=0, repeats=.false.)
1754 description=
"Value of the thermostat mass of centroid degree of freedom", &
1755 repeats=.false., default_r_val=-1.0_dp)
1759 description=
"Value of the thermostat mass of non-centroid degrees of freedom", &
1760 repeats=.false., default_r_val=-1.0_dp)
1764 description=
"mass scale factor for non-centroid degrees of freedom", &
1765 repeats=.false., default_r_val=1.0_dp)
1769 description=
"mass scale factor for non-centroid degrees of freedom, &
1770& naming convention according to Witt, 2008, <https://doi.org/10.1063/1.3125009>.", &
1771 repeats=.false., default_r_val=8.0_dp)
1779 description=
"The section that controls the staging transformation", &
1780 n_keywords=2, n_subsections=0, repeats=.false.)
1782 description=
"Value of the j parameter for the staging transformation", &
1783 repeats=.false., default_i_val=2)
1787 description=
"Value of the nose-hoover mass for the endbead (Q_end)", &
1788 repeats=.false., default_i_val=2)
1795 description=
"Sets positions and velocities of the beads", &
1796 n_keywords=0, n_subsections=2, &
1798 CALL create_coord_section(subsubsection,
"BEADS")
1801 CALL create_velocity_section(subsubsection,
"BEADS")
1808 description=
"Controls the Nose-Hoover thermostats", &
1809 n_keywords=1, n_subsections=2, &
1812 description=
"length of nose-hoover chain. 0 means no thermostat", &
1813 repeats=.false., default_i_val=2)
1816 CALL create_coord_section(subsubsection,
"NOSE")
1819 CALL create_velocity_section(subsubsection,
"NOSE")
1830 description=
"Controls the PI Langevin Equation thermostat."// &
1831 " Needs the exact harmonic integrator."// &
1832 " May lead to unphysical motions if constraint e.g. FIXED_ATOMS, is applied."// &
1833 " RESTART_HELIUM section has to be .FALSE. when restarting the PIGLET job.", &
1835 n_keywords=3, n_subsections=1, &
1841 description=
"Time constant for centroid motion. "// &
1842 "If zero or negative the centroid is not thermostated.", &
1843 usage=
"TAU {real}", type_of_var=
real_t, &
1844 unit_str=
"fs", n_var=1, default_r_val=1000.0_dp)
1848 description=
"Scaling of friction to mode coupling", &
1849 usage=
"LAMBDA {real}", type_of_var=
real_t, &
1850 n_var=1, default_r_val=0.5_dp)
1853 CALL keyword_create(keyword, __location__, name=
"THERMOSTAT_ENERGY", &
1854 description=
"Thermostat energy for conserved quantity. "// &
1855 "Only useful in restart files.", &
1856 usage=
"THERMOSTAT_ENERGY {real}", type_of_var=
real_t, &
1857 n_var=1, default_r_val=0.0_dp)
1864 description=
"Controls the PI Generalized Langevin Equation thermostat."// &
1865 " Needs the exact harmonic integrator", &
1867 n_keywords=4, n_subsections=2, &
1872 CALL section_create(subsubsection, __location__, name=
"EXTRA_DOF", &
1873 description=
"Additional degrees of freedom to ensure Markovian Dynamics.", &
1874 n_keywords=1, n_subsections=0, repeats=.false.)
1875 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
1876 description=
"Restart values for additional degrees of freedom" &
1877 //
" (only for restarts, do not set explicitly)", &
1879 type_of_var=
real_t, n_var=-1)
1885 description=
"Number of extra degrees of freedom to ensure markovian dynamics", &
1886 repeats=.false., default_i_val=8)
1889 CALL keyword_create(keyword, __location__, name=
"MATRICES_FILE_NAME", &
1890 description=
"Filename containig the raw matrices from "// &
1891 "<https://gle4md.org/index.html?page=matrix>.", &
1892 repeats=.false., default_lc_val=
"PIGLET.MAT")
1895 CALL keyword_create(keyword, __location__, name=
"SMATRIX_INIT", &
1896 description=
"Select algorithm to initialize piglet S-matrices", &
1897 usage=
"SMATRIX_INIT (CHOLESKY|DIAGONAL)", &
1899 enum_c_vals=
s2a(
"CHOLESKY",
"DIAGONAL"), &
1903 CALL keyword_create(keyword, __location__, name=
"THERMOSTAT_ENERGY", &
1904 description=
"Thermostat energy for conserved quantity. "// &
1905 "Only useful in restart files.", &
1906 usage=
"THERMOSTAT_ENERGY {real}", type_of_var=
real_t, &
1907 n_var=1, default_r_val=0.0_dp)
1914 description=
"Controls the QTB-PILE thermostat."// &
1915 " Needs the exact harmonic integrator", &
1917 n_keywords=7, n_subsections=1, &
1923 description=
"Time constant for centroid motion. ", &
1924 usage=
"TAU {real}", type_of_var=
real_t, &
1925 unit_str=
"fs", n_var=1, default_r_val=1000.0_dp)
1929 description=
"Scaling of friction to ring polymer NM freq.", &
1930 usage=
"LAMBDA {real}", type_of_var=
real_t, &
1931 n_var=1, default_r_val=0.5_dp)
1935 description=
"Defines which version to use "// &
1936 "0: f_P^(0), 1: f_P^(1)", &
1937 usage=
"FP {integer}", type_of_var=
integer_t, &
1938 n_var=1, default_i_val=1)
1942 description=
"Inverse of cutoff freq. for the centroid mode", &
1943 usage=
"TAUCUT {real}", type_of_var=
real_t, &
1944 unit_str=
"fs", n_var=1, default_r_val=0.5_dp)
1948 description=
"Scaling of cutoff freq. to ring polymer NM freq.", &
1949 usage=
"LAMBCUT {real}", type_of_var=
real_t, &
1950 n_var=1, default_r_val=2.0_dp)
1954 description=
"Number of points used for the convolution product.", &
1955 usage=
"NF {integer}", type_of_var=
integer_t, &
1956 n_var=1, default_i_val=128)
1959 CALL keyword_create(keyword, __location__, name=
"THERMOSTAT_ENERGY", &
1960 description=
"Thermostat energy for conserved quantity. "// &
1961 "Only useful in restart files.", &
1962 usage=
"THERMOSTAT_ENERGY {real}", type_of_var=
real_t, &
1963 n_var=1, default_r_val=0.0_dp)
1970 description=
"Controls the initialization if the beads are not present", &
1973 CALL keyword_create(keyword, __location__, name=
"LEVY_POS_SAMPLE", &
1974 description=
"Sample bead positions assuming free particle "// &
1975 "behavior (performs a Levy random walk of length P around "// &
1976 "the classical position of each atom at the physical "// &
1977 "temperature defined in PINT%TEMP)", &
1978 repeats=.false., default_l_val=.false., &
1979 lone_keyword_l_val=.true.)
1982 CALL keyword_create(keyword, __location__, name=
"LEVY_CORRELATED", &
1983 description=
"Use the same Levy path for all atoms, though "// &
1984 "with mass-dependent variances (might help at very low T)", &
1985 repeats=.false., default_l_val=.false., &
1986 lone_keyword_l_val=.true.)
1989 CALL keyword_create(keyword, __location__, name=
"LEVY_TEMP_FACTOR", &
1990 description=
"Multiplicative correction factor for the "// &
1991 "temperature at which the Levy walk is performed "// &
1992 "(correction is due to the interactions that modify "// &
1993 "the spread of a free particle)", &
1994 repeats=.false., default_r_val=1.0_dp)
1998 description=
"Initial seed for the (pseudo)random number "// &
1999 "generator that controls Levy walk for bead positions.", &
2000 usage=
"LEVY_SEED <INTEGER>", default_i_val=1234, &
2004 CALL keyword_create(keyword, __location__, name=
"THERMOSTAT_SEED", &
2005 description=
"Initial seed for the (pseudo)random number "// &
2006 "generator that controls the PILE and PIGLET thermostats.", &
2007 usage=
"THERMOSTAT_SEED <INTEGER>", default_i_val=12345, &
2011 CALL keyword_create(keyword, __location__, name=
"RANDOMIZE_POS", &
2012 description=
"add gaussian noise to the positions of the beads", &
2013 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2017 CALL keyword_create(keyword, __location__, name=
"CENTROID_SPEED", &
2018 description=
"adds random velocity component to the centroid modes "// &
2019 "(useful to correct for the averaging out of the speed of various beads)", &
2020 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2024 CALL keyword_create(keyword, __location__, name=
"VELOCITY_QUENCH", &
2025 description=
"set the initial velocities to zero", &
2026 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2029 CALL keyword_create(keyword, __location__, name=
"VELOCITY_SCALE", &
2030 description=
"scale initial velocities to the temperature given in MOTION%PINT%TEMP", &
2031 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2038 CALL create_helium_section(subsection)
2043 description=
"Controls the path integral-specific output", &
2044 n_keywords=2, n_subsections=0, repeats=.false.)
2049 description=
"Controls the output of the path integral energies", &
2055 description=
"Controls the output of the path integral action", &
2061 description=
"Controls the output of the centroid's position", &
2062 unit_str=
"angstrom", &
2065 description=
"Output file format for the positions of centroid")
2070 description=
"Controls the output of the centroid's velocity", &
2071 unit_str=
"bohr*au_t^-1", &
2074 description=
"Output file format for the velocity of centroid")
2079 description=
"Controls the output of the centroid's radii of gyration", &
2080 unit_str=
"angstrom", &
2086 description=
"Controls the output of the center of mass", &
2091 CALL keyword_create(keyword, __location__, name=
"IMAGINARY_TIME_STRIDE", &
2092 description=
"Prints only every nth bead trajectory", &
2093 repeats=.false., default_i_val=1)
2100 END SUBROUTINE create_pint_section
2110 SUBROUTINE create_helium_section(section)
2114 TYPE(
section_type),
POINTER :: print_key, subsection, subsubsection
2116 cpassert(.NOT.
ASSOCIATED(section))
2119 description=
"The section that controls optional helium solvent"// &
2120 " environment (highly experimental, not for general use yet)", &
2121 n_keywords=31, n_subsections=11, repeats=.false.)
2124 CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
2125 description=
"Whether or not to actually use this section", &
2126 usage=
"silent", default_l_val=.false., lone_keyword_l_val=.true.)
2131 description=
"Simulate helium solvent only, "// &
2132 "disregard solute entirely", &
2133 repeats=.false., default_l_val=.false., &
2134 lone_keyword_l_val=.true.)
2138 CALL keyword_create(keyword, __location__, name=
"INTERACTION_POT_SCAN", &
2139 description=
"Scan solute-helium interaction potential, "// &
2140 "cubefile parameters set in subsection RHO", &
2141 repeats=.false., default_l_val=.false., &
2142 lone_keyword_l_val=.true.)
2147 description=
"Number of independent helium environments", &
2148 repeats=.false., default_i_val=1)
2152 CALL keyword_create(keyword, __location__, name=
"POTENTIAL_FILE_NAME", &
2153 description=
"Name of the Helium interaction potential file", &
2154 repeats=.false., default_lc_val=
"HELIUM.POT")
2159 description=
"Get average MC forces or last MC forces to propagate MD", &
2160 usage=
"GET_FORCES (AVERAGE|LAST)", &
2162 enum_c_vals=
s2a(
"AVERAGE",
"LAST"), &
2167 CALL keyword_create(keyword, __location__, name=
"SOLUTE_INTERACTION", &
2168 description=
"Interaction potential between helium and the solute", &
2169 usage=
"SOLUTE_INTERACTION (NONE | MWATER | NNP)", &
2171 enum_c_vals=
s2a(
"NONE",
"MWATER",
"NNP"), &
2177 "No interaction with solute", &
2178 "Test interaction with wrong Water", &
2179 "Interaction with NNP"))
2184 description=
"Number of helium atoms", &
2185 repeats=.false., default_i_val=64)
2190 description=
"Number of helium path integral beads", &
2191 repeats=.false., default_i_val=25)
2196 description=
"Initial seed for the (pseudo)random number "// &
2197 "generator that controls helium coordinate generation and propagation.", &
2198 usage=
"RNG_SEED <INTEGER>", default_i_val=12345, &
2204 variants=
s2a(
"INOROT"), &
2205 description=
"Number of MC iterations at the same time slice(s) "// &
2206 "(number of inner MC loop iterations)", &
2207 repeats=.false., default_i_val=6600)
2212 variants=
s2a(
"IROT"), &
2213 description=
"how often to reselect the time slice(s) to work on "// &
2214 "(number of outer MC loop iterations)", &
2215 repeats=.false., default_i_val=300)
2219 CALL keyword_create(keyword, __location__, name=
"SAMPLING_METHOD", &
2220 description=
"Choose between Ceperley or the worm algorithm", &
2221 usage=
"SAMPLING_METHOD (CEPERLEY|WORM)", &
2223 enum_c_vals=
s2a(
"CEPERLEY",
"WORM"), &
2228 CALL keyword_create(keyword, __location__, name=
"COORD_INIT_TEMP", &
2229 description=
"Temperature for thermal gaussian initialization of the helium."// &
2230 " Negative values correspond to a hot start.", &
2236 CALL keyword_create(keyword, __location__, name=
"SOLUTE_RADIUS", &
2237 description=
"Radius of the solute molecule for prevention of"// &
2238 " coordinate collision during initialization", &
2240 repeats=.false., type_of_var=
real_t, unit_str=
"angstrom")
2245 NULLIFY (subsection)
2247 description=
"This section contains all information to run an helium-solute "// &
2248 "interaction Neural Network Potential (NNP) calculation.", &
2249 n_keywords=2, n_subsections=3, repeats=.false.)
2251 CALL keyword_create(keyword, __location__, name=
"NNP_INPUT_FILE_NAME", &
2252 description=
"File containing the input information for the setup "// &
2253 "of the NNP (n2p2/RuNNer format). ", &
2254 repeats=.false., default_lc_val=
"input.nn")
2258 CALL keyword_create(keyword, __location__, name=
"SCALE_FILE_NAME", &
2259 description=
"File containing the scaling information for the symmetry "// &
2260 "functions of the NNP. ", &
2261 repeats=.false., default_lc_val=
"scaling.data")
2265 NULLIFY (subsubsection)
2266 CALL section_create(subsubsection, __location__, name=
"SR_CUTOFF", &
2267 description=
"Section for failsafe short range cutoffs for the NNPs, "// &
2268 "if the distance between solvent and specified solute element becomes "// &
2269 "smaller than the given cutoff, an artifical repulsive potential is "// &
2270 "introduced. Note this is only meant to prevent such configurations, "// &
2271 "not to physically sample them.", &
2272 n_keywords=2, n_subsections=0, repeats=.true.)
2275 description=
"Solute element for which the short range cutoff is in effect", &
2276 repeats=.false., default_c_val=
"none")
2281 description=
"Short range cutoff in Angstrom, below this cutoff, the energy "// &
2282 "is replaced by a sizable positive value plus a 1/r**2 term to guide particles "// &
2283 "away from each other.", &
2285 repeats=.false., type_of_var=
real_t, unit_str=
"angstrom")
2291 NULLIFY (subsubsection)
2293 description=
"Section for a single NNP model. If this section is repeated, "// &
2294 "a committee model (C-NNP)is used where the NNP members share the same "// &
2295 "symmetry functions. ", &
2296 n_keywords=1, n_subsections=0, repeats=.true.)
2299 description=
"File containing the weights for the artificial neural "// &
2300 "networks of the NNP. The specified name is extended by .XXX.data ", &
2301 repeats=.false., default_lc_val=
"weights")
2308 NULLIFY (subsubsection)
2310 description=
"Section of possible print options in NNP code.", &
2311 n_keywords=0, n_subsections=3, repeats=.false.)
2312 NULLIFY (print_key, keyword)
2315 description=
"Controls the printing of the NNP energies.", &
2321 description=
"Controls the printing of the STD per atom of the NNP forces.", &
2327 description=
"If activated, output structures with extrapolation "// &
2328 "warning in xyz-format", &
2339 NULLIFY (subsection)
2341 description=
"Enables sampling with Ceperley's algorithm", &
2342 n_keywords=2, n_subsections=1, repeats=.false.)
2345 description=
"how many time slices to change at once (+1). "// &
2346 "Must be a power of 2 currently", &
2347 repeats=.false., default_i_val=8)
2351 CALL keyword_create(keyword, __location__, name=
"MAX_PERM_CYCLE", &
2352 description=
"how large cyclic permutations to try", &
2353 repeats=.false., default_i_val=6)
2357 NULLIFY (subsubsection)
2358 CALL section_create(subsubsection, __location__, name=
"M-SAMPLING", &
2359 description=
"Permutation cycle length sampling settings", &
2360 n_keywords=3, n_subsections=0, repeats=.false.)
2361 CALL keyword_create(keyword, __location__, name=
"DISTRIBUTION-TYPE", &
2362 description=
"Distribution from which the cycle length m is sampled", &
2363 usage=
"DISTRIBUTION-TYPE (SINGLEV|UNIFORM|LINEAR|QUADRATIC|EXPONENTIAL|GAUSSIAN)", &
2382 description=
"Value of m treated in a special way "// &
2383 "(specific behavior depends on the distribution type chosen)", &
2389 description=
"Probability ratio betw M-VALUE and other cycle lengths", &
2391 default_r_val=1.0_dp)
2400 NULLIFY (subsection)
2402 description=
"Enables sampling via the canonical worm algorithm adapted from Bonisegni", &
2403 n_keywords=12, n_subsections=0, repeats=.false.)
2405 CALL keyword_create(keyword, __location__, name=
"CENTROID_DRMAX", &
2406 description=
"Maximum displacement allowed for the centroid moves", &
2407 repeats=.false., default_r_val=0.5_dp)
2412 description=
"From 2 up to max. L-1 beads will be moved", &
2413 repeats=.false., default_i_val=5)
2417 CALL keyword_create(keyword, __location__, name=
"OPEN_CLOSE_SCALE", &
2418 description=
"Open/Close acceptance adjustment parameter", &
2419 repeats=.false., default_r_val=0.01_dp)
2424 description=
"Enable bosonic exchange sampling", &
2425 repeats=.false., default_l_val=.true.)
2429 CALL keyword_create(keyword, __location__, name=
"MAX_OPEN_CYCLES", &
2430 description=
"If > 0 then reset positions and permutations to the previous closed &
2431 & state if staying more than this amount of MC cycles in open state to avoid staying &
2432 & trapped in open state for too long. Use with caution as it can potentially introduce &
2433 & a bias in the sampling.", &
2434 repeats=.false., default_i_val=0)
2438 CALL keyword_create(keyword, __location__, name=
"SHOW_STATISTICS", &
2439 description=
"Show sampling statistics in output", &
2440 repeats=.false., default_l_val=.true.)
2444 CALL keyword_create(keyword, __location__, name=
"CENTROID_WEIGHT", &
2445 description=
"Absolute weight of the centroid move", &
2446 repeats=.false., default_i_val=10)
2450 CALL keyword_create(keyword, __location__, name=
"STAGING_WEIGHT", &
2451 description=
"Absolute weight of the staging move", &
2452 repeats=.false., default_i_val=30)
2456 CALL keyword_create(keyword, __location__, name=
"OPEN_CLOSE_WEIGHT", &
2457 description=
"Absolute weight of the open/close move", &
2458 repeats=.false., default_i_val=10)
2462 CALL keyword_create(keyword, __location__, name=
"HEAD_TAIL_WEIGHT", &
2463 description=
"Absolute weight of the head/tail moves (both)", &
2464 repeats=.false., default_i_val=10)
2468 CALL keyword_create(keyword, __location__, name=
"CRAWL_WEIGHT", &
2469 description=
"Absolute weight of the crawl bwd/fwd moves (both)", &
2470 repeats=.false., default_i_val=10)
2474 CALL keyword_create(keyword, __location__, name=
"CRAWL_REPETITION", &
2475 description=
"Number of repeated crawl moves", &
2476 repeats=.false., default_i_val=4)
2481 description=
"Absolute weight of the crawl move", &
2482 repeats=.false., default_i_val=10)
2492 description=
"Use periodic boundary conditions for helium", &
2493 repeats=.false., default_l_val=.false.)
2498 description=
"PBC unit cell size (NOTE 1: density, number of atoms"// &
2499 " and volume are interdependent - give only two of them; "// &
2500 "NOTE 2: for small cell sizes specify NATOMS instead)", &
2501 repeats=.false., type_of_var=
real_t, unit_str=
"angstrom")
2506 description=
"PBC unit cell shape for helium", &
2507 usage=
"CELL_SHAPE (CUBE|OCTAHEDRON)", &
2509 enum_c_vals=
s2a(
"CUBE",
"OCTAHEDRON"), &
2514 CALL keyword_create(keyword, __location__, name=
"DROPLET_RADIUS", &
2515 description=
"Reject a move if any of the new positions does not lie within"// &
2516 " this range from the center of gravity", &
2517 repeats=.false., type_of_var=
real_t, default_r_val=huge(1.0_dp), &
2518 unit_str=
"angstrom")
2523 description=
"trial density of helium for determining the helium "// &
2527 unit_str=
"angstrom^-3")
2532 description=
"Presample He coordinates before first PIMD step", &
2533 repeats=.false., default_l_val=.false.)
2538 description=
"Radial distribution settings", &
2539 n_keywords=5, n_subsections=0, repeats=.false.)
2541 CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
2542 description=
"Whether or not to actually calculate this property", &
2543 default_l_val=.false., lone_keyword_l_val=.true.)
2548 description=
"Maximum RDF range, defaults to unit cell size", &
2549 repeats=.false., type_of_var=
real_t, &
2550 unit_str=
"angstrom")
2555 description=
"Number of bins", &
2562 description=
"Whether or not to calculate solute-He RDFs (if solute is present)", &
2563 default_l_val=.true., lone_keyword_l_val=.true.)
2568 description=
"Whether or not to calculate He-He RDFs", &
2569 default_l_val=.false., lone_keyword_l_val=.true.)
2576 NULLIFY (subsection)
2578 description=
"Spatial distribution settings", &
2579 n_keywords=10, n_subsections=0, repeats=.false.)
2580 CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
2581 description=
"Whether or not to actually calculate densities "// &
2582 "(requires significant amount of memory, depending on the value of NBIN)", &
2583 default_l_val=.false., lone_keyword_l_val=.true.)
2587 description=
"Number of grid points in each direction for density binning", &
2593 CALL keyword_create(keyword, __location__, name=
"MIN_CYCLE_LENGTHS_WDG", &
2594 description=
"Density of winding paths "// &
2595 "not shorter than the given length", &
2596 repeats=.false., usage=
"MIN_CYCLE_LENGTHS_WDG <INT> <INT> .. <INT>", &
2601 CALL keyword_create(keyword, __location__, name=
"MIN_CYCLE_LENGTHS_NON", &
2602 description=
"Density of non-winding paths "// &
2603 "not shorter than the given length", &
2604 repeats=.false., usage=
"MIN_CYCLE_LENGTHS_NON <INT> <INT> .. <INT>", &
2609 CALL keyword_create(keyword, __location__, name=
"MIN_CYCLE_LENGTHS_ALL", &
2610 description=
"Density of all paths "// &
2611 "not shorter than the given length", &
2612 repeats=.false., usage=
"MIN_CYCLE_LENGTHS_ALL <INT> <INT> .. <INT>", &
2618 description=
"Atom number density", &
2621 default_l_val=.true., &
2622 lone_keyword_l_val=.true.)
2626 CALL keyword_create(keyword, __location__, name=
"PROJECTED_AREA_2", &
2627 description=
"Projected area squared density, A*A(r)", &
2630 default_l_val=.false., &
2631 lone_keyword_l_val=.true.)
2635 CALL keyword_create(keyword, __location__, name=
"WINDING_NUMBER_2", &
2636 description=
"Winding number squared density, W*W(r)", &
2639 default_l_val=.false., &
2640 lone_keyword_l_val=.true.)
2644 CALL keyword_create(keyword, __location__, name=
"WINDING_CYCLE_2", &
2645 description=
"Winding number squared density, W^2(r)", &
2648 default_l_val=.false., &
2649 lone_keyword_l_val=.true.)
2653 CALL keyword_create(keyword, __location__, name=
"MOMENT_OF_INERTIA", &
2654 description=
"Moment of inertia density", &
2657 default_l_val=.false., &
2658 lone_keyword_l_val=.true.)
2666 CALL create_coord_section(subsection,
"HELIUM")
2671 description=
"Permutation state used for restart", &
2672 n_keywords=1, n_subsections=0, repeats=.false.)
2673 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
2674 description=
"Specify particle index permutation for every "// &
2675 "helium atom", repeats=.true., usage=
"<INT> <INT> .. <INT>", &
2683 description=
"Average properties (used for restarts)", &
2684 n_keywords=7, n_subsections=0, repeats=.false.)
2685 CALL keyword_create(keyword, __location__, name=
"PROJECTED_AREA", &
2686 description=
"Projected area vector for all environments", &
2687 repeats=.true., usage=
"PROJECTED_AREA <REAL> <REAL> .. <REAL>", &
2688 type_of_var=
real_t, n_var=-1)
2691 CALL keyword_create(keyword, __location__, name=
"PROJECTED_AREA_2", &
2692 description=
"Projected area vector squared for all environments", &
2693 repeats=.true., usage=
"PROJECTED_AREA_2 <REAL> <REAL> .. <REAL>", &
2694 type_of_var=
real_t, n_var=-1)
2697 CALL keyword_create(keyword, __location__, name=
"WINDING_NUMBER_2", &
2698 description=
"Winding number vector squared for all environments", &
2699 repeats=.true., usage=
"WINDING_NUMBER_2 <REAL> <REAL> .. <REAL>", &
2700 type_of_var=
real_t, n_var=-1)
2703 CALL keyword_create(keyword, __location__, name=
"MOMENT_OF_INERTIA", &
2704 description=
"Moment of inertia vector for all environments", &
2705 repeats=.true., usage=
"MOMENT_OF_INERTIA <REAL> <REAL> .. <REAL>", &
2706 type_of_var=
real_t, n_var=-1)
2710 description=
"Radial distributions averaged over all environments", &
2711 repeats=.true., usage=
"RDF <REAL> <REAL> .. <REAL>", &
2712 type_of_var=
real_t, n_var=-1)
2716 description=
"Spatial distributions averaged over all environments", &
2717 repeats=.true., usage=
"RHO <REAL> <REAL> .. <REAL>", &
2718 type_of_var=
real_t, n_var=-1)
2722 description=
"Weight for the restarted quantities "// &
2723 "(number of MC steps used to calculate the accumulated averages)", &
2732 description=
"Forces exerted by the helium on the solute system"// &
2733 " (used for restarts)", &
2734 n_keywords=1, n_subsections=0, repeats=.false.)
2735 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
2736 description=
"Number of real values should be 3 * "// &
2737 "<num_solute_atoms> * <num_solute_beads>", repeats=.true., &
2738 usage=
"<REAL> <REAL> .. <REAL>", type_of_var=
real_t, &
2745 CALL section_create(subsection, __location__, name=
"RNG_STATE", &
2746 description=
"Random number generator state for all processors", &
2747 n_keywords=1, n_subsections=0, repeats=.false.)
2748 CALL keyword_create(keyword, __location__, name=
"_DEFAULT_KEYWORD_", &
2749 description=
"Three real arrays of DIMENSION(3,2) times two RNG "// &
2750 "streams - 36 real values per processor", &
2751 repeats=.true., usage=
"automatically filled, do not edit by hand", &
2752 type_of_var=
real_t, n_var=-1)
2759 description=
"The section that controls the output of the helium code", &
2760 n_keywords=16, n_subsections=0, repeats=.false.)
2773 description=
"Controls the output of helium energies"// &
2774 " (averaged over MC step)", &
2780 description=
"Controls the output of the average projected area squared vector", &
2786 description=
"Controls the output of the average winding number vector squared", &
2792 description=
"Controls the output of the average moment of inertia vector", &
2800 description=
"Controls the output of helium radial distribution functions", &
2806 description=
"Controls the output of the helium density "// &
2807 "(Gaussian cube file format)", &
2808 each_iter_names=
s2a(
"PINT"), each_iter_values=[100], &
2811 CALL keyword_create(keyword, __location__, name=
"BACKUP_COPIES", &
2812 description=
"Specifies the maximum number of backup copies.", &
2813 usage=
"BACKUP_COPIES {int}", &
2821 description=
"Controls the output of the projected area vector", &
2827 description=
"Controls the output of the winding number vector", &
2833 description=
"Controls the output of the moment of inertia vector", &
2839 description=
"Controls the output of the helium permutation length", &
2845 description=
"Controls the output of the total helium action", &
2853 description=
"Controls the output of helium coordinates", &
2856 description=
"Output file format for the coordinates", &
2857 usage=
"FORMAT (PDB|XYZ)", &
2859 enum_c_vals=
s2a(
"PDB",
"XYZ"), &
2861 enum_desc=
s2a(
"Bead coordinates and connectivity is written in PDB format", &
2862 "Only bead coordinates are written in XYZ format"))
2869 description=
"Controls the output of the helium permutation state", &
2872 description=
"Output format for the permutation", &
2873 usage=
"FORMAT (CYCLE|PLAIN)", &
2875 enum_c_vals=
s2a(
"CYCLE",
"PLAIN"), &
2878 "Cycle notation with winding cycles enclosed"// &
2879 " in '[...]' and non-winding ones enclosed in '(...)'", &
2880 "Plain permutation output, i.e. P(1) ... P(N)"))
2887 description=
"Controls the output of the helium forces on the solute", &
2895 description=
"Controls the output of the helium acceptance data", &
2901 description=
"Controls the output of the instantaneous helium forces on the solute", &
2910 END SUBROUTINE create_helium_section
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public kapil2016
integer, save, public ceriotti2012
integer, save, public henkelman1999
integer, save, public ceriotti2010
integer, save, public henkelman2014
integer, save, public byrd1995
integer, save, public brieuc2016
integer, save, public ceriotti2014
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 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.