(git:34ef472)
input_cp2k_colvar.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \par History
10 !> - taken out of input_cp2k_motion
11 !> \author teo & fawzi
12 ! **************************************************************************************************
14  USE bibliography, ONLY: branduardi2007
15  USE colvar_types, ONLY: &
22  USE cp_units, ONLY: cp_unit_to_cp2k
23  USE input_constants, ONLY: gaussian,&
24  numerical,&
25  rmsd_all,&
26  rmsd_list,&
30  keyword_type
35  section_type
36  USE input_val_types, ONLY: char_t,&
37  integer_t,&
38  lchar_t,&
39  real_t
40  USE kinds, ONLY: dp
41  USE string_utilities, ONLY: s2a
42 #include "./base/base_uses.f90"
43 
44  IMPLICIT NONE
45  PRIVATE
46 
47  LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .false.
48  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_colvar'
49 
50  PUBLIC :: create_colvar_section, &
53 
54 CONTAINS
55 
56 ! **************************************************************************************************
57 !> \brief creates the colvar section
58 !> \param section the section to be created
59 !> \param skip_recursive_colvar ...
60 !> \author teo
61 ! **************************************************************************************************
62  RECURSIVE SUBROUTINE create_colvar_section(section, skip_recursive_colvar)
63  TYPE(section_type), POINTER :: section
64  LOGICAL, OPTIONAL :: skip_recursive_colvar
65 
66  LOGICAL :: skip
67  TYPE(section_type), POINTER :: print_key, subsection
68 
69  skip = .false.
70  IF (PRESENT(skip_recursive_colvar)) skip = skip_recursive_colvar
71  cpassert(.NOT. ASSOCIATED(section))
72  CALL section_create(section, __location__, name="COLVAR", &
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)
76 
77  CALL create_colvar_var_section(subsection=subsection, &
78  section=section, skip_recursive_colvar=skip)
79 
80  CALL section_create(subsection, __location__, name="PRINT", &
81  description="Controls the printing of the colvar specifications", &
82  n_keywords=0, n_subsections=1, repeats=.true.)
83  NULLIFY (print_key)
84  CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
85  description="Controls the printing of basic information during colvar setup.", &
86  print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
87  CALL section_add_subsection(subsection, print_key)
88  CALL section_release(print_key)
89  CALL section_add_subsection(section, subsection)
90  CALL section_release(subsection)
91 
92  CALL create_clv_info_section(subsection)
93  CALL section_add_subsection(section, subsection)
94  CALL section_release(subsection)
95 
96  END SUBROUTINE create_colvar_section
97 
98 ! **************************************************************************************************
99 !> \brief Create the restart section for colvar restraints
100 !> This section will be only used for restraint restarts.
101 !> Constraints are handled automatically
102 !> \param section the section to create
103 !> \author Teodoro Laino 08.2006
104 ! **************************************************************************************************
105  SUBROUTINE create_clv_info_section(section)
106  TYPE(section_type), POINTER :: section
107 
108  TYPE(keyword_type), POINTER :: keyword
109 
110  cpassert(.NOT. ASSOCIATED(section))
111  NULLIFY (keyword)
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.)
116 
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)
122  CALL section_add_keyword(section, keyword)
123  CALL keyword_release(keyword)
124 
125  END SUBROUTINE create_clv_info_section
126 
127 ! **************************************************************************************************
128 !> \brief creates the collective variables for the colvar section
129 !> \param subsection ...
130 !> \param section the section to be created
131 !> \param skip_recursive_colvar ...
132 !> \author teo
133 ! **************************************************************************************************
134  RECURSIVE SUBROUTINE create_colvar_var_section(subsection, section, skip_recursive_colvar)
135  TYPE(section_type), POINTER :: subsection, section
136  LOGICAL, INTENT(IN) :: skip_recursive_colvar
137 
138  cpassert(.NOT. ASSOCIATED(subsection))
139  cpassert(ASSOCIATED(section))
140 
141  CALL create_colvar_dist_section(subsection)
142  CALL section_add_subsection(section, subsection)
143  CALL section_release(subsection)
144 
145  CALL create_colvar_angle_section(subsection)
146  CALL section_add_subsection(section, subsection)
147  CALL section_release(subsection)
148 
149  CALL create_colvar_torsion_section(subsection)
150  CALL section_add_subsection(section, subsection)
151  CALL section_release(subsection)
152 
153  CALL create_colvar_coord_section(subsection)
154  CALL section_add_subsection(section, subsection)
155  CALL section_release(subsection)
156 
157  CALL create_colvar_pop_section(subsection)
158  CALL section_add_subsection(section, subsection)
159  CALL section_release(subsection)
160 
161  CALL create_colvar_gyr_section(subsection)
162  CALL section_add_subsection(section, subsection)
163  CALL section_release(subsection)
164 
165  CALL create_colvar_d_pl_section(subsection)
166  CALL section_add_subsection(section, subsection)
167  CALL section_release(subsection)
168 
169  CALL create_colvar_a_pl_section(subsection)
170  CALL section_add_subsection(section, subsection)
171  CALL section_release(subsection)
172 
173  CALL create_colvar_rot_section(subsection)
174  CALL section_add_subsection(section, subsection)
175  CALL section_release(subsection)
176 
177  CALL create_colvar_dfunct_section(subsection)
178  CALL section_add_subsection(section, subsection)
179  CALL section_release(subsection)
180 
181  CALL create_colvar_qparm_section(subsection)
182  CALL section_add_subsection(section, subsection)
183  CALL section_release(subsection)
184 
185  CALL create_colvar_hydronium_shell_section(subsection)
186  CALL section_add_subsection(section, subsection)
187  CALL section_release(subsection)
188 
189  CALL create_colvar_hydronium_dist_section(subsection)
190  CALL section_add_subsection(section, subsection)
191  CALL section_release(subsection)
192 
193  CALL create_colvar_acid_hyd_dist_section(subsection)
194  CALL section_add_subsection(section, subsection)
195  CALL section_release(subsection)
196 
197  CALL create_colvar_acid_hyd_shell_section(subsection)
198  CALL section_add_subsection(section, subsection)
199  CALL section_release(subsection)
200 
201  CALL create_colvar_rmsd_section(subsection)
202  CALL section_add_subsection(section, subsection)
203  CALL section_release(subsection)
204 
205  CALL create_colvar_xyz_d_section(subsection)
206  CALL section_add_subsection(section, subsection)
207  CALL section_release(subsection)
208 
209  CALL create_colvar_xyz_od_section(subsection)
210  CALL section_add_subsection(section, subsection)
211  CALL section_release(subsection)
212 
213  CALL create_colvar_u_section(subsection)
214  CALL section_add_subsection(section, subsection)
215  CALL section_release(subsection)
216 
217  CALL create_colvar_wc_section(subsection)
218  CALL section_add_subsection(section, subsection)
219  CALL section_release(subsection)
220 
221  CALL create_colvar_hbp_section(subsection)
222  CALL section_add_subsection(section, subsection)
223  CALL section_release(subsection)
224 
225  CALL create_colvar_ring_puckering_section(subsection)
226  CALL section_add_subsection(section, subsection)
227  CALL section_release(subsection)
228 
229  CALL create_colvar_cond_dist_section(subsection)
230  CALL section_add_subsection(section, subsection)
231  CALL section_release(subsection)
232 
233  IF (.NOT. skip_recursive_colvar) THEN
234  CALL create_colvar_rpath_section(subsection)
235  CALL section_add_subsection(section, subsection)
236  CALL section_release(subsection)
237 
238  CALL create_colvar_dpath_section(subsection)
239  CALL section_add_subsection(section, subsection)
240  CALL section_release(subsection)
241 
242  CALL create_colvar_comb_section(subsection)
243  CALL section_add_subsection(section, subsection)
244  CALL section_release(subsection)
245  END IF
246 
247  END SUBROUTINE create_colvar_var_section
248 
249 ! **************************************************************************************************
250 !> \brief collective variables specifying coordination
251 !> \param section the section to be created
252 !> \author teo
253 ! **************************************************************************************************
254  SUBROUTINE create_colvar_coord_section(section)
255  TYPE(section_type), POINTER :: section
256 
257  TYPE(keyword_type), POINTER :: keyword
258  TYPE(section_type), POINTER :: subsection
259 
260  cpassert(.NOT. ASSOCIATED(section))
261  CALL section_create(section, __location__, name="coordination", &
262  description="Section to define the coordination number as a collective variable.", &
263  n_keywords=1, n_subsections=0, repeats=.false.)
264 
265  NULLIFY (subsection, keyword)
266 
267  CALL keyword_create(keyword, __location__, name="ATOMS_FROM", &
268  variants=(/"POINTS_FROM"/), &
269  description="Specify indexes of atoms/points building the coordination variable. ", &
270  usage="ATOMS_FROM {integer} {integer} ..", repeats=.true., &
271  n_var=-1, type_of_var=integer_t)
272  CALL section_add_keyword(section, keyword)
273  CALL keyword_release(keyword)
274 
275  CALL keyword_create(keyword, __location__, name="ATOMS_TO", &
276  variants=(/"POINTS_TO"/), &
277  description="Specify indexes of atoms/points building the coordination variable. ", &
278  usage="ATOMS_TO {integer} {integer} ..", repeats=.true., &
279  n_var=-1, type_of_var=integer_t)
280  CALL section_add_keyword(section, keyword)
281  CALL keyword_release(keyword)
282 
283  CALL keyword_create(keyword, __location__, name="ATOMS_TO_B", &
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., &
288  n_var=-1, type_of_var=integer_t)
289  CALL section_add_keyword(section, keyword)
290  CALL keyword_release(keyword)
291 
292  CALL keyword_create(keyword, __location__, name="KINDS_FROM", &
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)
296  CALL section_add_keyword(section, keyword)
297  CALL keyword_release(keyword)
298 
299  CALL keyword_create(keyword, __location__, name="KINDS_TO", &
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)
303  CALL section_add_keyword(section, keyword)
304  CALL keyword_release(keyword)
305 
306  CALL keyword_create(keyword, __location__, name="KINDS_TO_B", &
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)
311  CALL section_add_keyword(section, keyword)
312  CALL keyword_release(keyword)
313 
314  ! Must be present in each colvar and handled properly
315  CALL create_point_section(subsection)
316  CALL section_add_subsection(section, subsection)
317  CALL section_release(subsection)
318 
319  CALL keyword_create(keyword, __location__, name="R0", &
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)
324  CALL section_add_keyword(section, keyword)
325  CALL keyword_release(keyword)
326 
327  CALL keyword_create(keyword, __location__, name="NN", &
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, &
332  n_var=1)
333  CALL section_add_keyword(section, keyword)
334  CALL keyword_release(keyword)
335 
336  CALL keyword_create(keyword, __location__, name="ND", &
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, &
341  n_var=1)
342  CALL section_add_keyword(section, keyword)
343  CALL keyword_release(keyword)
344 
345  CALL keyword_create(keyword, __location__, name="R0_B", &
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)
351  CALL section_add_keyword(section, keyword)
352  CALL keyword_release(keyword)
353 
354  CALL keyword_create(keyword, __location__, name="NN_B", &
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, &
360  n_var=1)
361  CALL section_add_keyword(section, keyword)
362  CALL keyword_release(keyword)
363 
364  CALL keyword_create(keyword, __location__, name="ND_B", &
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, &
370  n_var=1)
371  CALL section_add_keyword(section, keyword)
372  CALL keyword_release(keyword)
373 
374  END SUBROUTINE create_colvar_coord_section
375 
376 ! **************************************************************************************************
377 !> \brief ...
378 !> \param section ...
379 ! **************************************************************************************************
380  SUBROUTINE create_colvar_cond_dist_section(section)
381  TYPE(section_type), POINTER :: section
382 
383  TYPE(keyword_type), POINTER :: keyword
384  TYPE(section_type), POINTER :: subsection
385 
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.)
390 
391  NULLIFY (subsection, keyword)
392 
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., &
396  n_var=-1, type_of_var=integer_t)
397  CALL section_add_keyword(section, keyword)
398  CALL keyword_release(keyword)
399 
400  CALL keyword_create(keyword, __location__, name="ATOMS_FROM", &
401  variants=(/"POINTS_FROM"/), &
402  description="Specify indexes of atoms/points building the coordination variable. ", &
403  usage="ATOMS_FROM {integer} {integer} ..", repeats=.true., &
404  n_var=-1, type_of_var=integer_t)
405  CALL section_add_keyword(section, keyword)
406  CALL keyword_release(keyword)
407 
408  CALL keyword_create(keyword, __location__, name="ATOMS_TO", &
409  variants=(/"POINTS_TO"/), &
410  description="Specify indexes of atoms/points building the coordination variable. ", &
411  usage="ATOMS_TO {integer} {integer} ..", repeats=.true., &
412  n_var=-1, type_of_var=integer_t)
413  CALL section_add_keyword(section, keyword)
414  CALL keyword_release(keyword)
415 
416  CALL keyword_create(keyword, __location__, name="KINDS_FROM", &
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)
420  CALL section_add_keyword(section, keyword)
421  CALL keyword_release(keyword)
422 
423  CALL keyword_create(keyword, __location__, name="KINDS_TO", &
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)
427  CALL section_add_keyword(section, keyword)
428  CALL keyword_release(keyword)
429 
430  ! Must be present in each colvar and handled properly
431  CALL create_point_section(subsection)
432  CALL section_add_subsection(section, subsection)
433  CALL section_release(subsection)
434 
435  CALL keyword_create(keyword, __location__, name="R0", &
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)
440  CALL section_add_keyword(section, keyword)
441  CALL keyword_release(keyword)
442 
443  CALL keyword_create(keyword, __location__, name="NN", &
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, &
448  n_var=1)
449  CALL section_add_keyword(section, keyword)
450  CALL keyword_release(keyword)
451 
452  CALL keyword_create(keyword, __location__, name="ND", &
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, &
457  n_var=1)
458  CALL section_add_keyword(section, keyword)
459  CALL keyword_release(keyword)
460 
461  CALL keyword_create(keyword, __location__, name="LAMBDA", &
462  description="Specify the lambda parameter at the exponent of the conditioned distance function.", &
463  usage="R0 {real}", default_r_val=3.0_dp, &
464  unit_str="bohr", n_var=1)
465  CALL section_add_keyword(section, keyword)
466  CALL keyword_release(keyword)
467 
468  END SUBROUTINE create_colvar_cond_dist_section
469 
470 ! **************************************************************************************************
471 !> \brief collective variables specifying population of a specie based on coordination
472 !> \param section the section to be created
473 !> \date 01.2009
474 !> \author Fabio Sterpone
475 ! **************************************************************************************************
476  SUBROUTINE create_colvar_pop_section(section)
477  TYPE(section_type), POINTER :: section
478 
479  TYPE(keyword_type), POINTER :: keyword
480  TYPE(section_type), POINTER :: subsection
481 
482  cpassert(.NOT. ASSOCIATED(section))
483  CALL section_create(section, __location__, name="population", &
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.)
487 
488  NULLIFY (subsection, keyword)
489 
490  CALL keyword_create(keyword, __location__, name="ATOMS_FROM", &
491  variants=(/"POINTS_FROM"/), &
492  description="Specify indexes of atoms/points building the coordination variable. ", &
493  usage="ATOMS_FROM {integer} {integer} ..", repeats=.true., &
494  n_var=-1, type_of_var=integer_t)
495  CALL section_add_keyword(section, keyword)
496  CALL keyword_release(keyword)
497 
498  CALL keyword_create(keyword, __location__, name="ATOMS_TO", &
499  variants=(/"POINTS_TO"/), &
500  description="Specify indexes of atoms/points building the coordination variable. ", &
501  usage="ATOMS_TO {integer} {integer} ..", repeats=.true., &
502  n_var=-1, type_of_var=integer_t)
503  CALL section_add_keyword(section, keyword)
504  CALL keyword_release(keyword)
505 
506  CALL keyword_create(keyword, __location__, name="KINDS_FROM", &
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)
510  CALL section_add_keyword(section, keyword)
511  CALL keyword_release(keyword)
512 
513  CALL keyword_create(keyword, __location__, name="KINDS_TO", &
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)
517  CALL section_add_keyword(section, keyword)
518  CALL keyword_release(keyword)
519 
520  ! Must be present in each colvar and handled properly
521  CALL create_point_section(subsection)
522  CALL section_add_subsection(section, subsection)
523  CALL section_release(subsection)
524 
525  CALL keyword_create(keyword, __location__, name="R0", &
526  variants=(/"R_0"/), &
527  description="Specify the R0 parameter in the coordination function.", &
528  usage="R0 {real}", default_r_val=3.0_dp, &
529  n_var=1)
530  CALL section_add_keyword(section, keyword)
531  CALL keyword_release(keyword)
532 
533  CALL keyword_create(keyword, __location__, name="NN", &
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, &
538  n_var=1)
539  CALL section_add_keyword(section, keyword)
540  CALL keyword_release(keyword)
541 
542  CALL keyword_create(keyword, __location__, name="ND", &
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, &
547  n_var=1)
548  CALL section_add_keyword(section, keyword)
549  CALL keyword_release(keyword)
550 
551  CALL keyword_create(keyword, __location__, name="n0", &
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, &
555  n_var=1)
556  CALL section_add_keyword(section, keyword)
557  CALL keyword_release(keyword)
558 
559  CALL keyword_create(keyword, __location__, name="SIGMA", &
560  description="Specify the gaussian width of used to build the population istogram.", &
561  usage="SIGMA {real}", default_r_val=0.5_dp, &
562  n_var=1)
563  CALL section_add_keyword(section, keyword)
564  CALL keyword_release(keyword)
565 
566  END SUBROUTINE create_colvar_pop_section
567 
568 ! **************************************************************************************************
569 !> \brief ...
570 !> \param section ...
571 ! **************************************************************************************************
572  SUBROUTINE create_colvar_gyr_section(section)
573  TYPE(section_type), POINTER :: section
574 
575  TYPE(keyword_type), POINTER :: keyword
576  TYPE(section_type), POINTER :: subsection
577 
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.)
582 
583  NULLIFY (subsection, keyword)
584 
585  CALL keyword_create(keyword, __location__, name="ATOMS", &
586  variants=(/"POINTS"/), &
587  description="Specify indexes of atoms/points defyining the gyration radius variable. ", &
588  usage="ATOMS {integer} {integer} ..", repeats=.true., &
589  n_var=-1, type_of_var=integer_t)
590  CALL section_add_keyword(section, keyword)
591  CALL keyword_release(keyword)
592 
593  CALL keyword_create(keyword, __location__, name="KINDS", &
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)
597  CALL section_add_keyword(section, keyword)
598  CALL keyword_release(keyword)
599 
600  ! Must be present in each colvar and handled properly
601  CALL create_point_section(subsection)
602  CALL section_add_subsection(section, subsection)
603  CALL section_release(subsection)
604 
605  END SUBROUTINE create_colvar_gyr_section
606 
607 ! **************************************************************************************************
608 !> \brief collective variables specifying torsion
609 !> \param section the section to be created
610 !> \author teo
611 ! **************************************************************************************************
612  SUBROUTINE create_colvar_dfunct_section(section)
613  TYPE(section_type), POINTER :: section
614 
615  TYPE(keyword_type), POINTER :: keyword
616  TYPE(section_type), POINTER :: subsection
617 
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.)
623 
624  NULLIFY (keyword, subsection)
625 
626  CALL keyword_create(keyword, __location__, name="ATOMS", &
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}", &
630  n_var=4, type_of_var=integer_t)
631  CALL section_add_keyword(section, keyword)
632  CALL keyword_release(keyword)
633 
634  CALL keyword_create(keyword, __location__, name="COEFFICIENT", &
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}", &
638  type_of_var=real_t)
639  CALL section_add_keyword(section, keyword)
640  CALL keyword_release(keyword)
641 
642  CALL keyword_create(keyword, __location__, name="PBC", &
643  description="Whether periodic boundary conditions should be applied on the "// &
644  "atomic position before computing the colvar or not.", &
645  usage="PBC", &
646  default_l_val=.true., lone_keyword_l_val=.true.)
647  CALL section_add_keyword(section, keyword)
648  CALL keyword_release(keyword)
649 
650  ! Must be present in each colvar and handled properly
651  CALL create_point_section(subsection)
652  CALL section_add_subsection(section, subsection)
653  CALL section_release(subsection)
654 
655  END SUBROUTINE create_colvar_dfunct_section
656 
657 ! **************************************************************************************************
658 !> \brief collective variables specifying torsion
659 !> \param section the section to be created
660 !> \author teo
661 ! **************************************************************************************************
662  SUBROUTINE create_colvar_torsion_section(section)
663  TYPE(section_type), POINTER :: section
664 
665  TYPE(keyword_type), POINTER :: keyword
666  TYPE(section_type), POINTER :: subsection
667 
668  cpassert(.NOT. ASSOCIATED(section))
669  CALL section_create(section, __location__, name="torsion", &
670  description="Section to define the torsion as a collective variables.", &
671  n_keywords=1, n_subsections=0, repeats=.false.)
672 
673  NULLIFY (keyword, subsection)
674 
675  CALL keyword_create(keyword, __location__, name="ATOMS", &
676  variants=(/"POINTS"/), &
677  description="Specifies the indexes of atoms/points defining the torsion.", &
678  usage="ATOMS {integer} {integer} {integer} {integer}", &
679  n_var=4, type_of_var=integer_t)
680  CALL section_add_keyword(section, keyword)
681  CALL keyword_release(keyword)
682 
683  ! Must be present in each colvar and handled properly
684  CALL create_point_section(subsection)
685  CALL section_add_subsection(section, subsection)
686  CALL section_release(subsection)
687 
688  END SUBROUTINE create_colvar_torsion_section
689 
690 ! **************************************************************************************************
691 !> \brief collective variables specifying torsion
692 !> \param section the section to be created
693 !> \author teo
694 ! **************************************************************************************************
695  SUBROUTINE create_colvar_rot_section(section)
696  TYPE(section_type), POINTER :: section
697 
698  TYPE(keyword_type), POINTER :: keyword
699  TYPE(section_type), POINTER :: subsection
700 
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.)
706 
707  NULLIFY (keyword, subsection)
708 
709  CALL keyword_create(keyword, __location__, name="P1_BOND1", &
710  description="Specifies the index of atom/point defining the first point"// &
711  " of the first bond/line.", &
712  usage="P1_BOND1 {integer}", &
713  n_var=1, type_of_var=integer_t)
714  CALL section_add_keyword(section, keyword)
715  CALL keyword_release(keyword)
716 
717  CALL keyword_create(keyword, __location__, name="P2_BOND1", &
718  description="Specifies the index of atom/point defining the second point"// &
719  " of the first bond/line.", &
720  usage="P2_BOND1 {integer}", &
721  n_var=1, type_of_var=integer_t)
722  CALL section_add_keyword(section, keyword)
723  CALL keyword_release(keyword)
724 
725  CALL keyword_create(keyword, __location__, name="P1_BOND2", &
726  description="Specifies the index of atom/point defining the first point"// &
727  " of the second bond/line.", &
728  usage="P1_BOND2 {integer}", &
729  n_var=1, type_of_var=integer_t)
730  CALL section_add_keyword(section, keyword)
731  CALL keyword_release(keyword)
732 
733  CALL keyword_create(keyword, __location__, name="P2_BOND2", &
734  description="Specifies the index of atom/point defining the second point"// &
735  " of the second bond/line.", &
736  usage="P2_BOND2 {integer}", &
737  n_var=1, type_of_var=integer_t)
738  CALL section_add_keyword(section, keyword)
739  CALL keyword_release(keyword)
740 
741  ! Must be present in each colvar and handled properly
742  CALL create_point_section(subsection)
743  CALL section_add_subsection(section, subsection)
744  CALL section_release(subsection)
745 
746  END SUBROUTINE create_colvar_rot_section
747 
748 ! **************************************************************************************************
749 !> \brief collective variables specifying angles
750 !> \param section the section to be created
751 !> \author teo
752 ! **************************************************************************************************
753  SUBROUTINE create_colvar_angle_section(section)
754  TYPE(section_type), POINTER :: section
755 
756  TYPE(keyword_type), POINTER :: keyword
757  TYPE(section_type), POINTER :: subsection
758 
759  cpassert(.NOT. ASSOCIATED(section))
760  CALL section_create(section, __location__, name="angle", &
761  description="Section to define the angle as a collective variables.", &
762  n_keywords=1, n_subsections=0, repeats=.false.)
763  NULLIFY (keyword, subsection)
764 
765  CALL keyword_create(keyword, __location__, name="ATOMS", &
766  variants=(/"POINTS"/), &
767  description="Specifies the indexes of atoms/points defining the angle.", &
768  usage="ATOMS {integer} {integer} {integer}", &
769  n_var=3, type_of_var=integer_t)
770  CALL section_add_keyword(section, keyword)
771  CALL keyword_release(keyword)
772 
773  ! Must be present in each colvar and handled properly
774  CALL create_point_section(subsection)
775  CALL section_add_subsection(section, subsection)
776  CALL section_release(subsection)
777 
778  END SUBROUTINE create_colvar_angle_section
779 
780 ! **************************************************************************************************
781 !> \brief creates the colvar section regarded to the collective variables dist
782 !> \param section the section to be created
783 !> \author teo
784 ! **************************************************************************************************
785  SUBROUTINE create_colvar_dist_section(section)
786  TYPE(section_type), POINTER :: section
787 
788  TYPE(keyword_type), POINTER :: keyword
789  TYPE(section_type), POINTER :: subsection
790 
791  cpassert(.NOT. ASSOCIATED(section))
792  CALL section_create(section, __location__, name="distance", &
793  description="Section to define the distance as a collective variables.", &
794  n_keywords=1, n_subsections=0, repeats=.false.)
795  NULLIFY (keyword, subsection)
796 
797  CALL keyword_create(keyword, __location__, name="ATOMS", &
798  variants=(/"POINTS"/), &
799  description="Specifies the indexes of atoms/points defining the distance.", &
800  usage="ATOMS {integer} {integer}", &
801  n_var=2, type_of_var=integer_t)
802  CALL section_add_keyword(section, keyword)
803  CALL keyword_release(keyword)
804  CALL keyword_create(keyword, __location__, name="AXIS", &
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"), &
809  default_i_val=do_clv_xyz)
810  CALL section_add_keyword(section, keyword)
811  CALL keyword_release(keyword)
812 
813  CALL keyword_create(keyword, __location__, name="SIGN", &
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.", &
816  usage="SIGN", &
817  default_l_val=.false., lone_keyword_l_val=.true.)
818  CALL section_add_keyword(section, keyword)
819  CALL keyword_release(keyword)
820 
821  ! Must be present in each colvar and handled properly
822  CALL create_point_section(subsection)
823  CALL section_add_subsection(section, subsection)
824  CALL section_release(subsection)
825 
826  END SUBROUTINE create_colvar_dist_section
827 
828 ! **************************************************************************************************
829 !> \brief creates the colvar section regarded to the collective variables dist
830 !> \param section the section to be created
831 !> \author teo
832 ! **************************************************************************************************
833  SUBROUTINE create_colvar_xyz_d_section(section)
834  TYPE(section_type), POINTER :: section
835 
836  TYPE(keyword_type), POINTER :: keyword
837  TYPE(section_type), POINTER :: subsection
838 
839  cpassert(.NOT. ASSOCIATED(section))
840  CALL section_create(section, __location__, name="XYZ_DIAG", &
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)
847 
848  CALL keyword_create(keyword, __location__, name="ATOM", &
849  variants=(/"POINT"/), &
850  description="Specifies the index of the atom/point.", &
851  usage="ATOM {integer}", &
852  n_var=1, type_of_var=integer_t)
853  CALL section_add_keyword(section, keyword)
854  CALL keyword_release(keyword)
855 
856  CALL keyword_create(keyword, __location__, name="COMPONENT", &
857  description="Define the component of the position vector which will be used "// &
858  "as a colvar.", &
859  usage="AXIS (XYZ | X | Y | Z | XY| XZ | YZ)", &
860  enum_c_vals=s2a("XYZ", "X", "Y", "Z", "XY", "XZ", "YZ"), &
862  default_i_val=do_clv_xyz)
863  CALL section_add_keyword(section, keyword)
864  CALL keyword_release(keyword)
865 
866  CALL keyword_create(keyword, __location__, name="PBC", &
867  description="Whether periodic boundary conditions should be applied on the "// &
868  "atomic position before computing the colvar or not.", &
869  usage="PBC", &
870  default_l_val=.true., lone_keyword_l_val=.true.)
871  CALL section_add_keyword(section, keyword)
872  CALL keyword_release(keyword)
873 
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.)
878  CALL section_add_keyword(section, keyword)
879  CALL keyword_release(keyword)
880 
881  ! Must be present in each colvar and handled properly
882  CALL create_point_section(subsection)
883  CALL section_add_subsection(section, subsection)
884  CALL section_release(subsection)
885 
886  END SUBROUTINE create_colvar_xyz_d_section
887 
888 ! **************************************************************************************************
889 !> \brief creates the colvar section regarded to the collective variables dist
890 !> \param section the section to be created
891 !> \author teo
892 ! **************************************************************************************************
893  SUBROUTINE create_colvar_xyz_od_section(section)
894  TYPE(section_type), POINTER :: section
895 
896  TYPE(keyword_type), POINTER :: keyword
897  TYPE(section_type), POINTER :: subsection
898 
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)
906 
907  CALL keyword_create(keyword, __location__, name="ATOMS", &
908  variants=(/"POINTS"/), &
909  description="Specifies the index of the atoms/points A and B.", &
910  usage="ATOMS {integer} {integer}", &
911  n_var=2, type_of_var=integer_t)
912  CALL section_add_keyword(section, keyword)
913  CALL keyword_release(keyword)
914 
915  CALL keyword_create(keyword, __location__, name="COMPONENT_A", &
916  description="Define the component of the position vector which will be used "// &
917  "as a colvar for atom A.", &
918  usage="AXIS (XYZ | X | Y | Z | XY| XZ | YZ)", &
919  enum_c_vals=s2a("XYZ", "X", "Y", "Z", "XY", "XZ", "YZ"), &
921  default_i_val=do_clv_xyz)
922  CALL section_add_keyword(section, keyword)
923  CALL keyword_release(keyword)
924 
925  CALL keyword_create(keyword, __location__, name="COMPONENT_B", &
926  description="Define the component of the position vector which will be used "// &
927  "as a colvar for atom B.", &
928  usage="AXIS (XYZ | X | Y | Z | XY| XZ | YZ)", &
929  enum_c_vals=s2a("XYZ", "X", "Y", "Z", "XY", "XZ", "YZ"), &
931  default_i_val=do_clv_xyz)
932  CALL section_add_keyword(section, keyword)
933  CALL keyword_release(keyword)
934 
935  CALL keyword_create(keyword, __location__, name="PBC", &
936  description="Whether periodic boundary conditions should be applied on the "// &
937  "atomic position before computing the colvar or not.", &
938  usage="PBC", &
939  default_l_val=.true., lone_keyword_l_val=.true.)
940  CALL section_add_keyword(section, keyword)
941  CALL keyword_release(keyword)
942 
943  ! Must be present in each colvar and handled properly
944  CALL create_point_section(subsection)
945  CALL section_add_subsection(section, subsection)
946  CALL section_release(subsection)
947 
948  END SUBROUTINE create_colvar_xyz_od_section
949 
950 ! **************************************************************************************************
951 !> \brief energy as collective variable
952 !> \param section the section to be created
953 !> \author Sebastiano Caravati
954 ! **************************************************************************************************
955  SUBROUTINE create_colvar_u_section(section)
956  TYPE(section_type), POINTER :: section
957 
958  TYPE(keyword_type), POINTER :: keyword
959  TYPE(section_type), POINTER :: subsection
960 
961  cpassert(.NOT. ASSOCIATED(section))
962  CALL section_create(section, __location__, name="u", &
963  description="Section to define the energy as a generalized collective variable.", &
964  n_keywords=0, n_subsections=0, repeats=.false.)
965 
966  NULLIFY (subsection, keyword)
967  CALL section_create(subsection, __location__, name="MIXED", &
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.)
971 
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, &
975  n_var=1)
976  CALL section_add_keyword(subsection, keyword)
977  CALL keyword_release(keyword)
978 
979  CALL keyword_create(keyword, __location__, name="VARIABLES", &
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, &
984  n_var=-1)
985  CALL section_add_keyword(subsection, keyword)
986  CALL keyword_release(keyword)
987 
988  CALL keyword_create(keyword, __location__, name="PARAMETERS", &
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.)
992  CALL section_add_keyword(subsection, keyword)
993  CALL keyword_release(keyword)
994 
995  CALL keyword_create(keyword, __location__, name="VALUES", &
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")
999  CALL section_add_keyword(subsection, keyword)
1000  CALL keyword_release(keyword)
1001 
1002  CALL keyword_create(keyword, __location__, name="UNITS", &
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.)
1007  CALL section_add_keyword(subsection, keyword)
1008  CALL keyword_release(keyword)
1009 
1010  CALL keyword_create(keyword, __location__, name="DX", &
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")
1013  CALL section_add_keyword(subsection, keyword)
1014  CALL keyword_release(keyword)
1015 
1016  CALL keyword_create(keyword, __location__, name="ERROR_LIMIT", &
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)
1020  CALL section_add_keyword(subsection, keyword)
1021  CALL keyword_release(keyword)
1022 
1023  CALL section_add_subsection(section, subsection)
1024  CALL section_release(subsection)
1025 
1026  END SUBROUTINE create_colvar_u_section
1027 
1028 ! **************************************************************************************************
1029 !> \brief creates the colvar section regarded to the collective variables distance
1030 !> of a point from a plane
1031 !> \param section the section to be created
1032 !> \author teo
1033 ! **************************************************************************************************
1034  SUBROUTINE create_colvar_d_pl_section(section)
1035  TYPE(section_type), POINTER :: section
1036 
1037  TYPE(keyword_type), POINTER :: keyword
1038  TYPE(section_type), POINTER :: subsection
1039 
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)
1046 
1047  CALL keyword_create(keyword, __location__, name="PBC", &
1048  description="Whether periodic boundary conditions should be applied on the "// &
1049  "atomic position before computing the colvar or not.", &
1050  usage="PBC", &
1051  default_l_val=.true., lone_keyword_l_val=.true.)
1052  CALL section_add_keyword(section, keyword)
1053  CALL keyword_release(keyword)
1054 
1055  CALL keyword_create(keyword, __location__, name="ATOMS_PLANE", &
1056  variants=(/"POINTS_PLANE"/), &
1057  description="Specifies the indexes of atoms/points defining the plane.", &
1058  usage="ATOMS_PLANE <INTEGER> <INTEGER> <INTEGER>", &
1059  n_var=3, type_of_var=integer_t)
1060  CALL section_add_keyword(section, keyword)
1061  CALL keyword_release(keyword)
1062 
1063  CALL keyword_create(keyword, __location__, name="ATOM_POINT", &
1064  variants=(/"POINT_POINT"/), &
1065  description="Specifies the atom/point index defining the point.", &
1066  usage="ATOM_POINT <INTEGER>", &
1067  n_var=1, type_of_var=integer_t)
1068  CALL section_add_keyword(section, keyword)
1069  CALL keyword_release(keyword)
1070 
1071  ! Must be present in each colvar and handled properly
1072  CALL create_point_section(subsection)
1073  CALL section_add_subsection(section, subsection)
1074  CALL section_release(subsection)
1075 
1076  END SUBROUTINE create_colvar_d_pl_section
1077 
1078 ! **************************************************************************************************
1079 !> \brief creates the colvar section regarded to the collective variables
1080 !> angles betweem two planes
1081 !> \param section the section to be created
1082 !> \author teo
1083 ! **************************************************************************************************
1084  SUBROUTINE create_colvar_a_pl_section(section)
1085  TYPE(section_type), POINTER :: section
1086 
1087  TYPE(keyword_type), POINTER :: keyword
1088  TYPE(section_type), POINTER :: subsection
1089 
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)
1096 
1097  CALL section_create(subsection, __location__, name="PLANE", &
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.)
1101 
1102  CALL keyword_create(keyword, __location__, name="DEF_TYPE", &
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", &
1106  default_i_val=plane_def_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"), &
1110  enum_i_vals=(/plane_def_atoms, plane_def_vec/))
1111  CALL section_add_keyword(subsection, keyword)
1112  CALL keyword_release(keyword)
1113 
1114  CALL keyword_create(keyword, __location__, name="ATOMS", &
1115  description="Specifies the indexes of 3 atoms/points defining the plane.", &
1116  usage="ATOMS <INTEGER> <INTEGER> <INTEGER>", &
1117  n_var=3, type_of_var=integer_t)
1118  CALL section_add_keyword(subsection, keyword)
1119  CALL keyword_release(keyword)
1120 
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)
1126  CALL section_add_keyword(subsection, keyword)
1127  CALL keyword_release(keyword)
1128  CALL section_add_subsection(section, subsection)
1129  CALL section_release(subsection)
1130 
1131  ! Must be present in each colvar and handled properly
1132  CALL create_point_section(subsection)
1133  CALL section_add_subsection(section, subsection)
1134  CALL section_release(subsection)
1135  END SUBROUTINE create_colvar_a_pl_section
1136 
1137 ! **************************************************************************************************
1138 !> \brief create a geometrical point as a function of several atom coordinates
1139 !> \param section the section to be created
1140 !> \author teo
1141 ! **************************************************************************************************
1142  SUBROUTINE create_point_section(section)
1143  TYPE(section_type), POINTER :: section
1144 
1145  TYPE(keyword_type), POINTER :: keyword
1146 
1147  cpassert(.NOT. ASSOCIATED(section))
1148  CALL section_create(section, __location__, name="POINT", &
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.)
1152 
1153  NULLIFY (keyword)
1154 
1155  CALL keyword_create(keyword, __location__, name="TYPE", &
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"), &
1161  enum_i_vals=(/do_clv_geo_center, do_clv_fix_point/), &
1162  default_i_val=do_clv_geo_center)
1163  CALL section_add_keyword(section, keyword)
1164  CALL keyword_release(keyword)
1165 
1166  CALL keyword_create(keyword, __location__, name="ATOMS", &
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.)
1170  CALL section_add_keyword(section, keyword)
1171  CALL keyword_release(keyword)
1172 
1173  CALL keyword_create( &
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.)
1178  CALL section_add_keyword(section, keyword)
1179  CALL keyword_release(keyword)
1180 
1181  CALL keyword_create(keyword, __location__, name="XYZ", &
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", &
1185  repeats=.false.)
1186  CALL section_add_keyword(section, keyword)
1187  CALL keyword_release(keyword)
1188 
1189  END SUBROUTINE create_point_section
1190 
1191 ! **************************************************************************************************
1192 !> \brief collective variables specifying torsion
1193 !> \param section the section to be created
1194 !> \author teo
1195 ! **************************************************************************************************
1196  SUBROUTINE create_colvar_qparm_section(section)
1197  TYPE(section_type), POINTER :: section
1198 
1199  TYPE(keyword_type), POINTER :: keyword
1200  TYPE(section_type), POINTER :: subsection
1201 
1202  cpassert(.NOT. ASSOCIATED(section))
1203  CALL section_create(section, __location__, name="qparm", &
1204  description="Section to define the Q parameter (crystalline order parameter) as a collective variable.", &
1205  n_keywords=1, n_subsections=0, repeats=.false.)
1206 
1207  NULLIFY (keyword, subsection)
1208 
1209  CALL keyword_create(keyword, __location__, name="ATOMS_FROM", &
1210  variants=(/"POINTS_FROM"/), &
1211  description="Specify indexes of atoms/points building the coordination variable. ", &
1212  usage="ATOMS_FROM {integer} {integer} ..", repeats=.true., &
1213  n_var=-1, type_of_var=integer_t)
1214  CALL section_add_keyword(section, keyword)
1215  CALL keyword_release(keyword)
1216 
1217  CALL keyword_create(keyword, __location__, name="ATOMS_TO", &
1218  variants=(/"POINTS_TO"/), &
1219  description="Specify indexes of atoms/points building the coordination variable. ", &
1220  usage="ATOMS_TO {integer} {integer} ..", repeats=.true., &
1221  n_var=-1, type_of_var=integer_t)
1222  CALL section_add_keyword(section, keyword)
1223  CALL keyword_release(keyword)
1224 
1225  CALL keyword_create(keyword, __location__, name="RCUT", &
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)
1230  CALL section_add_keyword(section, keyword)
1231  CALL keyword_release(keyword)
1232 
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.)
1237  CALL section_add_keyword(section, keyword)
1238  CALL keyword_release(keyword)
1239 
1240  CALL keyword_create(keyword, __location__, name="RSTART", &
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)
1245  CALL section_add_keyword(section, keyword)
1246  CALL keyword_release(keyword)
1247 
1248  CALL keyword_create(keyword, __location__, name="L", &
1249  description="Specifies the L spherical harmonics from Ylm.", &
1250  usage="L {integer}", &
1251  n_var=1, type_of_var=integer_t)
1252  CALL section_add_keyword(section, keyword)
1253  CALL keyword_release(keyword)
1254 
1255  !CALL keyword_create(keyword, __LOCATION__, name="ALPHA", &
1256  ! description="Specifies the width of the Fermi-Dirac style smearing around RCUT.", &
1257  ! usage="ALPHA {real}", unit_str="angstrom^-1", default_r_val=0.0_dp)
1258  !CALL section_add_keyword(section, keyword)
1259  !CALL keyword_release(keyword)
1260 
1261  ! Must be present in each colvar and handled properly
1262  CALL create_point_section(subsection)
1263  CALL section_add_subsection(section, subsection)
1264  CALL section_release(subsection)
1265 
1266  END SUBROUTINE create_colvar_qparm_section
1267 
1268 ! **************************************************************************************************
1269 !> \brief collective variables specifying hydronium solvation
1270 !> \param section the section to be created
1271 !> \author Marcel Baer
1272 ! **************************************************************************************************
1273  SUBROUTINE create_colvar_hydronium_shell_section(section)
1274  TYPE(section_type), POINTER :: section
1275 
1276  TYPE(keyword_type), POINTER :: keyword
1277 
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.)
1286 
1287  NULLIFY (keyword)
1288 
1289  CALL keyword_create(keyword, __location__, name="OXYGENS", &
1290  description="Specifies indexes of atoms building the coordination variable."// &
1291  " Oxygens of the water molecules.", &
1292  usage="OXYGENS {integer} {integer} ..", repeats=.true., &
1293  n_var=-1, type_of_var=integer_t)
1294  CALL section_add_keyword(section, keyword)
1295  CALL keyword_release(keyword)
1296 
1297  CALL keyword_create(keyword, __location__, name="HYDROGENS", &
1298  description="Specifies indexes of atoms building the coordination variable."// &
1299  " Hydrogens of the water molecules.", &
1300  usage="HYDROGENS {integer} {integer} ..", repeats=.true., &
1301  n_var=-1, type_of_var=integer_t)
1302  CALL section_add_keyword(section, keyword)
1303  CALL keyword_release(keyword)
1304 
1305  CALL keyword_create(keyword, __location__, name="ROO", &
1306  description="Specifies the rc parameter in the coordination function:"// &
1307  " number of oxygens per water oxygen.", &
1308  usage="ROO {real}", default_r_val=cp_unit_to_cp2k(value=3.0_dp, &
1309  unit_str="bohr"), unit_str="bohr", n_var=1)
1310  CALL section_add_keyword(section, keyword)
1311  CALL keyword_release(keyword)
1312 
1313  CALL keyword_create(keyword, __location__, name="pOO", &
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, &
1318  n_var=1)
1319  CALL section_add_keyword(section, keyword)
1320  CALL keyword_release(keyword)
1321 
1322  CALL keyword_create(keyword, __location__, name="qOO", &
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, &
1327  n_var=1)
1328  CALL section_add_keyword(section, keyword)
1329  CALL keyword_release(keyword)
1330 
1331  CALL keyword_create(keyword, __location__, name="ROH", &
1332  description="Specifies the rc parameter in the coordination function:"// &
1333  " number of hydrogens per water molecule.", &
1334  usage="ROH {real}", default_r_val=cp_unit_to_cp2k(value=3.0_dp, &
1335  unit_str="bohr"), unit_str="bohr", n_var=1)
1336  CALL section_add_keyword(section, keyword)
1337  CALL keyword_release(keyword)
1338 
1339  CALL keyword_create(keyword, __location__, name="pOH", &
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, &
1344  n_var=1)
1345  CALL section_add_keyword(section, keyword)
1346  CALL keyword_release(keyword)
1347 
1348  CALL keyword_create(keyword, __location__, name="qOH", &
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, &
1353  n_var=1)
1354  CALL section_add_keyword(section, keyword)
1355  CALL keyword_release(keyword)
1356 
1357  CALL keyword_create(keyword, __location__, name="NH", &
1358  description="Specifies the NH parameter in the M function.", &
1359  usage="NH {real}", default_r_val=3.0_dp, &
1360  n_var=1)
1361  CALL section_add_keyword(section, keyword)
1362  CALL keyword_release(keyword)
1363 
1364  CALL keyword_create(keyword, __location__, name="pM", &
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, &
1369  n_var=1)
1370  CALL section_add_keyword(section, keyword)
1371  CALL keyword_release(keyword)
1372 
1373  CALL keyword_create(keyword, __location__, name="qM", &
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, &
1378  n_var=1)
1379  CALL section_add_keyword(section, keyword)
1380  CALL keyword_release(keyword)
1381 
1382  CALL keyword_create(keyword, __location__, name="LAMBDA", &
1383  description="Specify the LAMBDA parameter in the hydronium function.", &
1384  usage="LAMBDA {real}", default_r_val=10.0_dp, &
1385  n_var=1)
1386  CALL section_add_keyword(section, keyword)
1387  CALL keyword_release(keyword)
1388 
1389  END SUBROUTINE create_colvar_hydronium_shell_section
1390 
1391 ! **************************************************************************************************
1392 !> \brief collective variables specifying the distance between hydronium and hydroxide ion
1393 !> \param section the section to be created
1394 !> \author Dorothea Golze
1395 ! **************************************************************************************************
1396  SUBROUTINE create_colvar_hydronium_dist_section(section)
1397  TYPE(section_type), POINTER :: section
1398 
1399  TYPE(keyword_type), POINTER :: keyword
1400 
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.)
1408 
1409  NULLIFY (keyword)
1410 
1411  CALL keyword_create(keyword, __location__, name="OXYGENS", &
1412  description="Specifies indexes of atoms building the coordination variable."// &
1413  " Oxygens of the water molecules.", &
1414  usage="OXYGENS {integer} {integer} ..", repeats=.true., &
1415  n_var=-1, type_of_var=integer_t)
1416  CALL section_add_keyword(section, keyword)
1417  CALL keyword_release(keyword)
1418 
1419  CALL keyword_create(keyword, __location__, name="HYDROGENS", &
1420  description="Specifies indexes of atoms building the coordination variable."// &
1421  " Hydrogens of the water molecules.", &
1422  usage="HYDROGENS {integer} {integer} ..", repeats=.true., &
1423  n_var=-1, type_of_var=integer_t)
1424  CALL section_add_keyword(section, keyword)
1425  CALL keyword_release(keyword)
1426 
1427  CALL keyword_create(keyword, __location__, name="ROH", &
1428  description="Specifies the rc parameter in the coordination function:"// &
1429  " number of hydrogens per water molecule.", &
1430  usage="ROH {real}", default_r_val=cp_unit_to_cp2k(value=2.4_dp, &
1431  unit_str="bohr"), unit_str="bohr", n_var=1)
1432  CALL section_add_keyword(section, keyword)
1433  CALL keyword_release(keyword)
1434 
1435  CALL keyword_create(keyword, __location__, name="pOH", &
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, &
1439  n_var=1)
1440  CALL section_add_keyword(section, keyword)
1441  CALL keyword_release(keyword)
1442 
1443  CALL keyword_create(keyword, __location__, name="qOH", &
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, &
1447  n_var=1)
1448  CALL section_add_keyword(section, keyword)
1449  CALL keyword_release(keyword)
1450 
1451  CALL keyword_create(keyword, __location__, name="NH", &
1452  description="Specifies the NH parameter in the M function.", &
1453  usage="NH {real}", default_r_val=2.2_dp, &
1454  n_var=1)
1455  CALL section_add_keyword(section, keyword)
1456  CALL keyword_release(keyword)
1457 
1458  CALL keyword_create(keyword, __location__, name="pM", &
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, &
1462  n_var=1)
1463  CALL section_add_keyword(section, keyword)
1464  CALL keyword_release(keyword)
1465 
1466  CALL keyword_create(keyword, __location__, name="qM", &
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, &
1470  n_var=1)
1471  CALL section_add_keyword(section, keyword)
1472  CALL keyword_release(keyword)
1473 
1474  CALL keyword_create(keyword, __location__, name="NN", &
1475  description="Specifies the NN parameter in the F function.", &
1476  usage="NN {real}", default_r_val=1.5_dp, &
1477  n_var=1)
1478  CALL section_add_keyword(section, keyword)
1479  CALL keyword_release(keyword)
1480 
1481  CALL keyword_create(keyword, __location__, name="pF", &
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, &
1485  n_var=1)
1486  CALL section_add_keyword(section, keyword)
1487  CALL keyword_release(keyword)
1488 
1489  CALL keyword_create(keyword, __location__, name="qF", &
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, &
1493  n_var=1)
1494  CALL section_add_keyword(section, keyword)
1495  CALL keyword_release(keyword)
1496 
1497  CALL keyword_create(keyword, __location__, name="LAMBDA", &
1498  description="Specify the LAMBDA parameter in the hydronium function.", &
1499  usage="LAMBDA {real}", default_r_val=20.0_dp, &
1500  n_var=1)
1501  CALL section_add_keyword(section, keyword)
1502  CALL keyword_release(keyword)
1503 
1504  END SUBROUTINE create_colvar_hydronium_dist_section
1505 
1506 ! **************************************************************************************************
1507 !> \brief collective variables specifying the solvation of carboxylic acid;
1508 !> distance between hydronium ion and acetate ion; Equation (2) in
1509 !> Supplementary Information of J. Am. Chem. Soc.,128, 2006, 11318
1510 !> \param section the section to be created
1511 !> \author Dorothea Golze
1512 ! **************************************************************************************************
1513  SUBROUTINE create_colvar_acid_hyd_dist_section(section)
1514  TYPE(section_type), POINTER :: section
1515 
1516  TYPE(keyword_type), POINTER :: keyword
1517 
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.)
1524 
1525  NULLIFY (keyword)
1526 
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 {integer} {integer} ..", repeats=.true., &
1531  n_var=-1, type_of_var=integer_t)
1532  CALL section_add_keyword(section, keyword)
1533  CALL keyword_release(keyword)
1534 
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 {integer} {integer} ..", repeats=.true., &
1539  n_var=-1, type_of_var=integer_t)
1540  CALL section_add_keyword(section, keyword)
1541  CALL keyword_release(keyword)
1542 
1543  CALL keyword_create(keyword, __location__, name="HYDROGENS", &
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., &
1547  n_var=-1, type_of_var=integer_t)
1548  CALL section_add_keyword(section, keyword)
1549  CALL keyword_release(keyword)
1550 
1551  CALL keyword_create(keyword, __location__, name="pWOH", &
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, &
1555  n_var=1)
1556  CALL section_add_keyword(section, keyword)
1557  CALL keyword_release(keyword)
1558 
1559  CALL keyword_create(keyword, __location__, name="qWOH", &
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, &
1563  n_var=1)
1564  CALL section_add_keyword(section, keyword)
1565  CALL keyword_release(keyword)
1566 
1567  CALL keyword_create(keyword, __location__, name="RWOH", &
1568  description="Specify the rc parameter in the coordination function:"// &
1569  " number of hydrogens per water molecule.", &
1570  usage="RWOH {real}", default_r_val=cp_unit_to_cp2k(value=2.4_dp, &
1571  unit_str="bohr"), unit_str="bohr", n_var=1)
1572  CALL section_add_keyword(section, keyword)
1573  CALL keyword_release(keyword)
1574 
1575  CALL keyword_create(keyword, __location__, name="pAOH", &
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, &
1579  n_var=1)
1580  CALL section_add_keyword(section, keyword)
1581  CALL keyword_release(keyword)
1582 
1583  CALL keyword_create(keyword, __location__, name="qAOH", &
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, &
1587  n_var=1)
1588  CALL section_add_keyword(section, keyword)
1589  CALL keyword_release(keyword)
1590 
1591  CALL keyword_create(keyword, __location__, name="RAOH", &
1592  description="Specify the rc parameter in the coordination function:"// &
1593  " number of hydrogens per carboxyl group.", &
1594  usage="RAOH {real}", default_r_val=cp_unit_to_cp2k(value=2.4_dp, &
1595  unit_str="bohr"), unit_str="bohr", n_var=1)
1596  CALL section_add_keyword(section, keyword)
1597  CALL keyword_release(keyword)
1598 
1599  CALL keyword_create(keyword, __location__, name="pCUT", &
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, &
1603  n_var=1)
1604  CALL section_add_keyword(section, keyword)
1605  CALL keyword_release(keyword)
1606 
1607  CALL keyword_create(keyword, __location__, name="qCUT", &
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, &
1611  n_var=1)
1612  CALL section_add_keyword(section, keyword)
1613  CALL keyword_release(keyword)
1614 
1615  CALL keyword_create(keyword, __location__, name="NC", &
1616  description="Specifies the NC parameter in the cutoff function.", &
1617  usage="NC {real}", default_r_val=0.56_dp, &
1618  n_var=1)
1619  CALL section_add_keyword(section, keyword)
1620  CALL keyword_release(keyword)
1621 
1622  CALL keyword_create(keyword, __location__, name="LAMBDA", &
1623  variants=(/"LAMBDA"/), &
1624  description="Specifies the LAMBDA parameter carboxylic acid function.", &
1625  usage="LAMBDA {real}", default_r_val=20.0_dp, &
1626  n_var=1)
1627  CALL section_add_keyword(section, keyword)
1628  CALL keyword_release(keyword)
1629 
1630  END SUBROUTINE create_colvar_acid_hyd_dist_section
1631 
1632 ! **************************************************************************************************
1633 !> \brief collective variables specifying the solvation of carboxylic acid;
1634 !> number of oxygens in the 1st shell of the hydronium; Equation (3) in
1635 !> Supplementary Information of J. Am. Chem. Soc.,128, 2006, 11318
1636 !> \param section the section to be created
1637 !> \author Dorothea Golze
1638 ! **************************************************************************************************
1639  SUBROUTINE create_colvar_acid_hyd_shell_section(section)
1640  TYPE(section_type), POINTER :: section
1641 
1642  TYPE(keyword_type), POINTER :: keyword
1643 
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.)
1651 
1652  NULLIFY (keyword)
1653 
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 {integer} {integer} ..", repeats=.true., &
1658  n_var=-1, type_of_var=integer_t)
1659  CALL section_add_keyword(section, keyword)
1660  CALL keyword_release(keyword)
1661 
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 {integer} {integer} ..", repeats=.true., &
1666  n_var=-1, type_of_var=integer_t)
1667  CALL section_add_keyword(section, keyword)
1668  CALL keyword_release(keyword)
1669 
1670  CALL keyword_create(keyword, __location__, name="HYDROGENS", &
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., &
1674  n_var=-1, type_of_var=integer_t)
1675  CALL section_add_keyword(section, keyword)
1676  CALL keyword_release(keyword)
1677 
1678  CALL keyword_create(keyword, __location__, name="pWOH", &
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, &
1682  n_var=1)
1683  CALL section_add_keyword(section, keyword)
1684  CALL keyword_release(keyword)
1685 
1686  CALL keyword_create(keyword, __location__, name="qWOH", &
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, &
1690  n_var=1)
1691  CALL section_add_keyword(section, keyword)
1692  CALL keyword_release(keyword)
1693 
1694  CALL keyword_create(keyword, __location__, name="RWOH", &
1695  description="Specifies the rc parameter in the coordination function:"// &
1696  " number of hydrogens per water molecule.", &
1697  usage="RWOH {real}", default_r_val=cp_unit_to_cp2k(value=2.4_dp, &
1698  unit_str="bohr"), unit_str="bohr", n_var=1)
1699  CALL section_add_keyword(section, keyword)
1700  CALL keyword_release(keyword)
1701 
1702  CALL keyword_create(keyword, __location__, name="pAOH", &
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, &
1706  n_var=1)
1707  CALL section_add_keyword(section, keyword)
1708  CALL keyword_release(keyword)
1709 
1710  CALL keyword_create(keyword, __location__, name="qAOH", &
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, &
1714  n_var=1)
1715  CALL section_add_keyword(section, keyword)
1716  CALL keyword_release(keyword)
1717 
1718  CALL keyword_create(keyword, __location__, name="RAOH", &
1719  description="Specifies the rc parameter in the coordination function:"// &
1720  " number of hydrogens per carboxyl group.", &
1721  usage="RAOH {real}", default_r_val=cp_unit_to_cp2k(value=2.4_dp, &
1722  unit_str="bohr"), unit_str="bohr", n_var=1)
1723  CALL section_add_keyword(section, keyword)
1724  CALL keyword_release(keyword)
1725 
1726  CALL keyword_create(keyword, __location__, name="pOO", &
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, &
1730  n_var=1)
1731  CALL section_add_keyword(section, keyword)
1732  CALL keyword_release(keyword)
1733 
1734  CALL keyword_create(keyword, __location__, name="qOO", &
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, &
1738  n_var=1)
1739  CALL section_add_keyword(section, keyword)
1740  CALL keyword_release(keyword)
1741 
1742  CALL keyword_create(keyword, __location__, name="ROO", &
1743  description="Specifies the rc parameter in the coordination function:"// &
1744  " number of oxygens per water oxygen.", &
1745  usage="ROO {real}", default_r_val=cp_unit_to_cp2k(value=5.5_dp, &
1746  unit_str="bohr"), unit_str="bohr", n_var=1)
1747  CALL section_add_keyword(section, keyword)
1748  CALL keyword_release(keyword)
1749 
1750  CALL keyword_create(keyword, __location__, name="pM", &
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, &
1754  n_var=1)
1755  CALL section_add_keyword(section, keyword)
1756  CALL keyword_release(keyword)
1757 
1758  CALL keyword_create(keyword, __location__, name="qM", &
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, &
1762  n_var=1)
1763  CALL section_add_keyword(section, keyword)
1764  CALL keyword_release(keyword)
1765 
1766  CALL keyword_create(keyword, __location__, name="NH", &
1767  description="Specifies the NH parameter in the M function.", &
1768  usage="NH {real}", default_r_val=2.2_dp, &
1769  n_var=1)
1770  CALL section_add_keyword(section, keyword)
1771  CALL keyword_release(keyword)
1772 
1773  CALL keyword_create(keyword, __location__, name="pCUT", &
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, &
1777  n_var=1)
1778  CALL section_add_keyword(section, keyword)
1779  CALL keyword_release(keyword)
1780 
1781  CALL keyword_create(keyword, __location__, name="qCUT", &
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, &
1785  n_var=1)
1786  CALL section_add_keyword(section, keyword)
1787  CALL keyword_release(keyword)
1788 
1789  CALL keyword_create(keyword, __location__, name="NC", &
1790  description="Specifies the NC parameter in the cutoff function.", &
1791  usage="NC {real}", default_r_val=0.9_dp, &
1792  n_var=1)
1793  CALL section_add_keyword(section, keyword)
1794  CALL keyword_release(keyword)
1795 
1796  CALL keyword_create(keyword, __location__, name="LAMBDA", &
1797  variants=(/"LAMBDA"/), &
1798  description="Specifies the LAMBDA parameter carboxylic acid function.", &
1799  usage="LAMBDA {real}", default_r_val=10.0_dp, &
1800  n_var=1)
1801  CALL section_add_keyword(section, keyword)
1802  CALL keyword_release(keyword)
1803 
1804  END SUBROUTINE create_colvar_acid_hyd_shell_section
1805 
1806 ! **************************************************************************************************
1807 !> \brief ...
1808 !> \param section ...
1809 ! **************************************************************************************************
1810  SUBROUTINE create_colvar_rmsd_section(section)
1811  TYPE(section_type), POINTER :: section
1812 
1813  TYPE(keyword_type), POINTER :: keyword
1814  TYPE(section_type), POINTER :: subsection, subsubsection
1815 
1816  cpassert(.NOT. ASSOCIATED(section))
1817  CALL section_create(section, __location__, name="rmsd", &
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.)
1823 
1824  NULLIFY (keyword, subsection, subsubsection)
1825  CALL keyword_create(keyword, __location__, name="SUBSET_TYPE", &
1826  description="Define the subsytem used to compute the RMSD", &
1827  usage="SUBSET_TYPE ALL", &
1828  enum_c_vals=s2a("ALL", "LIST", "WEIGHT_LIST"), &
1829  enum_i_vals=(/rmsd_all, rmsd_list, rmsd_weightlist/), &
1830  default_i_val=rmsd_all)
1831  CALL section_add_keyword(section, keyword)
1832  CALL keyword_release(keyword)
1833 
1834  CALL keyword_create(keyword, __location__, name="ALIGN_FRAMES", &
1835  description="Whether the reference frames should be aligned to minimize the RMSD", &
1836  usage="ALIGN_FRAME", &
1837  default_l_val=.false., lone_keyword_l_val=.true.)
1838  CALL section_add_keyword(section, keyword)
1839  CALL keyword_release(keyword)
1840 
1841  CALL keyword_create(keyword, __location__, name="ATOMS", &
1842  description="Specify indexes of atoms building the subset. ", &
1843  usage="ATOMS {integer} {integer} ..", repeats=.true., &
1844  n_var=-1, type_of_var=integer_t)
1845  CALL section_add_keyword(section, keyword)
1846  CALL keyword_release(keyword)
1847 
1848  CALL keyword_create(keyword, __location__, name="WEIGHTS", &
1849  description="Specify weights of atoms building the subset. ", &
1850  usage="weightS {real} {real} ..", repeats=.true., &
1851  n_var=-1, type_of_var=real_t)
1852  CALL section_add_keyword(section, keyword)
1853  CALL keyword_release(keyword)
1854 
1855  CALL section_create(subsection, __location__, name="FRAME", &
1856  description="Specify coordinates of the frame (number of frames can be either 1 or 2)", &
1857  repeats=.true.)
1858 
1859  CALL keyword_create(keyword, __location__, name="COORD_FILE_NAME", &
1860  description="Name of the xyz file with coordinates (alternative to &COORD section)", &
1861  usage="COORD_FILE_NAME <CHAR>", &
1862  default_lc_val="")
1863  CALL section_add_keyword(subsection, keyword)
1864  CALL keyword_release(keyword)
1865 
1866  CALL create_coord_section_cv(subsubsection, "RMSD")
1867  CALL section_add_subsection(subsection, subsubsection)
1868  CALL section_release(subsubsection)
1869 
1870  CALL section_add_subsection(section, subsection)
1871  CALL section_release(subsection)
1872 
1873  END SUBROUTINE create_colvar_rmsd_section
1874 
1875 ! **************************************************************************************************
1876 !> \brief collective variables specifying the space orthogonal to the reaction path
1877 !> in the space spanned by the involved collective coordinates
1878 !> \param section the section to be created
1879 !> \author fschiff
1880 ! **************************************************************************************************
1881  SUBROUTINE create_colvar_rpath_section(section)
1882  TYPE(section_type), POINTER :: section
1883 
1884  cpassert(.NOT. ASSOCIATED(section))
1885  CALL section_create(section, __location__, name="REACTION_PATH", &
1886  description="Section defining a one dimensional reaction path in an Q-dimensional space of colvars. "// &
1887  "Constraining this colvar, allows to sample the space orthogonal to the reaction path, "// &
1888  "both in the Q-dimensional colvar and 3N-Q remaining coordinates. "// &
1889  "For the details of the function see cited literature.", &
1890  n_keywords=1, n_subsections=0, repeats=.false., &
1891  citations=(/branduardi2007/))
1892 
1893  CALL keywords_colvar_path(section)
1894  END SUBROUTINE create_colvar_rpath_section
1895 
1896 ! **************************************************************************************************
1897 !> \brief Distance from reaction path
1898 !> \param section the section to be created
1899 !> \author 01.2010
1900 ! **************************************************************************************************
1901  SUBROUTINE create_colvar_dpath_section(section)
1902  TYPE(section_type), POINTER :: section
1903 
1904  cpassert(.NOT. ASSOCIATED(section))
1905  CALL section_create(section, __location__, name="DISTANCE_FROM_PATH", &
1906  description="Section defining the distance from a one dimensional reaction "// &
1907  "path in an Q-dimensional space of colvars. "// &
1908  "Constraining this colvar, allows to sample the space equidistant to the reaction path, "// &
1909  "both in the Q-dimensional colvar and 3N-Q remaining coordinates. "// &
1910  "For the details of the function see cited literature.", &
1911  n_keywords=1, n_subsections=0, repeats=.false., &
1912  citations=(/branduardi2007/))
1913 
1914  CALL keywords_colvar_path(section)
1915  END SUBROUTINE create_colvar_dpath_section
1916 
1917 ! **************************************************************************************************
1918 !> \brief Section describinf keywords for both reaction path and distance from reaction path
1919 !> \param section the section to be created
1920 !> \author 01.2010
1921 ! **************************************************************************************************
1922  SUBROUTINE keywords_colvar_path(section)
1923 
1924  TYPE(section_type), POINTER :: section
1925 
1926  TYPE(keyword_type), POINTER :: keyword
1927  TYPE(section_type), POINTER :: print_key, subsection, subsubsection
1928 
1929  NULLIFY (keyword, subsection, subsubsection, print_key)
1930  CALL create_colvar_section(subsection, skip_recursive_colvar=.true.)
1931  CALL section_add_subsection(section, subsection)
1932  CALL section_release(subsection)
1933 
1934  CALL keyword_create(keyword, __location__, name="DISTANCES_RMSD", &
1935  description=" ", &
1936  usage="DISTANCES_RMSD T", &
1937  default_l_val=.false., lone_keyword_l_val=.true.)
1938  CALL section_add_keyword(section, keyword)
1939  CALL keyword_release(keyword)
1940 
1941  CALL keyword_create(keyword, __location__, name="RMSD", &
1942  description=" ", &
1943  usage="RMSD T", &
1944  default_l_val=.false., lone_keyword_l_val=.true.)
1945  CALL section_add_keyword(section, keyword)
1946  CALL keyword_release(keyword)
1947 
1948  CALL keyword_create(keyword, __location__, name="SUBSET_TYPE", &
1949  description="Define the subsytem used to compute the RMSD", &
1950  usage="SUBSET_TYPE ALL", &
1951  enum_c_vals=s2a("ALL", "LIST"), &
1952  enum_i_vals=(/rmsd_all, rmsd_list/), &
1953  default_i_val=rmsd_all)
1954  CALL section_add_keyword(section, keyword)
1955  CALL keyword_release(keyword)
1956 
1957  CALL keyword_create(keyword, __location__, name="ALIGN_FRAMES", &
1958  description="Whether the reference frames should be aligned to minimize the RMSD", &
1959  usage="ALIGN_FRAME", &
1960  default_l_val=.false., lone_keyword_l_val=.true.)
1961  CALL section_add_keyword(section, keyword)
1962  CALL keyword_release(keyword)
1963 
1964  CALL keyword_create(keyword, __location__, name="ATOMS", &
1965  description="Specify indexes of atoms building the subset. ", &
1966  usage="ATOMS {integer} {integer} ..", repeats=.true., &
1967  n_var=-1, type_of_var=integer_t)
1968  CALL section_add_keyword(section, keyword)
1969  CALL keyword_release(keyword)
1970 
1971  CALL section_create(subsection, __location__, name="FRAME", &
1972  description="Specify coordinates of the frame", &
1973  repeats=.true.)
1974 
1975  CALL keyword_create(keyword, __location__, name="COORD_FILE_NAME", &
1976  description="Name of the xyz file with coordinates (alternative to &COORD section)", &
1977  usage="COORD_FILE_NAME <CHAR>", &
1978  default_lc_val="")
1979  CALL section_add_keyword(subsection, keyword)
1980  CALL keyword_release(keyword)
1981 
1982  CALL create_coord_section_cv(subsubsection, "RMSD")
1983  CALL section_add_subsection(subsection, subsubsection)
1984  CALL section_release(subsubsection)
1985 
1986  CALL section_add_subsection(section, subsection)
1987  CALL section_release(subsection)
1988 
1989  CALL keyword_create(keyword, __location__, name="FUNCTION", &
1990  description="Specifies the ith element of the vector valued function that defines the reaction path. "// &
1991  "This keyword needs to repeat exactly Q times, and the order must match the order of the colvars. "// &
1992  "The VARIABLE (e.g. T) which parametrises the curve can be used as the target of a constraint.", &
1993  usage="FUNCTION (sin(T+2)+2*T)", type_of_var=lchar_t, &
1994  n_var=1, default_lc_val="0", repeats=.true.)
1995  CALL section_add_keyword(section, keyword)
1996  CALL keyword_release(keyword)
1997 
1998  CALL keyword_create(keyword, __location__, name="VARIABLE", &
1999  description="Specifies the name of the variable that parametrises the FUNCTION "// &
2000  "defining the reaction path.", &
2001  usage="VARIABLE T", type_of_var=char_t, &
2002  n_var=1, repeats=.false.)
2003  CALL section_add_keyword(section, keyword)
2004  CALL keyword_release(keyword)
2005 
2006  CALL keyword_create( &
2007  keyword, __location__, name="LAMBDA", &
2008  description="Specifies the exponent of the Gaussian used in the integral representation of the colvar. "// &
2009  "The shape of the space orthogonal to the reaction path is defined by this choice. "// &
2010  "In the limit of large values, it is given by the plane orthogonal to the path. "// &
2011  "In practice, modest values are required for stable numerical integration.", &
2012  usage="LAMBDA {real}", &
2013  type_of_var=real_t, default_r_val=5.0_dp)
2014  CALL section_add_keyword(section, keyword)
2015  CALL keyword_release(keyword)
2016 
2017  CALL keyword_create(keyword, __location__, name="STEP_SIZE", &
2018  description="Step size in the numerical integration, "// &
2019  "a few thousand points are common, and the proper number also depends on LAMBDA.", &
2020  usage="STEP_SIZE {real}", &
2021  type_of_var=real_t, default_r_val=0.01_dp)
2022  CALL section_add_keyword(section, keyword)
2023  CALL keyword_release(keyword)
2024 
2025  CALL keyword_create(keyword, __location__, name="RANGE", &
2026  description="The range of VARIABLE used for the parametrisation.", &
2027  usage="RANGE <REAL> <REAL>", &
2028  n_var=2, type_of_var=real_t)
2029  CALL section_add_keyword(section, keyword)
2030  CALL keyword_release(keyword)
2031 
2033  print_key, __location__, name="MAP", &
2034  description="Activating this print key will print once a file with the values of the FUNCTION on a grid "// &
2035  "of COLVAR values in a specified range. "// &
2036  "GRID_SPACING and RANGE for every COLVAR has to be specified again in the same order as they are in the input.", &
2037  print_level=high_print_level, filename="PATH")
2038 
2039  CALL keyword_create(keyword, __location__, name="RANGE", &
2040  description="The range of of the grid of the COLVAR.", &
2041  usage="RANGE <REAL> <REAL>", &
2042  n_var=2, type_of_var=real_t, repeats=.true.)
2043  CALL section_add_keyword(print_key, keyword)
2044  CALL keyword_release(keyword)
2045 
2046  CALL keyword_create(keyword, __location__, name="GRID_SPACING", &
2047  description="Distance between two gridpoints for the grid on the COLVAR", &
2048  usage="STEP_SIZE {real}", repeats=.true., &
2049  type_of_var=real_t, default_r_val=0.01_dp)
2050  CALL section_add_keyword(print_key, keyword)
2051  CALL keyword_release(keyword)
2052 
2053  CALL section_add_subsection(section, print_key)
2054  CALL section_release(print_key)
2055 
2056  END SUBROUTINE keywords_colvar_path
2057 
2058 ! **************************************************************************************************
2059 !> \brief Colvar allowing a combination of COLVARS
2060 !> \param section the section to be created
2061 !> \author Teodoro Laino [tlaino] - 12.2008
2062 ! **************************************************************************************************
2063  SUBROUTINE create_colvar_comb_section(section)
2064  TYPE(section_type), POINTER :: section
2065 
2066  TYPE(keyword_type), POINTER :: keyword
2067  TYPE(section_type), POINTER :: subsection
2068 
2069  cpassert(.NOT. ASSOCIATED(section))
2070  CALL section_create(section, __location__, name="COMBINE_COLVAR", &
2071  description="Allows the possibility to combine several COLVARs into one COLVAR "// &
2072  "with a generic function.", &
2073  n_keywords=1, n_subsections=0, repeats=.false.)
2074 
2075  NULLIFY (keyword, subsection)
2076  CALL create_colvar_section(subsection, skip_recursive_colvar=.true.)
2077  CALL section_add_subsection(section, subsection)
2078  CALL section_release(subsection)
2079 
2080  CALL keyword_create(keyword, __location__, name="FUNCTION", &
2081  description="Specifies the function used to combine different COLVARs into one.", &
2082  ! **************************************************************************************************
2083  !> \brief ...
2084  !> \param CV1^2 ...
2085  !> \param CV2^2 ...
2086  !> \param " ...
2087  !> \param type_of_var=lchar_t ...
2088  !> \param n_var=1 ...
2089  !> \param error=error ...
2090  ! **************************************************************************************************
2091  usage="FUNCTION SQRT(CV1^2+CV2^2)", type_of_var=lchar_t, &
2092  n_var=1)
2093  CALL section_add_keyword(section, keyword)
2094  CALL keyword_release(keyword)
2095 
2096  CALL keyword_create(keyword, __location__, name="VARIABLES", &
2097  description="Specifies the name of the variable that parametrises the FUNCTION "// &
2098  "defining how COLVARS should be combined. The matching follows the same order of the "// &
2099  "COLVARS definition in the input file.", &
2100  usage="VARIABLE CV1 CV2 CV3", type_of_var=char_t, n_var=-1, repeats=.false.)
2101  CALL section_add_keyword(section, keyword)
2102  CALL keyword_release(keyword)
2103 
2104  CALL keyword_create(keyword, __location__, name="PARAMETERS", &
2105  description="Defines the parameters of the functional form", &
2106  usage="PARAMETERS a b D", type_of_var=char_t, &
2107  n_var=-1, repeats=.true.)
2108  CALL section_add_keyword(section, keyword)
2109  CALL keyword_release(keyword)
2110 
2111  CALL keyword_create(keyword, __location__, name="VALUES", &
2112  description="Defines the values of parameter of the functional form", &
2113  usage="VALUES ", type_of_var=real_t, &
2114  n_var=-1, repeats=.true., unit_str="internal_cp2k")
2115  CALL section_add_keyword(section, keyword)
2116  CALL keyword_release(keyword)
2117 
2118  CALL keyword_create(keyword, __location__, name="DX", &
2119  description="Parameter used for computing the derivative of the combination "// &
2120  "of COLVARs with the Ridders' method.", &
2121  usage="DX <REAL>", default_r_val=0.1_dp, unit_str="bohr")
2122  CALL section_add_keyword(section, keyword)
2123  CALL keyword_release(keyword)
2124 
2125  CALL keyword_create(keyword, __location__, name="ERROR_LIMIT", &
2126  description="Checks that the error in computing the derivative is not larger than "// &
2127  "the value set; in case error is larger a warning message is printed.", &
2128  usage="ERROR_LIMIT <REAL>", default_r_val=1.0e-12_dp)
2129  CALL section_add_keyword(section, keyword)
2130  CALL keyword_release(keyword)
2131 
2132  END SUBROUTINE create_colvar_comb_section
2133 
2134 ! **************************************************************************************************
2135 !> \brief Creates the coord section
2136 !> \param section the section to create
2137 !> \param name ...
2138 !> \author teo
2139 ! **************************************************************************************************
2140  SUBROUTINE create_coord_section_cv(section, name)
2141  TYPE(section_type), POINTER :: section
2142  CHARACTER(LEN=*), INTENT(IN) :: name
2143 
2144  TYPE(keyword_type), POINTER :: keyword
2145 
2146  cpassert(.NOT. ASSOCIATED(section))
2147  CALL section_create(section, __location__, name="coord", &
2148  description="The positions for "//trim(name)//" used for restart", &
2149  n_keywords=1, n_subsections=0, repeats=.false.)
2150  NULLIFY (keyword)
2151 
2152  CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2153  description="Specify positions of the system", repeats=.true., &
2154  usage="{Real} ...", type_of_var=real_t, n_var=-1)
2155  CALL section_add_keyword(section, keyword)
2156  CALL keyword_release(keyword)
2157 
2158  END SUBROUTINE create_coord_section_cv
2159 
2160 ! **************************************************************************************************
2161 !> \brief collective variables specifying h bonds
2162 !> \param section the section to be created
2163 !> \author alin m elena
2164 ! **************************************************************************************************
2165  SUBROUTINE create_colvar_wc_section(section)
2166  TYPE(section_type), POINTER :: section
2167 
2168  TYPE(keyword_type), POINTER :: keyword
2169  TYPE(section_type), POINTER :: subsection
2170 
2171  cpassert(.NOT. ASSOCIATED(section))
2172  CALL section_create(section, __location__, name="wc", &
2173  description="Section to define the hbond wannier centre as a collective variables.", &
2174  n_keywords=1, n_subsections=0, repeats=.false.)
2175  NULLIFY (keyword, subsection)
2176 
2177  CALL keyword_create(keyword, __location__, name="RCUT", &
2178  description="Parameter used for computing the cutoff radius for searching "// &
2179  "the wannier centres around an atom", &
2180  usage="RCUT <REAL>", default_r_val=0.529177208590000_dp, unit_str="angstrom", &
2181  type_of_var=real_t, repeats=.false.)
2182  CALL section_add_keyword(section, keyword)
2183  CALL keyword_release(keyword)
2184 
2185  CALL keyword_create(keyword, __location__, name="ATOMS", &
2186  variants=(/"POINTS"/), &
2187  description="Specifies the indexes of atoms/points defining the bond (Od, H, Oa).", &
2188  usage="ATOMS {integer} {integer} {integer}", &
2189  n_var=3, type_of_var=integer_t, repeats=.true.)
2190  CALL section_add_keyword(section, keyword)
2191  CALL keyword_release(keyword)
2192 
2193  ! Must be present in each colvar and handled properly
2194  CALL create_point_section(subsection)
2195  CALL section_add_subsection(section, subsection)
2196  CALL section_release(subsection)
2197 
2198  END SUBROUTINE create_colvar_wc_section
2199 
2200  ! **************************************************************************************************
2201 !> \brief collective variables specifying h bonds= wire
2202 !> \param section the section to be created
2203 !> \author alin m elena
2204 ! **************************************************************************************************
2205  SUBROUTINE create_colvar_hbp_section(section)
2206  TYPE(section_type), POINTER :: section
2207 
2208  TYPE(keyword_type), POINTER :: keyword
2209  TYPE(section_type), POINTER :: subsection
2210 
2211  cpassert(.NOT. ASSOCIATED(section))
2212  CALL section_create(section, __location__, name="hbp", &
2213  description="Section to define the hbond wannier centre as a collective variables.", &
2214  n_keywords=1, n_subsections=0, repeats=.false.)
2215  NULLIFY (keyword, subsection)
2216 
2217  CALL keyword_create(keyword, __location__, name="RCUT", &
2218  description="Parameter used for computing the cutoff radius for searching "// &
2219  "the wannier centres around an atom", &
2220  usage="RCUT <REAL>", default_r_val=0.529177208590000_dp, unit_str="angstrom", &
2221  type_of_var=real_t, repeats=.false.)
2222  CALL section_add_keyword(section, keyword)
2223  CALL keyword_release(keyword)
2224 
2225  CALL keyword_create(keyword, __location__, name="SHIFT", &
2226  description="Parameter used for shifting each term in the sum ", &
2227  usage="SHIFT <REAL>", default_r_val=0.5_dp, &
2228  type_of_var=real_t, repeats=.false.)
2229  CALL section_add_keyword(section, keyword)
2230  CALL keyword_release(keyword)
2231 
2232  CALL keyword_create(keyword, __location__, name="NPOINTS", &
2233  description="The number of points in the path", &
2234  usage="NPOINTS {integer}", default_i_val=-1, &
2235  n_var=1, type_of_var=integer_t, repeats=.false.)
2236  CALL section_add_keyword(section, keyword)
2237  CALL keyword_release(keyword)
2238 
2239  CALL keyword_create(keyword, __location__, name="ATOMS", &
2240  variants=(/"POINTS"/), &
2241  description="Specifies the indexes of atoms/points defining the bond (Od, H, Oa).", &
2242  usage="ATOMS {integer} {integer} {integer}", &
2243  n_var=3, type_of_var=integer_t, repeats=.true.)
2244  CALL section_add_keyword(section, keyword)
2245  CALL keyword_release(keyword)
2246 
2247  ! Must be present in each colvar and handled properly
2248  CALL create_point_section(subsection)
2249  CALL section_add_subsection(section, subsection)
2250  CALL section_release(subsection)
2251 
2252  END SUBROUTINE create_colvar_hbp_section
2253 
2254 ! **************************************************************************************************
2255 !> \brief collective variables specifying ring puckering
2256 !> \brief D. Cremer and J.A. Pople, JACS 97 1354 (1975)
2257 !> \param section the section to be created
2258 !> \author Marcel Baer
2259 ! **************************************************************************************************
2260  SUBROUTINE create_colvar_ring_puckering_section(section)
2261  TYPE(section_type), POINTER :: section
2262 
2263  TYPE(keyword_type), POINTER :: keyword
2264  TYPE(section_type), POINTER :: subsection
2265 
2266  cpassert(.NOT. ASSOCIATED(section))
2267  CALL section_create(section, __location__, name="RING_PUCKERING", &
2268  description="Section to define general ring puckering collective variables.", &
2269  n_keywords=1, n_subsections=0, repeats=.false.)
2270 
2271  NULLIFY (keyword, subsection)
2272 
2273  CALL keyword_create(keyword, __location__, name="ATOMS", &
2274  variants=(/"POINTS"/), &
2275  description="Specifies the indexes of atoms/points defining the ring. "// &
2276  "At least 4 Atoms are needed.", &
2277  usage="ATOMS {integer} {integer} {integer} ..", &
2278  n_var=-1, type_of_var=integer_t)
2279  CALL section_add_keyword(section, keyword)
2280  CALL keyword_release(keyword)
2281 
2282  CALL keyword_create(keyword, __location__, name="COORDINATE", &
2283  description="Indicate the coordinate to be used. Follow the Cremer-Pople definition for a N ring. "// &
2284  "0 is the total puckering variable Q, "// &
2285  "2..[N/2] are puckering coordinates. "// &
2286  "-2..-[N/2-1] are puckering angles.", &
2287  usage="COORDINATE {integer}", default_i_val=0, &
2288  n_var=1)
2289  CALL section_add_keyword(section, keyword)
2290  CALL keyword_release(keyword)
2291 
2292  ! Must be present in each colvar and handled properly
2293  CALL create_point_section(subsection)
2294  CALL section_add_subsection(section, subsection)
2295  CALL section_release(subsection)
2296 
2297  END SUBROUTINE create_colvar_ring_puckering_section
2298 
2299 ! **************************************************************************************************
2300 
2301 END MODULE input_cp2k_colvar
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public branduardi2007
Definition: bibliography.F:43
Initialize the collective variables types.
Definition: colvar_types.F:15
integer, parameter, public do_clv_geo_center
Definition: colvar_types.F:33
integer, parameter, public do_clv_xyz
Definition: colvar_types.F:33
integer, parameter, public do_clv_xz
Definition: colvar_types.F:33
integer, parameter, public do_clv_fix_point
Definition: colvar_types.F:33
integer, parameter, public do_clv_z
Definition: colvar_types.F:33
integer, parameter, public plane_def_atoms
Definition: colvar_types.F:30
integer, parameter, public do_clv_yz
Definition: colvar_types.F:33
integer, parameter, public do_clv_xy
Definition: colvar_types.F:33
integer, parameter, public do_clv_y
Definition: colvar_types.F:33
integer, parameter, public plane_def_vec
Definition: colvar_types.F:30
integer, parameter, public do_clv_x
Definition: colvar_types.F:33
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
unit conversion facility
Definition: cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition: cp_units.F:1150
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public rmsd_weightlist
integer, parameter, public rmsd_list
integer, parameter, public rmsd_all
integer, parameter, public gaussian
integer, parameter, public numerical
subroutine, public create_colvar_xyz_d_section(section)
creates the colvar section regarded to the collective variables dist
recursive subroutine, public create_colvar_section(section, skip_recursive_colvar)
creates the colvar section
subroutine, public create_colvar_xyz_od_section(section)
creates the colvar section regarded to the collective variables dist
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public lchar_t
integer, parameter, public char_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Utilities for string manipulations.