(git:04040e4)
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-2026 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("2PNT", "GOLD", "FIT"), &
1361 enum_desc=s2a("extrapolate based on 2 points", &
1362 "perform 1D golden section search of the minimum (very expensive)", &
1363 "perform 1D fit of a parabola on several evaluation of energy "// &
1364 "(very expensive and more robust vs numerical noise)"), &
1365 enum_i_vals=[ls_2pnt, ls_gold, ls_fit])
1366 CALL section_add_keyword(subsection, keyword)
1367 CALL keyword_release(keyword)
1368
1369 ! 2PNT
1370 NULLIFY (subsubsection)
1371 CALL section_create(subsubsection, __location__, name="2PNT", &
1372 description="Provides parameters to tune the line search for the two point based line search.", &
1373 n_keywords=0, n_subsections=1, repeats=.false.)
1374
1375 CALL keyword_create(keyword, __location__, name="MAX_ALLOWED_STEP", &
1376 description="Max allowed value for the line search step.", &
1377 usage="MAX_ALLOWED_STEP {real}", unit_str="internal_cp2k", &
1378 default_r_val=0.25_dp)
1379 CALL section_add_keyword(subsubsection, keyword)
1380 CALL keyword_release(keyword)
1381
1382 CALL keyword_create( &
1383 keyword, __location__, name="LINMIN_GRAD_ONLY", &
1384 description="Use only the gradient, not the energy for line minimizations (e.g. in conjugate gradients).", &
1385 usage="LINMIN_GRAD_ONLY T", &
1386 default_l_val=.false., lone_keyword_l_val=.true.)
1387 CALL section_add_keyword(subsubsection, keyword)
1388 CALL keyword_release(keyword)
1389
1390 CALL section_add_subsection(subsection, subsubsection)
1391 CALL section_release(subsubsection)
1392
1393 ! GOLD
1394 NULLIFY (subsubsection)
1395 CALL section_create(subsubsection, __location__, name="GOLD", &
1396 description="Provides parameters to tune the line search for the gold search.", &
1397 n_keywords=0, n_subsections=1, repeats=.false.)
1398
1399 CALL keyword_create(keyword, __location__, name="INITIAL_STEP", &
1400 description="Initial step size used, e.g. for bracketing or minimizers. "// &
1401 "Might need to be reduced for systems with close contacts", &
1402 usage="INITIAL_STEP {real}", unit_str="internal_cp2k", &
1403 default_r_val=0.2_dp)
1404 CALL section_add_keyword(subsubsection, keyword)
1405 CALL keyword_release(keyword)
1406
1407 CALL keyword_create(keyword, __location__, name="BRACK_LIMIT", &
1408 description="Limit in 1D bracketing during line search in Conjugate Gradients Optimization.", &
1409 usage="BRACK_LIMIT {real}", unit_str="internal_cp2k", &
1410 default_r_val=100.0_dp)
1411 CALL section_add_keyword(subsubsection, keyword)
1412 CALL keyword_release(keyword)
1413
1414 CALL keyword_create(keyword, __location__, name="BRENT_TOL", &
1415 description="Tolerance requested during Brent line search in Conjugate Gradients Optimization.", &
1416 usage="BRENT_TOL {real}", unit_str="internal_cp2k", &
1417 default_r_val=0.01_dp)
1418 CALL section_add_keyword(subsubsection, keyword)
1419 CALL keyword_release(keyword)
1420
1421 CALL keyword_create(keyword, __location__, name="BRENT_MAX_ITER", &
1422 description="Maximum number of iterations in brent algorithm "// &
1423 "(used for the line search in Conjugated Gradients Optimization)", &
1424 usage="BRENT_MAX_ITER {integer}", &
1425 default_i_val=100)
1426 CALL section_add_keyword(subsubsection, keyword)
1427 CALL keyword_release(keyword)
1428 CALL section_add_subsection(subsection, subsubsection)
1429 CALL section_release(subsubsection)
1430
1431 CALL section_add_subsection(section, subsection)
1432 CALL section_release(subsection)
1433 END SUBROUTINE create_cg_section
1434
1435! **************************************************************************************************
1436!> \brief creates the LBFGS section
1437!> \param section the section to be created
1438!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1439! **************************************************************************************************
1440 SUBROUTINE create_lbfgs_section(section)
1441 TYPE(section_type), POINTER :: section
1442
1443 TYPE(keyword_type), POINTER :: keyword
1444
1445! create the LBFGS section
1446
1447 NULLIFY (section, keyword)
1448 CALL section_create(section, __location__, name="LBFGS", &
1449 description="Provides parameters to tune the limited memory BFGS (LBFGS) optimization", &
1450 n_keywords=0, n_subsections=1, repeats=.false., &
1451 citations=[byrd1995])
1452
1453 CALL keyword_create(keyword, __location__, name="MAX_H_RANK", &
1454 description="Maximum rank (and consequently size) of the "// &
1455 "approximate Hessian matrix used by the LBFGS optimizer. "// &
1456 "Larger values (e.g. 30) will accelerate the convergence behaviour "// &
1457 "at the cost of a larger memory consumption.", &
1458 usage="MAX_H_RANK {integer}", &
1459 default_i_val=5)
1460 CALL section_add_keyword(section, keyword)
1461 CALL keyword_release(keyword)
1462
1463 CALL keyword_create(keyword, __location__, name="MAX_F_PER_ITER", &
1464 description="Maximum number of force evaluations per iteration"// &
1465 " (used for the line search)", &
1466 usage="MAX_F_PER_ITER {integer}", &
1467 default_i_val=20)
1468 CALL section_add_keyword(section, keyword)
1469 CALL keyword_release(keyword)
1470
1471 CALL keyword_create(keyword, __location__, name="WANTED_PROJ_GRADIENT", &
1472 description="Convergence criterion (overrides the general ones):"// &
1473 " Requested norm threshold of the gradient multiplied"// &
1474 " by the approximate Hessian.", &
1475 usage="WANTED_PROJ_GRADIENT {real}", unit_str="internal_cp2k", &
1476 default_r_val=1.0e-16_dp)
1477 CALL section_add_keyword(section, keyword)
1478 CALL keyword_release(keyword)
1479
1480 CALL keyword_create(keyword, __location__, name="WANTED_REL_F_ERROR", &
1481 description="Convergence criterion (overrides the general ones):"// &
1482 " Requested relative error on the objective function"// &
1483 " of the optimizer (the energy)", &
1484 usage="WANTED_REL_F_ERROR {real}", unit_str="internal_cp2k", &
1485 default_r_val=1.0e-16_dp)
1486 CALL section_add_keyword(section, keyword)
1487 CALL keyword_release(keyword)
1488
1489 CALL keyword_create( &
1490 keyword, __location__, name="TRUST_RADIUS", &
1491 description="Trust radius used in LBFGS. Not completely in depth tested. Negativ values means no trust radius is used.", &
1492 usage="TRUST_RADIUS {real}", unit_str='angstrom', &
1493 default_r_val=-1.0_dp)
1494 CALL section_add_keyword(section, keyword)
1495 CALL keyword_release(keyword)
1496
1497 END SUBROUTINE create_lbfgs_section
1498
1499! **************************************************************************************************
1500!> \brief creates the flexible_partitioning section
1501!> \param section the section to be created
1502!> \author Joost VandeVondele [04.2006]
1503! **************************************************************************************************
1504 SUBROUTINE create_fp_section(section)
1505 TYPE(section_type), POINTER :: section
1506
1507 TYPE(keyword_type), POINTER :: keyword
1508 TYPE(section_type), POINTER :: print_key
1509
1510 cpassert(.NOT. ASSOCIATED(section))
1511 CALL section_create(section, __location__, name="FLEXIBLE_PARTITIONING", &
1512 description="This section sets up flexible_partitioning", &
1513 n_keywords=1, n_subsections=1, repeats=.false.)
1514
1515 NULLIFY (keyword, print_key)
1516
1517 CALL keyword_create(keyword, __location__, name="CENTRAL_ATOM", &
1518 description="Specifies the central atom.", &
1519 usage="CENTRAL_ATOM {integer}", &
1520 n_var=1, type_of_var=integer_t)
1521 CALL section_add_keyword(section, keyword)
1522 CALL keyword_release(keyword)
1523
1524 CALL keyword_create(keyword, __location__, name="INNER_ATOMS", &
1525 description="Specifies the list of atoms that should remain close to the central atom.", &
1526 usage="INNER_ATOMS {integer} {integer} .. {integer}", &
1527 n_var=-1, type_of_var=integer_t)
1528 CALL section_add_keyword(section, keyword)
1529 CALL keyword_release(keyword)
1530
1531 CALL keyword_create(keyword, __location__, name="OUTER_ATOMS", &
1532 description="Specifies the list of atoms that should remain far from the central atom.", &
1533 usage="OUTER_ATOMS {integer} {integer} .. {integer}", &
1534 n_var=-1, type_of_var=integer_t)
1535 CALL section_add_keyword(section, keyword)
1536 CALL keyword_release(keyword)
1537
1538 CALL keyword_create(keyword, __location__, name="INNER_RADIUS", &
1539 description="radius of the inner wall", &
1540 usage="INNER_RADIUS {real} ", type_of_var=real_t, &
1541 n_var=1, unit_str="angstrom")
1542 CALL section_add_keyword(section, keyword)
1543 CALL keyword_release(keyword)
1544
1545 CALL keyword_create(keyword, __location__, name="OUTER_RADIUS", &
1546 description="radius of the outer wall", &
1547 usage="OUTER_RADIUS {real} ", type_of_var=real_t, &
1548 n_var=1, unit_str="angstrom")
1549 CALL section_add_keyword(section, keyword)
1550 CALL keyword_release(keyword)
1551
1552 CALL keyword_create(keyword, __location__, name="STRENGTH", &
1553 description="Sets the force constant of the repulsive harmonic potential", &
1554 usage="STRENGTH 1.0", default_r_val=1.0_dp)
1555 CALL section_add_keyword(section, keyword)
1556 CALL keyword_release(keyword)
1557
1558 CALL keyword_create(keyword, __location__, name="BIAS", &
1559 description="If a bias potential counter-acting the weight term should be applied (recommended).", &
1560 usage="BIAS F", default_l_val=.true., lone_keyword_l_val=.true.)
1561 CALL section_add_keyword(section, keyword)
1562 CALL keyword_release(keyword)
1563
1564 CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
1565 description="Sets the temperature parameter that is used in the baising potential."// &
1566 " It is recommended to use the actual simulation temperature", &
1567 usage="TEMPERATURE 300", default_r_val=300.0_dp, unit_str='K')
1568 CALL section_add_keyword(section, keyword)
1569 CALL keyword_release(keyword)
1570
1571 CALL keyword_create(keyword, __location__, name="SMOOTH_WIDTH", &
1572 description="Sets the width of the smooth counting function.", &
1573 usage="SMOOTH_WIDTH 0.2", default_r_val=0.02_dp, unit_str='angstrom')
1574 CALL section_add_keyword(section, keyword)
1575 CALL keyword_release(keyword)
1576
1577 CALL cp_print_key_section_create(print_key, __location__, "WEIGHTS", &
1578 description="Controls the printing of FP info during flexible partitioning simulations.", &
1579 print_level=low_print_level, common_iter_levels=1, &
1580 filename="FLEXIBLE_PARTIONING")
1581 CALL section_add_subsection(section, print_key)
1582 CALL section_release(print_key)
1583
1584 CALL cp_print_key_section_create(print_key, __location__, "CONTROL", &
1585 description="Controls the printing of FP info at startup", &
1586 print_level=low_print_level, common_iter_levels=1, &
1587 filename="__STD_OUT__")
1588 CALL section_add_subsection(section, print_key)
1589 CALL section_release(print_key)
1590
1591 END SUBROUTINE create_fp_section
1592
1593! **************************************************************************************************
1594!> \brief ...
1595!> \param section will contain the driver section
1596!> \author mceriotti
1597! **************************************************************************************************
1598 SUBROUTINE create_driver_section(section)
1599 TYPE(section_type), POINTER :: section
1600
1601 TYPE(keyword_type), POINTER :: keyword
1602
1603 cpassert(.NOT. ASSOCIATED(section))
1604 CALL section_create(section, __location__, name="DRIVER", &
1605 description="This section defines the parameters needed to run in i-PI driver mode.", &
1606 citations=[ceriotti2014, kapil2016], &
1607 n_keywords=3, n_subsections=0, repeats=.false.)
1608
1609 NULLIFY (keyword)
1610 CALL keyword_create(keyword, __location__, name="unix", &
1611 description="Use a UNIX socket rather than an INET socket.", &
1612 usage="unix LOGICAL", &
1613 default_l_val=.false., lone_keyword_l_val=.true.)
1614 CALL section_add_keyword(section, keyword)
1615 CALL keyword_release(keyword)
1616
1617 CALL keyword_create(keyword, __location__, name="port", &
1618 description="Port number for the i-PI server.", &
1619 usage="port <INTEGER>", &
1620 default_i_val=12345)
1621 CALL section_add_keyword(section, keyword)
1622 CALL keyword_release(keyword)
1623
1624 CALL keyword_create(keyword, __location__, name="host", &
1625 description="Host name for the i-PI server.", &
1626 usage="host <HOSTNAME>", &
1627 default_c_val="localhost")
1628 CALL section_add_keyword(section, keyword)
1629 CALL keyword_release(keyword)
1630
1631 CALL keyword_create(keyword, __location__, name="SLEEP_TIME", &
1632 description="Sleeping time while waiting for for driver commands [s].", &
1633 usage="SLEEP_TIME 0.1", &
1634 default_r_val=0.01_dp)
1635 CALL section_add_keyword(section, keyword)
1636 CALL keyword_release(keyword)
1637
1638 END SUBROUTINE create_driver_section
1639
1640! **************************************************************************************************
1641!> \brief creates the section for a path integral run
1642!> \param section will contain the pint section
1643!> \author fawzi
1644! **************************************************************************************************
1645 SUBROUTINE create_pint_section(section)
1646 TYPE(section_type), POINTER :: section
1647
1648 TYPE(keyword_type), POINTER :: keyword
1649 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
1650
1651 cpassert(.NOT. ASSOCIATED(section))
1652 CALL section_create(section, __location__, name="PINT", &
1653 description="The section that controls a path integral run", &
1654 n_keywords=13, n_subsections=9, repeats=.false.)
1655 NULLIFY (keyword)
1656
1657 CALL keyword_create(keyword, __location__, name="p", &
1658 description="Specify number beads to use", repeats=.false., &
1659 default_i_val=3)
1660 CALL section_add_keyword(section, keyword)
1661 CALL keyword_release(keyword)
1662 CALL keyword_create(keyword, __location__, name="proc_per_replica", &
1663 description="Specify number of processors to use for each replica", &
1664 repeats=.false., default_i_val=0)
1665 CALL section_add_keyword(section, keyword)
1666 CALL keyword_release(keyword)
1667 CALL keyword_create(keyword, __location__, name="num_steps", &
1668 description="Number of steps (if MAX_STEP is not explicitly given"// &
1669 " the program will perform this number of steps)", repeats=.false., &
1670 default_i_val=3)
1671 CALL section_add_keyword(section, keyword)
1672 CALL keyword_release(keyword)
1673 CALL keyword_create(keyword, __location__, name="MAX_STEP", &
1674 description="Maximum step number (the program will stop if"// &
1675 " ITERATION >= MAX_STEP even if NUM_STEPS has not been reached)", &
1676 repeats=.false., default_i_val=10)
1677 CALL section_add_keyword(section, keyword)
1678 CALL keyword_release(keyword)
1679 CALL keyword_create(keyword, __location__, name="iteration", &
1680 description="Specify the iteration number from which it should be "// &
1681 "counted", default_i_val=0)
1682 CALL section_add_keyword(section, keyword)
1683 CALL keyword_release(keyword)
1684 CALL keyword_create(keyword, __location__, name="Temp", &
1685 description="The temperature you want to simulate", &
1686 default_r_val=cp_unit_to_cp2k(300._dp, "K"), &
1687 unit_str="K")
1688 CALL section_add_keyword(section, keyword)
1689 CALL keyword_release(keyword)
1690 CALL keyword_create(keyword, __location__, name="kT_CORRECTION", &
1691 description="Corrects for the loss of temperature due to constrained "// &
1692 "degrees of freedom for Nose-Hover chains and numeric integration", &
1693 repeats=.false., default_l_val=.false.)
1694 CALL section_add_keyword(section, keyword)
1695 CALL keyword_release(keyword)
1696 CALL keyword_create(keyword, __location__, name="T_tol", variants=["temp_to"], &
1697 description="threshold for the oscillations of the temperature "// &
1698 "excedeed which the temperature is rescaled. 0 means no rescaling.", &
1699 default_r_val=0._dp, unit_str="K")
1700 CALL section_add_keyword(section, keyword)
1701 CALL keyword_release(keyword)
1702 CALL keyword_create(keyword, __location__, name="dt", &
1703 description="timestep (might be subdivised in nrespa subtimesteps", &
1704 repeats=.false., &
1705 default_r_val=cp_unit_to_cp2k(1.0_dp, "fs"), &
1706 usage="dt 1.0", unit_str="fs")
1707 CALL section_add_keyword(section, keyword)
1708 CALL keyword_release(keyword)
1709 CALL keyword_create(keyword, __location__, name="HARM_INT", &
1710 description="integrator scheme for integrating the harmonic bead springs.", &
1711 usage="HARM_INT (NUMERIC|EXACT)", &
1712 default_i_val=integrate_numeric, &
1713 enum_c_vals=s2a("NUMERIC", "EXACT"), &
1714 enum_i_vals=[integrate_numeric, integrate_exact])
1715 CALL section_add_keyword(section, keyword)
1716 CALL keyword_release(keyword)
1717 CALL keyword_create(keyword, __location__, name="nrespa", &
1718 description="number of respa steps for the bead for each md step", &
1719 repeats=.false., default_i_val=5)
1720 CALL section_add_keyword(section, keyword)
1721 CALL keyword_release(keyword)
1722
1723 CALL keyword_create(keyword, __location__, name="transformation", &
1724 description="Specifies the coordinate transformation to use", &
1725 usage="TRANSFORMATION (NORMAL|STAGE)", &
1726 default_i_val=transformation_normal, &
1727 enum_c_vals=s2a("NORMAL", "STAGE"), &
1729
1730 CALL section_add_keyword(section, keyword)
1731 CALL keyword_release(keyword)
1732 CALL keyword_create(keyword, __location__, name="propagator", &
1733 description="Specifies the real time propagator to use", &
1734 usage="PROPAGATOR (PIMD|RPMD|CMD)", &
1735 default_i_val=propagator_pimd, &
1736 enum_c_vals=s2a("PIMD", "RPMD", "CMD"), &
1738 CALL section_add_keyword(section, keyword)
1739 CALL keyword_release(keyword)
1740 CALL keyword_create(keyword, __location__, name="FIX_CENTROID_POS", &
1741 description="Propagate all DOF but the centroid - "// &
1742 "useful for equilibration of the non-centroid modes "// &
1743 "(activated only if TRANSFORMATION==NORMAL)", &
1744 repeats=.false., default_l_val=.false., &
1745 lone_keyword_l_val=.true.)
1746 CALL section_add_keyword(section, keyword)
1747 CALL keyword_release(keyword)
1748
1749 NULLIFY (subsection, subsubsection)
1750 CALL section_create(subsection, __location__, name="NORMALMODE", &
1751 description="Controls the normal mode transformation", &
1752 n_keywords=3, n_subsections=0, repeats=.false.)
1753 CALL keyword_create(keyword, __location__, name="Q_CENTROID", &
1754 description="Value of the thermostat mass of centroid degree of freedom", &
1755 repeats=.false., default_r_val=-1.0_dp)
1756 CALL section_add_keyword(subsection, keyword)
1757 CALL keyword_release(keyword)
1758 CALL keyword_create(keyword, __location__, name="Q_BEAD", &
1759 description="Value of the thermostat mass of non-centroid degrees of freedom", &
1760 repeats=.false., default_r_val=-1.0_dp)
1761 CALL section_add_keyword(subsection, keyword)
1762 CALL keyword_release(keyword)
1763 CALL keyword_create(keyword, __location__, name="MODEFACTOR", &
1764 description="mass scale factor for non-centroid degrees of freedom", &
1765 repeats=.false., default_r_val=1.0_dp)
1766 CALL section_add_keyword(subsection, keyword)
1767 CALL keyword_release(keyword)
1768 CALL keyword_create(keyword, __location__, name="GAMMA", &
1769 description="mass scale factor for non-centroid degrees of freedom, &
1770& naming convention according to Witt, 2008, <https://doi.org/10.1063/1.3125009>.", &
1771 repeats=.false., default_r_val=8.0_dp)
1772 CALL section_add_keyword(subsection, keyword)
1773 CALL keyword_release(keyword)
1774
1775 CALL section_add_subsection(section, subsection)
1776 CALL section_release(subsection)
1777
1778 CALL section_create(subsection, __location__, name="staging", &
1779 description="The section that controls the staging transformation", &
1780 n_keywords=2, n_subsections=0, repeats=.false.)
1781 CALL keyword_create(keyword, __location__, name="j", &
1782 description="Value of the j parameter for the staging transformation", &
1783 repeats=.false., default_i_val=2)
1784 CALL section_add_keyword(subsection, keyword)
1785 CALL keyword_release(keyword)
1786 CALL keyword_create(keyword, __location__, name="Q_END", &
1787 description="Value of the nose-hoover mass for the endbead (Q_end)", &
1788 repeats=.false., default_i_val=2)
1789 CALL section_add_keyword(subsection, keyword)
1790 CALL keyword_release(keyword)
1791 CALL section_add_subsection(section, subsection)
1792 CALL section_release(subsection)
1793
1794 CALL section_create(subsection, __location__, name="BEADS", &
1795 description="Sets positions and velocities of the beads", &
1796 n_keywords=0, n_subsections=2, &
1797 repeats=.false.)
1798 CALL create_coord_section(subsubsection, "BEADS")
1799 CALL section_add_subsection(subsection, subsubsection)
1800 CALL section_release(subsubsection)
1801 CALL create_velocity_section(subsubsection, "BEADS")
1802 CALL section_add_subsection(subsection, subsubsection)
1803 CALL section_release(subsubsection)
1804 CALL section_add_subsection(section, subsection)
1805 CALL section_release(subsection)
1806
1807 CALL section_create(subsection, __location__, name="NOSE", &
1808 description="Controls the Nose-Hoover thermostats", &
1809 n_keywords=1, n_subsections=2, &
1810 repeats=.false.)
1811 CALL keyword_create(keyword, __location__, name="nnos", &
1812 description="length of nose-hoover chain. 0 means no thermostat", &
1813 repeats=.false., default_i_val=2)
1814 CALL section_add_keyword(subsection, keyword)
1815 CALL keyword_release(keyword)
1816 CALL create_coord_section(subsubsection, "NOSE")
1817 CALL section_add_subsection(subsection, subsubsection)
1818 CALL section_release(subsubsection)
1819 CALL create_velocity_section(subsubsection, "NOSE")
1820 CALL section_add_subsection(subsection, subsubsection)
1821 CALL section_release(subsubsection)
1822 CALL section_add_subsection(section, subsection)
1823 CALL section_release(subsection)
1824
1825 CALL create_gle_section(subsection)
1826 CALL section_add_subsection(section, subsection)
1827 CALL section_release(subsection)
1828
1829 CALL section_create(subsection, __location__, name="PILE", &
1830 description="Controls the PI Langevin Equation thermostat."// &
1831 " Needs the exact harmonic integrator."// &
1832 " May lead to unphysical motions if constraint e.g. FIXED_ATOMS, is applied."// &
1833 " RESTART_HELIUM section has to be .FALSE. when restarting the PIGLET job.", &
1834 citations=[ceriotti2010], &
1835 n_keywords=3, n_subsections=1, &
1836 repeats=.false.)
1837 CALL create_rng_section(subsubsection)
1838 CALL section_add_subsection(subsection, subsubsection)
1839 CALL section_release(subsubsection)
1840 CALL keyword_create(keyword, __location__, name="TAU", &
1841 description="Time constant for centroid motion. "// &
1842 "If zero or negative the centroid is not thermostated.", &
1843 usage="TAU {real}", type_of_var=real_t, &
1844 unit_str="fs", n_var=1, default_r_val=1000.0_dp)
1845 CALL section_add_keyword(subsection, keyword)
1846 CALL keyword_release(keyword)
1847 CALL keyword_create(keyword, __location__, name="LAMBDA", &
1848 description="Scaling of friction to mode coupling", &
1849 usage="LAMBDA {real}", type_of_var=real_t, &
1850 n_var=1, default_r_val=0.5_dp)
1851 CALL section_add_keyword(subsection, keyword)
1852 CALL keyword_release(keyword)
1853 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1854 description="Thermostat energy for conserved quantity. "// &
1855 "Only useful in restart files.", &
1856 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1857 n_var=1, default_r_val=0.0_dp)
1858 CALL section_add_keyword(subsection, keyword)
1859 CALL keyword_release(keyword)
1860 CALL section_add_subsection(section, subsection)
1861 CALL section_release(subsection)
1862
1863 CALL section_create(subsection, __location__, name="PIGLET", &
1864 description="Controls the PI Generalized Langevin Equation thermostat."// &
1865 " Needs the exact harmonic integrator", &
1866 citations=[ceriotti2012], &
1867 n_keywords=4, n_subsections=2, &
1868 repeats=.false.)
1869 CALL create_rng_section(subsubsection)
1870 CALL section_add_subsection(subsection, subsubsection)
1871 CALL section_release(subsubsection)
1872 CALL section_create(subsubsection, __location__, name="EXTRA_DOF", &
1873 description="Additional degrees of freedom to ensure Markovian Dynamics.", &
1874 n_keywords=1, n_subsections=0, repeats=.false.)
1875 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1876 description="Restart values for additional degrees of freedom" &
1877 //" (only for restarts, do not set explicitly)", &
1878 repeats=.false., &
1879 type_of_var=real_t, n_var=-1)
1880 CALL section_add_keyword(subsubsection, keyword)
1881 CALL keyword_release(keyword)
1882 CALL section_add_subsection(subsection, subsubsection)
1883 CALL section_release(subsubsection)
1884 CALL keyword_create(keyword, __location__, name="NEXTRA_DOF", &
1885 description="Number of extra degrees of freedom to ensure markovian dynamics", &
1886 repeats=.false., default_i_val=8)
1887 CALL section_add_keyword(subsection, keyword)
1888 CALL keyword_release(keyword)
1889 CALL keyword_create(keyword, __location__, name="MATRICES_FILE_NAME", &
1890 description="Filename containig the raw matrices from "// &
1891 "<https://gle4md.org/index.html?page=matrix>.", &
1892 repeats=.false., default_lc_val="PIGLET.MAT")
1893 CALL section_add_keyword(subsection, keyword)
1894 CALL keyword_release(keyword)
1895 CALL keyword_create(keyword, __location__, name="SMATRIX_INIT", &
1896 description="Select algorithm to initialize piglet S-matrices", &
1897 usage="SMATRIX_INIT (CHOLESKY|DIAGONAL)", &
1898 default_i_val=matrix_init_cholesky, &
1899 enum_c_vals=s2a("CHOLESKY", "DIAGONAL"), &
1901 CALL section_add_keyword(subsection, keyword)
1902 CALL keyword_release(keyword)
1903 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1904 description="Thermostat energy for conserved quantity. "// &
1905 "Only useful in restart files.", &
1906 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1907 n_var=1, default_r_val=0.0_dp)
1908 CALL section_add_keyword(subsection, keyword)
1909 CALL keyword_release(keyword)
1910 CALL section_add_subsection(section, subsection)
1911 CALL section_release(subsection)
1912
1913 CALL section_create(subsection, __location__, name="QTB", &
1914 description="Controls the QTB-PILE thermostat."// &
1915 " Needs the exact harmonic integrator", &
1916 citations=[brieuc2016], &
1917 n_keywords=7, n_subsections=1, &
1918 repeats=.false.)
1919 CALL create_rng_section(subsubsection)
1920 CALL section_add_subsection(subsection, subsubsection)
1921 CALL section_release(subsubsection)
1922 CALL keyword_create(keyword, __location__, name="TAU", &
1923 description="Time constant for centroid motion. ", &
1924 usage="TAU {real}", type_of_var=real_t, &
1925 unit_str="fs", n_var=1, default_r_val=1000.0_dp)
1926 CALL section_add_keyword(subsection, keyword)
1927 CALL keyword_release(keyword)
1928 CALL keyword_create(keyword, __location__, name="LAMBDA", &
1929 description="Scaling of friction to ring polymer NM freq.", &
1930 usage="LAMBDA {real}", type_of_var=real_t, &
1931 n_var=1, default_r_val=0.5_dp)
1932 CALL section_add_keyword(subsection, keyword)
1933 CALL keyword_release(keyword)
1934 CALL keyword_create(keyword, __location__, name="FP", &
1935 description="Defines which version to use "// &
1936 "0: f_P^(0), 1: f_P^(1)", &
1937 usage="FP {integer}", type_of_var=integer_t, &
1938 n_var=1, default_i_val=1)
1939 CALL section_add_keyword(subsection, keyword)
1940 CALL keyword_release(keyword)
1941 CALL keyword_create(keyword, __location__, name="TAUCUT", &
1942 description="Inverse of cutoff freq. for the centroid mode", &
1943 usage="TAUCUT {real}", type_of_var=real_t, &
1944 unit_str="fs", n_var=1, default_r_val=0.5_dp)
1945 CALL section_add_keyword(subsection, keyword)
1946 CALL keyword_release(keyword)
1947 CALL keyword_create(keyword, __location__, name="LAMBCUT", &
1948 description="Scaling of cutoff freq. to ring polymer NM freq.", &
1949 usage="LAMBCUT {real}", type_of_var=real_t, &
1950 n_var=1, default_r_val=2.0_dp)
1951 CALL section_add_keyword(subsection, keyword)
1952 CALL keyword_release(keyword)
1953 CALL keyword_create(keyword, __location__, name="NF", &
1954 description="Number of points used for the convolution product.", &
1955 usage="NF {integer}", type_of_var=integer_t, &
1956 n_var=1, default_i_val=128)
1957 CALL section_add_keyword(subsection, keyword)
1958 CALL keyword_release(keyword)
1959 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1960 description="Thermostat energy for conserved quantity. "// &
1961 "Only useful in restart files.", &
1962 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1963 n_var=1, default_r_val=0.0_dp)
1964 CALL section_add_keyword(subsection, keyword)
1965 CALL keyword_release(keyword)
1966 CALL section_add_subsection(section, subsection)
1967 CALL section_release(subsection)
1968
1969 CALL section_create(subsection, __location__, name="INIT", &
1970 description="Controls the initialization if the beads are not present", &
1971 repeats=.false.)
1972
1973 CALL keyword_create(keyword, __location__, name="LEVY_POS_SAMPLE", &
1974 description="Sample bead positions assuming free particle "// &
1975 "behavior (performs a Levy random walk of length P around "// &
1976 "the classical position of each atom at the physical "// &
1977 "temperature defined in PINT%TEMP)", &
1978 repeats=.false., default_l_val=.false., &
1979 lone_keyword_l_val=.true.)
1980 CALL section_add_keyword(subsection, keyword)
1981 CALL keyword_release(keyword)
1982 CALL keyword_create(keyword, __location__, name="LEVY_CORRELATED", &
1983 description="Use the same Levy path for all atoms, though "// &
1984 "with mass-dependent variances (might help at very low T)", &
1985 repeats=.false., default_l_val=.false., &
1986 lone_keyword_l_val=.true.)
1987 CALL section_add_keyword(subsection, keyword)
1988 CALL keyword_release(keyword)
1989 CALL keyword_create(keyword, __location__, name="LEVY_TEMP_FACTOR", &
1990 description="Multiplicative correction factor for the "// &
1991 "temperature at which the Levy walk is performed "// &
1992 "(correction is due to the interactions that modify "// &
1993 "the spread of a free particle)", &
1994 repeats=.false., default_r_val=1.0_dp)
1995 CALL section_add_keyword(subsection, keyword)
1996 CALL keyword_release(keyword)
1997 CALL keyword_create(keyword, __location__, name="LEVY_SEED", &
1998 description="Initial seed for the (pseudo)random number "// &
1999 "generator that controls Levy walk for bead positions.", &
2000 usage="LEVY_SEED <INTEGER>", default_i_val=1234, &
2001 repeats=.false.)
2002 CALL section_add_keyword(subsection, keyword)
2003 CALL keyword_release(keyword)
2004 CALL keyword_create(keyword, __location__, name="THERMOSTAT_SEED", &
2005 description="Initial seed for the (pseudo)random number "// &
2006 "generator that controls the PILE and PIGLET thermostats.", &
2007 usage="THERMOSTAT_SEED <INTEGER>", default_i_val=12345, &
2008 repeats=.false.)
2009 CALL section_add_keyword(subsection, keyword)
2010 CALL keyword_release(keyword)
2011 CALL keyword_create(keyword, __location__, name="RANDOMIZE_POS", &
2012 description="add gaussian noise to the positions of the beads", &
2013 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2014 CALL section_add_keyword(subsection, keyword)
2015 CALL keyword_release(keyword)
2016
2017 CALL keyword_create(keyword, __location__, name="CENTROID_SPEED", &
2018 description="adds random velocity component to the centroid modes "// &
2019 "(useful to correct for the averaging out of the speed of various beads)", &
2020 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2021 CALL section_add_keyword(subsection, keyword)
2022 CALL keyword_release(keyword)
2023
2024 CALL keyword_create(keyword, __location__, name="VELOCITY_QUENCH", &
2025 description="set the initial velocities to zero", &
2026 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2027 CALL section_add_keyword(subsection, keyword)
2028 CALL keyword_release(keyword)
2029 CALL keyword_create(keyword, __location__, name="VELOCITY_SCALE", &
2030 description="scale initial velocities to the temperature given in MOTION%PINT%TEMP", &
2031 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2032 CALL section_add_keyword(subsection, keyword)
2033 CALL keyword_release(keyword)
2034
2035 CALL section_add_subsection(section, subsection)
2036 CALL section_release(subsection)
2037
2038 CALL create_helium_section(subsection)
2039 CALL section_add_subsection(section, subsection)
2040 CALL section_release(subsection)
2041
2042 CALL section_create(subsection, __location__, name="PRINT", &
2043 description="Controls the path integral-specific output", &
2044 n_keywords=2, n_subsections=0, repeats=.false.)
2045
2046 NULLIFY (print_key)
2047
2048 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
2049 description="Controls the output of the path integral energies", &
2050 print_level=low_print_level, common_iter_levels=1)
2051 CALL section_add_subsection(subsection, print_key)
2052 CALL section_release(print_key)
2053
2054 CALL cp_print_key_section_create(print_key, __location__, "ACTION", &
2055 description="Controls the output of the path integral action", &
2056 print_level=medium_print_level, common_iter_levels=1)
2057 CALL section_add_subsection(subsection, print_key)
2058 CALL section_release(print_key)
2059
2060 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_POS", &
2061 description="Controls the output of the centroid's position", &
2062 unit_str="angstrom", &
2063 print_level=low_print_level, common_iter_levels=1)
2064 CALL add_format_keyword(keyword, print_key, pos=.true., &
2065 description="Output file format for the positions of centroid")
2066 CALL section_add_subsection(subsection, print_key)
2067 CALL section_release(print_key)
2068
2069 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_VEL", &
2070 description="Controls the output of the centroid's velocity", &
2071 unit_str="bohr*au_t^-1", &
2072 print_level=low_print_level, common_iter_levels=1)
2073 CALL add_format_keyword(keyword, print_key, pos=.false., &
2074 description="Output file format for the velocity of centroid")
2075 CALL section_add_subsection(subsection, print_key)
2076 CALL section_release(print_key)
2077
2078 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_GYR", &
2079 description="Controls the output of the centroid's radii of gyration", &
2080 unit_str="angstrom", &
2081 print_level=low_print_level, common_iter_levels=1)
2082 CALL section_add_subsection(subsection, print_key)
2083 CALL section_release(print_key)
2084
2085 CALL cp_print_key_section_create(print_key, __location__, "COM", &
2086 description="Controls the output of the center of mass", &
2087 print_level=high_print_level, common_iter_levels=1)
2088 CALL section_add_subsection(subsection, print_key)
2089 CALL section_release(print_key)
2090
2091 CALL keyword_create(keyword, __location__, name="IMAGINARY_TIME_STRIDE", &
2092 description="Prints only every nth bead trajectory", &
2093 repeats=.false., default_i_val=1)
2094 CALL section_add_keyword(subsection, keyword)
2095 CALL keyword_release(keyword)
2096
2097 CALL section_add_subsection(section, subsection)
2098 CALL section_release(subsection)
2099
2100 END SUBROUTINE create_pint_section
2101
2102 ! ***************************************************************************
2103 !> \brief Create the input section for superfluid helium solvent.
2104 !> \author Lukasz Walewski
2105 ! ***************************************************************************
2106! **************************************************************************************************
2107!> \brief ...
2108!> \param section ...
2109! **************************************************************************************************
2110 SUBROUTINE create_helium_section(section)
2111 TYPE(section_type), POINTER :: section
2112
2113 TYPE(keyword_type), POINTER :: keyword
2114 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
2115
2116 cpassert(.NOT. ASSOCIATED(section))
2117
2118 CALL section_create(section, __location__, name="HELIUM", &
2119 description="The section that controls optional helium solvent"// &
2120 " environment (highly experimental, not for general use yet)", &
2121 n_keywords=31, n_subsections=11, repeats=.false.)
2122
2123 NULLIFY (keyword)
2124 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2125 description="Whether or not to actually use this section", &
2126 usage="silent", default_l_val=.false., lone_keyword_l_val=.true.)
2127 CALL section_add_keyword(section, keyword)
2128 CALL keyword_release(keyword)
2129
2130 CALL keyword_create(keyword, __location__, name="HELIUM_ONLY", &
2131 description="Simulate helium solvent only, "// &
2132 "disregard solute entirely", &
2133 repeats=.false., default_l_val=.false., &
2134 lone_keyword_l_val=.true.)
2135 CALL section_add_keyword(section, keyword)
2136 CALL keyword_release(keyword)
2137
2138 CALL keyword_create(keyword, __location__, name="INTERACTION_POT_SCAN", &
2139 description="Scan solute-helium interaction potential, "// &
2140 "cubefile parameters set in subsection RHO", &
2141 repeats=.false., default_l_val=.false., &
2142 lone_keyword_l_val=.true.)
2143 CALL section_add_keyword(section, keyword)
2144 CALL keyword_release(keyword)
2145
2146 CALL keyword_create(keyword, __location__, name="NUM_ENV", &
2147 description="Number of independent helium environments", &
2148 repeats=.false., default_i_val=1)
2149 CALL section_add_keyword(section, keyword)
2150 CALL keyword_release(keyword)
2151
2152 CALL keyword_create(keyword, __location__, name="POTENTIAL_FILE_NAME", &
2153 description="Name of the Helium interaction potential file", &
2154 repeats=.false., default_lc_val="HELIUM.POT")
2155 CALL section_add_keyword(section, keyword)
2156 CALL keyword_release(keyword)
2157
2158 CALL keyword_create(keyword, __location__, name="GET_FORCES", &
2159 description="Get average MC forces or last MC forces to propagate MD", &
2160 usage="GET_FORCES (AVERAGE|LAST)", &
2161 default_i_val=helium_forces_average, &
2162 enum_c_vals=s2a("AVERAGE", "LAST"), &
2164 CALL section_add_keyword(section, keyword)
2165 CALL keyword_release(keyword)
2166
2167 CALL keyword_create(keyword, __location__, name="SOLUTE_INTERACTION", &
2168 description="Interaction potential between helium and the solute", &
2169 usage="SOLUTE_INTERACTION (NONE | MWATER | NNP)", &
2170 default_i_val=helium_solute_intpot_none, &
2171 enum_c_vals=s2a("NONE", "MWATER", "NNP"), &
2172 enum_i_vals=[ &
2176 enum_desc=s2a( &
2177 "No interaction with solute", &
2178 "Test interaction with wrong Water", &
2179 "Interaction with NNP"))
2180 CALL section_add_keyword(section, keyword)
2181 CALL keyword_release(keyword)
2182
2183 CALL keyword_create(keyword, __location__, name="NATOMS", &
2184 description="Number of helium atoms", &
2185 repeats=.false., default_i_val=64)
2186 CALL section_add_keyword(section, keyword)
2187 CALL keyword_release(keyword)
2188
2189 CALL keyword_create(keyword, __location__, name="NBEADS", &
2190 description="Number of helium path integral beads", &
2191 repeats=.false., default_i_val=25)
2192 CALL section_add_keyword(section, keyword)
2193 CALL keyword_release(keyword)
2194
2195 CALL keyword_create(keyword, __location__, name="RNG_SEED", &
2196 description="Initial seed for the (pseudo)random number "// &
2197 "generator that controls helium coordinate generation and propagation.", &
2198 usage="RNG_SEED <INTEGER>", default_i_val=12345, &
2199 repeats=.false.)
2200 CALL section_add_keyword(section, keyword)
2201 CALL keyword_release(keyword)
2202
2203 CALL keyword_create(keyword, __location__, name="N_INNER", &
2204 variants=s2a("INOROT"), &
2205 description="Number of MC iterations at the same time slice(s) "// &
2206 "(number of inner MC loop iterations)", &
2207 repeats=.false., default_i_val=6600)
2208 CALL section_add_keyword(section, keyword)
2209 CALL keyword_release(keyword)
2210
2211 CALL keyword_create(keyword, __location__, name="N_OUTER", &
2212 variants=s2a("IROT"), &
2213 description="how often to reselect the time slice(s) to work on "// &
2214 "(number of outer MC loop iterations)", &
2215 repeats=.false., default_i_val=300)
2216 CALL section_add_keyword(section, keyword)
2217 CALL keyword_release(keyword)
2218
2219 CALL keyword_create(keyword, __location__, name="SAMPLING_METHOD", &
2220 description="Choose between Ceperley or the worm algorithm", &
2221 usage="SAMPLING_METHOD (CEPERLEY|WORM)", &
2222 default_i_val=helium_sampling_ceperley, &
2223 enum_c_vals=s2a("CEPERLEY", "WORM"), &
2225 CALL section_add_keyword(section, keyword)
2226 CALL keyword_release(keyword)
2227
2228 CALL keyword_create(keyword, __location__, name="COORD_INIT_TEMP", &
2229 description="Temperature for thermal gaussian initialization of the helium."// &
2230 " Negative values correspond to a hot start.", &
2231 default_r_val=cp_unit_to_cp2k(300._dp, "K"), &
2232 unit_str="K")
2233 CALL section_add_keyword(section, keyword)
2234 CALL keyword_release(keyword)
2235
2236 CALL keyword_create(keyword, __location__, name="SOLUTE_RADIUS", &
2237 description="Radius of the solute molecule for prevention of"// &
2238 " coordinate collision during initialization", &
2239 default_r_val=cp_unit_to_cp2k(0.0_dp, "angstrom"), &
2240 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2241 CALL section_add_keyword(section, keyword)
2242 CALL keyword_release(keyword)
2243
2244 ! Helium-solute interaction NNP
2245 NULLIFY (subsection)
2246 CALL section_create(subsection, __location__, name="NNP", &
2247 description="This section contains all information to run an helium-solute "// &
2248 "interaction Neural Network Potential (NNP) calculation.", &
2249 n_keywords=2, n_subsections=3, repeats=.false.)
2250
2251 CALL keyword_create(keyword, __location__, name="NNP_INPUT_FILE_NAME", &
2252 description="File containing the input information for the setup "// &
2253 "of the NNP (n2p2/RuNNer format). ", &
2254 repeats=.false., default_lc_val="input.nn")
2255 CALL section_add_keyword(subsection, keyword)
2256 CALL keyword_release(keyword)
2257
2258 CALL keyword_create(keyword, __location__, name="SCALE_FILE_NAME", &
2259 description="File containing the scaling information for the symmetry "// &
2260 "functions of the NNP. ", &
2261 repeats=.false., default_lc_val="scaling.data")
2262 CALL section_add_keyword(subsection, keyword)
2263 CALL keyword_release(keyword)
2264
2265 NULLIFY (subsubsection)
2266 CALL section_create(subsubsection, __location__, name="SR_CUTOFF", &
2267 description="Section for failsafe short range cutoffs for the NNPs, "// &
2268 "if the distance between solvent and specified solute element becomes "// &
2269 "smaller than the given cutoff, an artifical repulsive potential is "// &
2270 "introduced. Note this is only meant to prevent such configurations, "// &
2271 "not to physically sample them.", &
2272 n_keywords=2, n_subsections=0, repeats=.true.)
2273
2274 CALL keyword_create(keyword, __location__, name="ELEMENT", &
2275 description="Solute element for which the short range cutoff is in effect", &
2276 repeats=.false., default_c_val="none")
2277 CALL section_add_keyword(subsubsection, keyword)
2278 CALL keyword_release(keyword)
2279
2280 CALL keyword_create(keyword, __location__, name="RADIUS", &
2281 description="Short range cutoff in Angstrom, below this cutoff, the energy "// &
2282 "is replaced by a sizable positive value plus a 1/r**2 term to guide particles "// &
2283 "away from each other.", &
2284 default_r_val=cp_unit_to_cp2k(0.0_dp, "angstrom"), &
2285 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2286 CALL section_add_keyword(subsubsection, keyword)
2287 CALL keyword_release(keyword)
2288 CALL section_add_subsection(subsection, subsubsection)
2289 CALL section_release(subsubsection)
2290
2291 NULLIFY (subsubsection)
2292 CALL section_create(subsubsection, __location__, name="MODEL", &
2293 description="Section for a single NNP model. If this section is repeated, "// &
2294 "a committee model (C-NNP)is used where the NNP members share the same "// &
2295 "symmetry functions. ", &
2296 n_keywords=1, n_subsections=0, repeats=.true.)
2297
2298 CALL keyword_create(keyword, __location__, name="WEIGHTS", &
2299 description="File containing the weights for the artificial neural "// &
2300 "networks of the NNP. The specified name is extended by .XXX.data ", &
2301 repeats=.false., default_lc_val="weights")
2302 CALL section_add_keyword(subsubsection, keyword)
2303 CALL keyword_release(keyword)
2304 CALL section_add_subsection(subsection, subsubsection)
2305 CALL section_release(subsubsection)
2306
2307 ! Create the PRINT subsection
2308 NULLIFY (subsubsection)
2309 CALL section_create(subsubsection, __location__, name="PRINT", &
2310 description="Section of possible print options in NNP code.", &
2311 n_keywords=0, n_subsections=3, repeats=.false.)
2312 NULLIFY (print_key, keyword)
2313
2314 CALL cp_print_key_section_create(print_key, __location__, "ENERGIES", &
2315 description="Controls the printing of the NNP energies.", &
2316 print_level=medium_print_level, common_iter_levels=1)
2317 CALL section_add_subsection(subsubsection, print_key)
2318 CALL section_release(print_key)
2319
2320 CALL cp_print_key_section_create(print_key, __location__, "FORCES_SIGMA", &
2321 description="Controls the printing of the STD per atom of the NNP forces.", &
2322 print_level=medium_print_level, common_iter_levels=1)
2323 CALL section_add_subsection(subsubsection, print_key)
2324 CALL section_release(print_key)
2325
2326 CALL cp_print_key_section_create(print_key, __location__, "EXTRAPOLATION", &
2327 description="If activated, output structures with extrapolation "// &
2328 "warning in xyz-format", &
2329 print_level=medium_print_level, common_iter_levels=1)
2330 CALL section_add_subsection(subsubsection, print_key)
2331 CALL section_release(print_key)
2332 CALL section_add_subsection(subsection, subsubsection)
2333 CALL section_release(subsubsection)
2334
2335 CALL section_add_subsection(section, subsection)
2336 CALL section_release(subsection) ! release NNP subsection
2337
2338 ! Ceperley's sampling algorithm
2339 NULLIFY (subsection)
2340 CALL section_create(subsection, __location__, name="CEPERLEY", &
2341 description="Enables sampling with Ceperley's algorithm", &
2342 n_keywords=2, n_subsections=1, repeats=.false.)
2343
2344 CALL keyword_create(keyword, __location__, name="BISECTION", &
2345 description="how many time slices to change at once (+1). "// &
2346 "Must be a power of 2 currently", &
2347 repeats=.false., default_i_val=8)
2348 CALL section_add_keyword(subsection, keyword)
2349 CALL keyword_release(keyword)
2350
2351 CALL keyword_create(keyword, __location__, name="MAX_PERM_CYCLE", &
2352 description="how large cyclic permutations to try", &
2353 repeats=.false., default_i_val=6)
2354 CALL section_add_keyword(subsection, keyword)
2355 CALL keyword_release(keyword)
2356
2357 NULLIFY (subsubsection)
2358 CALL section_create(subsubsection, __location__, name="M-SAMPLING", &
2359 description="Permutation cycle length sampling settings", &
2360 n_keywords=3, n_subsections=0, repeats=.false.)
2361 CALL keyword_create(keyword, __location__, name="DISTRIBUTION-TYPE", &
2362 description="Distribution from which the cycle length m is sampled", &
2363 usage="DISTRIBUTION-TYPE (SINGLEV|UNIFORM|LINEAR|QUADRATIC|EXPONENTIAL|GAUSSIAN)", &
2364 default_i_val=helium_mdist_uniform, &
2365 enum_c_vals=s2a( &
2366 "SINGLEV", &
2367 "UNIFORM", &
2368 "LINEAR", &
2369 "QUADRATIC", &
2370 "EXPONENTIAL", &
2371 "GAUSSIAN"), &
2372 enum_i_vals=[ &
2379 CALL section_add_keyword(subsubsection, keyword)
2380 CALL keyword_release(keyword)
2381 CALL keyword_create(keyword, __location__, name="M-VALUE", &
2382 description="Value of m treated in a special way "// &
2383 "(specific behavior depends on the distribution type chosen)", &
2384 repeats=.false., &
2385 default_i_val=1)
2386 CALL section_add_keyword(subsubsection, keyword)
2387 CALL keyword_release(keyword)
2388 CALL keyword_create(keyword, __location__, name="M-RATIO", &
2389 description="Probability ratio betw M-VALUE and other cycle lengths", &
2390 repeats=.false., &
2391 default_r_val=1.0_dp)
2392 CALL section_add_keyword(subsubsection, keyword)
2393 CALL keyword_release(keyword)
2394 CALL section_add_subsection(subsection, subsubsection)
2395 CALL section_release(subsubsection)
2396 CALL section_add_subsection(section, subsection)
2397 CALL section_release(subsection) ! release CEPERLEY subsection
2398
2399! worm algorithm parameters:
2400 NULLIFY (subsection)
2401 CALL section_create(subsection, __location__, name="WORM", &
2402 description="Enables sampling via the canonical worm algorithm adapted from Bonisegni", &
2403 n_keywords=12, n_subsections=0, repeats=.false.)
2404
2405 CALL keyword_create(keyword, __location__, name="CENTROID_DRMAX", &
2406 description="Maximum displacement allowed for the centroid moves", &
2407 repeats=.false., default_r_val=0.5_dp)
2408 CALL section_add_keyword(subsection, keyword)
2409 CALL keyword_release(keyword)
2410
2411 CALL keyword_create(keyword, __location__, name="STAGING_L", &
2412 description="From 2 up to max. L-1 beads will be moved", &
2413 repeats=.false., default_i_val=5)
2414 CALL section_add_keyword(subsection, keyword)
2415 CALL keyword_release(keyword)
2416
2417 CALL keyword_create(keyword, __location__, name="OPEN_CLOSE_SCALE", &
2418 description="Open/Close acceptance adjustment parameter", &
2419 repeats=.false., default_r_val=0.01_dp)
2420 CALL section_add_keyword(subsection, keyword)
2421 CALL keyword_release(keyword)
2422
2423 CALL keyword_create(keyword, __location__, name="ALLOW_OPEN", &
2424 description="Enable bosonic exchange sampling", &
2425 repeats=.false., default_l_val=.true.)
2426 CALL section_add_keyword(subsection, keyword)
2427 CALL keyword_release(keyword)
2428
2429 CALL keyword_create(keyword, __location__, name="MAX_OPEN_CYCLES", &
2430 description="If > 0 then reset positions and permutations to the previous closed &
2431 & state if staying more than this amount of MC cycles in open state to avoid staying &
2432 & trapped in open state for too long. Use with caution as it can potentially introduce &
2433 & a bias in the sampling.", &
2434 repeats=.false., default_i_val=0)
2435 CALL section_add_keyword(subsection, keyword)
2436 CALL keyword_release(keyword)
2437
2438 CALL keyword_create(keyword, __location__, name="SHOW_STATISTICS", &
2439 description="Show sampling statistics in output", &
2440 repeats=.false., default_l_val=.true.)
2441 CALL section_add_keyword(subsection, keyword)
2442 CALL keyword_release(keyword)
2443
2444 CALL keyword_create(keyword, __location__, name="CENTROID_WEIGHT", &
2445 description="Absolute weight of the centroid move", &
2446 repeats=.false., default_i_val=10)
2447 CALL section_add_keyword(subsection, keyword)
2448 CALL keyword_release(keyword)
2449
2450 CALL keyword_create(keyword, __location__, name="STAGING_WEIGHT", &
2451 description="Absolute weight of the staging move", &
2452 repeats=.false., default_i_val=30)
2453 CALL section_add_keyword(subsection, keyword)
2454 CALL keyword_release(keyword)
2455
2456 CALL keyword_create(keyword, __location__, name="OPEN_CLOSE_WEIGHT", &
2457 description="Absolute weight of the open/close move", &
2458 repeats=.false., default_i_val=10)
2459 CALL section_add_keyword(subsection, keyword)
2460 CALL keyword_release(keyword)
2461
2462 CALL keyword_create(keyword, __location__, name="HEAD_TAIL_WEIGHT", &
2463 description="Absolute weight of the head/tail moves (both)", &
2464 repeats=.false., default_i_val=10)
2465 CALL section_add_keyword(subsection, keyword)
2466 CALL keyword_release(keyword)
2467
2468 CALL keyword_create(keyword, __location__, name="CRAWL_WEIGHT", &
2469 description="Absolute weight of the crawl bwd/fwd moves (both)", &
2470 repeats=.false., default_i_val=10)
2471 CALL section_add_keyword(subsection, keyword)
2472 CALL keyword_release(keyword)
2473
2474 CALL keyword_create(keyword, __location__, name="CRAWL_REPETITION", &
2475 description="Number of repeated crawl moves", &
2476 repeats=.false., default_i_val=4)
2477 CALL section_add_keyword(subsection, keyword)
2478 CALL keyword_release(keyword)
2479
2480 CALL keyword_create(keyword, __location__, name="SWAP_WEIGHT", &
2481 description="Absolute weight of the crawl move", &
2482 repeats=.false., default_i_val=10)
2483 CALL section_add_keyword(subsection, keyword)
2484 CALL keyword_release(keyword)
2485
2486 CALL section_add_subsection(section, subsection)
2487 CALL section_release(subsection) ! release WORM subsection
2488
2489! end of worm parameters
2490
2491 CALL keyword_create(keyword, __location__, name="PERIODIC", &
2492 description="Use periodic boundary conditions for helium", &
2493 repeats=.false., default_l_val=.false.)
2494 CALL section_add_keyword(section, keyword)
2495 CALL keyword_release(keyword)
2496
2497 CALL keyword_create(keyword, __location__, name="CELL_SIZE", &
2498 description="PBC unit cell size (NOTE 1: density, number of atoms"// &
2499 " and volume are interdependent - give only two of them; "// &
2500 "NOTE 2: for small cell sizes specify NATOMS instead)", &
2501 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2502 CALL section_add_keyword(section, keyword)
2503 CALL keyword_release(keyword)
2504
2505 CALL keyword_create(keyword, __location__, name="CELL_SHAPE", &
2506 description="PBC unit cell shape for helium", &
2507 usage="CELL_SHAPE (CUBE|OCTAHEDRON)", &
2508 default_i_val=helium_cell_shape_cube, &
2509 enum_c_vals=s2a("CUBE", "OCTAHEDRON"), &
2511 CALL section_add_keyword(section, keyword)
2512 CALL keyword_release(keyword)
2513
2514 CALL keyword_create(keyword, __location__, name="DROPLET_RADIUS", &
2515 description="Reject a move if any of the new positions does not lie within"// &
2516 " this range from the center of gravity", &
2517 repeats=.false., type_of_var=real_t, default_r_val=huge(1.0_dp), &
2518 unit_str="angstrom")
2519 CALL section_add_keyword(section, keyword)
2520 CALL keyword_release(keyword)
2521
2522 CALL keyword_create(keyword, __location__, name="DENSITY", &
2523 description="trial density of helium for determining the helium "// &
2524 "box size", &
2525 repeats=.false., &
2526 default_r_val=cp_unit_to_cp2k(0.02186_dp, "angstrom^-3"), &
2527 unit_str="angstrom^-3")
2528 CALL section_add_keyword(section, keyword)
2529 CALL keyword_release(keyword)
2530
2531 CALL keyword_create(keyword, __location__, name="PRESAMPLE", &
2532 description="Presample He coordinates before first PIMD step", &
2533 repeats=.false., default_l_val=.false.)
2534 CALL section_add_keyword(section, keyword)
2535 CALL keyword_release(keyword)
2536
2537 CALL section_create(subsection, __location__, name="RDF", &
2538 description="Radial distribution settings", &
2539 n_keywords=5, n_subsections=0, repeats=.false.)
2540
2541 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2542 description="Whether or not to actually calculate this property", &
2543 default_l_val=.false., lone_keyword_l_val=.true.)
2544 CALL section_add_keyword(subsection, keyword)
2545 CALL keyword_release(keyword)
2546
2547 CALL keyword_create(keyword, __location__, name="MAXR", &
2548 description="Maximum RDF range, defaults to unit cell size", &
2549 repeats=.false., type_of_var=real_t, &
2550 unit_str="angstrom")
2551 CALL section_add_keyword(subsection, keyword)
2552 CALL keyword_release(keyword)
2553
2554 CALL keyword_create(keyword, __location__, name="NBIN", &
2555 description="Number of bins", &
2556 repeats=.false., &
2557 default_i_val=250)
2558 CALL section_add_keyword(subsection, keyword)
2559 CALL keyword_release(keyword)
2560
2561 CALL keyword_create(keyword, __location__, name="SOLUTE_HE", &
2562 description="Whether or not to calculate solute-He RDFs (if solute is present)", &
2563 default_l_val=.true., lone_keyword_l_val=.true.)
2564 CALL section_add_keyword(subsection, keyword)
2565 CALL keyword_release(keyword)
2566
2567 CALL keyword_create(keyword, __location__, name="HE_HE", &
2568 description="Whether or not to calculate He-He RDFs", &
2569 default_l_val=.false., lone_keyword_l_val=.true.)
2570 CALL section_add_keyword(subsection, keyword)
2571 CALL keyword_release(keyword)
2572
2573 CALL section_add_subsection(section, subsection)
2574 CALL section_release(subsection)
2575
2576 NULLIFY (subsection)
2577 CALL section_create(subsection, __location__, name="RHO", &
2578 description="Spatial distribution settings", &
2579 n_keywords=10, n_subsections=0, repeats=.false.)
2580 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2581 description="Whether or not to actually calculate densities "// &
2582 "(requires significant amount of memory, depending on the value of NBIN)", &
2583 default_l_val=.false., lone_keyword_l_val=.true.)
2584 CALL section_add_keyword(subsection, keyword)
2585 CALL keyword_release(keyword)
2586 CALL keyword_create(keyword, __location__, name="NBIN", &
2587 description="Number of grid points in each direction for density binning", &
2588 repeats=.false., &
2589 default_i_val=100)
2590 CALL section_add_keyword(subsection, keyword)
2591 CALL keyword_release(keyword)
2592 !
2593 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_WDG", &
2594 description="Density of winding paths "// &
2595 "not shorter than the given length", &
2596 repeats=.false., usage="MIN_CYCLE_LENGTHS_WDG <INT> <INT> .. <INT>", &
2597 type_of_var=integer_t, n_var=-1)
2598 CALL section_add_keyword(subsection, keyword)
2599 CALL keyword_release(keyword)
2600 !
2601 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_NON", &
2602 description="Density of non-winding paths "// &
2603 "not shorter than the given length", &
2604 repeats=.false., usage="MIN_CYCLE_LENGTHS_NON <INT> <INT> .. <INT>", &
2605 type_of_var=integer_t, n_var=-1)
2606 CALL section_add_keyword(subsection, keyword)
2607 CALL keyword_release(keyword)
2608 !
2609 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_ALL", &
2610 description="Density of all paths "// &
2611 "not shorter than the given length", &
2612 repeats=.false., usage="MIN_CYCLE_LENGTHS_ALL <INT> <INT> .. <INT>", &
2613 type_of_var=integer_t, n_var=-1)
2614 CALL section_add_keyword(subsection, keyword)
2615 CALL keyword_release(keyword)
2616 !
2617 CALL keyword_create(keyword, __location__, name="ATOM_NUMBER", &
2618 description="Atom number density", &
2619 repeats=.false., &
2620 type_of_var=logical_t, &
2621 default_l_val=.true., &
2622 lone_keyword_l_val=.true.)
2623 CALL section_add_keyword(subsection, keyword)
2624 CALL keyword_release(keyword)
2625 !
2626 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA_2", &
2627 description="Projected area squared density, A*A(r)", &
2628 repeats=.false., &
2629 type_of_var=logical_t, &
2630 default_l_val=.false., &
2631 lone_keyword_l_val=.true.)
2632 CALL section_add_keyword(subsection, keyword)
2633 CALL keyword_release(keyword)
2634 !
2635 CALL keyword_create(keyword, __location__, name="WINDING_NUMBER_2", &
2636 description="Winding number squared density, W*W(r)", &
2637 repeats=.false., &
2638 type_of_var=logical_t, &
2639 default_l_val=.false., &
2640 lone_keyword_l_val=.true.)
2641 CALL section_add_keyword(subsection, keyword)
2642 CALL keyword_release(keyword)
2643 !
2644 CALL keyword_create(keyword, __location__, name="WINDING_CYCLE_2", &
2645 description="Winding number squared density, W^2(r)", &
2646 repeats=.false., &
2647 type_of_var=logical_t, &
2648 default_l_val=.false., &
2649 lone_keyword_l_val=.true.)
2650 CALL section_add_keyword(subsection, keyword)
2651 CALL keyword_release(keyword)
2652 !
2653 CALL keyword_create(keyword, __location__, name="MOMENT_OF_INERTIA", &
2654 description="Moment of inertia density", &
2655 repeats=.false., &
2656 type_of_var=logical_t, &
2657 default_l_val=.false., &
2658 lone_keyword_l_val=.true.)
2659 CALL section_add_keyword(subsection, keyword)
2660 CALL keyword_release(keyword)
2661
2662 CALL section_add_subsection(section, subsection)
2663 CALL section_release(subsection)
2664 ! end of subsection RHO
2665
2666 CALL create_coord_section(subsection, "HELIUM")
2667 CALL section_add_subsection(section, subsection)
2668 CALL section_release(subsection)
2669
2670 CALL section_create(subsection, __location__, name="PERM", &
2671 description="Permutation state used for restart", &
2672 n_keywords=1, n_subsections=0, repeats=.false.)
2673 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2674 description="Specify particle index permutation for every "// &
2675 "helium atom", repeats=.true., usage="<INT> <INT> .. <INT>", &
2676 type_of_var=integer_t, n_var=-1)
2677 CALL section_add_keyword(subsection, keyword)
2678 CALL keyword_release(keyword)
2679 CALL section_add_subsection(section, subsection)
2680 CALL section_release(subsection)
2681
2682 CALL section_create(subsection, __location__, name="AVERAGES", &
2683 description="Average properties (used for restarts)", &
2684 n_keywords=7, n_subsections=0, repeats=.false.)
2685 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA", &
2686 description="Projected area vector for all environments", &
2687 repeats=.true., usage="PROJECTED_AREA <REAL> <REAL> .. <REAL>", &
2688 type_of_var=real_t, n_var=-1)
2689 CALL section_add_keyword(subsection, keyword)
2690 CALL keyword_release(keyword)
2691 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA_2", &
2692 description="Projected area vector squared for all environments", &
2693 repeats=.true., usage="PROJECTED_AREA_2 <REAL> <REAL> .. <REAL>", &
2694 type_of_var=real_t, n_var=-1)
2695 CALL section_add_keyword(subsection, keyword)
2696 CALL keyword_release(keyword)
2697 CALL keyword_create(keyword, __location__, name="WINDING_NUMBER_2", &
2698 description="Winding number vector squared for all environments", &
2699 repeats=.true., usage="WINDING_NUMBER_2 <REAL> <REAL> .. <REAL>", &
2700 type_of_var=real_t, n_var=-1)
2701 CALL section_add_keyword(subsection, keyword)
2702 CALL keyword_release(keyword)
2703 CALL keyword_create(keyword, __location__, name="MOMENT_OF_INERTIA", &
2704 description="Moment of inertia vector for all environments", &
2705 repeats=.true., usage="MOMENT_OF_INERTIA <REAL> <REAL> .. <REAL>", &
2706 type_of_var=real_t, n_var=-1)
2707 CALL section_add_keyword(subsection, keyword)
2708 CALL keyword_release(keyword)
2709 CALL keyword_create(keyword, __location__, name="RDF", &
2710 description="Radial distributions averaged over all environments", &
2711 repeats=.true., usage="RDF <REAL> <REAL> .. <REAL>", &
2712 type_of_var=real_t, n_var=-1)
2713 CALL section_add_keyword(subsection, keyword)
2714 CALL keyword_release(keyword)
2715 CALL keyword_create(keyword, __location__, name="RHO", &
2716 description="Spatial distributions averaged over all environments", &
2717 repeats=.true., usage="RHO <REAL> <REAL> .. <REAL>", &
2718 type_of_var=real_t, n_var=-1)
2719 CALL section_add_keyword(subsection, keyword)
2720 CALL keyword_release(keyword)
2721 CALL keyword_create(keyword, __location__, name="IWEIGHT", &
2722 description="Weight for the restarted quantities "// &
2723 "(number of MC steps used to calculate the accumulated averages)", &
2724 repeats=.false., &
2725 default_i_val=0)
2726 CALL section_add_keyword(subsection, keyword)
2727 CALL keyword_release(keyword)
2728 CALL section_add_subsection(section, subsection)
2729 CALL section_release(subsection)
2730
2731 CALL section_create(subsection, __location__, name="FORCE", &
2732 description="Forces exerted by the helium on the solute system"// &
2733 " (used for restarts)", &
2734 n_keywords=1, n_subsections=0, repeats=.false.)
2735 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2736 description="Number of real values should be 3 * "// &
2737 "<num_solute_atoms> * <num_solute_beads>", repeats=.true., &
2738 usage="<REAL> <REAL> .. <REAL>", type_of_var=real_t, &
2739 n_var=-1)
2740 CALL section_add_keyword(subsection, keyword)
2741 CALL keyword_release(keyword)
2742 CALL section_add_subsection(section, subsection)
2743 CALL section_release(subsection)
2744
2745 CALL section_create(subsection, __location__, name="RNG_STATE", &
2746 description="Random number generator state for all processors", &
2747 n_keywords=1, n_subsections=0, repeats=.false.)
2748 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2749 description="Three real arrays of DIMENSION(3,2) times two RNG "// &
2750 "streams - 36 real values per processor", &
2751 repeats=.true., usage="automatically filled, do not edit by hand", &
2752 type_of_var=real_t, n_var=-1)
2753 CALL section_add_keyword(subsection, keyword)
2754 CALL keyword_release(keyword)
2755 CALL section_add_subsection(section, subsection)
2756 CALL section_release(subsection)
2757
2758 CALL section_create(subsection, __location__, name="PRINT", &
2759 description="The section that controls the output of the helium code", &
2760 n_keywords=16, n_subsections=0, repeats=.false.)
2761
2762 ! *************************************************************************
2763 !> Printkeys for properties output
2764 ! *************************************************************************
2765 NULLIFY (print_key)
2766
2767 ! Properties printed at SILENT print level
2768 !
2769
2770 ! Properties printed at LOW print level
2771 !
2772 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
2773 description="Controls the output of helium energies"// &
2774 " (averaged over MC step)", &
2775 print_level=low_print_level, common_iter_levels=1)
2776 CALL section_add_subsection(subsection, print_key)
2777 CALL section_release(print_key)
2778 !
2779 CALL cp_print_key_section_create(print_key, __location__, "PROJECTED_AREA_2_AVG", &
2780 description="Controls the output of the average projected area squared vector", &
2781 print_level=low_print_level, common_iter_levels=1)
2782 CALL section_add_subsection(subsection, print_key)
2783 CALL section_release(print_key)
2784 !
2785 CALL cp_print_key_section_create(print_key, __location__, "WINDING_NUMBER_2_AVG", &
2786 description="Controls the output of the average winding number vector squared", &
2787 print_level=low_print_level, common_iter_levels=1)
2788 CALL section_add_subsection(subsection, print_key)
2789 CALL section_release(print_key)
2790 !
2791 CALL cp_print_key_section_create(print_key, __location__, "MOMENT_OF_INERTIA_AVG", &
2792 description="Controls the output of the average moment of inertia vector", &
2793 print_level=low_print_level, common_iter_levels=1)
2794 CALL section_add_subsection(subsection, print_key)
2795 CALL section_release(print_key)
2796
2797 ! Properties printed at MEDIUM print level
2798 !
2799 CALL cp_print_key_section_create(print_key, __location__, "RDF", &
2800 description="Controls the output of helium radial distribution functions", &
2801 print_level=medium_print_level, common_iter_levels=1)
2802 CALL section_add_subsection(subsection, print_key)
2803 CALL section_release(print_key)
2804
2805 CALL cp_print_key_section_create(print_key, __location__, "RHO", &
2806 description="Controls the output of the helium density "// &
2807 "(Gaussian cube file format)", &
2808 each_iter_names=s2a("PINT"), each_iter_values=[100], &
2809 print_level=medium_print_level, common_iter_levels=1, &
2810 add_last=add_last_numeric)
2811 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
2812 description="Specifies the maximum number of backup copies.", &
2813 usage="BACKUP_COPIES {int}", &
2814 default_i_val=1)
2815 CALL section_add_keyword(print_key, keyword)
2816 CALL keyword_release(keyword)
2817 CALL section_add_subsection(subsection, print_key)
2818 CALL section_release(print_key)
2819 !
2820 CALL cp_print_key_section_create(print_key, __location__, "PROJECTED_AREA", &
2821 description="Controls the output of the projected area vector", &
2822 print_level=medium_print_level, common_iter_levels=1)
2823 CALL section_add_subsection(subsection, print_key)
2824 CALL section_release(print_key)
2825 !
2826 CALL cp_print_key_section_create(print_key, __location__, "WINDING_NUMBER", &
2827 description="Controls the output of the winding number vector", &
2828 print_level=medium_print_level, common_iter_levels=1)
2829 CALL section_add_subsection(subsection, print_key)
2830 CALL section_release(print_key)
2831 !
2832 CALL cp_print_key_section_create(print_key, __location__, "MOMENT_OF_INERTIA", &
2833 description="Controls the output of the moment of inertia vector", &
2834 print_level=medium_print_level, common_iter_levels=1)
2835 CALL section_add_subsection(subsection, print_key)
2836 CALL section_release(print_key)
2837 !
2838 CALL cp_print_key_section_create(print_key, __location__, "PLENGTH", &
2839 description="Controls the output of the helium permutation length", &
2840 print_level=medium_print_level, common_iter_levels=1)
2841 CALL section_add_subsection(subsection, print_key)
2842 CALL section_release(print_key)
2843
2844 CALL cp_print_key_section_create(print_key, __location__, "ACTION", &
2845 description="Controls the output of the total helium action", &
2846 print_level=medium_print_level, common_iter_levels=1)
2847 CALL section_add_subsection(subsection, print_key)
2848 CALL section_release(print_key)
2849
2850 ! Properties printed at HIGH print level
2851 !
2852 CALL cp_print_key_section_create(print_key, __location__, "COORDINATES", &
2853 description="Controls the output of helium coordinates", &
2854 print_level=high_print_level, common_iter_levels=1)
2855 CALL keyword_create(keyword, __location__, name="FORMAT", &
2856 description="Output file format for the coordinates", &
2857 usage="FORMAT (PDB|XYZ)", &
2858 default_i_val=fmt_id_pdb, &
2859 enum_c_vals=s2a("PDB", "XYZ"), &
2860 enum_i_vals=[fmt_id_pdb, fmt_id_xyz], &
2861 enum_desc=s2a("Bead coordinates and connectivity is written in PDB format", &
2862 "Only bead coordinates are written in XYZ format"))
2863 CALL section_add_keyword(print_key, keyword)
2864 CALL keyword_release(keyword)
2865 CALL section_add_subsection(subsection, print_key)
2866 CALL section_release(print_key)
2867 !
2868 CALL cp_print_key_section_create(print_key, __location__, "PERM", &
2869 description="Controls the output of the helium permutation state", &
2870 print_level=high_print_level, common_iter_levels=1)
2871 CALL keyword_create(keyword, __location__, name="FORMAT", &
2872 description="Output format for the permutation", &
2873 usage="FORMAT (CYCLE|PLAIN)", &
2874 default_i_val=perm_cycle, &
2875 enum_c_vals=s2a("CYCLE", "PLAIN"), &
2876 enum_i_vals=[perm_cycle, perm_plain], &
2877 enum_desc=s2a( &
2878 "Cycle notation with winding cycles enclosed"// &
2879 " in '[...]' and non-winding ones enclosed in '(...)'", &
2880 "Plain permutation output, i.e. P(1) ... P(N)"))
2881 CALL section_add_keyword(print_key, keyword)
2882 CALL keyword_release(keyword)
2883 CALL section_add_subsection(subsection, print_key)
2884 CALL section_release(print_key)
2885
2886 CALL cp_print_key_section_create(print_key, __location__, "FORCES", &
2887 description="Controls the output of the helium forces on the solute", &
2888 print_level=high_print_level, common_iter_levels=1)
2889 CALL section_add_subsection(subsection, print_key)
2890 CALL section_release(print_key)
2891
2892 ! Properties printed at DEBUG print level
2893 !
2894 CALL cp_print_key_section_create(print_key, __location__, "ACCEPTS", &
2895 description="Controls the output of the helium acceptance data", &
2896 print_level=debug_print_level, common_iter_levels=1)
2897 CALL section_add_subsection(subsection, print_key)
2898 CALL section_release(print_key)
2899 !
2900 CALL cp_print_key_section_create(print_key, __location__, "FORCES_INST", &
2901 description="Controls the output of the instantaneous helium forces on the solute", &
2902 print_level=debug_print_level, common_iter_levels=1)
2903 CALL section_add_subsection(subsection, print_key)
2904 CALL section_release(print_key)
2905
2906 CALL section_add_subsection(section, subsection)
2907 CALL section_release(subsection)
2908
2909 RETURN
2910 END SUBROUTINE create_helium_section
2911
2912END 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:1149
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