(git:1f285aa)
input_cp2k_constraints.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 !> 10.2005 split input_cp2k into smaller modules [fawzi]
11 !> Teodoro Laino [tlaino] 12.2008 - Preparing for VIRTUAL SITE constraints
12 !> (patch by Marcel Baer)
13 !> \author teo & fawzi
14 ! **************************************************************************************************
16  USE cell_types, ONLY: use_perd_x,&
17  use_perd_xy,&
18  use_perd_xyz,&
19  use_perd_xz,&
20  use_perd_y,&
21  use_perd_yz,&
30  keyword_type
35  section_type
36  USE input_val_types, ONLY: char_t,&
37  integer_t,&
38  real_t
39  USE kinds, ONLY: dp
40  USE string_utilities, ONLY: s2a
41 #include "./base/base_uses.f90"
42 
43  IMPLICIT NONE
44  PRIVATE
45 
46  LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
47  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_constraints'
48 
50 
51 !***
52 CONTAINS
53 
54 ! **************************************************************************************************
55 !> \brief Create the constraint section. This section is useful to impose
56 !> constraints
57 !> \param section the section to create
58 !> \author teo
59 ! **************************************************************************************************
60  SUBROUTINE create_constraint_section(section)
61  TYPE(section_type), POINTER :: section
62 
63  TYPE(keyword_type), POINTER :: keyword
64  TYPE(section_type), POINTER :: print_key, subsection
65 
66  cpassert(.NOT. ASSOCIATED(section))
67  CALL section_create(section, __location__, name="constraint", &
68  description="Section specifying information regarding how to impose constraints"// &
69  " on the system.", &
70  n_keywords=0, n_subsections=2, repeats=.false.)
71 
72  NULLIFY (subsection, keyword, print_key)
73  CALL keyword_create(keyword, __location__, name="SHAKE_TOLERANCE", &
74  variants=s2a("SHAKE_TOL", "SHAKE"), &
75  description="Set the tolerance for the shake/rattle constraint algorithm.", &
76  usage="SHAKE_TOLERANCE <REAL>", &
77  default_r_val=1.0e-6_dp, unit_str="internal_cp2k")
78  CALL section_add_keyword(section, keyword)
79  CALL keyword_release(keyword)
80 
81  CALL keyword_create(keyword, __location__, name="ROLL_TOLERANCE", &
82  variants=s2a("ROLL_TOL", "ROLL"), &
83  description="Set the tolerance for the roll constraint algorithm.", &
84  usage="ROLL_TOLERANCE <REAL>", &
85  default_r_val=1.0e-10_dp, unit_str="internal_cp2k")
86  CALL section_add_keyword(section, keyword)
87  CALL keyword_release(keyword)
88 
89  CALL keyword_create(keyword, __location__, name="CONSTRAINT_INIT", &
90  description="Apply constraints to the initial position and velocities."// &
91  " Default is to apply constraints only after the first MD step.", &
92  usage="CONSTRAINT_INIT <LOGICAL>", &
93  default_l_val=.false., lone_keyword_l_val=.true.)
94  CALL section_add_keyword(section, keyword)
95  CALL keyword_release(keyword)
96 
97  CALL keyword_create(keyword, __location__, name="PIMD_BEADWISE_CONSTRAINT", &
98  description="Apply beadwise constraints to PIMD.", &
99  usage="PIMD_BEADWISE_CONSTRAINT <LOGICAL>", &
100  default_l_val=.false., lone_keyword_l_val=.true.)
101  CALL section_add_keyword(section, keyword)
102  CALL keyword_release(keyword)
103 
104  CALL create_hbonds_section(subsection)
105  CALL restraint_info_section(subsection)
106  CALL section_add_subsection(section, subsection)
107  CALL section_release(subsection)
108 
109  CALL create_g3x3_section(subsection)
110  CALL restraint_info_section(subsection)
111  CALL section_add_subsection(section, subsection)
112  CALL section_release(subsection)
113 
114  CALL create_g4x6_section(subsection)
115  CALL restraint_info_section(subsection)
116  CALL section_add_subsection(section, subsection)
117  CALL section_release(subsection)
118 
119  CALL create_vsite_section(subsection)
120  CALL restraint_info_section(subsection)
121  CALL section_add_subsection(section, subsection)
122  CALL section_release(subsection)
123 
124  CALL create_collective_section(subsection)
125  CALL restraint_info_section(subsection)
126  CALL section_add_subsection(section, subsection)
127  CALL section_release(subsection)
128 
129  CALL create_fixed_atom_section(subsection)
130  CALL restraint_info_section(subsection)
131  CALL section_add_subsection(section, subsection)
132  CALL section_release(subsection)
133 
134  CALL create_f_a_rest_section(subsection)
135  CALL section_add_subsection(section, subsection)
136  CALL section_release(subsection)
137 
138  CALL create_clv_rest_section(subsection)
139  CALL section_add_subsection(section, subsection)
140  CALL section_release(subsection)
141 
142  CALL cp_print_key_section_create(print_key, __location__, "constraint_info", &
143  description="Prints information about iterative constraints solutions", &
144  print_level=high_print_level, filename="__STD_OUT__")
145  CALL section_add_subsection(section, print_key)
146  CALL section_release(print_key)
147 
149  print_key, __location__, "lagrange_multipliers", &
150  description="Prints out the lagrange multipliers of the specified constraints during an MD.", &
151  print_level=high_print_level, filename="")
152  CALL section_add_subsection(section, print_key)
153  CALL section_release(print_key)
154 
155  END SUBROUTINE create_constraint_section
156 
157 ! **************************************************************************************************
158 !> \brief Create the restart section for colvar restraints
159 !> This section will be only used for restraint restarts.
160 !> Constraints are handled automatically
161 !> \param section the section to create
162 !> \author Teodoro Laino 08.2006
163 ! **************************************************************************************************
164  SUBROUTINE create_clv_rest_section(section)
165  TYPE(section_type), POINTER :: section
166 
167  TYPE(keyword_type), POINTER :: keyword
168 
169  cpassert(.NOT. ASSOCIATED(section))
170  NULLIFY (keyword)
171  CALL section_create(section, __location__, name="COLVAR_RESTART", &
172  description="Specify restart position only for COLVAR restraints.", &
173  n_subsections=0, repeats=.false.)
174 
175  CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
176  description="The restarting values for COLVAR restraints."// &
177  " The order is an internal order. So if you decide to modify these values by hand"// &
178  " first think what you're doing!", repeats=.true., &
179  usage="{Real}", type_of_var=real_t, n_var=1)
180  CALL section_add_keyword(section, keyword)
181  CALL keyword_release(keyword)
182 
183  END SUBROUTINE create_clv_rest_section
184 
185 ! **************************************************************************************************
186 !> \brief Create the restart section for fixed atoms restraints
187 !> This section will be only used for restraint restarts.
188 !> Constraints are handled automatically
189 !> \param section the section to create
190 !> \author Teodoro Laino 08.2006
191 ! **************************************************************************************************
192  SUBROUTINE create_f_a_rest_section(section)
193  TYPE(section_type), POINTER :: section
194 
195  TYPE(keyword_type), POINTER :: keyword
196 
197  cpassert(.NOT. ASSOCIATED(section))
198  NULLIFY (keyword)
199  CALL section_create(section, __location__, name="FIX_ATOM_RESTART", &
200  description="Specify restart position only for FIXED_ATOMS restraints.", &
201  n_subsections=0, repeats=.false.)
202 
203  CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
204  description="The restarting position of fixed atoms for restraints."// &
205  " The order is an internal order. So if you decide to modify these values by hand"// &
206  " first think what you're doing!", repeats=.true., &
207  usage="{Real} ...", type_of_var=real_t, n_var=-1)
208  CALL section_add_keyword(section, keyword)
209  CALL keyword_release(keyword)
210 
211  END SUBROUTINE create_f_a_rest_section
212 
213 ! **************************************************************************************************
214 !> \brief Create the restraint info section in the constraint section
215 !> \param section the section to create
216 !> \author Teodoro Laino 08.2006
217 ! **************************************************************************************************
218  SUBROUTINE restraint_info_section(section)
219  TYPE(section_type), POINTER :: section
220 
221  TYPE(keyword_type), POINTER :: keyword
222  TYPE(section_type), POINTER :: subsection
223 
224  cpassert(ASSOCIATED(section))
225  NULLIFY (subsection, keyword)
226  CALL section_create(subsection, __location__, name="RESTRAINT", &
227  description="Activate and specify information on restraint instead of constraint", &
228  n_subsections=0, repeats=.false.)
229 
230  CALL keyword_create(keyword, __location__, name="K", &
231  description="Specifies the force constant for the harmonic restraint. The functional "// &
232  "form for the restraint is: K*(X-TARGET)^2.", &
233  usage="K {real}", &
234  type_of_var=real_t, default_r_val=0.0_dp, unit_str="internal_cp2k")
235  CALL section_add_keyword(subsection, keyword)
236  CALL keyword_release(keyword)
237 
238  CALL section_add_subsection(section, subsection)
239  CALL section_release(subsection)
240 
241  END SUBROUTINE restraint_info_section
242 
243 ! **************************************************************************************************
244 !> \brief Create the constraint section for collective constraints
245 !> \param section the section to create
246 !> \author Joost VandeVondele [01.2006]
247 ! **************************************************************************************************
248  SUBROUTINE create_collective_section(section)
249  TYPE(section_type), POINTER :: section
250 
251  TYPE(keyword_type), POINTER :: keyword
252 
253  cpassert(.NOT. ASSOCIATED(section))
254  CALL section_create(section, __location__, name="COLLECTIVE", &
255  description="Used to constraint collective (general) degrees of freedom, "// &
256  "writing langrangian multipliers to file.", &
257  n_subsections=0, repeats=.true.)
258  NULLIFY (keyword)
259 
260  CALL keyword_create(keyword, __location__, name="COLVAR", &
261  description="Specifies the index (in input file order) of the type of colvar to constrain.", &
262  usage="COLVAR {int}", &
263  type_of_var=integer_t)
264  CALL section_add_keyword(section, keyword)
265  CALL keyword_release(keyword)
266 
267  CALL keyword_create(keyword, __location__, name="MOLECULE", &
268  description="Specifies the index of the molecule kind (in input file order)"// &
269  " on which the constraint will be applied."// &
270  " MOLECULE and MOLNAME keyword exclude themself mutually.", &
271  usage="MOLECULE {integer}", 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="MOLNAME", &
276  variants=(/"SEGNAME"/), &
277  description="Specifies the name of the molecule on which the constraint will be applied.", &
278  usage="MOLNAME {character}", n_var=1, type_of_var=char_t)
279  CALL section_add_keyword(section, keyword)
280  CALL keyword_release(keyword)
281 
282  CALL keyword_create(keyword, __location__, name="INTERMOLECULAR", &
283  description="Specify if the constraint/restraint is intermolecular.", &
284  usage="INTERMOLECULAR <LOGICAL>", &
285  default_l_val=.false., lone_keyword_l_val=.true.)
286  CALL section_add_keyword(section, keyword)
287  CALL keyword_release(keyword)
288 
289  CALL keyword_create(keyword, __location__, name="TARGET", &
290  description="Specifies the target value of the constrained collective"// &
291  " variable (units depend on the colvar).", &
292  usage="TARGET {real}", &
293  type_of_var=real_t, unit_str="internal_cp2k")
294  CALL section_add_keyword(section, keyword)
295  CALL keyword_release(keyword)
296 
297  CALL keyword_create(keyword, __location__, name="TARGET_GROWTH", &
298  description="Specifies the growth speed of the target value of the constrained collective"// &
299  " variable.", &
300  usage="TARGET_GROWTH {real}", &
301  default_r_val=0.0_dp, unit_str="internal_cp2k")
302  CALL section_add_keyword(section, keyword)
303  CALL keyword_release(keyword)
304 
305  CALL keyword_create(keyword, __location__, name="TARGET_LIMIT", &
306  description="Specifies the limit of the growth of the target value of the constrained collective"// &
307  " variable. By default no limit at the colvar growth is set.", &
308  usage="TARGET_LIMIT {real}", type_of_var=real_t, &
309  unit_str="internal_cp2k")
310  CALL section_add_keyword(section, keyword)
311  CALL keyword_release(keyword)
312 
313  CALL keyword_create(keyword, __location__, name="EXCLUDE_QM", &
314  description="Does not apply the constraint to the QM region within a QM/MM calculation", &
315  usage="EXCLUDE_QM <LOGICAL>", &
316  default_l_val=.false., lone_keyword_l_val=.true.)
317  CALL section_add_keyword(section, keyword)
318  CALL keyword_release(keyword)
319 
320  CALL keyword_create(keyword, __location__, name="EXCLUDE_MM", &
321  description="Does not apply the constraint to the MM region within a QM/MM calculation", &
322  usage="EXCLUDE_MM <LOGICAL>", &
323  default_l_val=.false., lone_keyword_l_val=.true.)
324  CALL section_add_keyword(section, keyword)
325  CALL keyword_release(keyword)
326 
327  END SUBROUTINE create_collective_section
328 
329 ! **************************************************************************************************
330 !> \brief Create the constraint section that fixes atoms
331 !> \param section the section to create
332 !> \author teo
333 ! **************************************************************************************************
334  SUBROUTINE create_fixed_atom_section(section)
335  TYPE(section_type), POINTER :: section
336 
337  TYPE(keyword_type), POINTER :: keyword
338 
339  cpassert(.NOT. ASSOCIATED(section))
340  CALL section_create(section, __location__, name="fixed_atoms", &
341  description="This section is used to constraint the fractional atomic position (X,Y,Z). Note "// &
342  "that fractional coordinates are constrained, not real space coordinates. In case "// &
343  "a restraint is specified the value of the TARGET is considered to be the value of the "// &
344  "coordinates at the beginning of the run or alternatively the corresponding value in the section: "// &
345  "FIX_ATOM_RESTART.", n_keywords=3, n_subsections=0, repeats=.true.)
346  NULLIFY (keyword)
347 
348  ! Section Parameter
349  CALL keyword_create(keyword, __location__, name="COMPONENTS_TO_FIX", &
350  description="Specify which fractional components (X,Y,Z or combinations) of the atoms specified "// &
351  "in the section will be constrained/restrained.", &
352  usage="COMPONENTS_TO_FIX (x|y|z|xy|xz|yz|xyz)", &
353  default_i_val=use_perd_xyz, &
354  enum_c_vals=s2a("x", "y", "z", "xy", "xz", "yz", "xyz"), &
355  enum_i_vals=(/use_perd_x, use_perd_y, use_perd_z, &
357  use_perd_xyz/), &
358  enum_desc=s2a("Fix only X component", &
359  "Fix only Y component", &
360  "Fix only Z component", &
361  "Fix X-Y components", &
362  "Fix X-Z components", &
363  "Fix Y-Z components", &
364  "Fix the full components of the atomic position."), &
365  repeats=.false.)
366  CALL section_add_keyword(section, keyword)
367  CALL keyword_release(keyword)
368 
369  ! Integer
370  CALL keyword_create(keyword, __location__, name="LIST", &
371  description="Specifies a list of atoms to freeze.", &
372  usage="LIST {integer} {integer} .. {integer}", repeats=.true., &
373  n_var=-1, type_of_var=integer_t)
374  CALL section_add_keyword(section, keyword)
375  CALL keyword_release(keyword)
376 
377  CALL keyword_create(keyword, __location__, name="MOLNAME", &
378  variants=(/"SEGNAME"/), &
379  description="Specifies the name of the molecule to fix", &
380  usage="MOLNAME WAT MEOH", repeats=.true., &
381  n_var=-1, type_of_var=char_t)
382  CALL section_add_keyword(section, keyword)
383  CALL keyword_release(keyword)
384 
385  CALL keyword_create( &
386  keyword, __location__, name="MM_SUBSYS", &
387  variants=(/"PROTEIN"/), &
388  description="In a QM/MM run all MM atoms are fixed according to the argument.", &
389  usage="MM_SUBSYS (NONE|ATOMIC|MOLECULAR)", &
390  enum_c_vals=s2a("NONE", "ATOMIC", "MOLECULAR"), &
391  enum_i_vals=(/do_constr_none, do_constr_atomic, do_constr_molec/), &
392  enum_desc=s2a("fix nothing", &
393  "only the MM atoms itself", &
394  "the full molecule/residue that contains a MM atom (i.e. some QM atoms might be fixed as well)"), &
395  default_i_val=do_constr_none, repeats=.false.)
396  CALL section_add_keyword(section, keyword)
397  CALL keyword_release(keyword)
398 
399  CALL keyword_create( &
400  keyword, __location__, name="QM_SUBSYS", &
401  description="In a QM/MM run all QM atoms are fixed according to the argument.", &
402  usage="QM_SUBSYS (NONE|ATOMIC|MOLECULAR)", &
403  enum_c_vals=s2a("NONE", "ATOMIC", "MOLECULAR"), &
404  enum_desc=s2a("fix nothing", &
405  "only the QM atoms itself", &
406  "the full molecule/residue that contains a QM atom (i.e. some MM atoms might be fixed as well)"), &
407  enum_i_vals=(/do_constr_none, do_constr_atomic, do_constr_molec/), &
408  default_i_val=do_constr_none, repeats=.false.)
409  CALL section_add_keyword(section, keyword)
410  CALL keyword_release(keyword)
411 
412  CALL keyword_create(keyword, __location__, name="EXCLUDE_QM", &
413  description="Does not apply the constraint to the QM region within a QM/MM calculation."// &
414  " This keyword is active only together with MOLNAME", &
415  usage="EXCLUDE_QM <LOGICAL>", &
416  default_l_val=.false., lone_keyword_l_val=.true.)
417  CALL section_add_keyword(section, keyword)
418  CALL keyword_release(keyword)
419 
420  CALL keyword_create(keyword, __location__, name="EXCLUDE_MM", &
421  description="Does not apply the constraint to the MM region within a QM/MM calculation."// &
422  " This keyword is active only together with MOLNAME", &
423  usage="EXCLUDE_MM <LOGICAL>", &
424  default_l_val=.false., lone_keyword_l_val=.true.)
425  CALL section_add_keyword(section, keyword)
426  CALL keyword_release(keyword)
427 
428  END SUBROUTINE create_fixed_atom_section
429 
430 ! **************************************************************************************************
431 !> \brief Create the constraint section specialized on g3x3 constraints
432 !> \param section the section to create
433 !> \author teo
434 ! **************************************************************************************************
435  SUBROUTINE create_g3x3_section(section)
436  TYPE(section_type), POINTER :: section
437 
438  TYPE(keyword_type), POINTER :: keyword
439 
440  cpassert(.NOT. ASSOCIATED(section))
441  CALL section_create(section, __location__, name="g3x3", &
442  description="This section is used to set 3x3 (3 atoms and 3 distances) constraints.", &
443  n_keywords=3, n_subsections=0, repeats=.true.)
444 
445  NULLIFY (keyword)
446 
447  ! Integer
448  CALL keyword_create(keyword, __location__, name="MOLECULE", &
449  variants=(/"MOL"/), &
450  description="Specifies the molecule kind number on which constraint will be applied."// &
451  " MOLECULE and MOLNAME keyword exclude themself mutually.", &
452  usage="MOL {integer}", n_var=1, type_of_var=integer_t)
453  CALL section_add_keyword(section, keyword)
454  CALL keyword_release(keyword)
455 
456  CALL keyword_create(keyword, __location__, name="MOLNAME", &
457  variants=(/"SEGNAME"/), &
458  description="Specifies the name of the molecule on which the constraint will be applied.", &
459  usage="MOLNAME {character}", n_var=1, type_of_var=char_t)
460  CALL section_add_keyword(section, keyword)
461  CALL keyword_release(keyword)
462 
463  CALL keyword_create(keyword, __location__, name="INTERMOLECULAR", &
464  description="Specify if the constraint/restraint is intermolecular.", &
465  usage="INTERMOLECULAR <LOGICAL>", &
466  default_l_val=.false., lone_keyword_l_val=.true.)
467  CALL section_add_keyword(section, keyword)
468  CALL keyword_release(keyword)
469 
470  CALL keyword_create(keyword, __location__, name="ATOMS", &
471  description="Atoms' index on which apply the constraint", usage="ATOMS 1 3 6", &
472  n_var=-1, type_of_var=integer_t)
473  CALL section_add_keyword(section, keyword)
474  CALL keyword_release(keyword)
475 
476  ! Real
477  CALL keyword_create(keyword, __location__, name="DISTANCES", &
478  description="The constrained distances' values.", &
479  usage="DISTANCES {real} {real} {real}", type_of_var=real_t, &
480  unit_str="internal_cp2k", n_var=-1)
481  CALL section_add_keyword(section, keyword)
482  CALL keyword_release(keyword)
483 
484  ! Logical
485  CALL keyword_create(keyword, __location__, name="EXCLUDE_QM", &
486  description="Does not apply the constraint to the QM region within a QM/MM calculation", &
487  usage="EXCLUDE_QM <LOGICAL>", &
488  default_l_val=.false., lone_keyword_l_val=.true.)
489  CALL section_add_keyword(section, keyword)
490  CALL keyword_release(keyword)
491 
492  CALL keyword_create(keyword, __location__, name="EXCLUDE_MM", &
493  description="Does not apply the constraint to the MM region within a QM/MM calculation", &
494  usage="EXCLUDE_MM <LOGICAL>", &
495  default_l_val=.false., lone_keyword_l_val=.true.)
496  CALL section_add_keyword(section, keyword)
497  CALL keyword_release(keyword)
498 
499  END SUBROUTINE create_g3x3_section
500 
501 ! **************************************************************************************************
502 !> \brief Create the constraint section specialized on H BONDS constraints
503 !> \param section the section to create
504 !> \author teo
505 ! **************************************************************************************************
506  SUBROUTINE create_hbonds_section(section)
507  TYPE(section_type), POINTER :: section
508 
509  TYPE(keyword_type), POINTER :: keyword
510 
511  cpassert(.NOT. ASSOCIATED(section))
512  CALL section_create(section, __location__, name="HBONDS", &
513  description="This section is used to set bonds constraints involving Hydrogen atoms", &
514  n_keywords=3, n_subsections=0, repeats=.false.)
515 
516  NULLIFY (keyword)
517  ! Character
518  CALL keyword_create(keyword, __location__, name="ATOM_TYPE", &
519  description="Defines the atoms' type forming a bond with an hydrogen. If not specified"// &
520  " the default bond value of the first molecule is used as constraint target", &
521  usage="ATOMS <CHARACTER>", &
522  n_var=-1, type_of_var=char_t)
523  CALL section_add_keyword(section, keyword)
524  CALL keyword_release(keyword)
525 
526  CALL keyword_create(keyword, __location__, name="MOLECULE", &
527  description="Specifies the indexes of the molecule kind (in input file order)"// &
528  " on which the constraint will be applied."// &
529  " MOLECULE and MOLNAME keyword exclude themself mutually.", &
530  usage="MOLECULE {integer} .. {integer} ", n_var=-1, &
531  type_of_var=integer_t)
532  CALL section_add_keyword(section, keyword)
533  CALL keyword_release(keyword)
534 
535  CALL keyword_create(keyword, __location__, name="MOLNAME", &
536  variants=(/"SEGNAME"/), &
537  description="Specifies the names of the molecule on which the constraint will be applied.", &
538  usage="MOLNAME {character} .. {character} ", n_var=-1, &
539  type_of_var=char_t)
540  CALL section_add_keyword(section, keyword)
541  CALL keyword_release(keyword)
542 
543  CALL keyword_create(keyword, __location__, name="EXCLUDE_QM", &
544  description="Does not shake HBONDS in the QM region within a QM/MM calculation", &
545  usage="EXCLUDE_QM <LOGICAL>", &
546  default_l_val=.false., lone_keyword_l_val=.true.)
547  CALL section_add_keyword(section, keyword)
548  CALL keyword_release(keyword)
549 
550  CALL keyword_create(keyword, __location__, name="EXCLUDE_MM", &
551  description="Does not shake HBONDS in the MM region within a QM/MM calculation", &
552  usage="EXCLUDE_MM <LOGICAL>", &
553  default_l_val=.false., lone_keyword_l_val=.true.)
554  CALL section_add_keyword(section, keyword)
555  CALL keyword_release(keyword)
556 
557  ! Real
558  CALL keyword_create(keyword, __location__, name="TARGETS", &
559  description="The constrained distances' values for the types defines in ATOM_TYPE.", &
560  usage="TARGETS {real} {real} {real}", type_of_var=real_t, n_var=-1, &
561  unit_str="internal_cp2k")
562  CALL section_add_keyword(section, keyword)
563  CALL keyword_release(keyword)
564 
565  END SUBROUTINE create_hbonds_section
566 
567 ! **************************************************************************************************
568 !> \brief Create the constraint section specialized on g4x6 constraints
569 !> \param section the section to create
570 !> \author teo
571 ! **************************************************************************************************
572  SUBROUTINE create_g4x6_section(section)
573  TYPE(section_type), POINTER :: section
574 
575  TYPE(keyword_type), POINTER :: keyword
576 
577  cpassert(.NOT. ASSOCIATED(section))
578  CALL section_create(section, __location__, name="g4x6", &
579  description="This section is used to set 4x6 (4 atoms and 6 distances) constraints.", &
580  n_keywords=3, n_subsections=0, repeats=.true.)
581 
582  NULLIFY (keyword)
583 
584  ! Integer
585  CALL keyword_create(keyword, __location__, name="MOLECULE", &
586  variants=(/"MOL"/), &
587  description="Specifies the molecule number on which constraint will be applied."// &
588  " MOLECULE and MOLNAME keyword exclude themself mutually.", &
589  usage="MOL {integer}", 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="MOLNAME", &
594  variants=(/"SEGNAME"/), &
595  description="Specifies the name of the molecule on which the constraint will be applied.", &
596  usage="MOLNAME {character}", n_var=1, type_of_var=char_t)
597  CALL section_add_keyword(section, keyword)
598  CALL keyword_release(keyword)
599 
600  CALL keyword_create(keyword, __location__, name="INTERMOLECULAR", &
601  description="Specify if the constraint/restraint is intermolecular.", &
602  usage="INTERMOLECULAR <LOGICAL>", &
603  default_l_val=.false., lone_keyword_l_val=.true.)
604  CALL section_add_keyword(section, keyword)
605  CALL keyword_release(keyword)
606 
607  CALL keyword_create(keyword, __location__, name="ATOMS", &
608  description="Atoms' index on which apply the constraint", usage="ATOMS 1 3 6 4", &
609  n_var=4, type_of_var=integer_t)
610  CALL section_add_keyword(section, keyword)
611  CALL keyword_release(keyword)
612 
613  ! Real
614  CALL keyword_create(keyword, __location__, name="DISTANCES", &
615  description="The constrained distances' values.", &
616  usage="DISTANCES {real} {real} {real} {real} {real} {real}", &
617  type_of_var=real_t, n_var=6, unit_str="internal_cp2k")
618  CALL section_add_keyword(section, keyword)
619  CALL keyword_release(keyword)
620 
621  ! Logical
622  CALL keyword_create(keyword, __location__, name="EXCLUDE_QM", &
623  description="Does not apply the constraint to the QM region within a QM/MM calculation", &
624  usage="EXCLUDE_QM <LOGICAL>", &
625  default_l_val=.false., lone_keyword_l_val=.true.)
626  CALL section_add_keyword(section, keyword)
627  CALL keyword_release(keyword)
628 
629  CALL keyword_create(keyword, __location__, name="EXCLUDE_MM", &
630  description="Does not apply the constraint to the MM region within a QM/MM calculation", &
631  usage="EXCLUDE_MM <LOGICAL>", &
632  default_l_val=.false., lone_keyword_l_val=.true.)
633  CALL section_add_keyword(section, keyword)
634  CALL keyword_release(keyword)
635 
636  END SUBROUTINE create_g4x6_section
637 
638 ! **************************************************************************************************
639 !> \brief Create the constraint section specialized on vsite constraints
640 !> \param section the section to create
641 !> \author marcel baer
642 ! **************************************************************************************************
643  SUBROUTINE create_vsite_section(section)
644  TYPE(section_type), POINTER :: section
645 
646  TYPE(keyword_type), POINTER :: keyword
647 
648  cpassert(.NOT. ASSOCIATED(section))
649  CALL section_create(section, __location__, name="virtual_site", &
650  description="This section is used to set a virtual interaction-site constraint.", &
651  n_keywords=3, n_subsections=0, repeats=.true.)
652 
653  NULLIFY (keyword)
654 
655  ! Integer
656  CALL keyword_create(keyword, __location__, name="MOLECULE", &
657  variants=(/"MOL"/), &
658  description="Specifies the molecule number on which constraint will be applied."// &
659  " MOLECULE and MOLNAME keyword exclude themself mutually.", &
660  usage="MOL {integer}", n_var=1, type_of_var=integer_t)
661  CALL section_add_keyword(section, keyword)
662  CALL keyword_release(keyword)
663 
664  CALL keyword_create(keyword, __location__, name="MOLNAME", &
665  variants=(/"SEGNAME"/), &
666  description="Specifies the name of the molecule on which the constraint will be applied.", &
667  usage="MOLNAME {character}", n_var=1, type_of_var=char_t)
668  CALL section_add_keyword(section, keyword)
669  CALL keyword_release(keyword)
670 
671  CALL keyword_create(keyword, __location__, name="INTERMOLECULAR", &
672  description="Specify if the constraint/restraint is intermolecular.", &
673  usage="INTERMOLECULAR <LOGICAL>", &
674  default_l_val=.false., lone_keyword_l_val=.true.)
675  CALL section_add_keyword(section, keyword)
676  CALL keyword_release(keyword)
677 
678  CALL keyword_create(keyword, __location__, name="ATOMS", &
679  description="Atoms' index on which apply the constraint (v i j k), first is virtual site", &
680  usage="ATOMS 1 2 3 4", &
681  n_var=4, type_of_var=integer_t)
682  CALL section_add_keyword(section, keyword)
683  CALL keyword_release(keyword)
684 
685  ! Real
686  CALL keyword_create(keyword, __location__, name="PARAMETERS", &
687  description="The constrained parameters' values to construct virtual site. "// &
688  "r_v=a*r_ij+b*r_kj", &
689  usage="PARAMETERS {real} {real}", &
690  type_of_var=real_t, n_var=2, unit_str="internal_cp2k")
691  CALL section_add_keyword(section, keyword)
692  CALL keyword_release(keyword)
693 
694  ! Logical
695  CALL keyword_create(keyword, __location__, name="EXCLUDE_QM", &
696  description="Does not apply the constraint to the QM region within a QM/MM calculation", &
697  usage="EXCLUDE_QM <LOGICAL>", &
698  default_l_val=.false., lone_keyword_l_val=.true.)
699  CALL section_add_keyword(section, keyword)
700  CALL keyword_release(keyword)
701 
702  CALL keyword_create(keyword, __location__, name="EXCLUDE_MM", &
703  description="Does not apply the constraint to the MM region within a QM/MM calculation", &
704  usage="EXCLUDE_MM <LOGICAL>", &
705  default_l_val=.false., lone_keyword_l_val=.true.)
706  CALL section_add_keyword(section, keyword)
707  CALL keyword_release(keyword)
708 
709  END SUBROUTINE create_vsite_section
710 END MODULE input_cp2k_constraints
Handles all functions related to the CELL.
Definition: cell_types.F:15
integer, parameter, public use_perd_xyz
Definition: cell_types.F:42
integer, parameter, public use_perd_y
Definition: cell_types.F:42
integer, parameter, public use_perd_xz
Definition: cell_types.F:42
integer, parameter, public use_perd_x
Definition: cell_types.F:42
integer, parameter, public use_perd_z
Definition: cell_types.F:42
integer, parameter, public use_perd_yz
Definition: cell_types.F:42
integer, parameter, public use_perd_xy
Definition: cell_types.F:42
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public high_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_constr_atomic
integer, parameter, public do_constr_molec
integer, parameter, public do_constr_none
subroutine, public create_constraint_section(section)
Create the constraint section. This section is useful to impose constraints.
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 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.