(git:281339c)
Loading...
Searching...
No Matches
input_cp2k_motion.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 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!> 01.2020 add keywords related to Space Groups [pcazade]
12!> \author teo & fawzi
13! **************************************************************************************************
15 USE bibliography, ONLY: brieuc2016, &
16 byrd1995, &
29 USE cp_units, ONLY: cp_unit_to_cp2k
30 USE input_constants, ONLY: &
50 USE input_cp2k_thermostats, ONLY: create_coord_section, &
52 create_velocity_section
62 USE input_val_types, ONLY: integer_t, &
63 logical_t, &
64 real_t, &
65 char_t
66 USE kinds, ONLY: dp
67 USE string_utilities, ONLY: s2a
68#include "../base/base_uses.f90"
69
70 IMPLICIT NONE
71 PRIVATE
72
73 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
74 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_motion'
75
76 PUBLIC :: create_motion_section
77
78CONTAINS
79
80! **************************************************************************************************
81!> \brief creates the motion section
82!> \param section the section to be created
83!> \author teo
84! **************************************************************************************************
85 SUBROUTINE create_motion_section(section)
86 TYPE(section_type), POINTER :: section
87
88 TYPE(section_type), POINTER :: subsection
89
90 cpassert(.NOT. ASSOCIATED(section))
91 CALL section_create(section, __location__, name="motion", &
92 description="This section defines a set of tool connected with the motion of the nuclei.", &
93 n_keywords=1, n_subsections=1, repeats=.false.)
94
95 NULLIFY (subsection)
96
97 CALL create_geoopt_section(subsection, __location__, label="GEO_OPT", &
98 description="This section sets the environment of the geometry optimizer.", &
99 just_optimizers=.false., &
100 use_model_hessian=.true.)
101 CALL section_add_subsection(section, subsection)
102 CALL section_release(subsection)
103
104 CALL create_cell_opt_section(subsection)
105 CALL section_add_subsection(section, subsection)
106 CALL section_release(subsection)
107
108 CALL create_shellcore_opt_section(subsection)
109 CALL section_add_subsection(section, subsection)
110 CALL section_release(subsection)
111
112 CALL create_md_section(subsection)
113 CALL section_add_subsection(section, subsection)
114 CALL section_release(subsection)
115
116 CALL create_driver_section(subsection)
117 CALL section_add_subsection(section, subsection)
118 CALL section_release(subsection)
119
120 CALL create_fe_section(subsection)
121 CALL section_add_subsection(section, subsection)
122 CALL section_release(subsection)
123
124 CALL create_constraint_section(subsection)
125 CALL section_add_subsection(section, subsection)
126 CALL section_release(subsection)
127
128 CALL create_fp_section(subsection)
129 CALL section_add_subsection(section, subsection)
130 CALL section_release(subsection)
131
132 CALL create_mc_section(subsection)
133 CALL section_add_subsection(section, subsection)
134 CALL section_release(subsection)
135
136 CALL create_tmc_section(subsection)
137 CALL section_add_subsection(section, subsection)
138 CALL section_release(subsection)
139
140 CALL create_pint_section(subsection)
141 CALL section_add_subsection(section, subsection)
142 CALL section_release(subsection)
143
144 CALL create_band_section(subsection)
145 CALL section_add_subsection(section, subsection)
146 CALL section_release(subsection)
147
148 CALL create_motion_print_section(subsection)
149 CALL section_add_subsection(section, subsection)
150 CALL section_release(subsection)
151
152 END SUBROUTINE create_motion_section
153
154! **************************************************************************************************
155!> \brief creates the Monte Carlo section
156!> \param section the section to be created
157!> \author matt
158! **************************************************************************************************
159 SUBROUTINE create_mc_section(section)
160 TYPE(section_type), POINTER :: section
161
162 TYPE(keyword_type), POINTER :: keyword
163 TYPE(section_type), POINTER :: subsection
164
165 cpassert(.NOT. ASSOCIATED(section))
166 CALL section_create(section, __location__, name="mc", &
167 description="This section sets parameters to set up a MonteCarlo calculation.", &
168 n_keywords=10, n_subsections=2, repeats=.false.)
169
170 NULLIFY (keyword, subsection)
171
172 CALL keyword_create(keyword, __location__, name="NSTEP", &
173 description="Specifies the number of MC cycles.", &
174 usage="NSTEP {integer}", &
175 default_i_val=100)
176 CALL section_add_keyword(section, keyword)
177 CALL keyword_release(keyword)
178
179 CALL keyword_create(keyword, __location__, name="IPRINT", &
180 description="Prints coordinate/cell/etc information every IPRINT steps.", &
181 usage="IPRINT {integer}", &
182 default_i_val=1)
183 CALL section_add_keyword(section, keyword)
184 CALL keyword_release(keyword)
185
186 CALL keyword_create(keyword, __location__, name="NMOVES", &
187 description="Specifies the number of classical moves between energy evaluations. ", &
188 usage="NMOVES {integer}", &
189 default_i_val=4)
190 CALL section_add_keyword(section, keyword)
191 CALL keyword_release(keyword)
192
193 CALL keyword_create(keyword, __location__, name="NSWAPMOVES", &
194 description="How many insertions to try per swap move.", &
195 usage="NSWAPMOVES {integer}", &
196 default_i_val=16)
197 CALL section_add_keyword(section, keyword)
198 CALL keyword_release(keyword)
199
200 CALL keyword_create(keyword, __location__, name="LBIAS", &
201 description="Dictates if we presample moves with a different potential.", &
202 usage="LBIAS {logical}", &
203 default_l_val=.false.)
204 CALL section_add_keyword(section, keyword)
205 CALL keyword_release(keyword)
206
207 CALL keyword_create(keyword, __location__, name="LSTOP", &
208 description="Makes nstep in terms of steps, instead of cycles.", &
209 usage="LSTOP {logical}", &
210 default_l_val=.false.)
211 CALL section_add_keyword(section, keyword)
212 CALL keyword_release(keyword)
213
214 CALL keyword_create(keyword, __location__, name="LDISCRETE", &
215 description="Changes the volume of the box in discrete steps, one side at a time.", &
216 usage="LDISCRETE {logical}", &
217 default_l_val=.false.)
218 CALL section_add_keyword(section, keyword)
219 CALL keyword_release(keyword)
220
221 CALL keyword_create(keyword, __location__, name="RCLUS", &
222 description="The cluster cut off radius in angstroms.", &
223 usage="RCLUS {real}", &
224 default_r_val=1.0e0_dp)
225 CALL section_add_keyword(section, keyword)
226 CALL keyword_release(keyword)
227
228 CALL keyword_create(keyword, __location__, name="RESTART", &
229 description="Read initial configuration from restart file.", &
230 usage="RESTART {logical}", &
231 default_l_val=.false.)
232 CALL section_add_keyword(section, keyword)
233 CALL keyword_release(keyword)
234
235 CALL keyword_create( &
236 keyword, __location__, name="NVIRIAL", &
237 description="Use this many random orientations to compute the second virial coefficient (ENSEMBLE=VIRIAL)", &
238 usage="NVIRIAL {integer}", &
239 default_i_val=1000)
240 CALL section_add_keyword(section, keyword)
241 CALL keyword_release(keyword)
242
243 CALL keyword_create(keyword, __location__, name="ENSEMBLE", &
244 description="Specify the type of simulation", &
245 usage="ENSEMBLE (TRADITIONAL|GEMC_NVT|GEMC_NPT|VIRIAL)", &
246 enum_c_vals=s2a("TRADITIONAL", "GEMC_NVT", "GEMC_NPT", "VIRIAL"), &
248 default_i_val=do_mc_traditional)
249 CALL section_add_keyword(section, keyword)
250 CALL keyword_release(keyword)
251
252 CALL keyword_create(keyword, __location__, name="RESTART_FILE_NAME", &
253 description="Name of the restart file for MC information.", &
254 usage="RESTART_FILE_NAME {filename}", &
255 default_lc_val="")
256 CALL section_add_keyword(section, keyword)
257 CALL keyword_release(keyword)
258
259 CALL keyword_create(keyword, __location__, name="MOVES_FILE_NAME", &
260 description="The file to print the move statistics to.", &
261 usage="MOVES_FILE_NAME {filename}", &
262 default_lc_val="")
263 CALL section_add_keyword(section, keyword)
264 CALL keyword_release(keyword)
265
266 CALL keyword_create(keyword, __location__, name="MOLECULES_FILE_NAME", &
267 description="The file to print the number of molecules to.", &
268 usage="MOLECULES_FILE_NAME {filename}", &
269 default_lc_val="")
270 CALL section_add_keyword(section, keyword)
271 CALL keyword_release(keyword)
272
273 CALL keyword_create(keyword, __location__, name="COORDINATE_FILE_NAME", &
274 description="The file to print the current coordinates to.", &
275 usage="COORDINATE_FILE_NAME {filename}", &
276 default_lc_val="")
277 CALL section_add_keyword(section, keyword)
278 CALL keyword_release(keyword)
279
280 CALL keyword_create(keyword, __location__, name="ENERGY_FILE_NAME", &
281 description="The file to print current energies to.", &
282 usage="ENERGY_FILE_NAME {filename}", &
283 default_lc_val="")
284 CALL section_add_keyword(section, keyword)
285 CALL keyword_release(keyword)
286
287 CALL keyword_create(keyword, __location__, name="DATA_FILE_NAME", &
288 description="The file to print current configurational info to.", &
289 usage="DATA_FILE_NAME {filename}", &
290 default_lc_val="")
291 CALL section_add_keyword(section, keyword)
292 CALL keyword_release(keyword)
293
294 CALL keyword_create(keyword, __location__, name="CELL_FILE_NAME", &
295 description="The file to print current cell length info to.", &
296 usage="CELL_FILE_NAME {filename}", &
297 default_lc_val="")
298 CALL section_add_keyword(section, keyword)
299 CALL keyword_release(keyword)
300
301 CALL keyword_create(keyword, __location__, name="MAX_DISP_FILE_NAME", &
302 description="The file to print current maximum displacement info to.", &
303 usage="MAX_DISP_FILE_NAME {filename}", &
304 default_lc_val="")
305 CALL section_add_keyword(section, keyword)
306 CALL keyword_release(keyword)
307
308 CALL keyword_create(keyword, __location__, name="BOX2_FILE_NAME", &
309 description="For GEMC, the name of the input file for the other box.", &
310 usage="BOX2_FILE_NAME {filename}", &
311 default_lc_val="")
312 CALL section_add_keyword(section, keyword)
313 CALL keyword_release(keyword)
314
315 CALL keyword_create(keyword, __location__, name="PRESSURE", &
316 description="The pressure for NpT simulations, in bar.", &
317 usage="PRESSURE {real}", &
318 type_of_var=real_t)
319 CALL section_add_keyword(section, keyword)
320 CALL keyword_release(keyword)
321
322 CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
323 description="The temperature of the simulation, in Kelvin.", &
324 usage="TEMPERATURE {real}", &
325 type_of_var=real_t)
326 CALL section_add_keyword(section, keyword)
327 CALL keyword_release(keyword)
328
329 CALL keyword_create( &
330 keyword, __location__, name="VIRIAL_TEMPS", &
331 description="The temperatures you wish to compute the virial coefficient for. Only used if ensemble=VIRIAL.", &
332 usage="VIRIAL_TEMPS {real} {real} ... ", &
333 n_var=-1, type_of_var=real_t)
334 CALL section_add_keyword(section, keyword)
335 CALL keyword_release(keyword)
336
337 CALL keyword_create(keyword, __location__, name="DISCRETE_STEP", &
338 description="The size of the discrete volume move step, in angstroms.", &
339 usage="DISCRETE_STEP {real}", &
340 default_r_val=1.0e0_dp)
341 CALL section_add_keyword(section, keyword)
342 CALL keyword_release(keyword)
343
344 CALL keyword_create(keyword, __location__, name="ETA", &
345 description="The free energy bias (in Kelvin) for swapping a molecule of each type into this box.", &
346 usage="ETA {real} {real} ... ", &
347 n_var=-1, type_of_var=real_t)
348 CALL section_add_keyword(section, keyword)
349 CALL keyword_release(keyword)
350
351 CALL keyword_create(keyword, __location__, name="RANDOMTOSKIP", &
352 description="Number of random numbers from the acceptance/rejection stream to skip", &
353 usage="RANDOMTOSKIP {integer}", &
354 default_i_val=0)
355 CALL section_add_keyword(section, keyword)
356 CALL keyword_release(keyword)
357
358 CALL create_avbmc_section(subsection)
359 CALL section_add_subsection(section, subsection)
360 CALL section_release(subsection)
361
362 CALL create_move_prob_section(subsection)
363 CALL section_add_subsection(section, subsection)
364 CALL section_release(subsection)
365
366 CALL create_update_section(subsection)
367 CALL section_add_subsection(section, subsection)
368 CALL section_release(subsection)
369
370 CALL create_max_disp_section(subsection)
371 CALL section_add_subsection(section, subsection)
372 CALL section_release(subsection)
373
374 END SUBROUTINE create_mc_section
375
376! **************************************************************************************************
377!> \brief ...
378!> \param section will contain the AVBMC parameters for MC
379!> \author matt
380! **************************************************************************************************
381 SUBROUTINE create_avbmc_section(section)
382 TYPE(section_type), POINTER :: section
383
384 TYPE(keyword_type), POINTER :: keyword
385
386 cpassert(.NOT. ASSOCIATED(section))
387
388 CALL section_create(section, __location__, name="avbmc", &
389 description="Parameters for Aggregation Volume Bias Monte Carlo (AVBMC) "// &
390 "which explores cluster formation and destruction. "// &
391 "Chen and Siepmann, J. Phys. Chem. B 105, 11275-11282 (2001).", &
392 n_keywords=5, n_subsections=0, repeats=.false.)
393
394 NULLIFY (keyword)
395
396 CALL keyword_create( &
397 keyword, __location__, name="PBIAS", &
398 description="The probability of swapping to an inner region in an AVBMC swap move for each molecule type.", &
399 usage="PBIAS {real} {real} ... ", &
400 n_var=-1, type_of_var=real_t)
401 CALL section_add_keyword(section, keyword)
402 CALL keyword_release(keyword)
403
404 CALL keyword_create(keyword, __location__, name="AVBMC_ATOM", &
405 description="The target atom for an AVBMC swap move for each molecule type.", &
406 usage="AVBMC_ATOM {integer} {integer} ... ", &
407 n_var=-1, type_of_var=integer_t)
408 CALL section_add_keyword(section, keyword)
409 CALL keyword_release(keyword)
410
411 CALL keyword_create(keyword, __location__, name="AVBMC_RMIN", &
412 description="The inner radius for an AVBMC swap move, in angstroms for every molecule type.", &
413 usage="AVBMC_RMIN {real} {real} ... ", &
414 n_var=-1, type_of_var=real_t)
415 CALL section_add_keyword(section, keyword)
416 CALL keyword_release(keyword)
417
418 CALL keyword_create(keyword, __location__, name="AVBMC_RMAX", &
419 description="The outer radius for an AVBMC swap move, in angstroms, for every molecule type.", &
420 usage="AVBMC_RMAX {real} {real} ... ", &
421 n_var=-1, type_of_var=real_t)
422 CALL section_add_keyword(section, keyword)
423 CALL keyword_release(keyword)
424
425 END SUBROUTINE create_avbmc_section
426
427! **************************************************************************************************
428!> \brief ...
429!> \param section will contain the probabilities for attempting each move
430!> type in Monte Carlo
431!> \author matt
432! **************************************************************************************************
433 SUBROUTINE create_move_prob_section(section)
434 TYPE(section_type), POINTER :: section
435
436 TYPE(keyword_type), POINTER :: keyword
437 TYPE(section_type), POINTER :: subsection
438
439 cpassert(.NOT. ASSOCIATED(section))
440
441 CALL section_create(section, __location__, name="move_probabilities", &
442 description="Parameters for fraction of moves performed for each move type.", &
443 n_keywords=5, n_subsections=2, repeats=.false.)
444
445 NULLIFY (keyword, subsection)
446
447 CALL keyword_create(keyword, __location__, name="PMHMC", &
448 description="The probability of attempting a hybrid MC move.", &
449 usage="PMHMC {real}", &
450 type_of_var=real_t, default_r_val=0.0e0_dp)
451 CALL section_add_keyword(section, keyword)
452 CALL keyword_release(keyword)
453
454 CALL keyword_create(keyword, __location__, name="PMTRANS", &
455 description="The probability of attempting a molecule translation.", &
456 usage="PMTRANS {real}", &
457 type_of_var=real_t)
458 CALL section_add_keyword(section, keyword)
459 CALL keyword_release(keyword)
460
461 CALL keyword_create(keyword, __location__, name="PMCLTRANS", &
462 description="The probability of attempting a cluster translation.", &
463 usage="PMCLTRANS {real}", &
464 type_of_var=real_t, default_r_val=0.0e0_dp)
465 CALL section_add_keyword(section, keyword)
466 CALL keyword_release(keyword)
467
468 CALL keyword_create(keyword, __location__, name="PMAVBMC", &
469 description="The probability of attempting an AVBMC swap move.", &
470 usage="PMAVBMC {real}", &
471 default_r_val=0.0e0_dp)
472 CALL section_add_keyword(section, keyword)
473 CALL keyword_release(keyword)
474
475 CALL keyword_create(keyword, __location__, name="PMTRAION", &
476 description="The probability of attempting a conformational change.", &
477 usage="PMTRAION {real}", &
478 type_of_var=real_t)
479 CALL section_add_keyword(section, keyword)
480 CALL keyword_release(keyword)
481
482 CALL keyword_create(keyword, __location__, name="PMSWAP", &
483 description="The probability of attempting a swap move.", &
484 usage="PMSWAP {real}", &
485 type_of_var=real_t, default_r_val=0.0e0_dp)
486 CALL section_add_keyword(section, keyword)
487 CALL keyword_release(keyword)
488
489 CALL keyword_create(keyword, __location__, name="PMVOLUME", &
490 description="The probability of attempting a volume move.", &
491 usage="PMVOLUME {real}", &
492 type_of_var=real_t, default_r_val=0.0e0_dp)
493 CALL section_add_keyword(section, keyword)
494 CALL keyword_release(keyword)
495
496 CALL create_mol_prob_section(subsection)
497 CALL section_add_subsection(section, subsection)
498 CALL section_release(subsection)
499
500 CALL create_box_prob_section(subsection)
501 CALL section_add_subsection(section, subsection)
502 CALL section_release(subsection)
503
504 END SUBROUTINE create_move_prob_section
505
506! **************************************************************************************************
507!> \brief ...
508!> \param section will contain the probabilities for attempting various moves
509!> on the various molecule types present in the system
510!> \author matt
511! **************************************************************************************************
512 SUBROUTINE create_mol_prob_section(section)
513 TYPE(section_type), POINTER :: section
514
515 TYPE(keyword_type), POINTER :: keyword
516
517 cpassert(.NOT. ASSOCIATED(section))
518
519 CALL section_create(section, __location__, name="mol_probabilities", &
520 description="Probabilities of attempting various moves types on "// &
521 "the various molecular types present in the simulation.", &
522 n_keywords=5, n_subsections=0, repeats=.false.)
523
524 NULLIFY (keyword)
525
526 CALL keyword_create(keyword, __location__, name="PMAVBMC_MOL", &
527 description="The probability of attempting an AVBMC swap move on each molecule type.", &
528 usage="PMAVBMC_MOL {real} {real} ... ", &
529 n_var=-1, type_of_var=real_t)
530 CALL section_add_keyword(section, keyword)
531 CALL keyword_release(keyword)
532
533 CALL keyword_create(keyword, __location__, name="PMSWAP_MOL", &
534 description="The probability of attempting a molecule swap of a given molecule type.", &
535 usage="PMSWAP_MOL {real} {real} ... ", &
536 n_var=-1, type_of_var=real_t)
537 CALL section_add_keyword(section, keyword)
538 CALL keyword_release(keyword)
539
540 CALL keyword_create(keyword, __location__, name="PMROT_MOL", &
541 description="The probability of attempting a molecule rotation of a given molecule type.", &
542 usage="PMROT_MOL {real} {real} ... ", &
543 n_var=-1, type_of_var=real_t)
544 CALL section_add_keyword(section, keyword)
545 CALL keyword_release(keyword)
546
547 CALL keyword_create(keyword, __location__, name="PMTRAION_MOL", &
548 description="The probability of attempting a conformational change of a given molecule type.", &
549 usage="PMTRAION_MOL {real} {real} ... ", &
550 n_var=-1, type_of_var=real_t)
551 CALL section_add_keyword(section, keyword)
552 CALL keyword_release(keyword)
553
554 CALL keyword_create(keyword, __location__, name="PMTRANS_MOL", &
555 description="The probability of attempting a molecule translation of a given molecule type.", &
556 usage="PMTRANS_MOL {real} {real} ... ", &
557 n_var=-1, type_of_var=real_t)
558 CALL section_add_keyword(section, keyword)
559 CALL keyword_release(keyword)
560
561 END SUBROUTINE create_mol_prob_section
562
563! **************************************************************************************************
564!> \brief ...
565!> \param section will contain the probabilities for attempting various moves
566!> on the box where the variable is present
567!> \author matt
568! **************************************************************************************************
569 SUBROUTINE create_box_prob_section(section)
570 TYPE(section_type), POINTER :: section
571
572 TYPE(keyword_type), POINTER :: keyword
573
574 cpassert(.NOT. ASSOCIATED(section))
575
576 CALL section_create(section, __location__, name="BOX_PROBABILITIES", &
577 description="Probabilities of attempting various moves types on "// &
578 "the box.", &
579 n_keywords=2, n_subsections=0, repeats=.false.)
580
581 NULLIFY (keyword)
582
583 CALL keyword_create(keyword, __location__, name="PMHMC_BOX", &
584 description="The probability of attempting a HMC move on this box.", &
585 usage="PMHMC_BOX {real}", &
586 type_of_var=real_t, default_r_val=1.0e0_dp)
587 CALL section_add_keyword(section, keyword)
588 CALL keyword_release(keyword)
589
590 CALL keyword_create(keyword, __location__, name="PMVOL_BOX", &
591 description="The probability of attempting a volume move on this box (GEMC_NpT).", &
592 usage="PMVOL_BOX {real}", &
593 type_of_var=real_t, default_r_val=1.0e0_dp)
594 CALL section_add_keyword(section, keyword)
595 CALL keyword_release(keyword)
596
597 CALL keyword_create(keyword, __location__, name="PMCLUS_BOX", &
598 description="The probability of attempting a cluster move in this box", &
599 usage="PMCLUS_BOX {real}", &
600 type_of_var=real_t, default_r_val=1.0e0_dp)
601 CALL section_add_keyword(section, keyword)
602 CALL keyword_release(keyword)
603
604 END SUBROUTINE create_box_prob_section
605
606! **************************************************************************************************
607!> \brief ...
608!> \param section will contain the frequency for updating maximum
609!> displacements for various moves
610!> \author matt
611! **************************************************************************************************
612 SUBROUTINE create_update_section(section)
613 TYPE(section_type), POINTER :: section
614
615 TYPE(keyword_type), POINTER :: keyword
616
617 cpassert(.NOT. ASSOCIATED(section))
618
619 CALL section_create(section, __location__, name="MOVE_UPDATES", &
620 description="Frequency for updating move maximum displacements.", &
621 n_keywords=2, n_subsections=0, repeats=.false.)
622
623 NULLIFY (keyword)
624
625 CALL keyword_create(keyword, __location__, name="IUPVOLUME", &
626 description="Every iupvolume steps update maximum volume displacement.", &
627 usage="IUPVOLUME {integer}", &
628 default_i_val=10000)
629 CALL section_add_keyword(section, keyword)
630 CALL keyword_release(keyword)
631
632 CALL keyword_create(keyword, __location__, name="IUPTRANS", &
633 description="Every iuptrans steps update maximum "// &
634 "translation/rotation/configurational changes.", &
635 usage="IUPTRANS {integer}", &
636 default_i_val=10000)
637 CALL section_add_keyword(section, keyword)
638 CALL keyword_release(keyword)
639
640 CALL keyword_create(keyword, __location__, name="IUPCLTRANS", &
641 description="Every iupcltrans steps update maximum cluster translation.", &
642 usage="IUPCLTRANS {integer}", &
643 default_i_val=10000)
644 CALL section_add_keyword(section, keyword)
645 CALL keyword_release(keyword)
646
647 END SUBROUTINE create_update_section
648
649! **************************************************************************************************
650!> \brief ...
651!> \param section will contain the maximum displacements for various moves
652!> \author matt
653! **************************************************************************************************
654 SUBROUTINE create_max_disp_section(section)
655 TYPE(section_type), POINTER :: section
656
657 TYPE(section_type), POINTER :: subsection
658
659 cpassert(.NOT. ASSOCIATED(section))
660
661 CALL section_create(section, __location__, name="max_displacements", &
662 description="The maximum displacements for all attempted moves.", &
663 n_keywords=1, n_subsections=2, repeats=.false.)
664
665 NULLIFY (subsection)
666
667 CALL create_mol_disp_section(subsection)
668 CALL section_add_subsection(section, subsection)
669 CALL section_release(subsection)
670
671 CALL create_box_disp_section(subsection)
672 CALL section_add_subsection(section, subsection)
673 CALL section_release(subsection)
674
675 END SUBROUTINE create_max_disp_section
676
677! **************************************************************************************************
678!> \brief ...
679!> \param section will contain the maximum displacements for all moves which
680!> require a value for each molecule type
681!> \author matt
682! **************************************************************************************************
683 SUBROUTINE create_mol_disp_section(section)
684 TYPE(section_type), POINTER :: section
685
686 TYPE(keyword_type), POINTER :: keyword
687
688 cpassert(.NOT. ASSOCIATED(section))
689
690 CALL section_create(section, __location__, name="mol_displacements", &
691 description="Maximum displacements for every move type that requires "// &
692 "a value for each molecular type in the simulation.", &
693 n_keywords=5, n_subsections=0, repeats=.false.)
694
695 NULLIFY (keyword)
696
697 CALL keyword_create(keyword, __location__, name="RMBOND", &
698 description="Maximum bond length displacement, in angstroms, for each molecule type.", &
699 usage="RMBOND {real} {real} ... ", &
700 n_var=-1, type_of_var=real_t)
701 CALL section_add_keyword(section, keyword)
702 CALL keyword_release(keyword)
703
704 CALL keyword_create(keyword, __location__, name="RMANGLE", &
705 description="Maximum bond angle displacement, in degrees, for each molecule type.", &
706 usage="RMANGLE {real} {real} ...", &
707 n_var=-1, type_of_var=real_t)
708 CALL section_add_keyword(section, keyword)
709 CALL keyword_release(keyword)
710
711 CALL keyword_create(keyword, __location__, name="RMDIHEDRAL", &
712 description="Maximum dihedral angle distplacement, in degrees, for each molecule type.", &
713 usage="RMDIHEDRAL {real} {real} ... ", &
714 n_var=-1, type_of_var=real_t)
715 CALL section_add_keyword(section, keyword)
716 CALL keyword_release(keyword)
717
718 CALL keyword_create(keyword, __location__, name="RMROT", &
719 description="Maximum rotational displacement, in degrees, for each molecule type.", &
720 usage="RMROT {real} {real} ... ", &
721 n_var=-1, type_of_var=real_t)
722 CALL section_add_keyword(section, keyword)
723 CALL keyword_release(keyword)
724
725 CALL keyword_create(keyword, __location__, name="RMTRANS", &
726 description="Maximum translational displacement, in angstroms, for each molecule type.", &
727 usage="RMTRANS {real} {real} ...", &
728 n_var=-1, type_of_var=real_t)
729 CALL section_add_keyword(section, keyword)
730 CALL keyword_release(keyword)
731
732 END SUBROUTINE create_mol_disp_section
733
734! **************************************************************************************************
735!> \brief ...
736!> \param section will contain the maximum displacements for any move that
737!> is done on each simulation box
738!> \author matt
739! **************************************************************************************************
740 SUBROUTINE create_box_disp_section(section)
741 TYPE(section_type), POINTER :: section
742
743 TYPE(keyword_type), POINTER :: keyword
744
745 cpassert(.NOT. ASSOCIATED(section))
746
747 CALL section_create(section, __location__, name="BOX_DISPLACEMENTS", &
748 description="Maximum displacements for any move that is performed on each"// &
749 " simulation box.", &
750 n_keywords=1, n_subsections=0, repeats=.false.)
751
752 NULLIFY (keyword)
753
754 CALL keyword_create(keyword, __location__, name="RMVOLUME", &
755 description="Maximum volume displacement, in angstrom**3.", &
756 usage="RMVOLUME {real}", &
757 type_of_var=real_t)
758 CALL section_add_keyword(section, keyword)
759 CALL keyword_release(keyword)
760
761 CALL keyword_create(keyword, __location__, name="RMCLTRANS", &
762 description="Maximum translational displacement, in angstroms, for each cluster.", &
763 usage="RMCLTRANS {real}", &
764 default_r_val=1.0e0_dp)
765 CALL section_add_keyword(section, keyword)
766 CALL keyword_release(keyword)
767
768 END SUBROUTINE create_box_disp_section
769
770! **************************************************************************************************
771!> \brief creates the geometry optimization section
772!> \param section the section to be created
773!> \param location ...
774!> \param label ...
775!> \param description ...
776!> \param just_optimizers ...
777!> \param use_model_hessian ...
778!> \par History
779!> 01.2020 keywords related to Space Group Symmetry added [pcazade]
780!> \author teo
781! **************************************************************************************************
782 RECURSIVE SUBROUTINE create_geoopt_section(section, location, label, description, just_optimizers, use_model_hessian)
783 TYPE(section_type), POINTER :: section
784 CHARACTER(LEN=*), INTENT(IN) :: location, label, description
785 LOGICAL, INTENT(IN) :: just_optimizers, use_model_hessian
786
787 TYPE(keyword_type), POINTER :: keyword
788 TYPE(section_type), POINTER :: print_key, subsection
789
790 cpassert(.NOT. ASSOCIATED(section))
791 CALL section_create(section, location=location, name=label, description=description, &
792 n_keywords=1, n_subsections=1, repeats=.false.)
793
794 NULLIFY (keyword)
795 IF (.NOT. just_optimizers) THEN
796 CALL keyword_create(keyword, __location__, name="TYPE", &
797 description="Specify which kind of geometry optimization to perform", &
798 usage="TYPE (MINIMIZATION|TRANSITION_STATE)", &
799 enum_c_vals=s2a("MINIMIZATION", "TRANSITION_STATE"), &
800 enum_desc=s2a("Performs a geometry minimization.", &
801 "Performs a transition state optimization."), &
803 default_i_val=default_minimization_method_id)
804 CALL section_add_keyword(section, keyword)
805 CALL keyword_release(keyword)
806 END IF
807
808 CALL keyword_create( &
809 keyword, __location__, name="OPTIMIZER", &
810 variants=(/"MINIMIZER"/), &
811 citations=(/byrd1995/), &
812 description="Specify which method to use to perform a geometry optimization.", &
813 usage="OPTIMIZER {BFGS|LBFGS|CG}", &
814 enum_c_vals=s2a("BFGS", "LBFGS", "CG"), &
815 enum_desc=s2a("Most efficient minimizer, but only for 'small' systems, "// &
816 "as it relies on diagonalization of a full Hessian matrix", &
817 "Limited-memory variant of BFGS suitable for large systems. "// &
818 "Not as well fine-tuned but can be more robust.", &
819 "conjugate gradients, robust minimizer (depending on the line search) also OK for large systems"), &
821 default_i_val=default_bfgs_method_id)
822 CALL section_add_keyword(section, keyword)
823 CALL keyword_release(keyword)
824
825 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
826 description="Specifies the maximum number of geometry optimization steps. "// &
827 "One step might imply several force evaluations for the CG and LBFGS optimizers.", &
828 usage="MAX_ITER {integer}", &
829 default_i_val=200)
830 CALL section_add_keyword(section, keyword)
831 CALL keyword_release(keyword)
832
833 CALL keyword_create(keyword, __location__, name="MAX_DR", &
834 description="Convergence criterion for the maximum geometry change "// &
835 "between the current and the last optimizer iteration.", &
836 usage="MAX_DR {real}", &
837 default_r_val=0.0030_dp, unit_str="bohr")
838 CALL section_add_keyword(section, keyword)
839 CALL keyword_release(keyword)
840
841 CALL keyword_create(keyword, __location__, name="MAX_FORCE", &
842 description="Convergence criterion for the maximum force component of the current configuration.", &
843 usage="MAX_FORCE {real}", &
844 default_r_val=0.00045_dp, unit_str="hartree/bohr")
845 CALL section_add_keyword(section, keyword)
846 CALL keyword_release(keyword)
847
848 CALL keyword_create(keyword, __location__, name="RMS_DR", &
849 description="Convergence criterion for the root mean square (RMS) geometry"// &
850 " change between the current and the last optimizer iteration.", &
851 usage="RMS_DR {real}", unit_str="bohr", &
852 default_r_val=0.0015_dp)
853 CALL section_add_keyword(section, keyword)
854 CALL keyword_release(keyword)
855
856 CALL keyword_create(keyword, __location__, name="RMS_FORCE", &
857 description="Convergence criterion for the root mean square (RMS) force of the current configuration.", &
858 usage="RMS_FORCE {real}", unit_str="hartree/bohr", &
859 default_r_val=0.00030_dp)
860 CALL section_add_keyword(section, keyword)
861 CALL keyword_release(keyword)
862
863 CALL keyword_create(keyword, __location__, name="step_start_val", &
864 description="The starting step value for the "//trim(label)//" module.", &
865 usage="step_start_val <integer>", default_i_val=0)
866 CALL section_add_keyword(section, keyword)
867 CALL keyword_release(keyword)
868
869 ! collects keywords related to Space Group Symmetry
870 CALL keyword_create( &
871 keyword, __location__, name="KEEP_SPACE_GROUP", &
872 description="Detect space group of the system and preserve it during optimization. "// &
873 "The space group symmetry is applied to coordinates, forces, and the stress tensor. "// &
874 "It works for supercell. It does not affect/reduce computational cost. "// &
875 "Use EPS_SYMMETRY to adjust the detection threshold.", &
876 usage="KEEP_SPACE_GROUP .TRUE.", &
877 default_l_val=.false., lone_keyword_l_val=.true., repeats=.false.)
878 CALL section_add_keyword(section, keyword)
879 CALL keyword_release(keyword)
880
881 ! collects keywords related to Space Group Symmetry analysis
882 CALL keyword_create( &
883 keyword, __location__, name="SHOW_SPACE_GROUP", &
884 description="Detect and show space group of the system after optimization. "// &
885 "It works for supercell. It does not affect/reduce computational cost. "// &
886 "Use EPS_SYMMETRY to adjust the detection threshold.", &
887 usage="SHOW_SPACE_GROUP .TRUE.", &
888 default_l_val=.false., lone_keyword_l_val=.true., repeats=.false.)
889 CALL section_add_keyword(section, keyword)
890 CALL keyword_release(keyword)
891
892 ! collects keywords related to precision for finding the space group
893 CALL keyword_create( &
894 keyword, __location__, name="EPS_SYMMETRY", &
895 description="Accuracy for space group determination. EPS_SYMMETRY is dimensionless. "// &
896 "Roughly speaking, two scaled (fractional) atomic positions v1, v2 are considered identical if |v1 - v2| < EPS_SYMMETRY. ", &
897 usage="EPS_SYMMETRY {REAL}", &
898 default_r_val=1.e-4_dp, repeats=.false.)
899 CALL section_add_keyword(section, keyword)
900 CALL keyword_release(keyword)
901
902 ! collects keywords related to reduction of symmetry due to an external field
903 CALL keyword_create( &
904 keyword, __location__, name="SYMM_REDUCTION", &
905 description="Direction of the external static electric field. "// &
906 "Some symmetry operations are not compatible with the direction of an electric field. "// &
907 "These operations are used when enforcing the space group.", &
908 usage="SYMM_REDUCTION 0.0 0.0 0.0", &
909 repeats=.false., n_var=3, &
910 type_of_var=real_t, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
911 CALL section_add_keyword(section, keyword)
912 CALL keyword_release(keyword)
913
914 ! collects keywords related to ranges of atoms to symmetrize
915 CALL keyword_create( &
916 keyword, __location__, name="SYMM_EXCLUDE_RANGE", &
917 description="Range of atoms to exclude from space group symmetry. "// &
918 "These atoms are excluded from both identification and enforcement. "// &
919 "This keyword can be repeated.", &
920 repeats=.true., usage="SYMM_EXCLUDE_RANGE {Int} {Int}", type_of_var=integer_t, n_var=2)
921 CALL section_add_keyword(section, keyword)
922 CALL keyword_release(keyword)
923
924 CALL keyword_create( &
925 keyword, __location__, name="SPGR_PRINT_ATOMS", &
926 description="Print equivalent atoms list for each space group symmetry operation.", &
927 default_l_val=.false., lone_keyword_l_val=.true.)
928 CALL section_add_keyword(section, keyword)
929 CALL keyword_release(keyword)
930
931 CALL create_lbfgs_section(subsection)
932 CALL section_add_subsection(section, subsection)
933 CALL section_release(subsection)
934
935 CALL create_cg_section(subsection)
936 CALL section_add_subsection(section, subsection)
937 CALL section_release(subsection)
938
939 CALL create_bfgs_section(subsection, use_model_hessian)
940 CALL section_add_subsection(section, subsection)
941 CALL section_release(subsection)
942
943 IF (.NOT. just_optimizers) THEN
944 ! Transition states section
945 CALL create_ts_section(subsection)
946 CALL section_add_subsection(section, subsection)
947 CALL section_release(subsection)
948
949 ! Create the PRINT subsection
950 NULLIFY (subsection)
951 CALL section_create(subsection, __location__, name="PRINT", &
952 description="Controls the printing properties during a geometry optimization run", &
953 n_keywords=0, n_subsections=1, repeats=.true.)
954 NULLIFY (print_key)
956 print_key, __location__, "program_run_info", &
957 description="Controls the printing of basic information during the Geometry Optimization", &
958 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
959 CALL section_add_subsection(subsection, print_key)
960 CALL section_release(print_key)
961 CALL section_add_subsection(section, subsection)
962 CALL section_release(subsection)
963 END IF
964
965 END SUBROUTINE create_geoopt_section
966
967! **************************************************************************************************
968!> \brief creates the section for the shell-core optimization
969!> \param section the section to be created
970!> \author Caino
971! **************************************************************************************************
972 SUBROUTINE create_shellcore_opt_section(section)
973 TYPE(section_type), POINTER :: section
974
975 TYPE(section_type), POINTER :: print_key, subsection
976
977 CALL create_geoopt_section( &
978 section, __location__, label="SHELL_OPT", &
979 description="This section sets the environment for the optimization of the shell-core distances"// &
980 " that might turn to be necessary along a MD run using a shell-model potential."// &
981 " The optimization procedure is activated when at least one of the shell-core"// &
982 " pairs becomes too elongated, i.e. when the assumption of point dipole is not longer valid.", &
983 just_optimizers=.true., &
984 use_model_hessian=.false.)
985
986 NULLIFY (print_key, subsection)
987
988 ! Create the PRINT subsection
989 NULLIFY (subsection)
990 CALL section_create(subsection, __location__, name="PRINT", &
991 description="Controls the printing properties during a shell-core optimization procedure", &
992 n_keywords=0, n_subsections=1, repeats=.true.)
993 NULLIFY (print_key)
994 CALL cp_print_key_section_create(print_key, __location__, "program_run_info", &
995 description="Controls the printing of basic information during the Optimization", &
996 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
997 CALL section_add_subsection(subsection, print_key)
998 CALL section_release(print_key)
999 CALL section_add_subsection(section, subsection)
1000 CALL section_release(subsection)
1001
1002 END SUBROUTINE create_shellcore_opt_section
1003
1004! **************************************************************************************************
1005!> \brief creates the section for the cell optimization
1006!> \param section the section to be created
1007!> \author Teodoro Laino [tlaino] - University of Zurich - 03.2008
1008! **************************************************************************************************
1009 SUBROUTINE create_cell_opt_section(section)
1010 TYPE(section_type), POINTER :: section
1011
1012 TYPE(keyword_type), POINTER :: keyword
1013 TYPE(section_type), POINTER :: print_key, subsection
1014
1015 CALL create_geoopt_section(section, __location__, label="CELL_OPT", &
1016 description="This section sets the environment for the optimization of the simulation cell."// &
1017 " Two possible schemes are available: (1) Zero temperature optimization;"// &
1018 " (2) Finite temperature optimization.", &
1019 just_optimizers=.true., &
1020 use_model_hessian=.false.)
1021
1022 NULLIFY (keyword, print_key, subsection)
1023 CALL keyword_create( &
1024 keyword, __location__, name="TYPE", &
1025 description="Specify which kind of method to use for the optimization of the simulation cell", &
1026 usage="TYPE (GEO_OPT|MD|DIRECT_CELL_OPT)", &
1027 enum_c_vals=s2a("GEO_OPT", "MD", "DIRECT_CELL_OPT"), &
1028 enum_desc=s2a( &
1029 "Performs a geometry optimization (the GEO_OPT section must be defined) between cell optimization steps."// &
1030 " The stress tensor is computed at the optimized geometry.", &
1031 "Performs a molecular dynamics run (the MD section needs must defined) for computing the stress tensor"// &
1032 " used for the cell optimization.", &
1033 "Performs a geometry and cell optimization at the same time."// &
1034 " The stress tensor is computed at every step"), &
1036 default_i_val=default_cell_direct_id)
1037 CALL section_add_keyword(section, keyword)
1038 CALL keyword_release(keyword)
1039
1040 CALL keyword_create( &
1041 keyword, __location__, name="EXTERNAL_PRESSURE", &
1042 description="Specifies the external pressure (1 value or the full 9 components of the pressure tensor) "// &
1043 "applied during the cell optimization.", &
1044 usage="EXTERNAL_PRESSURE {REAL} .. {REAL}", unit_str="bar", &
1045 default_r_vals=(/cp_unit_to_cp2k(100.0_dp, "bar"), 0.0_dp, 0.0_dp, &
1046 0.0_dp, cp_unit_to_cp2k(100.0_dp, "bar"), 0.0_dp, &
1047 0.0_dp, 0.0_dp, cp_unit_to_cp2k(100.0_dp, "bar")/), n_var=-1)
1048 CALL section_add_keyword(section, keyword)
1049 CALL keyword_release(keyword)
1050
1051 CALL keyword_create( &
1052 keyword, __location__, name="KEEP_ANGLES", &
1053 description="Keep angles between the cell vectors constant, but allow the lengths of the"// &
1054 " cell vectors to change independently."// &
1055 " Albeit general, this is most useful for triclinic cells, to enforce higher symmetry, see KEEP_SYMMETRY.", &
1056 usage="KEEP_ANGLES TRUE", default_l_val=.false., lone_keyword_l_val=.true.)
1057 CALL section_add_keyword(section, keyword)
1058 CALL keyword_release(keyword)
1059
1060 CALL keyword_create(keyword, __location__, name="KEEP_SYMMETRY", &
1061 description="Keep the requested initial cell symmetry (e.g. during a cell optimisation). "// &
1062 "The initial symmetry must be specified in the &CELL section.", &
1063 usage="KEEP_SYMMETRY yes", default_l_val=.false., lone_keyword_l_val=.true.)
1064 CALL section_add_keyword(section, keyword)
1065 CALL keyword_release(keyword)
1066
1067 CALL keyword_create( &
1068 keyword, __location__, name="CONSTRAINT", &
1069 description="Imposes a constraint on the pressure tensor by fixing the specified cell components.", &
1070 usage="CONSTRAINT (none|x|y|z|xy|xz|yz)", &
1071 enum_desc=s2a("Fix nothing", &
1072 "Fix only x component", &
1073 "Fix only y component", &
1074 "Fix only z component", &
1075 "Fix x and y component", &
1076 "Fix x and z component", &
1077 "Fix y and z component"), &
1078 enum_c_vals=s2a("NONE", "X", "Y", "Z", "XY", "XZ", "YZ"), &
1079 enum_i_vals=(/fix_none, fix_x, fix_y, fix_z, fix_xy, fix_xz, fix_yz/), &
1080 default_i_val=fix_none)
1081 CALL section_add_keyword(section, keyword)
1082 CALL keyword_release(keyword)
1083
1084 CALL keyword_create(keyword, __location__, name="PRESSURE_TOLERANCE", &
1085 description="Specifies the Pressure tolerance (compared to the external pressure) to achieve "// &
1086 "during the cell optimization.", &
1087 usage="PRESSURE_TOLERANCE {REAL}", unit_str="bar", &
1088 default_r_val=cp_unit_to_cp2k(100.0_dp, "bar"))
1089 CALL section_add_keyword(section, keyword)
1090 CALL keyword_release(keyword)
1091
1092 ! Create the PRINT subsection
1093 NULLIFY (subsection)
1094 CALL section_create(subsection, __location__, name="PRINT", &
1095 description="Controls the printing properties during a geometry optimization run", &
1096 n_keywords=0, n_subsections=1, repeats=.true.)
1097 NULLIFY (print_key)
1098 CALL cp_print_key_section_create(print_key, __location__, "program_run_info", &
1099 description="Controls the printing of basic information during the Geometry Optimization", &
1100 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1101 CALL section_add_subsection(subsection, print_key)
1102 CALL section_release(print_key)
1103 CALL cp_print_key_section_create(print_key, __location__, "cell", &
1104 description="Controls the printing of the cell eveytime a calculation using a new cell is started.", &
1105 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__", &
1106 unit_str="angstrom")
1107 CALL section_add_subsection(subsection, print_key)
1108 CALL section_release(print_key)
1109 CALL section_add_subsection(section, subsection)
1110 CALL section_release(subsection)
1111
1112 END SUBROUTINE create_cell_opt_section
1113
1114! **************************************************************************************************
1115!> \brief creates the section for tuning transition states search
1116!> \param section the section to be created
1117!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1118! **************************************************************************************************
1119 SUBROUTINE create_ts_section(section)
1120 TYPE(section_type), POINTER :: section
1121
1122 TYPE(keyword_type), POINTER :: keyword
1123 TYPE(section_type), POINTER :: print_key, subsection, subsection2, &
1124 subsection3
1125
1126! Create the Transition State subsection
1127
1128 NULLIFY (section, keyword, subsection, subsection2)
1129 CALL section_create(section, __location__, name="TRANSITION_STATE", &
1130 description="Specifies parameters to perform a transition state search", &
1131 n_keywords=0, n_subsections=1, repeats=.false.)
1132
1133 CALL keyword_create(keyword, __location__, name="METHOD", &
1134 description="Specify which kind of method to use for locating transition states", &
1135 citations=(/henkelman1999/), &
1136 usage="METHOD (DIMER)", &
1137 enum_c_vals=s2a("DIMER"), &
1138 enum_desc=s2a("Uses the dimer method to optimize transition states."), &
1139 enum_i_vals=(/default_dimer_method_id/), &
1140 default_i_val=default_dimer_method_id)
1141 CALL section_add_keyword(section, keyword)
1142 CALL keyword_release(keyword)
1143
1144 CALL section_create(subsection, __location__, name="DIMER", &
1145 description="Specifies parameters for Dimer Method", &
1146 n_keywords=0, n_subsections=1, repeats=.false.)
1147
1148 CALL keyword_create(keyword, __location__, name="DR", &
1149 description="This keyword sets the value for the DR parameter.", &
1150 usage="DR {real}", unit_str='angstrom', &
1151 default_r_val=cp_unit_to_cp2k(0.01_dp, "angstrom"))
1152 CALL section_add_keyword(subsection, keyword)
1153 CALL keyword_release(keyword)
1154
1155 CALL keyword_create(keyword, __location__, name="INTERPOLATE_GRADIENT", &
1156 description="This keyword controls the interpolation of the gradient whenever possible"// &
1157 " during the optimization of the Dimer. The use of this keywords saves 1 evaluation"// &
1158 " of energy/forces.", usage="INTERPOLATE_GRADIENT {logical}", default_l_val=.true., &
1159 lone_keyword_l_val=.true.)
1160 CALL section_add_keyword(subsection, keyword)
1161 CALL keyword_release(keyword)
1162
1163 CALL keyword_create(keyword, __location__, name="ANGLE_TOLERANCE", &
1164 description="This keyword sets the value of the tolerance angle for the line search"// &
1165 " performed to optimize the orientation of the dimer.", &
1166 usage="ANGLE_TOLERANCE {real}", unit_str='rad', &
1167 default_r_val=cp_unit_to_cp2k(5.0_dp, "deg"))
1168 CALL section_add_keyword(subsection, keyword)
1169 CALL keyword_release(keyword)
1170
1171 CALL keyword_create(keyword, __location__, name="K-DIMER", &
1172 description="This keyword activates the constrained k-dimer translation"// &
1173 " J. Chem. Phys. 141, 164111 (2014).", &
1174 citations=(/henkelman2014/), &
1175 usage="K-DIMER {logica}", &
1176 default_l_val=.false., &
1177 lone_keyword_l_val=.false.)
1178 CALL section_add_keyword(subsection, keyword)
1179 CALL keyword_release(keyword)
1180
1181 CALL keyword_create(keyword, __location__, name="BETA", &
1182 description="Exponential factor for the switching function used in K-DIMER", &
1183 usage="BETA {real}", &
1184 default_r_val=5.0_dp, &
1185 lone_keyword_r_val=5.0_dp)
1186 CALL section_add_keyword(subsection, keyword)
1187 CALL keyword_release(keyword)
1188
1189 CALL create_geoopt_section( &
1190 subsection2, __location__, label="ROT_OPT", &
1191 description="This section sets the environment for the optimization of the rotation of the Dimer.", &
1192 just_optimizers=.true., &
1193 use_model_hessian=.false.)
1194 NULLIFY (subsection3)
1195 CALL section_create(subsection3, __location__, name="PRINT", &
1196 description="Controls the printing properties during the dimer rotation optimization run", &
1197 n_keywords=0, n_subsections=1, repeats=.true.)
1198 NULLIFY (print_key)
1199
1200 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
1201 description="Controls the printing of basic information during the Geometry Optimization", &
1202 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1203 CALL section_add_subsection(subsection3, print_key)
1204 CALL section_release(print_key)
1205
1206 CALL cp_print_key_section_create(print_key, __location__, "ROTATIONAL_INFO", &
1207 description="Controls the printing basic info during the cleaning of the "// &
1208 "rotational degrees of freedom.", print_level=low_print_level, &
1209 add_last=add_last_numeric, filename="__STD_OUT__")
1210 CALL keyword_create(keyword, __location__, name="COORDINATES", &
1211 description="Prints atomic coordinates after rotation", &
1212 default_l_val=.false., lone_keyword_l_val=.true.)
1213 CALL section_add_keyword(print_key, keyword)
1214 CALL keyword_release(keyword)
1215 CALL section_add_subsection(subsection3, print_key)
1216 CALL section_release(print_key)
1217
1218 CALL section_add_subsection(subsection2, subsection3)
1219 CALL section_release(subsection3)
1220 CALL section_add_subsection(subsection, subsection2)
1221 CALL section_release(subsection2)
1222
1223 CALL section_create(subsection2, __location__, name="DIMER_VECTOR", &
1224 description="Specifies the initial dimer vector (used frequently to restart DIMER calculations)."// &
1225 " If not provided the starting orientation of the dimer is chosen randomly.", &
1226 n_keywords=0, n_subsections=1, repeats=.false.)
1227 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1228 description="Specify on each line the components of the dimer vector.", repeats=.true., &
1229 usage="{Real} {Real} {Real}", type_of_var=real_t, n_var=-1)
1230 CALL section_add_keyword(subsection2, keyword)
1231 CALL keyword_release(keyword)
1232 CALL section_add_subsection(subsection, subsection2)
1233 CALL section_release(subsection2)
1234
1235 CALL section_add_subsection(section, subsection)
1236 CALL section_release(subsection)
1237
1238 END SUBROUTINE create_ts_section
1239
1240! **************************************************************************************************
1241!> \brief creates the BFGS section
1242!> \param section the section to be created
1243!> \param use_model_hessian ...
1244!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1245! **************************************************************************************************
1246 SUBROUTINE create_bfgs_section(section, use_model_hessian)
1247 TYPE(section_type), POINTER :: section
1248 LOGICAL, INTENT(IN) :: use_model_hessian
1249
1250 TYPE(keyword_type), POINTER :: keyword
1251 TYPE(section_type), POINTER :: print_key
1252
1253! create the BFGS subsection
1254
1255 NULLIFY (section, keyword, print_key)
1256 CALL section_create(section, __location__, name="BFGS", &
1257 description="Provides parameters to tune the BFGS optimization", &
1258 n_keywords=0, n_subsections=1, repeats=.false.)
1259
1260 CALL keyword_create(keyword, __location__, name="TRUST_RADIUS", &
1261 description="Trust radius used in BFGS. Previously set to 0.1. "// &
1262 "Large values can lead to instabilities", &
1263 usage="TRUST_RADIUS {real}", unit_str='angstrom', &
1264 default_r_val=cp_unit_to_cp2k(0.25_dp, "angstrom"))
1265 CALL section_add_keyword(section, keyword)
1266 CALL keyword_release(keyword)
1267
1268 CALL keyword_create(keyword, __location__, name="USE_MODEL_HESSIAN", &
1269 description="Uses a model Hessian as initial guess instead of a unit matrix."// &
1270 " Should lead in general to improved convergence might be switched off for exotic cases", &
1271 usage="USE_MODEL_HESSIAN", &
1272 default_l_val=use_model_hessian, lone_keyword_l_val=.true.)
1273 CALL section_add_keyword(section, keyword)
1274 CALL keyword_release(keyword)
1275
1276 CALL keyword_create(keyword, __location__, name="USE_RAT_FUN_OPT", &
1277 description="Includes a rational function optimization to determine the step."// &
1278 " Previously default but did not improve convergence in many cases", &
1279 usage="USE_RAT_FUN_OPT", &
1280 default_l_val=.false., lone_keyword_l_val=.true.)
1281 CALL section_add_keyword(section, keyword)
1282 CALL keyword_release(keyword)
1283
1284 CALL keyword_create(keyword, __location__, name="RESTART_HESSIAN", &
1285 description="Controls the reading of the initial Hessian from file.", &
1286 usage="RESTART_HESSIAN", &
1287 default_l_val=.false., lone_keyword_l_val=.true.)
1288 CALL section_add_keyword(section, keyword)
1289 CALL keyword_release(keyword)
1290
1291 CALL keyword_create(keyword, __location__, name="RESTART_FILE_NAME", &
1292 description="Specifies the name of the file used to read the initial Hessian.", &
1293 usage="RESTART_FILE_NAME {filename}", &
1294 default_lc_val="")
1295 CALL section_add_keyword(section, keyword)
1296 CALL keyword_release(keyword)
1297
1298 CALL cp_print_key_section_create(print_key, __location__, "RESTART", &
1299 description="Controls the printing of Hessian Restart file", &
1300 print_level=low_print_level, add_last=add_last_numeric, filename="BFGS", &
1301 common_iter_levels=2)
1302 CALL section_add_subsection(section, print_key)
1303 CALL section_release(print_key)
1304
1305 END SUBROUTINE create_bfgs_section
1306
1307! **************************************************************************************************
1308!> \brief creates the CG section
1309!> \param section the section to be created
1310!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1311! **************************************************************************************************
1312 SUBROUTINE create_cg_section(section)
1313 TYPE(section_type), POINTER :: section
1314
1315 TYPE(keyword_type), POINTER :: keyword
1316 TYPE(section_type), POINTER :: subsection, subsubsection
1317
1318! create the CG subsection
1319
1320 NULLIFY (section, subsection, subsubsection, keyword)
1321 CALL section_create(section, __location__, name="CG", &
1322 description="Provides parameters to tune the conjugate gradient optimization", &
1323 n_keywords=0, n_subsections=1, repeats=.false.)
1324
1325 CALL keyword_create(keyword, __location__, name="MAX_STEEP_STEPS", &
1326 description="Maximum number of steepest descent steps before starting the"// &
1327 " conjugate gradients optimization.", &
1328 usage="MAX_STEEP_STEPS {integer}", &
1329 default_i_val=0)
1330 CALL section_add_keyword(section, keyword)
1331 CALL keyword_release(keyword)
1332
1333 CALL keyword_create(keyword, __location__, name="RESTART_LIMIT", &
1334 description="Cosine of the angle between two consecutive searching directions."// &
1335 " If the angle during a CG optimization is less than the one corresponding to"// &
1336 " to the RESTART_LIMIT the CG is reset and one step of steepest descent is"// &
1337 " performed.", &
1338 usage="RESTART_LIMIT {real}", &
1339 default_r_val=0.9_dp)
1340 CALL section_add_keyword(section, keyword)
1341 CALL keyword_release(keyword)
1342
1343 CALL keyword_create(keyword, __location__, name="FLETCHER_REEVES", &
1344 description="Uses FLETCHER-REEVES instead of POLAK-RIBIERE when using Conjugate Gradients", &
1345 usage="FLETCHER_REEVES", &
1346 default_l_val=.false., lone_keyword_l_val=.true.)
1347 CALL section_add_keyword(section, keyword)
1348 CALL keyword_release(keyword)
1349
1350 ! Line Search section
1351 CALL section_create(subsection, __location__, name="LINE_SEARCH", &
1352 description="Provides parameters to tune the line search during the conjugate gradient optimization", &
1353 n_keywords=0, n_subsections=1, repeats=.false.)
1354
1355 CALL keyword_create(keyword, __location__, name="TYPE", &
1356 description="1D line search algorithm to be used with the CG optimizer,"// &
1357 " in increasing order of robustness and cost. ", &
1358 usage="TYPE GOLD", &
1359 default_i_val=ls_gold, &
1360 enum_c_vals=s2a("NONE", "2PNT", "3PNT", "GOLD", "FIT"), &
1361 enum_desc=s2a("take fixed length steps", &
1362 "extrapolate based on 2 points", &
1363 "extrapolate based on on 3 points", &
1364 "perform 1D golden section search of the minimum (very expensive)", &
1365 "perform 1D fit of a parabola on several evaluation of energy "// &
1366 "(very expensive and more robust vs numerical noise)"), &
1367 enum_i_vals=(/ls_none, ls_2pnt, ls_3pnt, ls_gold, ls_fit/))
1368 CALL section_add_keyword(subsection, keyword)
1369 CALL keyword_release(keyword)
1370
1371 ! 2PNT
1372 NULLIFY (subsubsection)
1373 CALL section_create(subsubsection, __location__, name="2PNT", &
1374 description="Provides parameters to tune the line search for the two point based line search.", &
1375 n_keywords=0, n_subsections=1, repeats=.false.)
1376
1377 CALL keyword_create(keyword, __location__, name="MAX_ALLOWED_STEP", &
1378 description="Max allowed value for the line search step.", &
1379 usage="MAX_ALLOWED_STEP {real}", unit_str="internal_cp2k", &
1380 default_r_val=0.25_dp)
1381 CALL section_add_keyword(subsubsection, keyword)
1382 CALL keyword_release(keyword)
1383
1384 CALL keyword_create( &
1385 keyword, __location__, name="LINMIN_GRAD_ONLY", &
1386 description="Use only the gradient, not the energy for line minimizations (e.g. in conjugate gradients).", &
1387 usage="LINMIN_GRAD_ONLY T", &
1388 default_l_val=.false., lone_keyword_l_val=.true.)
1389 CALL section_add_keyword(subsubsection, keyword)
1390 CALL keyword_release(keyword)
1391
1392 CALL section_add_subsection(subsection, subsubsection)
1393 CALL section_release(subsubsection)
1394
1395 ! GOLD
1396 NULLIFY (subsubsection)
1397 CALL section_create(subsubsection, __location__, name="GOLD", &
1398 description="Provides parameters to tune the line search for the gold search.", &
1399 n_keywords=0, n_subsections=1, repeats=.false.)
1400
1401 CALL keyword_create(keyword, __location__, name="INITIAL_STEP", &
1402 description="Initial step size used, e.g. for bracketing or minimizers. "// &
1403 "Might need to be reduced for systems with close contacts", &
1404 usage="INITIAL_STEP {real}", unit_str="internal_cp2k", &
1405 default_r_val=0.2_dp)
1406 CALL section_add_keyword(subsubsection, keyword)
1407 CALL keyword_release(keyword)
1408
1409 CALL keyword_create(keyword, __location__, name="BRACK_LIMIT", &
1410 description="Limit in 1D bracketing during line search in Conjugate Gradients Optimization.", &
1411 usage="BRACK_LIMIT {real}", unit_str="internal_cp2k", &
1412 default_r_val=100.0_dp)
1413 CALL section_add_keyword(subsubsection, keyword)
1414 CALL keyword_release(keyword)
1415
1416 CALL keyword_create(keyword, __location__, name="BRENT_TOL", &
1417 description="Tolerance requested during Brent line search in Conjugate Gradients Optimization.", &
1418 usage="BRENT_TOL {real}", unit_str="internal_cp2k", &
1419 default_r_val=0.01_dp)
1420 CALL section_add_keyword(subsubsection, keyword)
1421 CALL keyword_release(keyword)
1422
1423 CALL keyword_create(keyword, __location__, name="BRENT_MAX_ITER", &
1424 description="Maximum number of iterations in brent algorithm "// &
1425 "(used for the line search in Conjugated Gradients Optimization)", &
1426 usage="BRENT_MAX_ITER {integer}", &
1427 default_i_val=100)
1428 CALL section_add_keyword(subsubsection, keyword)
1429 CALL keyword_release(keyword)
1430 CALL section_add_subsection(subsection, subsubsection)
1431 CALL section_release(subsubsection)
1432
1433 CALL section_add_subsection(section, subsection)
1434 CALL section_release(subsection)
1435 END SUBROUTINE create_cg_section
1436
1437! **************************************************************************************************
1438!> \brief creates the LBFGS section
1439!> \param section the section to be created
1440!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1441! **************************************************************************************************
1442 SUBROUTINE create_lbfgs_section(section)
1443 TYPE(section_type), POINTER :: section
1444
1445 TYPE(keyword_type), POINTER :: keyword
1446
1447! create the LBFGS section
1448
1449 NULLIFY (section, keyword)
1450 CALL section_create(section, __location__, name="LBFGS", &
1451 description="Provides parameters to tune the limited memory BFGS (LBFGS) optimization", &
1452 n_keywords=0, n_subsections=1, repeats=.false., &
1453 citations=(/byrd1995/))
1454
1455 CALL keyword_create(keyword, __location__, name="MAX_H_RANK", &
1456 description="Maximum rank (and consequently size) of the "// &
1457 "approximate Hessian matrix used by the LBFGS optimizer. "// &
1458 "Larger values (e.g. 30) will accelerate the convergence behaviour "// &
1459 "at the cost of a larger memory consumption.", &
1460 usage="MAX_H_RANK {integer}", &
1461 default_i_val=5)
1462 CALL section_add_keyword(section, keyword)
1463 CALL keyword_release(keyword)
1464
1465 CALL keyword_create(keyword, __location__, name="MAX_F_PER_ITER", &
1466 description="Maximum number of force evaluations per iteration"// &
1467 " (used for the line search)", &
1468 usage="MAX_F_PER_ITER {integer}", &
1469 default_i_val=20)
1470 CALL section_add_keyword(section, keyword)
1471 CALL keyword_release(keyword)
1472
1473 CALL keyword_create(keyword, __location__, name="WANTED_PROJ_GRADIENT", &
1474 description="Convergence criterion (overrides the general ones):"// &
1475 " Requested norm threshold of the gradient multiplied"// &
1476 " by the approximate Hessian.", &
1477 usage="WANTED_PROJ_GRADIENT {real}", unit_str="internal_cp2k", &
1478 default_r_val=1.0e-16_dp)
1479 CALL section_add_keyword(section, keyword)
1480 CALL keyword_release(keyword)
1481
1482 CALL keyword_create(keyword, __location__, name="WANTED_REL_F_ERROR", &
1483 description="Convergence criterion (overrides the general ones):"// &
1484 " Requested relative error on the objective function"// &
1485 " of the optimizer (the energy)", &
1486 usage="WANTED_REL_F_ERROR {real}", unit_str="internal_cp2k", &
1487 default_r_val=1.0e-16_dp)
1488 CALL section_add_keyword(section, keyword)
1489 CALL keyword_release(keyword)
1490
1491 CALL keyword_create( &
1492 keyword, __location__, name="TRUST_RADIUS", &
1493 description="Trust radius used in LBFGS. Not completely in depth tested. Negativ values means no trust radius is used.", &
1494 usage="TRUST_RADIUS {real}", unit_str='angstrom', &
1495 default_r_val=-1.0_dp)
1496 CALL section_add_keyword(section, keyword)
1497 CALL keyword_release(keyword)
1498
1499 END SUBROUTINE create_lbfgs_section
1500
1501! **************************************************************************************************
1502!> \brief creates the flexible_partitioning section
1503!> \param section the section to be created
1504!> \author Joost VandeVondele [04.2006]
1505! **************************************************************************************************
1506 SUBROUTINE create_fp_section(section)
1507 TYPE(section_type), POINTER :: section
1508
1509 TYPE(keyword_type), POINTER :: keyword
1510 TYPE(section_type), POINTER :: print_key
1511
1512 cpassert(.NOT. ASSOCIATED(section))
1513 CALL section_create(section, __location__, name="FLEXIBLE_PARTITIONING", &
1514 description="This section sets up flexible_partitioning", &
1515 n_keywords=1, n_subsections=1, repeats=.false.)
1516
1517 NULLIFY (keyword, print_key)
1518
1519 CALL keyword_create(keyword, __location__, name="CENTRAL_ATOM", &
1520 description="Specifies the central atom.", &
1521 usage="CENTRAL_ATOM {integer}", &
1522 n_var=1, type_of_var=integer_t)
1523 CALL section_add_keyword(section, keyword)
1524 CALL keyword_release(keyword)
1525
1526 CALL keyword_create(keyword, __location__, name="INNER_ATOMS", &
1527 description="Specifies the list of atoms that should remain close to the central atom.", &
1528 usage="INNER_ATOMS {integer} {integer} .. {integer}", &
1529 n_var=-1, type_of_var=integer_t)
1530 CALL section_add_keyword(section, keyword)
1531 CALL keyword_release(keyword)
1532
1533 CALL keyword_create(keyword, __location__, name="OUTER_ATOMS", &
1534 description="Specifies the list of atoms that should remain far from the central atom.", &
1535 usage="OUTER_ATOMS {integer} {integer} .. {integer}", &
1536 n_var=-1, type_of_var=integer_t)
1537 CALL section_add_keyword(section, keyword)
1538 CALL keyword_release(keyword)
1539
1540 CALL keyword_create(keyword, __location__, name="INNER_RADIUS", &
1541 description="radius of the inner wall", &
1542 usage="INNER_RADIUS {real} ", type_of_var=real_t, &
1543 n_var=1, unit_str="angstrom")
1544 CALL section_add_keyword(section, keyword)
1545 CALL keyword_release(keyword)
1546
1547 CALL keyword_create(keyword, __location__, name="OUTER_RADIUS", &
1548 description="radius of the outer wall", &
1549 usage="OUTER_RADIUS {real} ", type_of_var=real_t, &
1550 n_var=1, unit_str="angstrom")
1551 CALL section_add_keyword(section, keyword)
1552 CALL keyword_release(keyword)
1553
1554 CALL keyword_create(keyword, __location__, name="STRENGTH", &
1555 description="Sets the force constant of the repulsive harmonic potential", &
1556 usage="STRENGTH 1.0", default_r_val=1.0_dp)
1557 CALL section_add_keyword(section, keyword)
1558 CALL keyword_release(keyword)
1559
1560 CALL keyword_create(keyword, __location__, name="BIAS", &
1561 description="If a bias potential counter-acting the weight term should be applied (recommended).", &
1562 usage="BIAS F", default_l_val=.true., lone_keyword_l_val=.true.)
1563 CALL section_add_keyword(section, keyword)
1564 CALL keyword_release(keyword)
1565
1566 CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
1567 description="Sets the temperature parameter that is used in the baising potential."// &
1568 " It is recommended to use the actual simulation temperature", &
1569 usage="TEMPERATURE 300", default_r_val=300.0_dp, unit_str='K')
1570 CALL section_add_keyword(section, keyword)
1571 CALL keyword_release(keyword)
1572
1573 CALL keyword_create(keyword, __location__, name="SMOOTH_WIDTH", &
1574 description="Sets the width of the smooth counting function.", &
1575 usage="SMOOTH_WIDTH 0.2", default_r_val=0.02_dp, unit_str='angstrom')
1576 CALL section_add_keyword(section, keyword)
1577 CALL keyword_release(keyword)
1578
1579 CALL cp_print_key_section_create(print_key, __location__, "WEIGHTS", &
1580 description="Controls the printing of FP info during flexible partitioning simulations.", &
1581 print_level=low_print_level, common_iter_levels=1, &
1582 filename="FLEXIBLE_PARTIONING")
1583 CALL section_add_subsection(section, print_key)
1584 CALL section_release(print_key)
1585
1586 CALL cp_print_key_section_create(print_key, __location__, "CONTROL", &
1587 description="Controls the printing of FP info at startup", &
1588 print_level=low_print_level, common_iter_levels=1, &
1589 filename="__STD_OUT__")
1590 CALL section_add_subsection(section, print_key)
1591 CALL section_release(print_key)
1592
1593 END SUBROUTINE create_fp_section
1594
1595! **************************************************************************************************
1596!> \brief ...
1597!> \param section will contain the driver section
1598!> \author mceriotti
1599! **************************************************************************************************
1600 SUBROUTINE create_driver_section(section)
1601 TYPE(section_type), POINTER :: section
1602
1603 TYPE(keyword_type), POINTER :: keyword
1604
1605 cpassert(.NOT. ASSOCIATED(section))
1606 CALL section_create(section, __location__, name="DRIVER", &
1607 description="This section defines the parameters needed to run in i-PI driver mode.", &
1608 citations=(/ceriotti2014, kapil2016/), &
1609 n_keywords=3, n_subsections=0, repeats=.false.)
1610
1611 NULLIFY (keyword)
1612 CALL keyword_create(keyword, __location__, name="unix", &
1613 description="Use a UNIX socket rather than an INET socket.", &
1614 usage="unix LOGICAL", &
1615 default_l_val=.false., lone_keyword_l_val=.true.)
1616 CALL section_add_keyword(section, keyword)
1617 CALL keyword_release(keyword)
1618
1619 CALL keyword_create(keyword, __location__, name="port", &
1620 description="Port number for the i-PI server.", &
1621 usage="port <INTEGER>", &
1622 default_i_val=12345)
1623 CALL section_add_keyword(section, keyword)
1624 CALL keyword_release(keyword)
1625
1626 CALL keyword_create(keyword, __location__, name="host", &
1627 description="Host name for the i-PI server.", &
1628 usage="host <HOSTNAME>", &
1629 default_c_val="localhost")
1630 CALL section_add_keyword(section, keyword)
1631 CALL keyword_release(keyword)
1632
1633 CALL keyword_create(keyword, __location__, name="SLEEP_TIME", &
1634 description="Sleeping time while waiting for for driver commands [s].", &
1635 usage="SLEEP_TIME 0.1", &
1636 default_r_val=0.01_dp)
1637 CALL section_add_keyword(section, keyword)
1638 CALL keyword_release(keyword)
1639
1640 END SUBROUTINE create_driver_section
1641
1642! **************************************************************************************************
1643!> \brief creates the section for a path integral run
1644!> \param section will contain the pint section
1645!> \author fawzi
1646! **************************************************************************************************
1647 SUBROUTINE create_pint_section(section)
1648 TYPE(section_type), POINTER :: section
1649
1650 TYPE(keyword_type), POINTER :: keyword
1651 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
1652
1653 cpassert(.NOT. ASSOCIATED(section))
1654 CALL section_create(section, __location__, name="PINT", &
1655 description="The section that controls a path integral run", &
1656 n_keywords=13, n_subsections=9, repeats=.false.)
1657 NULLIFY (keyword)
1658
1659 CALL keyword_create(keyword, __location__, name="p", &
1660 description="Specify number beads to use", repeats=.false., &
1661 default_i_val=3)
1662 CALL section_add_keyword(section, keyword)
1663 CALL keyword_release(keyword)
1664 CALL keyword_create(keyword, __location__, name="proc_per_replica", &
1665 description="Specify number of processors to use for each replica", &
1666 repeats=.false., default_i_val=0)
1667 CALL section_add_keyword(section, keyword)
1668 CALL keyword_release(keyword)
1669 CALL keyword_create(keyword, __location__, name="num_steps", &
1670 description="Number of steps (if MAX_STEP is not explicitly given"// &
1671 " the program will perform this number of steps)", repeats=.false., &
1672 default_i_val=3)
1673 CALL section_add_keyword(section, keyword)
1674 CALL keyword_release(keyword)
1675 CALL keyword_create(keyword, __location__, name="MAX_STEP", &
1676 description="Maximum step number (the program will stop if"// &
1677 " ITERATION >= MAX_STEP even if NUM_STEPS has not been reached)", &
1678 repeats=.false., default_i_val=10)
1679 CALL section_add_keyword(section, keyword)
1680 CALL keyword_release(keyword)
1681 CALL keyword_create(keyword, __location__, name="iteration", &
1682 description="Specify the iteration number from which it should be "// &
1683 "counted", default_i_val=0)
1684 CALL section_add_keyword(section, keyword)
1685 CALL keyword_release(keyword)
1686 CALL keyword_create(keyword, __location__, name="Temp", &
1687 description="The temperature you want to simulate", &
1688 default_r_val=cp_unit_to_cp2k(300._dp, "K"), &
1689 unit_str="K")
1690 CALL section_add_keyword(section, keyword)
1691 CALL keyword_release(keyword)
1692 CALL keyword_create(keyword, __location__, name="kT_CORRECTION", &
1693 description="Corrects for the loss of temperature due to constrained "// &
1694 "degrees of freedom for Nose-Hover chains and numeric integration", &
1695 repeats=.false., default_l_val=.false.)
1696 CALL section_add_keyword(section, keyword)
1697 CALL keyword_release(keyword)
1698 CALL keyword_create(keyword, __location__, name="T_tol", variants=(/"temp_to"/), &
1699 description="threshold for the oscillations of the temperature "// &
1700 "excedeed which the temperature is rescaled. 0 means no rescaling.", &
1701 default_r_val=0._dp, unit_str="K")
1702 CALL section_add_keyword(section, keyword)
1703 CALL keyword_release(keyword)
1704 CALL keyword_create(keyword, __location__, name="dt", &
1705 description="timestep (might be subdivised in nrespa subtimesteps", &
1706 repeats=.false., &
1707 default_r_val=cp_unit_to_cp2k(1.0_dp, "fs"), &
1708 usage="dt 1.0", unit_str="fs")
1709 CALL section_add_keyword(section, keyword)
1710 CALL keyword_release(keyword)
1711 CALL keyword_create(keyword, __location__, name="HARM_INT", &
1712 description="integrator scheme for integrating the harmonic bead springs.", &
1713 usage="HARM_INT (NUMERIC|EXACT)", &
1714 default_i_val=integrate_numeric, &
1715 enum_c_vals=s2a("NUMERIC", "EXACT"), &
1716 enum_i_vals=(/integrate_numeric, integrate_exact/))
1717 CALL section_add_keyword(section, keyword)
1718 CALL keyword_release(keyword)
1719 CALL keyword_create(keyword, __location__, name="nrespa", &
1720 description="number of respa steps for the bead for each md step", &
1721 repeats=.false., default_i_val=5)
1722 CALL section_add_keyword(section, keyword)
1723 CALL keyword_release(keyword)
1724
1725 CALL keyword_create(keyword, __location__, name="transformation", &
1726 description="Specifies the coordinate transformation to use", &
1727 usage="TRANSFORMATION (NORMAL|STAGE)", &
1728 default_i_val=transformation_normal, &
1729 enum_c_vals=s2a("NORMAL", "STAGE"), &
1731
1732 CALL section_add_keyword(section, keyword)
1733 CALL keyword_release(keyword)
1734 CALL keyword_create(keyword, __location__, name="propagator", &
1735 description="Specifies the real time propagator to use", &
1736 usage="PROPAGATOR (PIMD|RPMD|CMD)", &
1737 default_i_val=propagator_pimd, &
1738 enum_c_vals=s2a("PIMD", "RPMD", "CMD"), &
1740 CALL section_add_keyword(section, keyword)
1741 CALL keyword_release(keyword)
1742 CALL keyword_create(keyword, __location__, name="FIX_CENTROID_POS", &
1743 description="Propagate all DOF but the centroid - "// &
1744 "useful for equilibration of the non-centroid modes "// &
1745 "(activated only if TRANSFORMATION==NORMAL)", &
1746 repeats=.false., default_l_val=.false., &
1747 lone_keyword_l_val=.true.)
1748 CALL section_add_keyword(section, keyword)
1749 CALL keyword_release(keyword)
1750
1751 NULLIFY (subsection, subsubsection)
1752 CALL section_create(subsection, __location__, name="NORMALMODE", &
1753 description="Controls the normal mode transformation", &
1754 n_keywords=3, n_subsections=0, repeats=.false.)
1755 CALL keyword_create(keyword, __location__, name="Q_CENTROID", &
1756 description="Value of the thermostat mass of centroid degree of freedom", &
1757 repeats=.false., default_r_val=-1.0_dp)
1758 CALL section_add_keyword(subsection, keyword)
1759 CALL keyword_release(keyword)
1760 CALL keyword_create(keyword, __location__, name="Q_BEAD", &
1761 description="Value of the thermostat mass of non-centroid degrees of freedom", &
1762 repeats=.false., default_r_val=-1.0_dp)
1763 CALL section_add_keyword(subsection, keyword)
1764 CALL keyword_release(keyword)
1765 CALL keyword_create(keyword, __location__, name="MODEFACTOR", &
1766 description="mass scale factor for non-centroid degrees of freedom", &
1767 repeats=.false., default_r_val=1.0_dp)
1768 CALL section_add_keyword(subsection, keyword)
1769 CALL keyword_release(keyword)
1770 CALL keyword_create(keyword, __location__, name="GAMMA", &
1771 description="mass scale factor for non-centroid degrees of freedom, &
1772& naming convention according to Witt, 2008, <https://doi.org/10.1063/1.3125009>.", &
1773 repeats=.false., default_r_val=8.0_dp)
1774 CALL section_add_keyword(subsection, keyword)
1775 CALL keyword_release(keyword)
1776
1777 CALL section_add_subsection(section, subsection)
1778 CALL section_release(subsection)
1779
1780 CALL section_create(subsection, __location__, name="staging", &
1781 description="The section that controls the staging transformation", &
1782 n_keywords=2, n_subsections=0, repeats=.false.)
1783 CALL keyword_create(keyword, __location__, name="j", &
1784 description="Value of the j parameter for the staging transformation", &
1785 repeats=.false., default_i_val=2)
1786 CALL section_add_keyword(subsection, keyword)
1787 CALL keyword_release(keyword)
1788 CALL keyword_create(keyword, __location__, name="Q_END", &
1789 description="Value of the nose-hoover mass for the endbead (Q_end)", &
1790 repeats=.false., default_i_val=2)
1791 CALL section_add_keyword(subsection, keyword)
1792 CALL keyword_release(keyword)
1793 CALL section_add_subsection(section, subsection)
1794 CALL section_release(subsection)
1795
1796 CALL section_create(subsection, __location__, name="BEADS", &
1797 description="Sets positions and velocities of the beads", &
1798 n_keywords=0, n_subsections=2, &
1799 repeats=.false.)
1800 CALL create_coord_section(subsubsection, "BEADS")
1801 CALL section_add_subsection(subsection, subsubsection)
1802 CALL section_release(subsubsection)
1803 CALL create_velocity_section(subsubsection, "BEADS")
1804 CALL section_add_subsection(subsection, subsubsection)
1805 CALL section_release(subsubsection)
1806 CALL section_add_subsection(section, subsection)
1807 CALL section_release(subsection)
1808
1809 CALL section_create(subsection, __location__, name="NOSE", &
1810 description="Controls the Nose-Hoover thermostats", &
1811 n_keywords=1, n_subsections=2, &
1812 repeats=.false.)
1813 CALL keyword_create(keyword, __location__, name="nnos", &
1814 description="length of nose-hoover chain. 0 means no thermostat", &
1815 repeats=.false., default_i_val=2)
1816 CALL section_add_keyword(subsection, keyword)
1817 CALL keyword_release(keyword)
1818 CALL create_coord_section(subsubsection, "NOSE")
1819 CALL section_add_subsection(subsection, subsubsection)
1820 CALL section_release(subsubsection)
1821 CALL create_velocity_section(subsubsection, "NOSE")
1822 CALL section_add_subsection(subsection, subsubsection)
1823 CALL section_release(subsubsection)
1824 CALL section_add_subsection(section, subsection)
1825 CALL section_release(subsection)
1826
1827 CALL create_gle_section(subsection)
1828 CALL section_add_subsection(section, subsection)
1829 CALL section_release(subsection)
1830
1831 CALL section_create(subsection, __location__, name="PILE", &
1832 description="Controls the PI Langevin Equation thermostat."// &
1833 " Needs the exact harmonic integrator."// &
1834 " May lead to unphysical motions if constraint e.g. FIXED_ATOMS, is applied."// &
1835 " RESTART_HELIUM section has to be .FALSE. when restarting the PIGLET job.", &
1836 citations=(/ceriotti2010/), &
1837 n_keywords=3, n_subsections=1, &
1838 repeats=.false.)
1839 CALL create_rng_section(subsubsection)
1840 CALL section_add_subsection(subsection, subsubsection)
1841 CALL section_release(subsubsection)
1842 CALL keyword_create(keyword, __location__, name="TAU", &
1843 description="Time constant for centroid motion. "// &
1844 "If zero or negative the centroid is not thermostated.", &
1845 usage="TAU {real}", type_of_var=real_t, &
1846 unit_str="fs", n_var=1, default_r_val=1000.0_dp)
1847 CALL section_add_keyword(subsection, keyword)
1848 CALL keyword_release(keyword)
1849 CALL keyword_create(keyword, __location__, name="LAMBDA", &
1850 description="Scaling of friction to mode coupling", &
1851 usage="LAMBDA {real}", type_of_var=real_t, &
1852 n_var=1, default_r_val=0.5_dp)
1853 CALL section_add_keyword(subsection, keyword)
1854 CALL keyword_release(keyword)
1855 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1856 description="Thermostat energy for conserved quantity. "// &
1857 "Only useful in restart files.", &
1858 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1859 n_var=1, default_r_val=0.0_dp)
1860 CALL section_add_keyword(subsection, keyword)
1861 CALL keyword_release(keyword)
1862 CALL section_add_subsection(section, subsection)
1863 CALL section_release(subsection)
1864
1865 CALL section_create(subsection, __location__, name="PIGLET", &
1866 description="Controls the PI Generalized Langevin Equation thermostat."// &
1867 " Needs the exact harmonic integrator", &
1868 citations=(/ceriotti2012/), &
1869 n_keywords=4, n_subsections=2, &
1870 repeats=.false.)
1871 CALL create_rng_section(subsubsection)
1872 CALL section_add_subsection(subsection, subsubsection)
1873 CALL section_release(subsubsection)
1874 CALL section_create(subsubsection, __location__, name="EXTRA_DOF", &
1875 description="Additional degrees of freedom to ensure Markovian Dynamics.", &
1876 n_keywords=1, n_subsections=0, repeats=.false.)
1877 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1878 description="Restart values for additional degrees of freedom" &
1879 //" (only for restarts, do not set explicitly)", &
1880 repeats=.false., &
1881 type_of_var=real_t, n_var=-1)
1882 CALL section_add_keyword(subsubsection, keyword)
1883 CALL keyword_release(keyword)
1884 CALL section_add_subsection(subsection, subsubsection)
1885 CALL section_release(subsubsection)
1886 CALL keyword_create(keyword, __location__, name="NEXTRA_DOF", &
1887 description="Number of extra degrees of freedom to ensure markovian dynamics", &
1888 repeats=.false., default_i_val=8)
1889 CALL section_add_keyword(subsection, keyword)
1890 CALL keyword_release(keyword)
1891 CALL keyword_create(keyword, __location__, name="MATRICES_FILE_NAME", &
1892 description="Filename containig the raw matrices from "// &
1893 "<https://gle4md.org/index.html?page=matrix>.", &
1894 repeats=.false., default_lc_val="PIGLET.MAT")
1895 CALL section_add_keyword(subsection, keyword)
1896 CALL keyword_release(keyword)
1897 CALL keyword_create(keyword, __location__, name="SMATRIX_INIT", &
1898 description="Select algorithm to initialize piglet S-matrices", &
1899 usage="SMATRIX_INIT (CHOLESKY|DIAGONAL)", &
1900 default_i_val=matrix_init_cholesky, &
1901 enum_c_vals=s2a("CHOLESKY", "DIAGONAL"), &
1903 CALL section_add_keyword(subsection, keyword)
1904 CALL keyword_release(keyword)
1905 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1906 description="Thermostat energy for conserved quantity. "// &
1907 "Only useful in restart files.", &
1908 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1909 n_var=1, default_r_val=0.0_dp)
1910 CALL section_add_keyword(subsection, keyword)
1911 CALL keyword_release(keyword)
1912 CALL section_add_subsection(section, subsection)
1913 CALL section_release(subsection)
1914
1915 CALL section_create(subsection, __location__, name="QTB", &
1916 description="Controls the QTB-PILE thermostat."// &
1917 " Needs the exact harmonic integrator", &
1918 citations=(/brieuc2016/), &
1919 n_keywords=7, n_subsections=1, &
1920 repeats=.false.)
1921 CALL create_rng_section(subsubsection)
1922 CALL section_add_subsection(subsection, subsubsection)
1923 CALL section_release(subsubsection)
1924 CALL keyword_create(keyword, __location__, name="TAU", &
1925 description="Time constant for centroid motion. ", &
1926 usage="TAU {real}", type_of_var=real_t, &
1927 unit_str="fs", n_var=1, default_r_val=1000.0_dp)
1928 CALL section_add_keyword(subsection, keyword)
1929 CALL keyword_release(keyword)
1930 CALL keyword_create(keyword, __location__, name="LAMBDA", &
1931 description="Scaling of friction to ring polymer NM freq.", &
1932 usage="LAMBDA {real}", type_of_var=real_t, &
1933 n_var=1, default_r_val=0.5_dp)
1934 CALL section_add_keyword(subsection, keyword)
1935 CALL keyword_release(keyword)
1936 CALL keyword_create(keyword, __location__, name="FP", &
1937 description="Defines which version to use "// &
1938 "0: f_P^(0), 1: f_P^(1)", &
1939 usage="FP {integer}", type_of_var=integer_t, &
1940 n_var=1, default_i_val=1)
1941 CALL section_add_keyword(subsection, keyword)
1942 CALL keyword_release(keyword)
1943 CALL keyword_create(keyword, __location__, name="TAUCUT", &
1944 description="Inverse of cutoff freq. for the centroid mode", &
1945 usage="TAUCUT {real}", type_of_var=real_t, &
1946 unit_str="fs", n_var=1, default_r_val=0.5_dp)
1947 CALL section_add_keyword(subsection, keyword)
1948 CALL keyword_release(keyword)
1949 CALL keyword_create(keyword, __location__, name="LAMBCUT", &
1950 description="Scaling of cutoff freq. to ring polymer NM freq.", &
1951 usage="LAMBCUT {real}", type_of_var=real_t, &
1952 n_var=1, default_r_val=2.0_dp)
1953 CALL section_add_keyword(subsection, keyword)
1954 CALL keyword_release(keyword)
1955 CALL keyword_create(keyword, __location__, name="NF", &
1956 description="Number of points used for the convolution product.", &
1957 usage="NF {integer}", type_of_var=integer_t, &
1958 n_var=1, default_i_val=128)
1959 CALL section_add_keyword(subsection, keyword)
1960 CALL keyword_release(keyword)
1961 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1962 description="Thermostat energy for conserved quantity. "// &
1963 "Only useful in restart files.", &
1964 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1965 n_var=1, default_r_val=0.0_dp)
1966 CALL section_add_keyword(subsection, keyword)
1967 CALL keyword_release(keyword)
1968 CALL section_add_subsection(section, subsection)
1969 CALL section_release(subsection)
1970
1971 CALL section_create(subsection, __location__, name="INIT", &
1972 description="Controls the initialization if the beads are not present", &
1973 repeats=.false.)
1974
1975 CALL keyword_create(keyword, __location__, name="LEVY_POS_SAMPLE", &
1976 description="Sample bead positions assuming free particle "// &
1977 "behavior (performs a Levy random walk of length P around "// &
1978 "the classical position of each atom at the physical "// &
1979 "temperature defined in PINT%TEMP)", &
1980 repeats=.false., default_l_val=.false., &
1981 lone_keyword_l_val=.true.)
1982 CALL section_add_keyword(subsection, keyword)
1983 CALL keyword_release(keyword)
1984 CALL keyword_create(keyword, __location__, name="LEVY_CORRELATED", &
1985 description="Use the same Levy path for all atoms, though "// &
1986 "with mass-dependent variances (might help at very low T)", &
1987 repeats=.false., default_l_val=.false., &
1988 lone_keyword_l_val=.true.)
1989 CALL section_add_keyword(subsection, keyword)
1990 CALL keyword_release(keyword)
1991 CALL keyword_create(keyword, __location__, name="LEVY_TEMP_FACTOR", &
1992 description="Multiplicative correction factor for the "// &
1993 "temperature at which the Levy walk is performed "// &
1994 "(correction is due to the interactions that modify "// &
1995 "the spread of a free particle)", &
1996 repeats=.false., default_r_val=1.0_dp)
1997 CALL section_add_keyword(subsection, keyword)
1998 CALL keyword_release(keyword)
1999 CALL keyword_create(keyword, __location__, name="LEVY_SEED", &
2000 description="Initial seed for the (pseudo)random number "// &
2001 "generator that controls Levy walk for bead positions.", &
2002 usage="LEVY_SEED <INTEGER>", default_i_val=1234, &
2003 repeats=.false.)
2004 CALL section_add_keyword(subsection, keyword)
2005 CALL keyword_release(keyword)
2006 CALL keyword_create(keyword, __location__, name="THERMOSTAT_SEED", &
2007 description="Initial seed for the (pseudo)random number "// &
2008 "generator that controls the PILE and PIGLET thermostats.", &
2009 usage="THERMOSTAT_SEED <INTEGER>", default_i_val=12345, &
2010 repeats=.false.)
2011 CALL section_add_keyword(subsection, keyword)
2012 CALL keyword_release(keyword)
2013 CALL keyword_create(keyword, __location__, name="RANDOMIZE_POS", &
2014 description="add gaussian noise to the positions of the beads", &
2015 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2016 CALL section_add_keyword(subsection, keyword)
2017 CALL keyword_release(keyword)
2018
2019 CALL keyword_create(keyword, __location__, name="CENTROID_SPEED", &
2020 description="adds random velocity component to the centroid modes "// &
2021 "(useful to correct for the averaging out of the speed of various beads)", &
2022 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2023 CALL section_add_keyword(subsection, keyword)
2024 CALL keyword_release(keyword)
2025
2026 CALL keyword_create(keyword, __location__, name="VELOCITY_QUENCH", &
2027 description="set the initial velocities to zero", &
2028 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2029 CALL section_add_keyword(subsection, keyword)
2030 CALL keyword_release(keyword)
2031 CALL keyword_create(keyword, __location__, name="VELOCITY_SCALE", &
2032 description="scale initial velocities to the temperature given in MOTION%PINT%TEMP", &
2033 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2034 CALL section_add_keyword(subsection, keyword)
2035 CALL keyword_release(keyword)
2036
2037 CALL section_add_subsection(section, subsection)
2038 CALL section_release(subsection)
2039
2040 CALL create_helium_section(subsection)
2041 CALL section_add_subsection(section, subsection)
2042 CALL section_release(subsection)
2043
2044 CALL section_create(subsection, __location__, name="PRINT", &
2045 description="Controls the path integral-specific output", &
2046 n_keywords=2, n_subsections=0, repeats=.false.)
2047
2048 NULLIFY (print_key)
2049
2050 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
2051 description="Controls the output of the path integral energies", &
2052 print_level=low_print_level, common_iter_levels=1)
2053 CALL section_add_subsection(subsection, print_key)
2054 CALL section_release(print_key)
2055
2056 CALL cp_print_key_section_create(print_key, __location__, "ACTION", &
2057 description="Controls the output of the path integral action", &
2058 print_level=medium_print_level, common_iter_levels=1)
2059 CALL section_add_subsection(subsection, print_key)
2060 CALL section_release(print_key)
2061
2062 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_POS", &
2063 description="Controls the output of the centroid's position", &
2064 unit_str="angstrom", &
2065 print_level=low_print_level, common_iter_levels=1)
2066 CALL add_format_keyword(keyword, print_key, pos=.true., &
2067 description="Output file format for the positions of centroid")
2068 CALL section_add_subsection(subsection, print_key)
2069 CALL section_release(print_key)
2070
2071 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_VEL", &
2072 description="Controls the output of the centroid's velocity", &
2073 unit_str="bohr*au_t^-1", &
2074 print_level=low_print_level, common_iter_levels=1)
2075 CALL add_format_keyword(keyword, print_key, pos=.false., &
2076 description="Output file format for the velocity of centroid")
2077 CALL section_add_subsection(subsection, print_key)
2078 CALL section_release(print_key)
2079
2080 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_GYR", &
2081 description="Controls the output of the centroid's radii of gyration", &
2082 unit_str="angstrom", &
2083 print_level=low_print_level, common_iter_levels=1)
2084 CALL section_add_subsection(subsection, print_key)
2085 CALL section_release(print_key)
2086
2087 CALL cp_print_key_section_create(print_key, __location__, "COM", &
2088 description="Controls the output of the center of mass", &
2089 print_level=high_print_level, common_iter_levels=1)
2090 CALL section_add_subsection(subsection, print_key)
2091 CALL section_release(print_key)
2092
2093 CALL keyword_create(keyword, __location__, name="IMAGINARY_TIME_STRIDE", &
2094 description="Prints only every nth bead trajectory", &
2095 repeats=.false., default_i_val=1)
2096 CALL section_add_keyword(subsection, keyword)
2097 CALL keyword_release(keyword)
2098
2099 CALL section_add_subsection(section, subsection)
2100 CALL section_release(subsection)
2101
2102 END SUBROUTINE create_pint_section
2103
2104 ! ***************************************************************************
2105 !> \brief Create the input section for superfluid helium solvent.
2106 !> \author Lukasz Walewski
2107 ! ***************************************************************************
2108! **************************************************************************************************
2109!> \brief ...
2110!> \param section ...
2111! **************************************************************************************************
2112 SUBROUTINE create_helium_section(section)
2113 TYPE(section_type), POINTER :: section
2114
2115 TYPE(keyword_type), POINTER :: keyword
2116 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
2117
2118 cpassert(.NOT. ASSOCIATED(section))
2119
2120 CALL section_create(section, __location__, name="HELIUM", &
2121 description="The section that controls optional helium solvent"// &
2122 " environment (highly experimental, not for general use yet)", &
2123 n_keywords=31, n_subsections=11, repeats=.false.)
2124
2125 NULLIFY (keyword)
2126 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2127 description="Whether or not to actually use this section", &
2128 usage="silent", default_l_val=.false., lone_keyword_l_val=.true.)
2129 CALL section_add_keyword(section, keyword)
2130 CALL keyword_release(keyword)
2131
2132 CALL keyword_create(keyword, __location__, name="HELIUM_ONLY", &
2133 description="Simulate helium solvent only, "// &
2134 "disregard solute entirely", &
2135 repeats=.false., default_l_val=.false., &
2136 lone_keyword_l_val=.true.)
2137 CALL section_add_keyword(section, keyword)
2138 CALL keyword_release(keyword)
2139
2140 CALL keyword_create(keyword, __location__, name="INTERACTION_POT_SCAN", &
2141 description="Scan solute-helium interaction potential, "// &
2142 "cubefile parameters set in subsection RHO", &
2143 repeats=.false., default_l_val=.false., &
2144 lone_keyword_l_val=.true.)
2145 CALL section_add_keyword(section, keyword)
2146 CALL keyword_release(keyword)
2147
2148 CALL keyword_create(keyword, __location__, name="NUM_ENV", &
2149 description="Number of independent helium environments", &
2150 repeats=.false., default_i_val=1)
2151 CALL section_add_keyword(section, keyword)
2152 CALL keyword_release(keyword)
2153
2154 CALL keyword_create(keyword, __location__, name="POTENTIAL_FILE_NAME", &
2155 description="Name of the Helium interaction potential file", &
2156 repeats=.false., default_lc_val="HELIUM.POT")
2157 CALL section_add_keyword(section, keyword)
2158 CALL keyword_release(keyword)
2159
2160 CALL keyword_create(keyword, __location__, name="GET_FORCES", &
2161 description="Get average MC forces or last MC forces to propagate MD", &
2162 usage="GET_FORCES (AVERAGE|LAST)", &
2163 default_i_val=helium_forces_average, &
2164 enum_c_vals=s2a("AVERAGE", "LAST"), &
2166 CALL section_add_keyword(section, keyword)
2167 CALL keyword_release(keyword)
2168
2169 CALL keyword_create(keyword, __location__, name="SOLUTE_INTERACTION", &
2170 description="Interaction potential between helium and the solute", &
2171 usage="SOLUTE_INTERACTION (NONE | MWATER | NNP)", &
2172 default_i_val=helium_solute_intpot_none, &
2173 enum_c_vals=s2a("NONE", "MWATER", "NNP"), &
2174 enum_i_vals=(/ &
2178 enum_desc=s2a( &
2179 "No interaction with solute", &
2180 "Test interaction with wrong Water", &
2181 "Interaction with NNP"))
2182 CALL section_add_keyword(section, keyword)
2183 CALL keyword_release(keyword)
2184
2185 CALL keyword_create(keyword, __location__, name="NATOMS", &
2186 description="Number of helium atoms", &
2187 repeats=.false., default_i_val=64)
2188 CALL section_add_keyword(section, keyword)
2189 CALL keyword_release(keyword)
2190
2191 CALL keyword_create(keyword, __location__, name="NBEADS", &
2192 description="Number of helium path integral beads", &
2193 repeats=.false., default_i_val=25)
2194 CALL section_add_keyword(section, keyword)
2195 CALL keyword_release(keyword)
2196
2197 CALL keyword_create(keyword, __location__, name="RNG_SEED", &
2198 description="Initial seed for the (pseudo)random number "// &
2199 "generator that controls helium coordinate generation and propagation.", &
2200 usage="RNG_SEED <INTEGER>", default_i_val=12345, &
2201 repeats=.false.)
2202 CALL section_add_keyword(section, keyword)
2203 CALL keyword_release(keyword)
2204
2205 CALL keyword_create(keyword, __location__, name="N_INNER", &
2206 variants=s2a("INOROT"), &
2207 description="Number of MC iterations at the same time slice(s) "// &
2208 "(number of inner MC loop iterations)", &
2209 repeats=.false., default_i_val=6600)
2210 CALL section_add_keyword(section, keyword)
2211 CALL keyword_release(keyword)
2212
2213 CALL keyword_create(keyword, __location__, name="N_OUTER", &
2214 variants=s2a("IROT"), &
2215 description="how often to reselect the time slice(s) to work on "// &
2216 "(number of outer MC loop iterations)", &
2217 repeats=.false., default_i_val=300)
2218 CALL section_add_keyword(section, keyword)
2219 CALL keyword_release(keyword)
2220
2221 CALL keyword_create(keyword, __location__, name="SAMPLING_METHOD", &
2222 description="Choose between Ceperley or the worm algorithm", &
2223 usage="SAMPLING_METHOD (CEPERLEY|WORM)", &
2224 default_i_val=helium_sampling_ceperley, &
2225 enum_c_vals=s2a("CEPERLEY", "WORM"), &
2227 CALL section_add_keyword(section, keyword)
2228 CALL keyword_release(keyword)
2229
2230 CALL keyword_create(keyword, __location__, name="COORD_INIT_TEMP", &
2231 description="Temperature for thermal gaussian initialization of the helium."// &
2232 " Negative values correspond to a hot start.", &
2233 default_r_val=cp_unit_to_cp2k(300._dp, "K"), &
2234 unit_str="K")
2235 CALL section_add_keyword(section, keyword)
2236 CALL keyword_release(keyword)
2237
2238 CALL keyword_create(keyword, __location__, name="SOLUTE_RADIUS", &
2239 description="Radius of the solute molecule for prevention of"// &
2240 " coordinate collision during initialization", &
2241 default_r_val=cp_unit_to_cp2k(0.0_dp, "angstrom"), &
2242 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2243 CALL section_add_keyword(section, keyword)
2244 CALL keyword_release(keyword)
2245
2246 ! Helium-solute interaction NNP
2247 NULLIFY (subsection)
2248 CALL section_create(subsection, __location__, name="NNP", &
2249 description="This section contains all information to run an helium-solute "// &
2250 "interaction Neural Network Potential (NNP) calculation.", &
2251 n_keywords=2, n_subsections=3, repeats=.false.)
2252
2253 CALL keyword_create(keyword, __location__, name="NNP_INPUT_FILE_NAME", &
2254 description="File containing the input information for the setup "// &
2255 "of the NNP (n2p2/RuNNer format). ", &
2256 repeats=.false., default_lc_val="input.nn")
2257 CALL section_add_keyword(subsection, keyword)
2258 CALL keyword_release(keyword)
2259
2260 CALL keyword_create(keyword, __location__, name="SCALE_FILE_NAME", &
2261 description="File containing the scaling information for the symmetry "// &
2262 "functions of the NNP. ", &
2263 repeats=.false., default_lc_val="scaling.data")
2264 CALL section_add_keyword(subsection, keyword)
2265 CALL keyword_release(keyword)
2266
2267 NULLIFY (subsubsection)
2268 CALL section_create(subsubsection, __location__, name="SR_CUTOFF", &
2269 description="Section for failsafe short range cutoffs for the NNPs, "// &
2270 "if the distance between solvent and specified solute element becomes "// &
2271 "smaller than the given cutoff, an artifical repulsive potential is "// &
2272 "introduced. Note this is only meant to prevent such configurations, "// &
2273 "not to physically sample them.", &
2274 n_keywords=2, n_subsections=0, repeats=.true.)
2275
2276 CALL keyword_create(keyword, __location__, name="ELEMENT", &
2277 description="Solute element for which the short range cutoff is in effect", &
2278 repeats=.false., default_c_val="none")
2279 CALL section_add_keyword(subsubsection, keyword)
2280 CALL keyword_release(keyword)
2281
2282 CALL keyword_create(keyword, __location__, name="RADIUS", &
2283 description="Short range cutoff in Angstrom, below this cutoff, the energy "// &
2284 "is replaced by a sizable positive value plus a 1/r**2 term to guide particles "// &
2285 "away from each other.", &
2286 default_r_val=cp_unit_to_cp2k(0.0_dp, "angstrom"), &
2287 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2288 CALL section_add_keyword(subsubsection, keyword)
2289 CALL keyword_release(keyword)
2290 CALL section_add_subsection(subsection, subsubsection)
2291 CALL section_release(subsubsection)
2292
2293 NULLIFY (subsubsection)
2294 CALL section_create(subsubsection, __location__, name="MODEL", &
2295 description="Section for a single NNP model. If this section is repeated, "// &
2296 "a committee model (C-NNP)is used where the NNP members share the same "// &
2297 "symmetry functions. ", &
2298 n_keywords=1, n_subsections=0, repeats=.true.)
2299
2300 CALL keyword_create(keyword, __location__, name="WEIGHTS", &
2301 description="File containing the weights for the artificial neural "// &
2302 "networks of the NNP. The specified name is extended by .XXX.data ", &
2303 repeats=.false., default_lc_val="weights")
2304 CALL section_add_keyword(subsubsection, keyword)
2305 CALL keyword_release(keyword)
2306 CALL section_add_subsection(subsection, subsubsection)
2307 CALL section_release(subsubsection)
2308
2309 ! Create the PRINT subsection
2310 NULLIFY (subsubsection)
2311 CALL section_create(subsubsection, __location__, name="PRINT", &
2312 description="Section of possible print options in NNP code.", &
2313 n_keywords=0, n_subsections=3, repeats=.false.)
2314 NULLIFY (print_key, keyword)
2315
2316 CALL cp_print_key_section_create(print_key, __location__, "ENERGIES", &
2317 description="Controls the printing of the NNP energies.", &
2318 print_level=medium_print_level, common_iter_levels=1)
2319 CALL section_add_subsection(subsubsection, print_key)
2320 CALL section_release(print_key)
2321
2322 CALL cp_print_key_section_create(print_key, __location__, "FORCES_SIGMA", &
2323 description="Controls the printing of the STD per atom of the NNP forces.", &
2324 print_level=medium_print_level, common_iter_levels=1)
2325 CALL section_add_subsection(subsubsection, print_key)
2326 CALL section_release(print_key)
2327
2328 CALL cp_print_key_section_create(print_key, __location__, "EXTRAPOLATION", &
2329 description="If activated, output structures with extrapolation "// &
2330 "warning in xyz-format", &
2331 print_level=medium_print_level, common_iter_levels=1)
2332 CALL section_add_subsection(subsubsection, print_key)
2333 CALL section_release(print_key)
2334 CALL section_add_subsection(subsection, subsubsection)
2335 CALL section_release(subsubsection)
2336
2337 CALL section_add_subsection(section, subsection)
2338 CALL section_release(subsection) ! release NNP subsection
2339
2340 ! Ceperley's sampling algorithm
2341 NULLIFY (subsection)
2342 CALL section_create(subsection, __location__, name="CEPERLEY", &
2343 description="Enables sampling with Ceperley's algorithm", &
2344 n_keywords=2, n_subsections=1, repeats=.false.)
2345
2346 CALL keyword_create(keyword, __location__, name="BISECTION", &
2347 description="how many time slices to change at once (+1). "// &
2348 "Must be a power of 2 currently", &
2349 repeats=.false., default_i_val=8)
2350 CALL section_add_keyword(subsection, keyword)
2351 CALL keyword_release(keyword)
2352
2353 CALL keyword_create(keyword, __location__, name="MAX_PERM_CYCLE", &
2354 description="how large cyclic permutations to try", &
2355 repeats=.false., default_i_val=6)
2356 CALL section_add_keyword(subsection, keyword)
2357 CALL keyword_release(keyword)
2358
2359 NULLIFY (subsubsection)
2360 CALL section_create(subsubsection, __location__, name="M-SAMPLING", &
2361 description="Permutation cycle length sampling settings", &
2362 n_keywords=3, n_subsections=0, repeats=.false.)
2363 CALL keyword_create(keyword, __location__, name="DISTRIBUTION-TYPE", &
2364 description="Distribution from which the cycle length m is sampled", &
2365 usage="DISTRIBUTION-TYPE (SINGLEV|UNIFORM|LINEAR|QUADRATIC|EXPONENTIAL|GAUSSIAN)", &
2366 default_i_val=helium_mdist_uniform, &
2367 enum_c_vals=s2a( &
2368 "SINGLEV", &
2369 "UNIFORM", &
2370 "LINEAR", &
2371 "QUADRATIC", &
2372 "EXPONENTIAL", &
2373 "GAUSSIAN"), &
2374 enum_i_vals=(/ &
2381 CALL section_add_keyword(subsubsection, keyword)
2382 CALL keyword_release(keyword)
2383 CALL keyword_create(keyword, __location__, name="M-VALUE", &
2384 description="Value of m treated in a special way "// &
2385 "(specific behavior depends on the distribution type chosen)", &
2386 repeats=.false., &
2387 default_i_val=1)
2388 CALL section_add_keyword(subsubsection, keyword)
2389 CALL keyword_release(keyword)
2390 CALL keyword_create(keyword, __location__, name="M-RATIO", &
2391 description="Probability ratio betw M-VALUE and other cycle lengths", &
2392 repeats=.false., &
2393 default_r_val=1.0_dp)
2394 CALL section_add_keyword(subsubsection, keyword)
2395 CALL keyword_release(keyword)
2396 CALL section_add_subsection(subsection, subsubsection)
2397 CALL section_release(subsubsection)
2398 CALL section_add_subsection(section, subsection)
2399 CALL section_release(subsection) ! release CEPERLEY subsection
2400
2401! worm algorithm parameters:
2402 NULLIFY (subsection)
2403 CALL section_create(subsection, __location__, name="WORM", &
2404 description="Enables sampling via the canonical worm algorithm adapted from Bonisegni", &
2405 n_keywords=12, n_subsections=0, repeats=.false.)
2406
2407 CALL keyword_create(keyword, __location__, name="CENTROID_DRMAX", &
2408 description="Maximum displacement allowed for the centroid moves", &
2409 repeats=.false., default_r_val=0.5_dp)
2410 CALL section_add_keyword(subsection, keyword)
2411 CALL keyword_release(keyword)
2412
2413 CALL keyword_create(keyword, __location__, name="STAGING_L", &
2414 description="From 2 up to max. L-1 beads will be moved", &
2415 repeats=.false., default_i_val=5)
2416 CALL section_add_keyword(subsection, keyword)
2417 CALL keyword_release(keyword)
2418
2419 CALL keyword_create(keyword, __location__, name="OPEN_CLOSE_SCALE", &
2420 description="Open/Close acceptance adjustment parameter", &
2421 repeats=.false., default_r_val=0.01_dp)
2422 CALL section_add_keyword(subsection, keyword)
2423 CALL keyword_release(keyword)
2424
2425 CALL keyword_create(keyword, __location__, name="ALLOW_OPEN", &
2426 description="Enable bosonic exchange sampling", &
2427 repeats=.false., default_l_val=.true.)
2428 CALL section_add_keyword(subsection, keyword)
2429 CALL keyword_release(keyword)
2430
2431 CALL keyword_create(keyword, __location__, name="MAX_OPEN_CYCLES", &
2432 description="If > 0 then reset positions and permutations to the previous closed &
2433 & state if staying more than this amount of MC cycles in open state to avoid staying &
2434 & trapped in open state for too long. Use with caution as it can potentially introduce &
2435 & a bias in the sampling.", &
2436 repeats=.false., default_i_val=0)
2437 CALL section_add_keyword(subsection, keyword)
2438 CALL keyword_release(keyword)
2439
2440 CALL keyword_create(keyword, __location__, name="SHOW_STATISTICS", &
2441 description="Show sampling statistics in output", &
2442 repeats=.false., default_l_val=.true.)
2443 CALL section_add_keyword(subsection, keyword)
2444 CALL keyword_release(keyword)
2445
2446 CALL keyword_create(keyword, __location__, name="CENTROID_WEIGHT", &
2447 description="Absolute weight of the centroid move", &
2448 repeats=.false., default_i_val=10)
2449 CALL section_add_keyword(subsection, keyword)
2450 CALL keyword_release(keyword)
2451
2452 CALL keyword_create(keyword, __location__, name="STAGING_WEIGHT", &
2453 description="Absolute weight of the staging move", &
2454 repeats=.false., default_i_val=30)
2455 CALL section_add_keyword(subsection, keyword)
2456 CALL keyword_release(keyword)
2457
2458 CALL keyword_create(keyword, __location__, name="OPEN_CLOSE_WEIGHT", &
2459 description="Absolute weight of the open/close move", &
2460 repeats=.false., default_i_val=10)
2461 CALL section_add_keyword(subsection, keyword)
2462 CALL keyword_release(keyword)
2463
2464 CALL keyword_create(keyword, __location__, name="HEAD_TAIL_WEIGHT", &
2465 description="Absolute weight of the head/tail moves (both)", &
2466 repeats=.false., default_i_val=10)
2467 CALL section_add_keyword(subsection, keyword)
2468 CALL keyword_release(keyword)
2469
2470 CALL keyword_create(keyword, __location__, name="CRAWL_WEIGHT", &
2471 description="Absolute weight of the crawl bwd/fwd moves (both)", &
2472 repeats=.false., default_i_val=10)
2473 CALL section_add_keyword(subsection, keyword)
2474 CALL keyword_release(keyword)
2475
2476 CALL keyword_create(keyword, __location__, name="CRAWL_REPETITION", &
2477 description="Number of repeated crawl moves", &
2478 repeats=.false., default_i_val=4)
2479 CALL section_add_keyword(subsection, keyword)
2480 CALL keyword_release(keyword)
2481
2482 CALL keyword_create(keyword, __location__, name="SWAP_WEIGHT", &
2483 description="Absolute weight of the crawl move", &
2484 repeats=.false., default_i_val=10)
2485 CALL section_add_keyword(subsection, keyword)
2486 CALL keyword_release(keyword)
2487
2488 CALL section_add_subsection(section, subsection)
2489 CALL section_release(subsection) ! release WORM subsection
2490
2491! end of worm parameters
2492
2493 CALL keyword_create(keyword, __location__, name="PERIODIC", &
2494 description="Use periodic boundary conditions for helium", &
2495 repeats=.false., default_l_val=.false.)
2496 CALL section_add_keyword(section, keyword)
2497 CALL keyword_release(keyword)
2498
2499 CALL keyword_create(keyword, __location__, name="CELL_SIZE", &
2500 description="PBC unit cell size (NOTE 1: density, number of atoms"// &
2501 " and volume are interdependent - give only two of them; "// &
2502 "NOTE 2: for small cell sizes specify NATOMS instead)", &
2503 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2504 CALL section_add_keyword(section, keyword)
2505 CALL keyword_release(keyword)
2506
2507 CALL keyword_create(keyword, __location__, name="CELL_SHAPE", &
2508 description="PBC unit cell shape for helium", &
2509 usage="CELL_SHAPE (CUBE|OCTAHEDRON)", &
2510 default_i_val=helium_cell_shape_cube, &
2511 enum_c_vals=s2a("CUBE", "OCTAHEDRON"), &
2513 CALL section_add_keyword(section, keyword)
2514 CALL keyword_release(keyword)
2515
2516 CALL keyword_create(keyword, __location__, name="DROPLET_RADIUS", &
2517 description="Reject a move if any of the new positions does not lie within"// &
2518 " this range from the center of gravity", &
2519 repeats=.false., type_of_var=real_t, default_r_val=huge(1.0_dp), &
2520 unit_str="angstrom")
2521 CALL section_add_keyword(section, keyword)
2522 CALL keyword_release(keyword)
2523
2524 CALL keyword_create(keyword, __location__, name="DENSITY", &
2525 description="trial density of helium for determining the helium "// &
2526 "box size", &
2527 repeats=.false., &
2528 default_r_val=cp_unit_to_cp2k(0.02186_dp, "angstrom^-3"), &
2529 unit_str="angstrom^-3")
2530 CALL section_add_keyword(section, keyword)
2531 CALL keyword_release(keyword)
2532
2533 CALL keyword_create(keyword, __location__, name="PRESAMPLE", &
2534 description="Presample He coordinates before first PIMD step", &
2535 repeats=.false., default_l_val=.false.)
2536 CALL section_add_keyword(section, keyword)
2537 CALL keyword_release(keyword)
2538
2539 CALL section_create(subsection, __location__, name="RDF", &
2540 description="Radial distribution settings", &
2541 n_keywords=5, n_subsections=0, repeats=.false.)
2542
2543 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2544 description="Whether or not to actually calculate this property", &
2545 default_l_val=.false., lone_keyword_l_val=.true.)
2546 CALL section_add_keyword(subsection, keyword)
2547 CALL keyword_release(keyword)
2548
2549 CALL keyword_create(keyword, __location__, name="MAXR", &
2550 description="Maximum RDF range, defaults to unit cell size", &
2551 repeats=.false., type_of_var=real_t, &
2552 unit_str="angstrom")
2553 CALL section_add_keyword(subsection, keyword)
2554 CALL keyword_release(keyword)
2555
2556 CALL keyword_create(keyword, __location__, name="NBIN", &
2557 description="Number of bins", &
2558 repeats=.false., &
2559 default_i_val=250)
2560 CALL section_add_keyword(subsection, keyword)
2561 CALL keyword_release(keyword)
2562
2563 CALL keyword_create(keyword, __location__, name="SOLUTE_HE", &
2564 description="Whether or not to calculate solute-He RDFs (if solute is present)", &
2565 default_l_val=.true., lone_keyword_l_val=.true.)
2566 CALL section_add_keyword(subsection, keyword)
2567 CALL keyword_release(keyword)
2568
2569 CALL keyword_create(keyword, __location__, name="HE_HE", &
2570 description="Whether or not to calculate He-He RDFs", &
2571 default_l_val=.false., lone_keyword_l_val=.true.)
2572 CALL section_add_keyword(subsection, keyword)
2573 CALL keyword_release(keyword)
2574
2575 CALL section_add_subsection(section, subsection)
2576 CALL section_release(subsection)
2577
2578 NULLIFY (subsection)
2579 CALL section_create(subsection, __location__, name="RHO", &
2580 description="Spatial distribution settings", &
2581 n_keywords=10, n_subsections=0, repeats=.false.)
2582 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2583 description="Whether or not to actually calculate densities "// &
2584 "(requires significant amount of memory, depending on the value of NBIN)", &
2585 default_l_val=.false., lone_keyword_l_val=.true.)
2586 CALL section_add_keyword(subsection, keyword)
2587 CALL keyword_release(keyword)
2588 CALL keyword_create(keyword, __location__, name="NBIN", &
2589 description="Number of grid points in each direction for density binning", &
2590 repeats=.false., &
2591 default_i_val=100)
2592 CALL section_add_keyword(subsection, keyword)
2593 CALL keyword_release(keyword)
2594 !
2595 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_WDG", &
2596 description="Density of winding paths "// &
2597 "not shorter than the given length", &
2598 repeats=.false., usage="MIN_CYCLE_LENGTHS_WDG <INT> <INT> .. <INT>", &
2599 type_of_var=integer_t, n_var=-1)
2600 CALL section_add_keyword(subsection, keyword)
2601 CALL keyword_release(keyword)
2602 !
2603 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_NON", &
2604 description="Density of non-winding paths "// &
2605 "not shorter than the given length", &
2606 repeats=.false., usage="MIN_CYCLE_LENGTHS_NON <INT> <INT> .. <INT>", &
2607 type_of_var=integer_t, n_var=-1)
2608 CALL section_add_keyword(subsection, keyword)
2609 CALL keyword_release(keyword)
2610 !
2611 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_ALL", &
2612 description="Density of all paths "// &
2613 "not shorter than the given length", &
2614 repeats=.false., usage="MIN_CYCLE_LENGTHS_ALL <INT> <INT> .. <INT>", &
2615 type_of_var=integer_t, n_var=-1)
2616 CALL section_add_keyword(subsection, keyword)
2617 CALL keyword_release(keyword)
2618 !
2619 CALL keyword_create(keyword, __location__, name="ATOM_NUMBER", &
2620 description="Atom number density", &
2621 repeats=.false., &
2622 type_of_var=logical_t, &
2623 default_l_val=.true., &
2624 lone_keyword_l_val=.true.)
2625 CALL section_add_keyword(subsection, keyword)
2626 CALL keyword_release(keyword)
2627 !
2628 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA_2", &
2629 description="Projected area squared density, A*A(r)", &
2630 repeats=.false., &
2631 type_of_var=logical_t, &
2632 default_l_val=.false., &
2633 lone_keyword_l_val=.true.)
2634 CALL section_add_keyword(subsection, keyword)
2635 CALL keyword_release(keyword)
2636 !
2637 CALL keyword_create(keyword, __location__, name="WINDING_NUMBER_2", &
2638 description="Winding number squared density, W*W(r)", &
2639 repeats=.false., &
2640 type_of_var=logical_t, &
2641 default_l_val=.false., &
2642 lone_keyword_l_val=.true.)
2643 CALL section_add_keyword(subsection, keyword)
2644 CALL keyword_release(keyword)
2645 !
2646 CALL keyword_create(keyword, __location__, name="WINDING_CYCLE_2", &
2647 description="Winding number squared density, W^2(r)", &
2648 repeats=.false., &
2649 type_of_var=logical_t, &
2650 default_l_val=.false., &
2651 lone_keyword_l_val=.true.)
2652 CALL section_add_keyword(subsection, keyword)
2653 CALL keyword_release(keyword)
2654 !
2655 CALL keyword_create(keyword, __location__, name="MOMENT_OF_INERTIA", &
2656 description="Moment of inertia density", &
2657 repeats=.false., &
2658 type_of_var=logical_t, &
2659 default_l_val=.false., &
2660 lone_keyword_l_val=.true.)
2661 CALL section_add_keyword(subsection, keyword)
2662 CALL keyword_release(keyword)
2663
2664 CALL section_add_subsection(section, subsection)
2665 CALL section_release(subsection)
2666 ! end of subsection RHO
2667
2668 CALL create_coord_section(subsection, "HELIUM")
2669 CALL section_add_subsection(section, subsection)
2670 CALL section_release(subsection)
2671
2672 CALL section_create(subsection, __location__, name="PERM", &
2673 description="Permutation state used for restart", &
2674 n_keywords=1, n_subsections=0, repeats=.false.)
2675 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2676 description="Specify particle index permutation for every "// &
2677 "helium atom", repeats=.true., usage="<INT> <INT> .. <INT>", &
2678 type_of_var=integer_t, n_var=-1)
2679 CALL section_add_keyword(subsection, keyword)
2680 CALL keyword_release(keyword)
2681 CALL section_add_subsection(section, subsection)
2682 CALL section_release(subsection)
2683
2684 CALL section_create(subsection, __location__, name="AVERAGES", &
2685 description="Average properties (used for restarts)", &
2686 n_keywords=7, n_subsections=0, repeats=.false.)
2687 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA", &
2688 description="Projected area vector for all environments", &
2689 repeats=.true., usage="PROJECTED_AREA <REAL> <REAL> .. <REAL>", &
2690 type_of_var=real_t, n_var=-1)
2691 CALL section_add_keyword(subsection, keyword)
2692 CALL keyword_release(keyword)
2693 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA_2", &
2694 description="Projected area vector squared for all environments", &
2695 repeats=.true., usage="PROJECTED_AREA_2 <REAL> <REAL> .. <REAL>", &
2696 type_of_var=real_t, n_var=-1)
2697 CALL section_add_keyword(subsection, keyword)
2698 CALL keyword_release(keyword)
2699 CALL keyword_create(keyword, __location__, name="WINDING_NUMBER_2", &
2700 description="Winding number vector squared for all environments", &
2701 repeats=.true., usage="WINDING_NUMBER_2 <REAL> <REAL> .. <REAL>", &
2702 type_of_var=real_t, n_var=-1)
2703 CALL section_add_keyword(subsection, keyword)
2704 CALL keyword_release(keyword)
2705 CALL keyword_create(keyword, __location__, name="MOMENT_OF_INERTIA", &
2706 description="Moment of inertia vector for all environments", &
2707 repeats=.true., usage="MOMENT_OF_INERTIA <REAL> <REAL> .. <REAL>", &
2708 type_of_var=real_t, n_var=-1)
2709 CALL section_add_keyword(subsection, keyword)
2710 CALL keyword_release(keyword)
2711 CALL keyword_create(keyword, __location__, name="RDF", &
2712 description="Radial distributions averaged over all environments", &
2713 repeats=.true., usage="RDF <REAL> <REAL> .. <REAL>", &
2714 type_of_var=real_t, n_var=-1)
2715 CALL section_add_keyword(subsection, keyword)
2716 CALL keyword_release(keyword)
2717 CALL keyword_create(keyword, __location__, name="RHO", &
2718 description="Spatial distributions averaged over all environments", &
2719 repeats=.true., usage="RHO <REAL> <REAL> .. <REAL>", &
2720 type_of_var=real_t, n_var=-1)
2721 CALL section_add_keyword(subsection, keyword)
2722 CALL keyword_release(keyword)
2723 CALL keyword_create(keyword, __location__, name="IWEIGHT", &
2724 description="Weight for the restarted quantities "// &
2725 "(number of MC steps used to calculate the accumulated averages)", &
2726 repeats=.false., &
2727 default_i_val=0)
2728 CALL section_add_keyword(subsection, keyword)
2729 CALL keyword_release(keyword)
2730 CALL section_add_subsection(section, subsection)
2731 CALL section_release(subsection)
2732
2733 CALL section_create(subsection, __location__, name="FORCE", &
2734 description="Forces exerted by the helium on the solute system"// &
2735 " (used for restarts)", &
2736 n_keywords=1, n_subsections=0, repeats=.false.)
2737 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2738 description="Number of real values should be 3 * "// &
2739 "<num_solute_atoms> * <num_solute_beads>", repeats=.true., &
2740 usage="<REAL> <REAL> .. <REAL>", type_of_var=real_t, &
2741 n_var=-1)
2742 CALL section_add_keyword(subsection, keyword)
2743 CALL keyword_release(keyword)
2744 CALL section_add_subsection(section, subsection)
2745 CALL section_release(subsection)
2746
2747 CALL section_create(subsection, __location__, name="RNG_STATE", &
2748 description="Random number generator state for all processors", &
2749 n_keywords=1, n_subsections=0, repeats=.false.)
2750 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2751 description="Three real arrays of DIMENSION(3,2) times two RNG "// &
2752 "streams - 36 real values per processor", &
2753 repeats=.true., usage="automatically filled, do not edit by hand", &
2754 type_of_var=real_t, n_var=-1)
2755 CALL section_add_keyword(subsection, keyword)
2756 CALL keyword_release(keyword)
2757 CALL section_add_subsection(section, subsection)
2758 CALL section_release(subsection)
2759
2760 CALL section_create(subsection, __location__, name="PRINT", &
2761 description="The section that controls the output of the helium code", &
2762 n_keywords=16, n_subsections=0, repeats=.false.)
2763
2764 ! *************************************************************************
2765 !> Printkeys for properties output
2766 ! *************************************************************************
2767 NULLIFY (print_key)
2768
2769 ! Properties printed at SILENT print level
2770 !
2771
2772 ! Properties printed at LOW print level
2773 !
2774 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
2775 description="Controls the output of helium energies"// &
2776 " (averaged over MC step)", &
2777 print_level=low_print_level, common_iter_levels=1)
2778 CALL section_add_subsection(subsection, print_key)
2779 CALL section_release(print_key)
2780 !
2781 CALL cp_print_key_section_create(print_key, __location__, "PROJECTED_AREA_2_AVG", &
2782 description="Controls the output of the average projected area squared vector", &
2783 print_level=low_print_level, common_iter_levels=1)
2784 CALL section_add_subsection(subsection, print_key)
2785 CALL section_release(print_key)
2786 !
2787 CALL cp_print_key_section_create(print_key, __location__, "WINDING_NUMBER_2_AVG", &
2788 description="Controls the output of the average winding number vector squared", &
2789 print_level=low_print_level, common_iter_levels=1)
2790 CALL section_add_subsection(subsection, print_key)
2791 CALL section_release(print_key)
2792 !
2793 CALL cp_print_key_section_create(print_key, __location__, "MOMENT_OF_INERTIA_AVG", &
2794 description="Controls the output of the average moment of inertia vector", &
2795 print_level=low_print_level, common_iter_levels=1)
2796 CALL section_add_subsection(subsection, print_key)
2797 CALL section_release(print_key)
2798
2799 ! Properties printed at MEDIUM print level
2800 !
2801 CALL cp_print_key_section_create(print_key, __location__, "RDF", &
2802 description="Controls the output of helium radial distribution functions", &
2803 print_level=medium_print_level, common_iter_levels=1)
2804 CALL section_add_subsection(subsection, print_key)
2805 CALL section_release(print_key)
2806
2807 CALL cp_print_key_section_create(print_key, __location__, "RHO", &
2808 description="Controls the output of the helium density "// &
2809 "(Gaussian cube file format)", &
2810 each_iter_names=s2a("PINT"), each_iter_values=(/100/), &
2811 print_level=medium_print_level, common_iter_levels=1, &
2812 add_last=add_last_numeric)
2813 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
2814 description="Specifies the maximum number of backup copies.", &
2815 usage="BACKUP_COPIES {int}", &
2816 default_i_val=1)
2817 CALL section_add_keyword(print_key, keyword)
2818 CALL keyword_release(keyword)
2819 CALL section_add_subsection(subsection, print_key)
2820 CALL section_release(print_key)
2821 !
2822 CALL cp_print_key_section_create(print_key, __location__, "PROJECTED_AREA", &
2823 description="Controls the output of the projected area vector", &
2824 print_level=medium_print_level, common_iter_levels=1)
2825 CALL section_add_subsection(subsection, print_key)
2826 CALL section_release(print_key)
2827 !
2828 CALL cp_print_key_section_create(print_key, __location__, "WINDING_NUMBER", &
2829 description="Controls the output of the winding number vector", &
2830 print_level=medium_print_level, common_iter_levels=1)
2831 CALL section_add_subsection(subsection, print_key)
2832 CALL section_release(print_key)
2833 !
2834 CALL cp_print_key_section_create(print_key, __location__, "MOMENT_OF_INERTIA", &
2835 description="Controls the output of the moment of inertia vector", &
2836 print_level=medium_print_level, common_iter_levels=1)
2837 CALL section_add_subsection(subsection, print_key)
2838 CALL section_release(print_key)
2839 !
2840 CALL cp_print_key_section_create(print_key, __location__, "PLENGTH", &
2841 description="Controls the output of the helium permutation length", &
2842 print_level=medium_print_level, common_iter_levels=1)
2843 CALL section_add_subsection(subsection, print_key)
2844 CALL section_release(print_key)
2845
2846 CALL cp_print_key_section_create(print_key, __location__, "ACTION", &
2847 description="Controls the output of the total helium action", &
2848 print_level=medium_print_level, common_iter_levels=1)
2849 CALL section_add_subsection(subsection, print_key)
2850 CALL section_release(print_key)
2851
2852 ! Properties printed at HIGH print level
2853 !
2854 CALL cp_print_key_section_create(print_key, __location__, "COORDINATES", &
2855 description="Controls the output of helium coordinates", &
2856 print_level=high_print_level, common_iter_levels=1)
2857 CALL keyword_create(keyword, __location__, name="FORMAT", &
2858 description="Output file format for the coordinates", &
2859 usage="FORMAT (PDB|XYZ)", &
2860 default_i_val=fmt_id_pdb, &
2861 enum_c_vals=s2a("PDB", "XYZ"), &
2862 enum_i_vals=(/fmt_id_pdb, fmt_id_xyz/), &
2863 enum_desc=s2a("Bead coordinates and connectivity is written in PDB format", &
2864 "Only bead coordinates are written in XYZ format"))
2865 CALL section_add_keyword(print_key, keyword)
2866 CALL keyword_release(keyword)
2867 CALL section_add_subsection(subsection, print_key)
2868 CALL section_release(print_key)
2869 !
2870 CALL cp_print_key_section_create(print_key, __location__, "PERM", &
2871 description="Controls the output of the helium permutation state", &
2872 print_level=high_print_level, common_iter_levels=1)
2873 CALL keyword_create(keyword, __location__, name="FORMAT", &
2874 description="Output format for the permutation", &
2875 usage="FORMAT (CYCLE|PLAIN)", &
2876 default_i_val=perm_cycle, &
2877 enum_c_vals=s2a("CYCLE", "PLAIN"), &
2878 enum_i_vals=(/perm_cycle, perm_plain/), &
2879 enum_desc=s2a( &
2880 "Cycle notation with winding cycles enclosed"// &
2881 " in '[...]' and non-winding ones enclosed in '(...)'", &
2882 "Plain permutation output, i.e. P(1) ... P(N)"))
2883 CALL section_add_keyword(print_key, keyword)
2884 CALL keyword_release(keyword)
2885 CALL section_add_subsection(subsection, print_key)
2886 CALL section_release(print_key)
2887
2888 CALL cp_print_key_section_create(print_key, __location__, "FORCES", &
2889 description="Controls the output of the helium forces on the solute", &
2890 print_level=high_print_level, common_iter_levels=1)
2891 CALL section_add_subsection(subsection, print_key)
2892 CALL section_release(print_key)
2893
2894 ! Properties printed at DEBUG print level
2895 !
2896 CALL cp_print_key_section_create(print_key, __location__, "ACCEPTS", &
2897 description="Controls the output of the helium acceptance data", &
2898 print_level=debug_print_level, common_iter_levels=1)
2899 CALL section_add_subsection(subsection, print_key)
2900 CALL section_release(print_key)
2901 !
2902 CALL cp_print_key_section_create(print_key, __location__, "FORCES_INST", &
2903 description="Controls the output of the instantaneous helium forces on the solute", &
2904 print_level=debug_print_level, common_iter_levels=1)
2905 CALL section_add_subsection(subsection, print_key)
2906 CALL section_release(print_key)
2907
2908 CALL section_add_subsection(section, subsection)
2909 CALL section_release(subsection)
2910
2911 RETURN
2912 END SUBROUTINE create_helium_section
2913
2914END MODULE input_cp2k_motion
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public kapil2016
integer, save, public ceriotti2012
integer, save, public henkelman1999
integer, save, public ceriotti2010
integer, save, public henkelman2014
integer, save, public byrd1995
integer, save, public brieuc2016
integer, save, public ceriotti2014
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public add_last_numeric
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
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 propagator_cmd
integer, parameter, public default_cell_geo_opt_id
integer, parameter, public helium_solute_intpot_mwater
integer, parameter, public do_mc_virial
integer, parameter, public fix_xz
integer, parameter, public helium_forces_average
integer, parameter, public do_mc_gemc_nvt
integer, parameter, public helium_mdist_exponential
integer, parameter, public helium_sampling_ceperley
integer, parameter, public ls_3pnt
integer, parameter, public helium_cell_shape_octahedron
integer, parameter, public default_minimization_method_id
integer, parameter, public helium_solute_intpot_none
integer, parameter, public perm_cycle
integer, parameter, public propagator_rpmd
integer, parameter, public integrate_exact
integer, parameter, public default_ts_method_id
integer, parameter, public default_lbfgs_method_id
integer, parameter, public perm_plain
integer, parameter, public helium_forces_last
integer, parameter, public helium_mdist_gaussian
integer, parameter, public fix_y
integer, parameter, public fix_none
integer, parameter, public helium_mdist_quadratic
integer, parameter, public helium_mdist_uniform
integer, parameter, public fix_z
integer, parameter, public default_bfgs_method_id
integer, parameter, public default_cg_method_id
integer, parameter, public default_dimer_method_id
integer, parameter, public transformation_stage
integer, parameter, public helium_sampling_worm
integer, parameter, public matrix_init_cholesky
integer, parameter, public ls_2pnt
integer, parameter, public ls_none
integer, parameter, public default_cell_md_id
integer, parameter, public integrate_numeric
integer, parameter, public ls_fit
integer, parameter, public default_cell_direct_id
integer, parameter, public helium_mdist_singlev
integer, parameter, public ls_gold
integer, parameter, public propagator_pimd
integer, parameter, public do_mc_gemc_npt
integer, parameter, public helium_cell_shape_cube
integer, parameter, public fmt_id_pdb
integer, parameter, public gaussian
integer, parameter, public matrix_init_diagonal
integer, parameter, public fix_xy
integer, parameter, public do_mc_traditional
integer, parameter, public transformation_normal
integer, parameter, public helium_mdist_linear
integer, parameter, public helium_solute_intpot_nnp
integer, parameter, public fix_yz
integer, parameter, public fix_x
integer, parameter, public fmt_id_xyz
integer, parameter, public numerical
subroutine, public create_constraint_section(section)
Create the constraint section. This section is useful to impose constraints.
subroutine, public create_fe_section(section)
creates the free energy section
subroutine, public create_md_section(section)
...
subroutine, public add_format_keyword(keyword, section, pos, description)
creates the FORMAT keyword
subroutine, public create_motion_print_section(section)
creates the motionprint section
subroutine, public create_motion_section(section)
creates the motion section
subroutine, public create_band_section(section)
creates the section for a BAND run
builds the subsystem section of the input
subroutine, public create_rng_section(section)
Creates the random number restart section.
subroutine, public create_gle_section(section)
...
subroutine, public create_tmc_section(section)
creates the TreeMonteCarlo subsection
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, deprecation_notice)
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 logical_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.
represent a keyword in the input
represent a section of the input file