(git:374b731)
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-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \par History
10!> 10.2005 split input_cp2k into smaller modules [fawzi]
11!> 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="PROGRAM (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 precision for finding the space group
882 CALL keyword_create( &
883 keyword, __location__, name="EPS_SYMMETRY", &
884 description="Accuracy for space group determination. EPS_SYMMETRY is dimensionless. "// &
885 "Roughly speaking, two scaled (fractional) atomic positions v1, v2 are considered identical if |v1 - v2| < EPS_SYMMETRY. ", &
886 usage="EPS_SYMMETRY {REAL}", &
887 default_r_val=1.e-4_dp, repeats=.false.)
888 CALL section_add_keyword(section, keyword)
889 CALL keyword_release(keyword)
890
891 ! collects keywords related to reduction of symmetry due to an external field
892 CALL keyword_create( &
893 keyword, __location__, name="SYMM_REDUCTION", &
894 description="Direction of the external static electric field. "// &
895 "Some symmetry operations are not compatible with the direction of an electric field. "// &
896 "These operations are used when enforcing the space group.", &
897 usage="SYMM_REDUCTION 0.0 0.0 0.0", &
898 repeats=.false., n_var=3, &
899 type_of_var=real_t, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
900 CALL section_add_keyword(section, keyword)
901 CALL keyword_release(keyword)
902
903 ! collects keywords related to ranges of atoms to symmetrize
904 CALL keyword_create( &
905 keyword, __location__, name="SYMM_EXCLUDE_RANGE", &
906 description="Range of atoms to exclude from space group symmetry. "// &
907 "These atoms are excluded from both identification and enforcement. "// &
908 "This keyword can be repeated.", &
909 repeats=.true., usage="SYMM_EXCLUDE_RANGE {Int} {Int}", type_of_var=integer_t, n_var=2)
910 CALL section_add_keyword(section, keyword)
911 CALL keyword_release(keyword)
912
913 CALL keyword_create( &
914 keyword, __location__, name="SPGR_PRINT_ATOMS", &
915 description="Print equivalent atoms list for each space group symmetry operation.", &
916 default_l_val=.false., lone_keyword_l_val=.true.)
917 CALL section_add_keyword(section, keyword)
918 CALL keyword_release(keyword)
919
920 CALL create_lbfgs_section(subsection)
921 CALL section_add_subsection(section, subsection)
922 CALL section_release(subsection)
923
924 CALL create_cg_section(subsection)
925 CALL section_add_subsection(section, subsection)
926 CALL section_release(subsection)
927
928 CALL create_bfgs_section(subsection, use_model_hessian)
929 CALL section_add_subsection(section, subsection)
930 CALL section_release(subsection)
931
932 IF (.NOT. just_optimizers) THEN
933 ! Transition states section
934 CALL create_ts_section(subsection)
935 CALL section_add_subsection(section, subsection)
936 CALL section_release(subsection)
937
938 ! Create the PRINT subsection
939 NULLIFY (subsection)
940 CALL section_create(subsection, __location__, name="PRINT", &
941 description="Controls the printing properties during a geometry optimization run", &
942 n_keywords=0, n_subsections=1, repeats=.true.)
943 NULLIFY (print_key)
945 print_key, __location__, "program_run_info", &
946 description="Controls the printing of basic information during the Geometry Optimization", &
947 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
948 CALL section_add_subsection(subsection, print_key)
949 CALL section_release(print_key)
950 CALL section_add_subsection(section, subsection)
951 CALL section_release(subsection)
952 END IF
953
954 END SUBROUTINE create_geoopt_section
955
956! **************************************************************************************************
957!> \brief creates the section for the shell-core optimization
958!> \param section the section to be created
959!> \author Caino
960! **************************************************************************************************
961 SUBROUTINE create_shellcore_opt_section(section)
962 TYPE(section_type), POINTER :: section
963
964 TYPE(section_type), POINTER :: print_key, subsection
965
966 CALL create_geoopt_section( &
967 section, __location__, label="SHELL_OPT", &
968 description="This section sets the environment for the optimization of the shell-core distances"// &
969 " that might turn to be necessary along a MD run using a shell-model potential."// &
970 " The optimization procedure is activated when at least one of the shell-core"// &
971 " pairs becomes too elongated, i.e. when the assumption of point dipole is not longer valid.", &
972 just_optimizers=.true., &
973 use_model_hessian=.false.)
974
975 NULLIFY (print_key, subsection)
976
977 ! Create the PRINT subsection
978 NULLIFY (subsection)
979 CALL section_create(subsection, __location__, name="PRINT", &
980 description="Controls the printing properties during a shell-core optimization procedure", &
981 n_keywords=0, n_subsections=1, repeats=.true.)
982 NULLIFY (print_key)
983 CALL cp_print_key_section_create(print_key, __location__, "program_run_info", &
984 description="Controls the printing of basic information during the Optimization", &
985 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
986 CALL section_add_subsection(subsection, print_key)
987 CALL section_release(print_key)
988 CALL section_add_subsection(section, subsection)
989 CALL section_release(subsection)
990
991 END SUBROUTINE create_shellcore_opt_section
992
993! **************************************************************************************************
994!> \brief creates the section for the cell optimization
995!> \param section the section to be created
996!> \author Teodoro Laino [tlaino] - University of Zurich - 03.2008
997! **************************************************************************************************
998 SUBROUTINE create_cell_opt_section(section)
999 TYPE(section_type), POINTER :: section
1000
1001 TYPE(keyword_type), POINTER :: keyword
1002 TYPE(section_type), POINTER :: print_key, subsection
1003
1004 CALL create_geoopt_section(section, __location__, label="CELL_OPT", &
1005 description="This section sets the environment for the optimization of the simulation cell."// &
1006 " Two possible schemes are available: (1) Zero temperature optimization;"// &
1007 " (2) Finite temperature optimization.", &
1008 just_optimizers=.true., &
1009 use_model_hessian=.false.)
1010
1011 NULLIFY (keyword, print_key, subsection)
1012 CALL keyword_create( &
1013 keyword, __location__, name="TYPE", &
1014 description="Specify which kind of method to use for the optimization of the simulation cell", &
1015 usage="TYPE (GEO_OPT|MD|DIRECT_CELL_OPT)", &
1016 enum_c_vals=s2a("GEO_OPT", "MD", "DIRECT_CELL_OPT"), &
1017 enum_desc=s2a( &
1018 "Performs a geometry optimization (the GEO_OPT section must be defined) between cell optimization steps."// &
1019 " The stress tensor is computed at the optimized geometry.", &
1020 "Performs a molecular dynamics run (the MD section needs must defined) for computing the stress tensor"// &
1021 " used for the cell optimization.", &
1022 "Performs a geometry and cell optimization at the same time."// &
1023 " The stress tensor is computed at every step"), &
1025 default_i_val=default_cell_direct_id)
1026 CALL section_add_keyword(section, keyword)
1027 CALL keyword_release(keyword)
1028
1029 CALL keyword_create( &
1030 keyword, __location__, name="EXTERNAL_PRESSURE", &
1031 description="Specifies the external pressure (1 value or the full 9 components of the pressure tensor) "// &
1032 "applied during the cell optimization.", &
1033 usage="EXTERNAL_PRESSURE {REAL} .. {REAL}", unit_str="bar", &
1034 default_r_vals=(/cp_unit_to_cp2k(100.0_dp, "bar"), 0.0_dp, 0.0_dp, &
1035 0.0_dp, cp_unit_to_cp2k(100.0_dp, "bar"), 0.0_dp, &
1036 0.0_dp, 0.0_dp, cp_unit_to_cp2k(100.0_dp, "bar")/), n_var=-1)
1037 CALL section_add_keyword(section, keyword)
1038 CALL keyword_release(keyword)
1039
1040 CALL keyword_create( &
1041 keyword, __location__, name="KEEP_ANGLES", &
1042 description="Keep angles between the cell vectors constant, but allow the lengths of the"// &
1043 " cell vectors to change independently."// &
1044 " Albeit general, this is most useful for triclinic cells, to enforce higher symmetry, see KEEP_SYMMETRY.", &
1045 usage="KEEP_ANGLES TRUE", default_l_val=.false., lone_keyword_l_val=.true.)
1046 CALL section_add_keyword(section, keyword)
1047 CALL keyword_release(keyword)
1048
1049 CALL keyword_create(keyword, __location__, name="KEEP_SYMMETRY", &
1050 description="Keep the requested initial cell symmetry (e.g. during a cell optimisation). "// &
1051 "The initial symmetry must be specified in the &CELL section.", &
1052 usage="KEEP_SYMMETRY yes", default_l_val=.false., lone_keyword_l_val=.true.)
1053 CALL section_add_keyword(section, keyword)
1054 CALL keyword_release(keyword)
1055
1056 CALL keyword_create( &
1057 keyword, __location__, name="CONSTRAINT", &
1058 description="Imposes a constraint on the pressure tensor by fixing the specified cell components.", &
1059 usage="CONSTRAINT (none|x|y|z|xy|xz|yz)", &
1060 enum_desc=s2a("Fix nothing", &
1061 "Fix only x component", &
1062 "Fix only y component", &
1063 "Fix only z component", &
1064 "Fix x and y component", &
1065 "Fix x and z component", &
1066 "Fix y and z component"), &
1067 enum_c_vals=s2a("NONE", "X", "Y", "Z", "XY", "XZ", "YZ"), &
1068 enum_i_vals=(/fix_none, fix_x, fix_y, fix_z, fix_xy, fix_xz, fix_yz/), &
1069 default_i_val=fix_none)
1070 CALL section_add_keyword(section, keyword)
1071 CALL keyword_release(keyword)
1072
1073 CALL keyword_create(keyword, __location__, name="PRESSURE_TOLERANCE", &
1074 description="Specifies the Pressure tolerance (compared to the external pressure) to achieve "// &
1075 "during the cell optimization.", &
1076 usage="PRESSURE_TOLERANCE {REAL}", unit_str="bar", &
1077 default_r_val=cp_unit_to_cp2k(100.0_dp, "bar"))
1078 CALL section_add_keyword(section, keyword)
1079 CALL keyword_release(keyword)
1080
1081 ! Create the PRINT subsection
1082 NULLIFY (subsection)
1083 CALL section_create(subsection, __location__, name="PRINT", &
1084 description="Controls the printing properties during a geometry optimization run", &
1085 n_keywords=0, n_subsections=1, repeats=.true.)
1086 NULLIFY (print_key)
1087 CALL cp_print_key_section_create(print_key, __location__, "program_run_info", &
1088 description="Controls the printing of basic information during the Geometry Optimization", &
1089 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1090 CALL section_add_subsection(subsection, print_key)
1091 CALL section_release(print_key)
1092 CALL cp_print_key_section_create(print_key, __location__, "cell", &
1093 description="Controls the printing of the cell eveytime a calculation using a new cell is started.", &
1094 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__", &
1095 unit_str="angstrom")
1096 CALL section_add_subsection(subsection, print_key)
1097 CALL section_release(print_key)
1098 CALL section_add_subsection(section, subsection)
1099 CALL section_release(subsection)
1100
1101 END SUBROUTINE create_cell_opt_section
1102
1103! **************************************************************************************************
1104!> \brief creates the section for tuning transition states search
1105!> \param section the section to be created
1106!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1107! **************************************************************************************************
1108 SUBROUTINE create_ts_section(section)
1109 TYPE(section_type), POINTER :: section
1110
1111 TYPE(keyword_type), POINTER :: keyword
1112 TYPE(section_type), POINTER :: print_key, subsection, subsection2, &
1113 subsection3
1114
1115! Create the Transition State subsection
1116
1117 NULLIFY (section, keyword, subsection, subsection2)
1118 CALL section_create(section, __location__, name="TRANSITION_STATE", &
1119 description="Specifies parameters to perform a transition state search", &
1120 n_keywords=0, n_subsections=1, repeats=.false.)
1121
1122 CALL keyword_create(keyword, __location__, name="METHOD", &
1123 description="Specify which kind of method to use for locating transition states", &
1124 citations=(/henkelman1999/), &
1125 usage="TYPE (DIMER)", &
1126 enum_c_vals=s2a("DIMER"), &
1127 enum_desc=s2a("Uses the dimer method to optimize transition states."), &
1128 enum_i_vals=(/default_dimer_method_id/), &
1129 default_i_val=default_dimer_method_id)
1130 CALL section_add_keyword(section, keyword)
1131 CALL keyword_release(keyword)
1132
1133 CALL section_create(subsection, __location__, name="DIMER", &
1134 description="Specifies parameters for Dimer Method", &
1135 n_keywords=0, n_subsections=1, repeats=.false.)
1136
1137 CALL keyword_create(keyword, __location__, name="DR", &
1138 description="This keyword sets the value for the DR parameter.", &
1139 usage="DR {real}", unit_str='angstrom', &
1140 default_r_val=cp_unit_to_cp2k(0.01_dp, "angstrom"))
1141 CALL section_add_keyword(subsection, keyword)
1142 CALL keyword_release(keyword)
1143
1144 CALL keyword_create(keyword, __location__, name="INTERPOLATE_GRADIENT", &
1145 description="This keyword controls the interpolation of the gradient whenever possible"// &
1146 " during the optimization of the Dimer. The use of this keywords saves 1 evaluation"// &
1147 " of energy/forces.", usage="INTERPOLATE_GRADIENT {logical}", default_l_val=.true., &
1148 lone_keyword_l_val=.true.)
1149 CALL section_add_keyword(subsection, keyword)
1150 CALL keyword_release(keyword)
1151
1152 CALL keyword_create(keyword, __location__, name="ANGLE_TOLERANCE", &
1153 description="This keyword sets the value of the tolerance angle for the line search"// &
1154 " performed to optimize the orientation of the dimer.", &
1155 usage="ANGLE_TOL {real}", unit_str='rad', &
1156 default_r_val=cp_unit_to_cp2k(5.0_dp, "deg"))
1157 CALL section_add_keyword(subsection, keyword)
1158 CALL keyword_release(keyword)
1159
1160 CALL keyword_create(keyword, __location__, name="K-DIMER", &
1161 description="This keyword activates the constrained k-dimer translation"// &
1162 " J. Chem. Phys. 141, 164111 (2014).", &
1163 citations=(/henkelman2014/), &
1164 usage="K-DIMER {logica}", &
1165 default_l_val=.false., &
1166 lone_keyword_l_val=.false.)
1167 CALL section_add_keyword(subsection, keyword)
1168 CALL keyword_release(keyword)
1169
1170 CALL keyword_create(keyword, __location__, name="BETA", &
1171 description="Exponential factor for the switching function used in K-DIMER", &
1172 usage="BETA {real}", &
1173 default_r_val=5.0_dp, &
1174 lone_keyword_r_val=5.0_dp)
1175 CALL section_add_keyword(subsection, keyword)
1176 CALL keyword_release(keyword)
1177
1178 CALL create_geoopt_section( &
1179 subsection2, __location__, label="ROT_OPT", &
1180 description="This section sets the environment for the optimization of the rotation of the Dimer.", &
1181 just_optimizers=.true., &
1182 use_model_hessian=.false.)
1183 NULLIFY (subsection3)
1184 CALL section_create(subsection3, __location__, name="PRINT", &
1185 description="Controls the printing properties during the dimer rotation optimization run", &
1186 n_keywords=0, n_subsections=1, repeats=.true.)
1187 NULLIFY (print_key)
1188
1189 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
1190 description="Controls the printing of basic information during the Geometry Optimization", &
1191 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1192 CALL section_add_subsection(subsection3, print_key)
1193 CALL section_release(print_key)
1194
1195 CALL cp_print_key_section_create(print_key, __location__, "ROTATIONAL_INFO", &
1196 description="Controls the printing basic info during the cleaning of the "// &
1197 "rotational degrees of freedom.", print_level=low_print_level, &
1198 add_last=add_last_numeric, filename="__STD_OUT__")
1199 CALL keyword_create(keyword, __location__, name="COORDINATES", &
1200 description="Prints atomic coordinates after rotation", &
1201 default_l_val=.false., lone_keyword_l_val=.true.)
1202 CALL section_add_keyword(print_key, keyword)
1203 CALL keyword_release(keyword)
1204 CALL section_add_subsection(subsection3, print_key)
1205 CALL section_release(print_key)
1206
1207 CALL section_add_subsection(subsection2, subsection3)
1208 CALL section_release(subsection3)
1209 CALL section_add_subsection(subsection, subsection2)
1210 CALL section_release(subsection2)
1211
1212 CALL section_create(subsection2, __location__, name="DIMER_VECTOR", &
1213 description="Specifies the initial dimer vector (used frequently to restart DIMER calculations)."// &
1214 " If not provided the starting orientation of the dimer is chosen randomly.", &
1215 n_keywords=0, n_subsections=1, repeats=.false.)
1216 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1217 description="Specify on each line the components of the dimer vector.", repeats=.true., &
1218 usage="{Real} {Real} {Real}", type_of_var=real_t, n_var=-1)
1219 CALL section_add_keyword(subsection2, keyword)
1220 CALL keyword_release(keyword)
1221 CALL section_add_subsection(subsection, subsection2)
1222 CALL section_release(subsection2)
1223
1224 CALL section_add_subsection(section, subsection)
1225 CALL section_release(subsection)
1226
1227 END SUBROUTINE create_ts_section
1228
1229! **************************************************************************************************
1230!> \brief creates the BFGS section
1231!> \param section the section to be created
1232!> \param use_model_hessian ...
1233!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1234! **************************************************************************************************
1235 SUBROUTINE create_bfgs_section(section, use_model_hessian)
1236 TYPE(section_type), POINTER :: section
1237 LOGICAL, INTENT(IN) :: use_model_hessian
1238
1239 TYPE(keyword_type), POINTER :: keyword
1240 TYPE(section_type), POINTER :: print_key
1241
1242! create the BFGS subsection
1243
1244 NULLIFY (section, keyword, print_key)
1245 CALL section_create(section, __location__, name="BFGS", &
1246 description="Provides parameters to tune the BFGS optimization", &
1247 n_keywords=0, n_subsections=1, repeats=.false.)
1248
1249 CALL keyword_create(keyword, __location__, name="TRUST_RADIUS", &
1250 description="Trust radius used in BFGS. Previously set to 0.1. "// &
1251 "Large values can lead to instabilities", &
1252 usage="TRUST_RADIUS {real}", unit_str='angstrom', &
1253 default_r_val=cp_unit_to_cp2k(0.25_dp, "angstrom"))
1254 CALL section_add_keyword(section, keyword)
1255 CALL keyword_release(keyword)
1256
1257 CALL keyword_create(keyword, __location__, name="USE_MODEL_HESSIAN", &
1258 description="Uses a model Hessian as initial guess instead of a unit matrix."// &
1259 " Should lead in general to improved convergence might be switched off for exotic cases", &
1260 usage="USE_MODEL_HESSIAN", &
1261 default_l_val=use_model_hessian, lone_keyword_l_val=.true.)
1262 CALL section_add_keyword(section, keyword)
1263 CALL keyword_release(keyword)
1264
1265 CALL keyword_create(keyword, __location__, name="USE_RAT_FUN_OPT", &
1266 description="Includes a rational function optimization to determine the step."// &
1267 " Previously default but did not improve convergence in many cases", &
1268 usage="USE_RAT_FUN_OPT", &
1269 default_l_val=.false., lone_keyword_l_val=.true.)
1270 CALL section_add_keyword(section, keyword)
1271 CALL keyword_release(keyword)
1272
1273 CALL keyword_create(keyword, __location__, name="RESTART_HESSIAN", &
1274 description="Controls the reading of the initial Hessian from file.", &
1275 usage="RESTART_HESSIAN", &
1276 default_l_val=.false., lone_keyword_l_val=.true.)
1277 CALL section_add_keyword(section, keyword)
1278 CALL keyword_release(keyword)
1279
1280 CALL keyword_create(keyword, __location__, name="RESTART_FILE_NAME", &
1281 description="Specifies the name of the file used to read the initial Hessian.", &
1282 usage="RESTART_FILE_NAME {filename}", &
1283 default_lc_val="")
1284 CALL section_add_keyword(section, keyword)
1285 CALL keyword_release(keyword)
1286
1287 CALL cp_print_key_section_create(print_key, __location__, "RESTART", &
1288 description="Controls the printing of Hessian Restart file", &
1289 print_level=low_print_level, add_last=add_last_numeric, filename="BFGS", &
1290 common_iter_levels=2)
1291 CALL section_add_subsection(section, print_key)
1292 CALL section_release(print_key)
1293
1294 END SUBROUTINE create_bfgs_section
1295
1296! **************************************************************************************************
1297!> \brief creates the CG section
1298!> \param section the section to be created
1299!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1300! **************************************************************************************************
1301 SUBROUTINE create_cg_section(section)
1302 TYPE(section_type), POINTER :: section
1303
1304 TYPE(keyword_type), POINTER :: keyword
1305 TYPE(section_type), POINTER :: subsection, subsubsection
1306
1307! create the CG subsection
1308
1309 NULLIFY (section, subsection, subsubsection, keyword)
1310 CALL section_create(section, __location__, name="CG", &
1311 description="Provides parameters to tune the conjugate gradient optimization", &
1312 n_keywords=0, n_subsections=1, repeats=.false.)
1313
1314 CALL keyword_create(keyword, __location__, name="MAX_STEEP_STEPS", &
1315 description="Maximum number of steepest descent steps before starting the"// &
1316 " conjugate gradients optimization.", &
1317 usage="MAX_STEEP_STEPS {integer}", &
1318 default_i_val=0)
1319 CALL section_add_keyword(section, keyword)
1320 CALL keyword_release(keyword)
1321
1322 CALL keyword_create(keyword, __location__, name="RESTART_LIMIT", &
1323 description="Cosine of the angle between two consecutive searching directions."// &
1324 " If the angle during a CG optimization is less than the one corresponding to"// &
1325 " to the RESTART_LIMIT the CG is reset and one step of steepest descent is"// &
1326 " performed.", &
1327 usage="RESTART_LIMIT {real}", &
1328 default_r_val=0.9_dp)
1329 CALL section_add_keyword(section, keyword)
1330 CALL keyword_release(keyword)
1331
1332 CALL keyword_create(keyword, __location__, name="FLETCHER_REEVES", &
1333 description="Uses FLETCHER-REEVES instead of POLAK-RIBIERE when using Conjugate Gradients", &
1334 usage="FLETCHER-REEVES", &
1335 default_l_val=.false., lone_keyword_l_val=.true.)
1336 CALL section_add_keyword(section, keyword)
1337 CALL keyword_release(keyword)
1338
1339 ! Line Search section
1340 CALL section_create(subsection, __location__, name="LINE_SEARCH", &
1341 description="Provides parameters to tune the line search during the conjugate gradient optimization", &
1342 n_keywords=0, n_subsections=1, repeats=.false.)
1343
1344 CALL keyword_create(keyword, __location__, name="TYPE", &
1345 description="1D line search algorithm to be used with the CG optimizer,"// &
1346 " in increasing order of robustness and cost. ", &
1347 usage="TYPE GOLD", &
1348 default_i_val=ls_gold, &
1349 enum_c_vals=s2a("NONE", "2PNT", "3PNT", "GOLD", "FIT"), &
1350 enum_desc=s2a("take fixed length steps", &
1351 "extrapolate based on 2 points", &
1352 "extrapolate based on on 3 points", &
1353 "perform 1D golden section search of the minimum (very expensive)", &
1354 "perform 1D fit of a parabola on several evaluation of energy "// &
1355 "(very expensive and more robust vs numerical noise)"), &
1356 enum_i_vals=(/ls_none, ls_2pnt, ls_3pnt, ls_gold, ls_fit/))
1357 CALL section_add_keyword(subsection, keyword)
1358 CALL keyword_release(keyword)
1359
1360 ! 2PNT
1361 NULLIFY (subsubsection)
1362 CALL section_create(subsubsection, __location__, name="2PNT", &
1363 description="Provides parameters to tune the line search for the two point based line search.", &
1364 n_keywords=0, n_subsections=1, repeats=.false.)
1365
1366 CALL keyword_create(keyword, __location__, name="MAX_ALLOWED_STEP", &
1367 description="Max allowed value for the line search step.", &
1368 usage="MAX_ALLOWED_STEP {real}", unit_str="internal_cp2k", &
1369 default_r_val=0.25_dp)
1370 CALL section_add_keyword(subsubsection, keyword)
1371 CALL keyword_release(keyword)
1372
1373 CALL keyword_create( &
1374 keyword, __location__, name="LINMIN_GRAD_ONLY", &
1375 description="Use only the gradient, not the energy for line minimizations (e.g. in conjugate gradients).", &
1376 usage="LINMIN_GRAD_ONLY T", &
1377 default_l_val=.false., lone_keyword_l_val=.true.)
1378 CALL section_add_keyword(subsubsection, keyword)
1379 CALL keyword_release(keyword)
1380
1381 CALL section_add_subsection(subsection, subsubsection)
1382 CALL section_release(subsubsection)
1383
1384 ! GOLD
1385 NULLIFY (subsubsection)
1386 CALL section_create(subsubsection, __location__, name="GOLD", &
1387 description="Provides parameters to tune the line search for the gold search.", &
1388 n_keywords=0, n_subsections=1, repeats=.false.)
1389
1390 CALL keyword_create(keyword, __location__, name="INITIAL_STEP", &
1391 description="Initial step size used, e.g. for bracketing or minimizers. "// &
1392 "Might need to be reduced for systems with close contacts", &
1393 usage="INITIAL_STEP {real}", unit_str="internal_cp2k", &
1394 default_r_val=0.2_dp)
1395 CALL section_add_keyword(subsubsection, keyword)
1396 CALL keyword_release(keyword)
1397
1398 CALL keyword_create(keyword, __location__, name="BRACK_LIMIT", &
1399 description="Limit in 1D bracketing during line search in Conjugate Gradients Optimization.", &
1400 usage="BRACK_LIMIT {real}", unit_str="internal_cp2k", &
1401 default_r_val=100.0_dp)
1402 CALL section_add_keyword(subsubsection, keyword)
1403 CALL keyword_release(keyword)
1404
1405 CALL keyword_create(keyword, __location__, name="BRENT_TOL", &
1406 description="Tolerance requested during Brent line search in Conjugate Gradients Optimization.", &
1407 usage="BRENT_TOL {real}", unit_str="internal_cp2k", &
1408 default_r_val=0.01_dp)
1409 CALL section_add_keyword(subsubsection, keyword)
1410 CALL keyword_release(keyword)
1411
1412 CALL keyword_create(keyword, __location__, name="BRENT_MAX_ITER", &
1413 description="Maximum number of iterations in brent algorithm "// &
1414 "(used for the line search in Conjugated Gradients Optimization)", &
1415 usage="BRENT_MAX_ITER {integer}", &
1416 default_i_val=100)
1417 CALL section_add_keyword(subsubsection, keyword)
1418 CALL keyword_release(keyword)
1419 CALL section_add_subsection(subsection, subsubsection)
1420 CALL section_release(subsubsection)
1421
1422 CALL section_add_subsection(section, subsection)
1423 CALL section_release(subsection)
1424 END SUBROUTINE create_cg_section
1425
1426! **************************************************************************************************
1427!> \brief creates the LBFGS section
1428!> \param section the section to be created
1429!> \author Teodoro Laino [tlaino] - University of Zurich - 01.2008
1430! **************************************************************************************************
1431 SUBROUTINE create_lbfgs_section(section)
1432 TYPE(section_type), POINTER :: section
1433
1434 TYPE(keyword_type), POINTER :: keyword
1435
1436! create the LBFGS section
1437
1438 NULLIFY (section, keyword)
1439 CALL section_create(section, __location__, name="LBFGS", &
1440 description="Provides parameters to tune the limited memory BFGS (LBFGS) optimization", &
1441 n_keywords=0, n_subsections=1, repeats=.false., &
1442 citations=(/byrd1995/))
1443
1444 CALL keyword_create(keyword, __location__, name="MAX_H_RANK", &
1445 description="Maximum rank (and consequently size) of the "// &
1446 "approximate Hessian matrix used by the LBFGS optimizer. "// &
1447 "Larger values (e.g. 30) will accelerate the convergence behaviour "// &
1448 "at the cost of a larger memory consumption.", &
1449 usage="MAX_H_RANK {integer}", &
1450 default_i_val=5)
1451 CALL section_add_keyword(section, keyword)
1452 CALL keyword_release(keyword)
1453
1454 CALL keyword_create(keyword, __location__, name="MAX_F_PER_ITER", &
1455 description="Maximum number of force evaluations per iteration"// &
1456 " (used for the line search)", &
1457 usage="MAX_F_PER_ITER {integer}", &
1458 default_i_val=20)
1459 CALL section_add_keyword(section, keyword)
1460 CALL keyword_release(keyword)
1461
1462 CALL keyword_create(keyword, __location__, name="WANTED_PROJ_GRADIENT", &
1463 description="Convergence criterion (overrides the general ones):"// &
1464 " Requested norm threshold of the gradient multiplied"// &
1465 " by the approximate Hessian.", &
1466 usage="WANTED_PROJ_GRADIENT {real}", unit_str="internal_cp2k", &
1467 default_r_val=1.0e-16_dp)
1468 CALL section_add_keyword(section, keyword)
1469 CALL keyword_release(keyword)
1470
1471 CALL keyword_create(keyword, __location__, name="WANTED_REL_F_ERROR", &
1472 description="Convergence criterion (overrides the general ones):"// &
1473 " Requested relative error on the objective function"// &
1474 " of the optimizer (the energy)", &
1475 usage="WANTED_REL_F_ERROR {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( &
1481 keyword, __location__, name="TRUST_RADIUS", &
1482 description="Trust radius used in LBFGS. Not completely in depth tested. Negativ values means no trust radius is used.", &
1483 usage="TRUST_RADIUS {real}", unit_str='angstrom', &
1484 default_r_val=-1.0_dp)
1485 CALL section_add_keyword(section, keyword)
1486 CALL keyword_release(keyword)
1487
1488 END SUBROUTINE create_lbfgs_section
1489
1490! **************************************************************************************************
1491!> \brief creates the flexible_partitioning section
1492!> \param section the section to be created
1493!> \author Joost VandeVondele [04.2006]
1494! **************************************************************************************************
1495 SUBROUTINE create_fp_section(section)
1496 TYPE(section_type), POINTER :: section
1497
1498 TYPE(keyword_type), POINTER :: keyword
1499 TYPE(section_type), POINTER :: print_key
1500
1501 cpassert(.NOT. ASSOCIATED(section))
1502 CALL section_create(section, __location__, name="FLEXIBLE_PARTITIONING", &
1503 description="This section sets up flexible_partitioning", &
1504 n_keywords=1, n_subsections=1, repeats=.false.)
1505
1506 NULLIFY (keyword, print_key)
1507
1508 CALL keyword_create(keyword, __location__, name="CENTRAL_ATOM", &
1509 description="Specifies the central atom.", &
1510 usage="CENTRAL_ATOM {integer}", &
1511 n_var=1, type_of_var=integer_t)
1512 CALL section_add_keyword(section, keyword)
1513 CALL keyword_release(keyword)
1514
1515 CALL keyword_create(keyword, __location__, name="INNER_ATOMS", &
1516 description="Specifies the list of atoms that should remain close to the central atom.", &
1517 usage="INNER_ATOMS {integer} {integer} .. {integer}", &
1518 n_var=-1, type_of_var=integer_t)
1519 CALL section_add_keyword(section, keyword)
1520 CALL keyword_release(keyword)
1521
1522 CALL keyword_create(keyword, __location__, name="OUTER_ATOMS", &
1523 description="Specifies the list of atoms that should remain far from the central atom.", &
1524 usage="OUTER_ATOMS {integer} {integer} .. {integer}", &
1525 n_var=-1, type_of_var=integer_t)
1526 CALL section_add_keyword(section, keyword)
1527 CALL keyword_release(keyword)
1528
1529 CALL keyword_create(keyword, __location__, name="INNER_RADIUS", &
1530 description="radius of the inner wall", &
1531 usage="INNER_RADIUS {real} ", type_of_var=real_t, &
1532 n_var=1, unit_str="angstrom")
1533 CALL section_add_keyword(section, keyword)
1534 CALL keyword_release(keyword)
1535
1536 CALL keyword_create(keyword, __location__, name="OUTER_RADIUS", &
1537 description="radius of the outer wall", &
1538 usage="OUTER_RADIUS {real} ", type_of_var=real_t, &
1539 n_var=1, unit_str="angstrom")
1540 CALL section_add_keyword(section, keyword)
1541 CALL keyword_release(keyword)
1542
1543 CALL keyword_create(keyword, __location__, name="STRENGTH", &
1544 description="Sets the force constant of the repulsive harmonic potential", &
1545 usage="STRENGTH 1.0", default_r_val=1.0_dp)
1546 CALL section_add_keyword(section, keyword)
1547 CALL keyword_release(keyword)
1548
1549 CALL keyword_create(keyword, __location__, name="BIAS", &
1550 description="If a bias potential counter-acting the weight term should be applied (recommended).", &
1551 usage="BIAS F", default_l_val=.true., lone_keyword_l_val=.true.)
1552 CALL section_add_keyword(section, keyword)
1553 CALL keyword_release(keyword)
1554
1555 CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
1556 description="Sets the temperature parameter that is used in the baising potential."// &
1557 " It is recommended to use the actual simulation temperature", &
1558 usage="TEMPERATURE 300", default_r_val=300.0_dp, unit_str='K')
1559 CALL section_add_keyword(section, keyword)
1560 CALL keyword_release(keyword)
1561
1562 CALL keyword_create(keyword, __location__, name="SMOOTH_WIDTH", &
1563 description="Sets the width of the smooth counting function.", &
1564 usage="SMOOTH_WIDTH 0.2", default_r_val=0.02_dp, unit_str='angstrom')
1565 CALL section_add_keyword(section, keyword)
1566 CALL keyword_release(keyword)
1567
1568 CALL cp_print_key_section_create(print_key, __location__, "WEIGHTS", &
1569 description="Controls the printing of FP info during flexible partitioning simulations.", &
1570 print_level=low_print_level, common_iter_levels=1, &
1571 filename="FLEXIBLE_PARTIONING")
1572 CALL section_add_subsection(section, print_key)
1573 CALL section_release(print_key)
1574
1575 CALL cp_print_key_section_create(print_key, __location__, "CONTROL", &
1576 description="Controls the printing of FP info at startup", &
1577 print_level=low_print_level, common_iter_levels=1, &
1578 filename="__STD_OUT__")
1579 CALL section_add_subsection(section, print_key)
1580 CALL section_release(print_key)
1581
1582 END SUBROUTINE create_fp_section
1583
1584! **************************************************************************************************
1585!> \brief ...
1586!> \param section will contain the driver section
1587!> \author mceriotti
1588! **************************************************************************************************
1589 SUBROUTINE create_driver_section(section)
1590 TYPE(section_type), POINTER :: section
1591
1592 TYPE(keyword_type), POINTER :: keyword
1593
1594 cpassert(.NOT. ASSOCIATED(section))
1595 CALL section_create(section, __location__, name="DRIVER", &
1596 description="This section defines the parameters needed to run in i-PI driver mode.", &
1597 citations=(/ceriotti2014, kapil2016/), &
1598 n_keywords=3, n_subsections=0, repeats=.false.)
1599
1600 NULLIFY (keyword)
1601 CALL keyword_create(keyword, __location__, name="unix", &
1602 description="Use a UNIX socket rather than an INET socket.", &
1603 usage="unix LOGICAL", &
1604 default_l_val=.false., lone_keyword_l_val=.true.)
1605 CALL section_add_keyword(section, keyword)
1606 CALL keyword_release(keyword)
1607
1608 CALL keyword_create(keyword, __location__, name="port", &
1609 description="Port number for the i-PI server.", &
1610 usage="port <INTEGER>", &
1611 default_i_val=12345)
1612 CALL section_add_keyword(section, keyword)
1613 CALL keyword_release(keyword)
1614
1615 CALL keyword_create(keyword, __location__, name="host", &
1616 description="Host name for the i-PI server.", &
1617 usage="host <HOSTNAME>", &
1618 default_c_val="localhost")
1619 CALL section_add_keyword(section, keyword)
1620 CALL keyword_release(keyword)
1621
1622 CALL keyword_create(keyword, __location__, name="SLEEP_TIME", &
1623 description="Sleeping time while waiting for for driver commands [s].", &
1624 usage="SLEEP_TIME 0.1", &
1625 default_r_val=0.01_dp)
1626 CALL section_add_keyword(section, keyword)
1627 CALL keyword_release(keyword)
1628
1629 END SUBROUTINE create_driver_section
1630
1631! **************************************************************************************************
1632!> \brief creates the section for a path integral run
1633!> \param section will contain the pint section
1634!> \author fawzi
1635! **************************************************************************************************
1636 SUBROUTINE create_pint_section(section)
1637 TYPE(section_type), POINTER :: section
1638
1639 TYPE(keyword_type), POINTER :: keyword
1640 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
1641
1642 cpassert(.NOT. ASSOCIATED(section))
1643 CALL section_create(section, __location__, name="PINT", &
1644 description="The section that controls a path integral run", &
1645 n_keywords=13, n_subsections=9, repeats=.false.)
1646 NULLIFY (keyword)
1647
1648 CALL keyword_create(keyword, __location__, name="p", &
1649 description="Specify number beads to use", repeats=.false., &
1650 default_i_val=3)
1651 CALL section_add_keyword(section, keyword)
1652 CALL keyword_release(keyword)
1653 CALL keyword_create(keyword, __location__, name="proc_per_replica", &
1654 description="Specify number of processors to use for each replica", &
1655 repeats=.false., default_i_val=0)
1656 CALL section_add_keyword(section, keyword)
1657 CALL keyword_release(keyword)
1658 CALL keyword_create(keyword, __location__, name="num_steps", &
1659 description="Number of steps (if MAX_STEP is not explicitly given"// &
1660 " the program will perform this number of steps)", repeats=.false., &
1661 default_i_val=3)
1662 CALL section_add_keyword(section, keyword)
1663 CALL keyword_release(keyword)
1664 CALL keyword_create(keyword, __location__, name="MAX_STEP", &
1665 description="Maximum step number (the program will stop if"// &
1666 " ITERATION >= MAX_STEP even if NUM_STEPS has not been reached)", &
1667 repeats=.false., default_i_val=10)
1668 CALL section_add_keyword(section, keyword)
1669 CALL keyword_release(keyword)
1670 CALL keyword_create(keyword, __location__, name="iteration", &
1671 description="Specify the iteration number from which it should be "// &
1672 "counted", default_i_val=0)
1673 CALL section_add_keyword(section, keyword)
1674 CALL keyword_release(keyword)
1675 CALL keyword_create(keyword, __location__, name="Temp", &
1676 description="The temperature you want to simulate", &
1677 default_r_val=cp_unit_to_cp2k(300._dp, "K"), &
1678 unit_str="K")
1679 CALL section_add_keyword(section, keyword)
1680 CALL keyword_release(keyword)
1681 CALL keyword_create(keyword, __location__, name="kT_CORRECTION", &
1682 description="Corrects for the loss of temperature due to constrained "// &
1683 "degrees of freedom for Nose-Hover chains and numeric integration", &
1684 repeats=.false., default_l_val=.false.)
1685 CALL section_add_keyword(section, keyword)
1686 CALL keyword_release(keyword)
1687 CALL keyword_create(keyword, __location__, name="T_tol", variants=(/"temp_to"/), &
1688 description="threshold for the oscillations of the temperature "// &
1689 "excedeed which the temperature is rescaled. 0 means no rescaling.", &
1690 default_r_val=0._dp, unit_str="K")
1691 CALL section_add_keyword(section, keyword)
1692 CALL keyword_release(keyword)
1693 CALL keyword_create(keyword, __location__, name="dt", &
1694 description="timestep (might be subdivised in nrespa subtimesteps", &
1695 repeats=.false., &
1696 default_r_val=cp_unit_to_cp2k(1.0_dp, "fs"), &
1697 usage="dt 1.0", unit_str="fs")
1698 CALL section_add_keyword(section, keyword)
1699 CALL keyword_release(keyword)
1700 CALL keyword_create(keyword, __location__, name="HARM_INT", &
1701 description="integrator scheme for integrating the harmonic bead springs.", &
1702 usage="HARM_INT (NUMERIC|EXACT)", &
1703 default_i_val=integrate_numeric, &
1704 enum_c_vals=s2a("NUMERIC", "EXACT"), &
1705 enum_i_vals=(/integrate_numeric, integrate_exact/))
1706 CALL section_add_keyword(section, keyword)
1707 CALL keyword_release(keyword)
1708 CALL keyword_create(keyword, __location__, name="nrespa", &
1709 description="number of respa steps for the bead for each md step", &
1710 repeats=.false., default_i_val=5)
1711 CALL section_add_keyword(section, keyword)
1712 CALL keyword_release(keyword)
1713
1714 CALL keyword_create(keyword, __location__, name="transformation", &
1715 description="Specifies the coordinate transformation to use", &
1716 usage="TRANSFORMATION (NORMAL|STAGE)", &
1717 default_i_val=transformation_normal, &
1718 enum_c_vals=s2a("NORMAL", "STAGE"), &
1720
1721 CALL section_add_keyword(section, keyword)
1722 CALL keyword_release(keyword)
1723 CALL keyword_create(keyword, __location__, name="propagator", &
1724 description="Specifies the real time propagator to use", &
1725 usage="PROPAGATOR (PIMD|RPMD|CMD)", &
1726 default_i_val=propagator_pimd, &
1727 enum_c_vals=s2a("PIMD", "RPMD", "CMD"), &
1729 CALL section_add_keyword(section, keyword)
1730 CALL keyword_release(keyword)
1731 CALL keyword_create(keyword, __location__, name="FIX_CENTROID_POS", &
1732 description="Propagate all DOF but the centroid - "// &
1733 "useful for equilibration of the non-centroid modes "// &
1734 "(activated only if TRANSFORMATION==NORMAL)", &
1735 repeats=.false., default_l_val=.false., &
1736 lone_keyword_l_val=.true.)
1737 CALL section_add_keyword(section, keyword)
1738 CALL keyword_release(keyword)
1739
1740 NULLIFY (subsection, subsubsection)
1741 CALL section_create(subsection, __location__, name="NORMALMODE", &
1742 description="Controls the normal mode transformation", &
1743 n_keywords=3, n_subsections=0, repeats=.false.)
1744 CALL keyword_create(keyword, __location__, name="Q_CENTROID", &
1745 description="Value of the thermostat mass of centroid degree of freedom", &
1746 repeats=.false., default_r_val=-1.0_dp)
1747 CALL section_add_keyword(subsection, keyword)
1748 CALL keyword_release(keyword)
1749 CALL keyword_create(keyword, __location__, name="Q_BEAD", &
1750 description="Value of the thermostat mass of non-centroid degrees of freedom", &
1751 repeats=.false., default_r_val=-1.0_dp)
1752 CALL section_add_keyword(subsection, keyword)
1753 CALL keyword_release(keyword)
1754 CALL keyword_create(keyword, __location__, name="MODEFACTOR", &
1755 description="mass scale factor for non-centroid degrees of freedom", &
1756 repeats=.false., default_r_val=1.0_dp)
1757 CALL section_add_keyword(subsection, keyword)
1758 CALL keyword_release(keyword)
1759 CALL keyword_create(keyword, __location__, name="GAMMA", &
1760 description="mass scale factor for non-centroid degrees of freedom, &
1761& naming convention according to Witt, 2008, <https://doi.org/10.1063/1.3125009>.", &
1762 repeats=.false., default_r_val=8.0_dp)
1763 CALL section_add_keyword(subsection, keyword)
1764 CALL keyword_release(keyword)
1765
1766 CALL section_add_subsection(section, subsection)
1767 CALL section_release(subsection)
1768
1769 CALL section_create(subsection, __location__, name="staging", &
1770 description="The section that controls the staging transformation", &
1771 n_keywords=2, n_subsections=0, repeats=.false.)
1772 CALL keyword_create(keyword, __location__, name="j", &
1773 description="Value of the j parameter for the staging transformation", &
1774 repeats=.false., default_i_val=2)
1775 CALL section_add_keyword(subsection, keyword)
1776 CALL keyword_release(keyword)
1777 CALL keyword_create(keyword, __location__, name="Q_END", &
1778 description="Value of the nose-hoover mass for the endbead (Q_end)", &
1779 repeats=.false., default_i_val=2)
1780 CALL section_add_keyword(subsection, keyword)
1781 CALL keyword_release(keyword)
1782 CALL section_add_subsection(section, subsection)
1783 CALL section_release(subsection)
1784
1785 CALL section_create(subsection, __location__, name="BEADS", &
1786 description="Sets positions and velocities of the beads", &
1787 n_keywords=0, n_subsections=2, &
1788 repeats=.false.)
1789 CALL create_coord_section(subsubsection, "BEADS")
1790 CALL section_add_subsection(subsection, subsubsection)
1791 CALL section_release(subsubsection)
1792 CALL create_velocity_section(subsubsection, "BEADS")
1793 CALL section_add_subsection(subsection, subsubsection)
1794 CALL section_release(subsubsection)
1795 CALL section_add_subsection(section, subsection)
1796 CALL section_release(subsection)
1797
1798 CALL section_create(subsection, __location__, name="NOSE", &
1799 description="Controls the Nose-Hoover thermostats", &
1800 n_keywords=1, n_subsections=2, &
1801 repeats=.false.)
1802 CALL keyword_create(keyword, __location__, name="nnos", &
1803 description="length of nose-hoover chain. 0 means no thermostat", &
1804 repeats=.false., default_i_val=2)
1805 CALL section_add_keyword(subsection, keyword)
1806 CALL keyword_release(keyword)
1807 CALL create_coord_section(subsubsection, "NOSE")
1808 CALL section_add_subsection(subsection, subsubsection)
1809 CALL section_release(subsubsection)
1810 CALL create_velocity_section(subsubsection, "NOSE")
1811 CALL section_add_subsection(subsection, subsubsection)
1812 CALL section_release(subsubsection)
1813 CALL section_add_subsection(section, subsection)
1814 CALL section_release(subsection)
1815
1816 CALL create_gle_section(subsection)
1817 CALL section_add_subsection(section, subsection)
1818 CALL section_release(subsection)
1819
1820 CALL section_create(subsection, __location__, name="PILE", &
1821 description="Controls the PI Langevin Equation thermostat."// &
1822 " Needs the exact harmonic integrator."// &
1823 " May lead to unphysical motions if constraint e.g. FIXED_ATOMS, is applied."// &
1824 " RESTART_HELIUM section has to be .FALSE. when restarting the PIGLET job.", &
1825 citations=(/ceriotti2010/), &
1826 n_keywords=3, n_subsections=1, &
1827 repeats=.false.)
1828 CALL create_rng_section(subsubsection)
1829 CALL section_add_subsection(subsection, subsubsection)
1830 CALL section_release(subsubsection)
1831 CALL keyword_create(keyword, __location__, name="TAU", &
1832 description="Time constant for centroid motion. "// &
1833 "If zero or negative the centroid is not thermostated.", &
1834 usage="TAU {real}", type_of_var=real_t, &
1835 unit_str="fs", n_var=1, default_r_val=1000.0_dp)
1836 CALL section_add_keyword(subsection, keyword)
1837 CALL keyword_release(keyword)
1838 CALL keyword_create(keyword, __location__, name="LAMBDA", &
1839 description="Scaling of friction to mode coupling", &
1840 usage="LAMBDA {real}", type_of_var=real_t, &
1841 n_var=1, default_r_val=0.5_dp)
1842 CALL section_add_keyword(subsection, keyword)
1843 CALL keyword_release(keyword)
1844 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1845 description="Thermostat energy for conserved quantity. "// &
1846 "Only useful in restart files.", &
1847 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1848 n_var=1, default_r_val=0.0_dp)
1849 CALL section_add_keyword(subsection, keyword)
1850 CALL keyword_release(keyword)
1851 CALL section_add_subsection(section, subsection)
1852 CALL section_release(subsection)
1853
1854 CALL section_create(subsection, __location__, name="PIGLET", &
1855 description="Controls the PI Generalized Langevin Equation thermostat."// &
1856 " Needs the exact harmonic integrator", &
1857 citations=(/ceriotti2012/), &
1858 n_keywords=4, n_subsections=2, &
1859 repeats=.false.)
1860 CALL create_rng_section(subsubsection)
1861 CALL section_add_subsection(subsection, subsubsection)
1862 CALL section_release(subsubsection)
1863 CALL section_create(subsubsection, __location__, name="EXTRA_DOF", &
1864 description="Additional degrees of freedom to ensure Markovian Dynamics.", &
1865 n_keywords=1, n_subsections=0, repeats=.false.)
1866 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1867 description="Restart values for additional degrees of freedom" &
1868 //" (only for restarts, do not set explicitly)", &
1869 repeats=.false., &
1870 type_of_var=real_t, n_var=-1)
1871 CALL section_add_keyword(subsubsection, keyword)
1872 CALL keyword_release(keyword)
1873 CALL section_add_subsection(subsection, subsubsection)
1874 CALL section_release(subsubsection)
1875 CALL keyword_create(keyword, __location__, name="NEXTRA_DOF", &
1876 description="Number of extra degrees of freedom to ensure markovian dynamics", &
1877 repeats=.false., default_i_val=8)
1878 CALL section_add_keyword(subsection, keyword)
1879 CALL keyword_release(keyword)
1880 CALL keyword_create(keyword, __location__, name="MATRICES_FILE_NAME", &
1881 description="Filename containig the raw matrices from "// &
1882 "<https://gle4md.org/index.html?page=matrix>.", &
1883 repeats=.false., default_lc_val="PIGLET.MAT")
1884 CALL section_add_keyword(subsection, keyword)
1885 CALL keyword_release(keyword)
1886 CALL keyword_create(keyword, __location__, name="SMATRIX_INIT", &
1887 description="Select algorithm to initialize piglet S-matrices", &
1888 usage="SMATRIX_INIT (CHOLESKY|DIAGONAL)", &
1889 default_i_val=matrix_init_cholesky, &
1890 enum_c_vals=s2a("CHOLESKY", "DIAGONAL"), &
1892 CALL section_add_keyword(subsection, keyword)
1893 CALL keyword_release(keyword)
1894 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1895 description="Thermostat energy for conserved quantity. "// &
1896 "Only useful in restart files.", &
1897 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1898 n_var=1, default_r_val=0.0_dp)
1899 CALL section_add_keyword(subsection, keyword)
1900 CALL keyword_release(keyword)
1901 CALL section_add_subsection(section, subsection)
1902 CALL section_release(subsection)
1903
1904 CALL section_create(subsection, __location__, name="QTB", &
1905 description="Controls the QTB-PILE thermostat."// &
1906 " Needs the exact harmonic integrator", &
1907 citations=(/brieuc2016/), &
1908 n_keywords=7, n_subsections=1, &
1909 repeats=.false.)
1910 CALL create_rng_section(subsubsection)
1911 CALL section_add_subsection(subsection, subsubsection)
1912 CALL section_release(subsubsection)
1913 CALL keyword_create(keyword, __location__, name="TAU", &
1914 description="Time constant for centroid motion. ", &
1915 usage="TAU {real}", type_of_var=real_t, &
1916 unit_str="fs", n_var=1, default_r_val=1000.0_dp)
1917 CALL section_add_keyword(subsection, keyword)
1918 CALL keyword_release(keyword)
1919 CALL keyword_create(keyword, __location__, name="LAMBDA", &
1920 description="Scaling of friction to ring polymer NM freq.", &
1921 usage="LAMBDA {real}", type_of_var=real_t, &
1922 n_var=1, default_r_val=0.5_dp)
1923 CALL section_add_keyword(subsection, keyword)
1924 CALL keyword_release(keyword)
1925 CALL keyword_create(keyword, __location__, name="FP", &
1926 description="Defines which version to use "// &
1927 "0: f_P^(0), 1: f_P^(1)", &
1928 usage="FP {integer}", type_of_var=integer_t, &
1929 n_var=1, default_i_val=1)
1930 CALL section_add_keyword(subsection, keyword)
1931 CALL keyword_release(keyword)
1932 CALL keyword_create(keyword, __location__, name="TAUCUT", &
1933 description="Inverse of cutoff freq. for the centroid mode", &
1934 usage="TAUCUT {real}", type_of_var=real_t, &
1935 unit_str="fs", n_var=1, default_r_val=0.5_dp)
1936 CALL section_add_keyword(subsection, keyword)
1937 CALL keyword_release(keyword)
1938 CALL keyword_create(keyword, __location__, name="LAMBCUT", &
1939 description="Scaling of cutoff freq. to ring polymer NM freq.", &
1940 usage="LAMBCUT {real}", type_of_var=real_t, &
1941 n_var=1, default_r_val=2.0_dp)
1942 CALL section_add_keyword(subsection, keyword)
1943 CALL keyword_release(keyword)
1944 CALL keyword_create(keyword, __location__, name="NF", &
1945 description="Number of points used for the convolution product.", &
1946 usage="NF {integer}", type_of_var=integer_t, &
1947 n_var=1, default_i_val=128)
1948 CALL section_add_keyword(subsection, keyword)
1949 CALL keyword_release(keyword)
1950 CALL keyword_create(keyword, __location__, name="THERMOSTAT_ENERGY", &
1951 description="Thermostat energy for conserved quantity. "// &
1952 "Only useful in restart files.", &
1953 usage="THERMOSTAT_ENERGY {real}", type_of_var=real_t, &
1954 n_var=1, default_r_val=0.0_dp)
1955 CALL section_add_keyword(subsection, keyword)
1956 CALL keyword_release(keyword)
1957 CALL section_add_subsection(section, subsection)
1958 CALL section_release(subsection)
1959
1960 CALL section_create(subsection, __location__, name="INIT", &
1961 description="Controls the initialization if the beads are not present", &
1962 repeats=.false.)
1963
1964 CALL keyword_create(keyword, __location__, name="LEVY_POS_SAMPLE", &
1965 description="Sample bead positions assuming free particle "// &
1966 "behavior (performs a Levy random walk of length P around "// &
1967 "the classical position of each atom at the physical "// &
1968 "temperature defined in PINT%TEMP)", &
1969 repeats=.false., default_l_val=.false., &
1970 lone_keyword_l_val=.true.)
1971 CALL section_add_keyword(subsection, keyword)
1972 CALL keyword_release(keyword)
1973 CALL keyword_create(keyword, __location__, name="LEVY_CORRELATED", &
1974 description="Use the same Levy path for all atoms, though "// &
1975 "with mass-dependent variances (might help at very low T)", &
1976 repeats=.false., default_l_val=.false., &
1977 lone_keyword_l_val=.true.)
1978 CALL section_add_keyword(subsection, keyword)
1979 CALL keyword_release(keyword)
1980 CALL keyword_create(keyword, __location__, name="LEVY_TEMP_FACTOR", &
1981 description="Multiplicative correction factor for the "// &
1982 "temperature at which the Levy walk is performed "// &
1983 "(correction is due to the interactions that modify "// &
1984 "the spread of a free particle)", &
1985 repeats=.false., default_r_val=1.0_dp)
1986 CALL section_add_keyword(subsection, keyword)
1987 CALL keyword_release(keyword)
1988 CALL keyword_create(keyword, __location__, name="LEVY_SEED", &
1989 description="Initial seed for the (pseudo)random number "// &
1990 "generator that controls Levy walk for bead positions.", &
1991 usage="LEVY_SEED <INTEGER>", default_i_val=1234, &
1992 repeats=.false.)
1993 CALL section_add_keyword(subsection, keyword)
1994 CALL keyword_release(keyword)
1995 CALL keyword_create(keyword, __location__, name="THERMOSTAT_SEED", &
1996 description="Initial seed for the (pseudo)random number "// &
1997 "generator that controls the PILE and PIGLET thermostats.", &
1998 usage="THERMOSTAT_SEED <INTEGER>", default_i_val=12345, &
1999 repeats=.false.)
2000 CALL section_add_keyword(subsection, keyword)
2001 CALL keyword_release(keyword)
2002 CALL keyword_create(keyword, __location__, name="RANDOMIZE_POS", &
2003 description="add gaussian noise to the positions of the beads", &
2004 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2005 CALL section_add_keyword(subsection, keyword)
2006 CALL keyword_release(keyword)
2007
2008 CALL keyword_create(keyword, __location__, name="CENTROID_SPEED", &
2009 description="adds random velocity component to the centroid modes "// &
2010 "(useful to correct for the averaging out of the speed of various beads)", &
2011 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2012 CALL section_add_keyword(subsection, keyword)
2013 CALL keyword_release(keyword)
2014
2015 CALL keyword_create(keyword, __location__, name="VELOCITY_QUENCH", &
2016 description="set the initial velocities to zero", &
2017 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2018 CALL section_add_keyword(subsection, keyword)
2019 CALL keyword_release(keyword)
2020 CALL keyword_create(keyword, __location__, name="VELOCITY_SCALE", &
2021 description="scale initial velocities to the temperature given in MOTION%PINT%TEMP", &
2022 repeats=.false., default_l_val=.false., lone_keyword_l_val=.true.)
2023 CALL section_add_keyword(subsection, keyword)
2024 CALL keyword_release(keyword)
2025
2026 CALL section_add_subsection(section, subsection)
2027 CALL section_release(subsection)
2028
2029 CALL create_helium_section(subsection)
2030 CALL section_add_subsection(section, subsection)
2031 CALL section_release(subsection)
2032
2033 CALL section_create(subsection, __location__, name="PRINT", &
2034 description="Controls the path integral-specific output", &
2035 n_keywords=2, n_subsections=0, repeats=.false.)
2036
2037 NULLIFY (print_key)
2038
2039 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
2040 description="Controls the output of the path integral energies", &
2041 print_level=low_print_level, common_iter_levels=1)
2042 CALL section_add_subsection(subsection, print_key)
2043 CALL section_release(print_key)
2044
2045 CALL cp_print_key_section_create(print_key, __location__, "ACTION", &
2046 description="Controls the output of the path integral action", &
2047 print_level=medium_print_level, common_iter_levels=1)
2048 CALL section_add_subsection(subsection, print_key)
2049 CALL section_release(print_key)
2050
2051 CALL cp_print_key_section_create(print_key, __location__, "CENTROID_POS", &
2052 description="Controls the output of the centroid's position", &
2053 unit_str="angstrom", &
2054 print_level=low_print_level, common_iter_levels=1)
2055 CALL add_format_keyword(keyword, print_key, pos=.true., &
2056 description="Output file format for the positions of centroid")
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_VEL", &
2061 description="Controls the output of the centroid's velocity", &
2062 unit_str="bohr*au_t^-1", &
2063 print_level=low_print_level, common_iter_levels=1)
2064 CALL add_format_keyword(keyword, print_key, pos=.false., &
2065 description="Output file format for the velocity 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_GYR", &
2070 description="Controls the output of the centroid's radii of gyration", &
2071 unit_str="angstrom", &
2072 print_level=low_print_level, common_iter_levels=1)
2073 CALL section_add_subsection(subsection, print_key)
2074 CALL section_release(print_key)
2075
2076 CALL cp_print_key_section_create(print_key, __location__, "COM", &
2077 description="Controls the output of the center of mass", &
2078 print_level=high_print_level, common_iter_levels=1)
2079 CALL section_add_subsection(subsection, print_key)
2080 CALL section_release(print_key)
2081
2082 CALL keyword_create(keyword, __location__, name="IMAGINARY_TIME_STRIDE", &
2083 description="Prints only every nth bead trajectory", &
2084 repeats=.false., default_i_val=1)
2085 CALL section_add_keyword(subsection, keyword)
2086 CALL keyword_release(keyword)
2087
2088 CALL section_add_subsection(section, subsection)
2089 CALL section_release(subsection)
2090
2091 END SUBROUTINE create_pint_section
2092
2093 ! ***************************************************************************
2094 !> \brief Create the input section for superfluid helium solvent.
2095 !> \author Lukasz Walewski
2096 ! ***************************************************************************
2097! **************************************************************************************************
2098!> \brief ...
2099!> \param section ...
2100! **************************************************************************************************
2101 SUBROUTINE create_helium_section(section)
2102 TYPE(section_type), POINTER :: section
2103
2104 TYPE(keyword_type), POINTER :: keyword
2105 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
2106
2107 cpassert(.NOT. ASSOCIATED(section))
2108
2109 CALL section_create(section, __location__, name="HELIUM", &
2110 description="The section that controls optional helium solvent"// &
2111 " environment (highly experimental, not for general use yet)", &
2112 n_keywords=31, n_subsections=11, repeats=.false.)
2113
2114 NULLIFY (keyword)
2115 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2116 description="Whether or not to actually use this section", &
2117 usage="silent", default_l_val=.false., lone_keyword_l_val=.true.)
2118 CALL section_add_keyword(section, keyword)
2119 CALL keyword_release(keyword)
2120
2121 CALL keyword_create(keyword, __location__, name="HELIUM_ONLY", &
2122 description="Simulate helium solvent only, "// &
2123 "disregard solute entirely", &
2124 repeats=.false., default_l_val=.false., &
2125 lone_keyword_l_val=.true.)
2126 CALL section_add_keyword(section, keyword)
2127 CALL keyword_release(keyword)
2128
2129 CALL keyword_create(keyword, __location__, name="INTERACTION_POT_SCAN", &
2130 description="Scan solute-helium interaction potential, "// &
2131 "cubefile parameters set in subsection RHO", &
2132 repeats=.false., default_l_val=.false., &
2133 lone_keyword_l_val=.true.)
2134 CALL section_add_keyword(section, keyword)
2135 CALL keyword_release(keyword)
2136
2137 CALL keyword_create(keyword, __location__, name="NUM_ENV", &
2138 description="Number of independent helium environments", &
2139 repeats=.false., default_i_val=1)
2140 CALL section_add_keyword(section, keyword)
2141 CALL keyword_release(keyword)
2142
2143 CALL keyword_create(keyword, __location__, name="POTENTIAL_FILE_NAME", &
2144 description="Name of the Helium interaction potential file", &
2145 repeats=.false., default_lc_val="HELIUM.POT")
2146 CALL section_add_keyword(section, keyword)
2147 CALL keyword_release(keyword)
2148
2149 CALL keyword_create(keyword, __location__, name="GET_FORCES", &
2150 description="Get average MC forces or last MC forces to propagate MD", &
2151 usage="GET_FORCES (AVERAGE|LAST)", &
2152 default_i_val=helium_forces_average, &
2153 enum_c_vals=s2a("AVERAGE", "LAST"), &
2155 CALL section_add_keyword(section, keyword)
2156 CALL keyword_release(keyword)
2157
2158 CALL keyword_create(keyword, __location__, name="SOLUTE_INTERACTION", &
2159 description="Interaction potential between helium and the solute", &
2160 usage="SOLUTE_INTERACTION (NONE | MWATER | NNP)", &
2161 default_i_val=helium_solute_intpot_none, &
2162 enum_c_vals=s2a("NONE", "MWATER", "NNP"), &
2163 enum_i_vals=(/ &
2167 enum_desc=s2a( &
2168 "No interaction with solute", &
2169 "Test interaction with wrong Water", &
2170 "Interaction with NNP"))
2171 CALL section_add_keyword(section, keyword)
2172 CALL keyword_release(keyword)
2173
2174 CALL keyword_create(keyword, __location__, name="NATOMS", &
2175 description="Number of helium atoms", &
2176 repeats=.false., default_i_val=64)
2177 CALL section_add_keyword(section, keyword)
2178 CALL keyword_release(keyword)
2179
2180 CALL keyword_create(keyword, __location__, name="NBEADS", &
2181 description="Number of helium path integral beads", &
2182 repeats=.false., default_i_val=25)
2183 CALL section_add_keyword(section, keyword)
2184 CALL keyword_release(keyword)
2185
2186 CALL keyword_create(keyword, __location__, name="RNG_SEED", &
2187 description="Initial seed for the (pseudo)random number "// &
2188 "generator that controls helium coordinate generation and propagation.", &
2189 usage="RNG_SEED <INTEGER>", default_i_val=12345, &
2190 repeats=.false.)
2191 CALL section_add_keyword(section, keyword)
2192 CALL keyword_release(keyword)
2193
2194 CALL keyword_create(keyword, __location__, name="N_INNER", &
2195 variants=s2a("INOROT"), &
2196 description="Number of MC iterations at the same time slice(s) "// &
2197 "(number of inner MC loop iterations)", &
2198 repeats=.false., default_i_val=6600)
2199 CALL section_add_keyword(section, keyword)
2200 CALL keyword_release(keyword)
2201
2202 CALL keyword_create(keyword, __location__, name="N_OUTER", &
2203 variants=s2a("IROT"), &
2204 description="how often to reselect the time slice(s) to work on "// &
2205 "(number of outer MC loop iterations)", &
2206 repeats=.false., default_i_val=300)
2207 CALL section_add_keyword(section, keyword)
2208 CALL keyword_release(keyword)
2209
2210 CALL keyword_create(keyword, __location__, name="SAMPLING_METHOD", &
2211 description="Choose between Ceperley or the worm algorithm", &
2212 usage="SAMPLING_METHOD (CEPERLEY|WORM)", &
2213 default_i_val=helium_sampling_ceperley, &
2214 enum_c_vals=s2a("CEPERLEY", "WORM"), &
2216 CALL section_add_keyword(section, keyword)
2217 CALL keyword_release(keyword)
2218
2219 CALL keyword_create(keyword, __location__, name="COORD_INIT_TEMP", &
2220 description="Temperature for thermal gaussian initialization of the helium."// &
2221 " Negative values correspond to a hot start.", &
2222 default_r_val=cp_unit_to_cp2k(300._dp, "K"), &
2223 unit_str="K")
2224 CALL section_add_keyword(section, keyword)
2225 CALL keyword_release(keyword)
2226
2227 CALL keyword_create(keyword, __location__, name="SOLUTE_RADIUS", &
2228 description="Radius of the solute molecule for prevention of"// &
2229 " coordinate collision during initialization", &
2230 default_r_val=cp_unit_to_cp2k(0.0_dp, "angstrom"), &
2231 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2232 CALL section_add_keyword(section, keyword)
2233 CALL keyword_release(keyword)
2234
2235 ! Helium-solute interaction NNP
2236 NULLIFY (subsection)
2237 CALL section_create(subsection, __location__, name="NNP", &
2238 description="This section contains all information to run an helium-solute "// &
2239 "interaction Neural Network Potential (NNP) calculation.", &
2240 n_keywords=2, n_subsections=3, repeats=.false.)
2241
2242 CALL keyword_create(keyword, __location__, name="NNP_INPUT_FILE_NAME", &
2243 description="File containing the input information for the setup "// &
2244 "of the NNP (n2p2/RuNNer format). ", &
2245 repeats=.false., default_lc_val="input.nn")
2246 CALL section_add_keyword(subsection, keyword)
2247 CALL keyword_release(keyword)
2248
2249 CALL keyword_create(keyword, __location__, name="SCALE_FILE_NAME", &
2250 description="File containing the scaling information for the symmetry "// &
2251 "functions of the NNP. ", &
2252 repeats=.false., default_lc_val="scaling.data")
2253 CALL section_add_keyword(subsection, keyword)
2254 CALL keyword_release(keyword)
2255
2256 NULLIFY (subsubsection)
2257 CALL section_create(subsubsection, __location__, name="SR_CUTOFF", &
2258 description="Section for failsafe short range cutoffs for the NNPs, "// &
2259 "if the distance between solvent and specified solute element becomes "// &
2260 "smaller than the given cutoff, an artifical repulsive potential is "// &
2261 "introduced. Note this is only meant to prevent such configurations, "// &
2262 "not to physically sample them.", &
2263 n_keywords=2, n_subsections=0, repeats=.true.)
2264
2265 CALL keyword_create(keyword, __location__, name="ELEMENT", &
2266 description="Solute element for which the short range cutoff is in effect", &
2267 repeats=.false., default_c_val="none")
2268 CALL section_add_keyword(subsubsection, keyword)
2269 CALL keyword_release(keyword)
2270
2271 CALL keyword_create(keyword, __location__, name="RADIUS", &
2272 description="Short range cutoff in Angstrom, below this cutoff, the energy "// &
2273 "is replaced by a sizable positive value plus a 1/r**2 term to guide particles "// &
2274 "away from each other.", &
2275 default_r_val=cp_unit_to_cp2k(0.0_dp, "angstrom"), &
2276 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2277 CALL section_add_keyword(subsubsection, keyword)
2278 CALL keyword_release(keyword)
2279 CALL section_add_subsection(subsection, subsubsection)
2280 CALL section_release(subsubsection)
2281
2282 NULLIFY (subsubsection)
2283 CALL section_create(subsubsection, __location__, name="MODEL", &
2284 description="Section for a single NNP model. If this section is repeated, "// &
2285 "a committee model (C-NNP)is used where the NNP members share the same "// &
2286 "symmetry functions. ", &
2287 n_keywords=1, n_subsections=0, repeats=.true.)
2288
2289 CALL keyword_create(keyword, __location__, name="WEIGHTS", &
2290 description="File containing the weights for the artificial neural "// &
2291 "networks of the NNP. The specified name is extended by .XXX.data ", &
2292 repeats=.false., default_lc_val="weights")
2293 CALL section_add_keyword(subsubsection, keyword)
2294 CALL keyword_release(keyword)
2295 CALL section_add_subsection(subsection, subsubsection)
2296 CALL section_release(subsubsection)
2297
2298 ! Create the PRINT subsection
2299 NULLIFY (subsubsection)
2300 CALL section_create(subsubsection, __location__, name="PRINT", &
2301 description="Section of possible print options in NNP code.", &
2302 n_keywords=0, n_subsections=3, repeats=.false.)
2303 NULLIFY (print_key, keyword)
2304
2305 CALL cp_print_key_section_create(print_key, __location__, "ENERGIES", &
2306 description="Controls the printing of the NNP energies.", &
2307 print_level=medium_print_level, common_iter_levels=1)
2308 CALL section_add_subsection(subsubsection, print_key)
2309 CALL section_release(print_key)
2310
2311 CALL cp_print_key_section_create(print_key, __location__, "FORCES_SIGMA", &
2312 description="Controls the printing of the STD per atom of the NNP forces.", &
2313 print_level=medium_print_level, common_iter_levels=1)
2314 CALL section_add_subsection(subsubsection, print_key)
2315 CALL section_release(print_key)
2316
2317 CALL cp_print_key_section_create(print_key, __location__, "EXTRAPOLATION", &
2318 description="If activated, output structures with extrapolation "// &
2319 "warning in xyz-format", &
2320 print_level=medium_print_level, common_iter_levels=1)
2321 CALL section_add_subsection(subsubsection, print_key)
2322 CALL section_release(print_key)
2323 CALL section_add_subsection(subsection, subsubsection)
2324 CALL section_release(subsubsection)
2325
2326 CALL section_add_subsection(section, subsection)
2327 CALL section_release(subsection) ! release NNP subsection
2328
2329 ! Ceperley's sampling algorithm
2330 NULLIFY (subsection)
2331 CALL section_create(subsection, __location__, name="CEPERLEY", &
2332 description="Enables sampling with Ceperley's algorithm", &
2333 n_keywords=2, n_subsections=1, repeats=.false.)
2334
2335 CALL keyword_create(keyword, __location__, name="BISECTION", &
2336 description="how many time slices to change at once (+1). "// &
2337 "Must be a power of 2 currently", &
2338 repeats=.false., default_i_val=8)
2339 CALL section_add_keyword(subsection, keyword)
2340 CALL keyword_release(keyword)
2341
2342 CALL keyword_create(keyword, __location__, name="MAX_PERM_CYCLE", &
2343 description="how large cyclic permutations to try", &
2344 repeats=.false., default_i_val=6)
2345 CALL section_add_keyword(subsection, keyword)
2346 CALL keyword_release(keyword)
2347
2348 NULLIFY (subsubsection)
2349 CALL section_create(subsubsection, __location__, name="M-SAMPLING", &
2350 description="Permutation cycle length sampling settings", &
2351 n_keywords=3, n_subsections=0, repeats=.false.)
2352 CALL keyword_create(keyword, __location__, name="DISTRIBUTION-TYPE", &
2353 description="Distribution from which the cycle length m is sampled", &
2354 usage="DISTRIBUTION-TYPE (SINGLEV|UNIFORM|LINEAR|QUADRATIC|EXPONENTIAL|GAUSSIAN)", &
2355 default_i_val=helium_mdist_uniform, &
2356 enum_c_vals=s2a( &
2357 "SINGLEV", &
2358 "UNIFORM", &
2359 "LINEAR", &
2360 "QUADRATIC", &
2361 "EXPONENTIAL", &
2362 "GAUSSIAN"), &
2363 enum_i_vals=(/ &
2370 CALL section_add_keyword(subsubsection, keyword)
2371 CALL keyword_release(keyword)
2372 CALL keyword_create(keyword, __location__, name="M-VALUE", &
2373 description="Value of m treated in a special way "// &
2374 "(specific behavior depends on the distribution type chosen)", &
2375 repeats=.false., &
2376 default_i_val=1)
2377 CALL section_add_keyword(subsubsection, keyword)
2378 CALL keyword_release(keyword)
2379 CALL keyword_create(keyword, __location__, name="M-RATIO", &
2380 description="Probability ratio betw M-VALUE and other cycle lengths", &
2381 repeats=.false., &
2382 default_r_val=1.0_dp)
2383 CALL section_add_keyword(subsubsection, keyword)
2384 CALL keyword_release(keyword)
2385 CALL section_add_subsection(subsection, subsubsection)
2386 CALL section_release(subsubsection)
2387 CALL section_add_subsection(section, subsection)
2388 CALL section_release(subsection) ! release CEPERLEY subsection
2389
2390! worm algorithm parameters:
2391 NULLIFY (subsection)
2392 CALL section_create(subsection, __location__, name="WORM", &
2393 description="Enables sampling via the canonical worm algorithm adapted from Bonisegni", &
2394 n_keywords=12, n_subsections=0, repeats=.false.)
2395
2396 CALL keyword_create(keyword, __location__, name="CENTROID_DRMAX", &
2397 description="Maximum displacement allowed for the centroid moves", &
2398 repeats=.false., default_r_val=0.5_dp)
2399 CALL section_add_keyword(subsection, keyword)
2400 CALL keyword_release(keyword)
2401
2402 CALL keyword_create(keyword, __location__, name="STAGING_L", &
2403 description="From 2 up to max. L-1 beads will be moved", &
2404 repeats=.false., default_i_val=5)
2405 CALL section_add_keyword(subsection, keyword)
2406 CALL keyword_release(keyword)
2407
2408 CALL keyword_create(keyword, __location__, name="OPEN_CLOSE_SCALE", &
2409 description="Open/Close acceptance adjustment parameter", &
2410 repeats=.false., default_r_val=0.01_dp)
2411 CALL section_add_keyword(subsection, keyword)
2412 CALL keyword_release(keyword)
2413
2414 CALL keyword_create(keyword, __location__, name="ALLOW_OPEN", &
2415 description="Enable bosonic exchange sampling", &
2416 repeats=.false., default_l_val=.true.)
2417 CALL section_add_keyword(subsection, keyword)
2418 CALL keyword_release(keyword)
2419
2420 CALL keyword_create(keyword, __location__, name="MAX_OPEN_CYCLES", &
2421 description="If > 0 then reset positions and permutations to the previous closed &
2422 & state if staying more than this amount of MC cycles in open state to avoid staying &
2423 & trapped in open state for too long. Use with caution as it can potentially introduce &
2424 & a bias in the sampling.", &
2425 repeats=.false., default_i_val=0)
2426 CALL section_add_keyword(subsection, keyword)
2427 CALL keyword_release(keyword)
2428
2429 CALL keyword_create(keyword, __location__, name="SHOW_STATISTICS", &
2430 description="Show sampling statistics in output", &
2431 repeats=.false., default_l_val=.true.)
2432 CALL section_add_keyword(subsection, keyword)
2433 CALL keyword_release(keyword)
2434
2435 CALL keyword_create(keyword, __location__, name="CENTROID_WEIGHT", &
2436 description="Absolute weight of the centroid move", &
2437 repeats=.false., default_i_val=10)
2438 CALL section_add_keyword(subsection, keyword)
2439 CALL keyword_release(keyword)
2440
2441 CALL keyword_create(keyword, __location__, name="STAGING_WEIGHT", &
2442 description="Absolute weight of the staging move", &
2443 repeats=.false., default_i_val=30)
2444 CALL section_add_keyword(subsection, keyword)
2445 CALL keyword_release(keyword)
2446
2447 CALL keyword_create(keyword, __location__, name="OPEN_CLOSE_WEIGHT", &
2448 description="Absolute weight of the open/close move", &
2449 repeats=.false., default_i_val=10)
2450 CALL section_add_keyword(subsection, keyword)
2451 CALL keyword_release(keyword)
2452
2453 CALL keyword_create(keyword, __location__, name="HEAD_TAIL_WEIGHT", &
2454 description="Absolute weight of the head/tail moves (both)", &
2455 repeats=.false., default_i_val=10)
2456 CALL section_add_keyword(subsection, keyword)
2457 CALL keyword_release(keyword)
2458
2459 CALL keyword_create(keyword, __location__, name="CRAWL_WEIGHT", &
2460 description="Absolute weight of the crawl bwd/fwd moves (both)", &
2461 repeats=.false., default_i_val=10)
2462 CALL section_add_keyword(subsection, keyword)
2463 CALL keyword_release(keyword)
2464
2465 CALL keyword_create(keyword, __location__, name="CRAWL_REPETITION", &
2466 description="Number of repeated crawl moves", &
2467 repeats=.false., default_i_val=4)
2468 CALL section_add_keyword(subsection, keyword)
2469 CALL keyword_release(keyword)
2470
2471 CALL keyword_create(keyword, __location__, name="SWAP_WEIGHT", &
2472 description="Absolute weight of the crawl move", &
2473 repeats=.false., default_i_val=10)
2474 CALL section_add_keyword(subsection, keyword)
2475 CALL keyword_release(keyword)
2476
2477 CALL section_add_subsection(section, subsection)
2478 CALL section_release(subsection) ! release WORM subsection
2479
2480! end of worm parameters
2481
2482 CALL keyword_create(keyword, __location__, name="PERIODIC", &
2483 description="Use periodic boundary conditions for helium", &
2484 repeats=.false., default_l_val=.false.)
2485 CALL section_add_keyword(section, keyword)
2486 CALL keyword_release(keyword)
2487
2488 CALL keyword_create(keyword, __location__, name="CELL_SIZE", &
2489 description="PBC unit cell size (NOTE 1: density, number of atoms"// &
2490 " and volume are interdependent - give only two of them; "// &
2491 "NOTE 2: for small cell sizes specify NATOMS instead)", &
2492 repeats=.false., type_of_var=real_t, unit_str="angstrom")
2493 CALL section_add_keyword(section, keyword)
2494 CALL keyword_release(keyword)
2495
2496 CALL keyword_create(keyword, __location__, name="CELL_SHAPE", &
2497 description="PBC unit cell shape for helium", &
2498 usage="CELL_SHAPE (CUBE|OCTAHEDRON)", &
2499 default_i_val=helium_cell_shape_cube, &
2500 enum_c_vals=s2a("CUBE", "OCTAHEDRON"), &
2502 CALL section_add_keyword(section, keyword)
2503 CALL keyword_release(keyword)
2504
2505 CALL keyword_create(keyword, __location__, name="DROPLET_RADIUS", &
2506 description="Reject a move if any of the new positions does not lie within"// &
2507 " this range from the center of gravity", &
2508 repeats=.false., type_of_var=real_t, default_r_val=huge(1.0_dp), &
2509 unit_str="angstrom")
2510 CALL section_add_keyword(section, keyword)
2511 CALL keyword_release(keyword)
2512
2513 CALL keyword_create(keyword, __location__, name="DENSITY", &
2514 description="trial density of helium for determining the helium "// &
2515 "box size", &
2516 repeats=.false., &
2517 default_r_val=cp_unit_to_cp2k(0.02186_dp, "angstrom^-3"), &
2518 unit_str="angstrom^-3")
2519 CALL section_add_keyword(section, keyword)
2520 CALL keyword_release(keyword)
2521
2522 CALL keyword_create(keyword, __location__, name="PRESAMPLE", &
2523 description="Presample He coordinates before first PIMD step", &
2524 repeats=.false., default_l_val=.false.)
2525 CALL section_add_keyword(section, keyword)
2526 CALL keyword_release(keyword)
2527
2528 CALL section_create(subsection, __location__, name="RDF", &
2529 description="Radial distribution settings", &
2530 n_keywords=5, n_subsections=0, repeats=.false.)
2531
2532 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2533 description="Whether or not to actually calculate this property", &
2534 default_l_val=.false., lone_keyword_l_val=.true.)
2535 CALL section_add_keyword(subsection, keyword)
2536 CALL keyword_release(keyword)
2537
2538 CALL keyword_create(keyword, __location__, name="MAXR", &
2539 description="Maximum RDF range, defaults to unit cell size", &
2540 repeats=.false., type_of_var=real_t, &
2541 unit_str="angstrom")
2542 CALL section_add_keyword(subsection, keyword)
2543 CALL keyword_release(keyword)
2544
2545 CALL keyword_create(keyword, __location__, name="NBIN", &
2546 description="Number of bins", &
2547 repeats=.false., &
2548 default_i_val=250)
2549 CALL section_add_keyword(subsection, keyword)
2550 CALL keyword_release(keyword)
2551
2552 CALL keyword_create(keyword, __location__, name="SOLUTE_HE", &
2553 description="Whether or not to calculate solute-He RDFs (if solute is present)", &
2554 default_l_val=.true., lone_keyword_l_val=.true.)
2555 CALL section_add_keyword(subsection, keyword)
2556 CALL keyword_release(keyword)
2557
2558 CALL keyword_create(keyword, __location__, name="HE_HE", &
2559 description="Whether or not to calculate He-He RDFs", &
2560 default_l_val=.false., lone_keyword_l_val=.true.)
2561 CALL section_add_keyword(subsection, keyword)
2562 CALL keyword_release(keyword)
2563
2564 CALL section_add_subsection(section, subsection)
2565 CALL section_release(subsection)
2566
2567 NULLIFY (subsection)
2568 CALL section_create(subsection, __location__, name="RHO", &
2569 description="Spatial distribution settings", &
2570 n_keywords=10, n_subsections=0, repeats=.false.)
2571 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
2572 description="Whether or not to actually calculate densities "// &
2573 "(requires significant amount of memory, depending on the value of NBIN)", &
2574 default_l_val=.false., lone_keyword_l_val=.true.)
2575 CALL section_add_keyword(subsection, keyword)
2576 CALL keyword_release(keyword)
2577 CALL keyword_create(keyword, __location__, name="NBIN", &
2578 description="Number of grid points in each direction for density binning", &
2579 repeats=.false., &
2580 default_i_val=100)
2581 CALL section_add_keyword(subsection, keyword)
2582 CALL keyword_release(keyword)
2583 !
2584 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_WDG", &
2585 description="Density of winding paths "// &
2586 "not shorter than the given length", &
2587 repeats=.false., usage="<INT> <INT> .. <INT>", &
2588 type_of_var=integer_t, n_var=-1)
2589 CALL section_add_keyword(subsection, keyword)
2590 CALL keyword_release(keyword)
2591 !
2592 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_NON", &
2593 description="Density of non-winding paths "// &
2594 "not shorter than the given length", &
2595 repeats=.false., usage="<INT> <INT> .. <INT>", &
2596 type_of_var=integer_t, n_var=-1)
2597 CALL section_add_keyword(subsection, keyword)
2598 CALL keyword_release(keyword)
2599 !
2600 CALL keyword_create(keyword, __location__, name="MIN_CYCLE_LENGTHS_ALL", &
2601 description="Density of all paths "// &
2602 "not shorter than the given length", &
2603 repeats=.false., usage="<INT> <INT> .. <INT>", &
2604 type_of_var=integer_t, n_var=-1)
2605 CALL section_add_keyword(subsection, keyword)
2606 CALL keyword_release(keyword)
2607 !
2608 CALL keyword_create(keyword, __location__, name="ATOM_NUMBER", &
2609 description="Atom number density", &
2610 repeats=.false., &
2611 type_of_var=logical_t, &
2612 default_l_val=.true., &
2613 lone_keyword_l_val=.true.)
2614 CALL section_add_keyword(subsection, keyword)
2615 CALL keyword_release(keyword)
2616 !
2617 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA_2", &
2618 description="Projected area squared density, A*A(r)", &
2619 repeats=.false., &
2620 type_of_var=logical_t, &
2621 default_l_val=.false., &
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="WINDING_NUMBER_2", &
2627 description="Winding number squared density, W*W(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_CYCLE_2", &
2636 description="Winding number squared density, W^2(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="MOMENT_OF_INERTIA", &
2645 description="Moment of inertia density", &
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 section_add_subsection(section, subsection)
2654 CALL section_release(subsection)
2655 ! end of subsection RHO
2656
2657 CALL create_coord_section(subsection, "HELIUM")
2658 CALL section_add_subsection(section, subsection)
2659 CALL section_release(subsection)
2660
2661 CALL section_create(subsection, __location__, name="PERM", &
2662 description="Permutation state used for restart", &
2663 n_keywords=1, n_subsections=0, repeats=.false.)
2664 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2665 description="Specify particle index permutation for every "// &
2666 "helium atom", repeats=.true., usage="<INT> <INT> .. <INT>", &
2667 type_of_var=integer_t, n_var=-1)
2668 CALL section_add_keyword(subsection, keyword)
2669 CALL keyword_release(keyword)
2670 CALL section_add_subsection(section, subsection)
2671 CALL section_release(subsection)
2672
2673 CALL section_create(subsection, __location__, name="AVERAGES", &
2674 description="Average properties (used for restarts)", &
2675 n_keywords=7, n_subsections=0, repeats=.false.)
2676 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA", &
2677 description="Projected area vector for all environments", &
2678 repeats=.true., usage="<REAL> <REAL> .. <REAL>", &
2679 type_of_var=real_t, n_var=-1)
2680 CALL section_add_keyword(subsection, keyword)
2681 CALL keyword_release(keyword)
2682 CALL keyword_create(keyword, __location__, name="PROJECTED_AREA_2", &
2683 description="Projected area vector squared for all environments", &
2684 repeats=.true., usage="<REAL> <REAL> .. <REAL>", &
2685 type_of_var=real_t, n_var=-1)
2686 CALL section_add_keyword(subsection, keyword)
2687 CALL keyword_release(keyword)
2688 CALL keyword_create(keyword, __location__, name="WINDING_NUMBER_2", &
2689 description="Winding number vector squared for all environments", &
2690 repeats=.true., usage="<REAL> <REAL> .. <REAL>", &
2691 type_of_var=real_t, n_var=-1)
2692 CALL section_add_keyword(subsection, keyword)
2693 CALL keyword_release(keyword)
2694 CALL keyword_create(keyword, __location__, name="MOMENT_OF_INERTIA", &
2695 description="Moment of inertia vector for all environments", &
2696 repeats=.true., usage="<REAL> <REAL> .. <REAL>", &
2697 type_of_var=real_t, n_var=-1)
2698 CALL section_add_keyword(subsection, keyword)
2699 CALL keyword_release(keyword)
2700 CALL keyword_create(keyword, __location__, name="RDF", &
2701 description="Radial distributions averaged over all environments", &
2702 repeats=.true., usage="<REAL> <REAL> .. <REAL>", &
2703 type_of_var=real_t, n_var=-1)
2704 CALL section_add_keyword(subsection, keyword)
2705 CALL keyword_release(keyword)
2706 CALL keyword_create(keyword, __location__, name="RHO", &
2707 description="Spatial distributions averaged over all environments", &
2708 repeats=.true., usage="<REAL> <REAL> .. <REAL>", &
2709 type_of_var=real_t, n_var=-1)
2710 CALL section_add_keyword(subsection, keyword)
2711 CALL keyword_release(keyword)
2712 CALL keyword_create(keyword, __location__, name="IWEIGHT", &
2713 description="Weight for the restarted quantities "// &
2714 "(number of MC steps used to calculate the accumulated averages)", &
2715 repeats=.false., &
2716 default_i_val=0)
2717 CALL section_add_keyword(subsection, keyword)
2718 CALL keyword_release(keyword)
2719 CALL section_add_subsection(section, subsection)
2720 CALL section_release(subsection)
2721
2722 CALL section_create(subsection, __location__, name="FORCE", &
2723 description="Forces exerted by the helium on the solute system"// &
2724 " (used for restarts)", &
2725 n_keywords=1, n_subsections=0, repeats=.false.)
2726 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2727 description="Number of real values should be 3 * "// &
2728 "<num_solute_atoms> * <num_solute_beads>", repeats=.true., &
2729 usage="<REAL> <REAL> .. <REAL>", type_of_var=real_t, &
2730 n_var=-1)
2731 CALL section_add_keyword(subsection, keyword)
2732 CALL keyword_release(keyword)
2733 CALL section_add_subsection(section, subsection)
2734 CALL section_release(subsection)
2735
2736 CALL section_create(subsection, __location__, name="RNG_STATE", &
2737 description="Random number generator state for all processors", &
2738 n_keywords=1, n_subsections=0, repeats=.false.)
2739 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
2740 description="Three real arrays of DIMENSION(3,2) times two RNG "// &
2741 "streams - 36 real values per processor", &
2742 repeats=.true., usage="automatically filled, do not edit by hand", &
2743 type_of_var=real_t, n_var=-1)
2744 CALL section_add_keyword(subsection, keyword)
2745 CALL keyword_release(keyword)
2746 CALL section_add_subsection(section, subsection)
2747 CALL section_release(subsection)
2748
2749 CALL section_create(subsection, __location__, name="PRINT", &
2750 description="The section that controls the output of the helium code", &
2751 n_keywords=16, n_subsections=0, repeats=.false.)
2752
2753 ! *************************************************************************
2754 !> Printkeys for properties output
2755 ! *************************************************************************
2756 NULLIFY (print_key)
2757
2758 ! Properties printed at SILENT print level
2759 !
2760
2761 ! Properties printed at LOW print level
2762 !
2763 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
2764 description="Controls the output of helium energies"// &
2765 " (averaged over MC step)", &
2766 print_level=low_print_level, common_iter_levels=1)
2767 CALL section_add_subsection(subsection, print_key)
2768 CALL section_release(print_key)
2769 !
2770 CALL cp_print_key_section_create(print_key, __location__, "PROJECTED_AREA_2_AVG", &
2771 description="Controls the output of the average projected area squared vector", &
2772 print_level=low_print_level, common_iter_levels=1)
2773 CALL section_add_subsection(subsection, print_key)
2774 CALL section_release(print_key)
2775 !
2776 CALL cp_print_key_section_create(print_key, __location__, "WINDING_NUMBER_2_AVG", &
2777 description="Controls the output of the average winding number vector squared", &
2778 print_level=low_print_level, common_iter_levels=1)
2779 CALL section_add_subsection(subsection, print_key)
2780 CALL section_release(print_key)
2781 !
2782 CALL cp_print_key_section_create(print_key, __location__, "MOMENT_OF_INERTIA_AVG", &
2783 description="Controls the output of the average moment of inertia vector", &
2784 print_level=low_print_level, common_iter_levels=1)
2785 CALL section_add_subsection(subsection, print_key)
2786 CALL section_release(print_key)
2787
2788 ! Properties printed at MEDIUM print level
2789 !
2790 CALL cp_print_key_section_create(print_key, __location__, "RDF", &
2791 description="Controls the output of helium radial distribution functions", &
2792 print_level=medium_print_level, common_iter_levels=1)
2793 CALL section_add_subsection(subsection, print_key)
2794 CALL section_release(print_key)
2795
2796 CALL cp_print_key_section_create(print_key, __location__, "RHO", &
2797 description="Controls the output of the helium density "// &
2798 "(Gaussian cube file format)", &
2799 each_iter_names=s2a("PINT"), each_iter_values=(/100/), &
2800 print_level=medium_print_level, common_iter_levels=1, &
2801 add_last=add_last_numeric)
2802 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
2803 description="Specifies the maximum number of backup copies.", &
2804 usage="BACKUP_COPIES {int}", &
2805 default_i_val=1)
2806 CALL section_add_keyword(print_key, keyword)
2807 CALL keyword_release(keyword)
2808 CALL section_add_subsection(subsection, print_key)
2809 CALL section_release(print_key)
2810 !
2811 CALL cp_print_key_section_create(print_key, __location__, "PROJECTED_AREA", &
2812 description="Controls the output of the projected area vector", &
2813 print_level=medium_print_level, common_iter_levels=1)
2814 CALL section_add_subsection(subsection, print_key)
2815 CALL section_release(print_key)
2816 !
2817 CALL cp_print_key_section_create(print_key, __location__, "WINDING_NUMBER", &
2818 description="Controls the output of the winding number vector", &
2819 print_level=medium_print_level, common_iter_levels=1)
2820 CALL section_add_subsection(subsection, print_key)
2821 CALL section_release(print_key)
2822 !
2823 CALL cp_print_key_section_create(print_key, __location__, "MOMENT_OF_INERTIA", &
2824 description="Controls the output of the moment of inertia vector", &
2825 print_level=medium_print_level, common_iter_levels=1)
2826 CALL section_add_subsection(subsection, print_key)
2827 CALL section_release(print_key)
2828 !
2829 CALL cp_print_key_section_create(print_key, __location__, "PLENGTH", &
2830 description="Controls the output of the helium permutation length", &
2831 print_level=medium_print_level, common_iter_levels=1)
2832 CALL section_add_subsection(subsection, print_key)
2833 CALL section_release(print_key)
2834
2835 CALL cp_print_key_section_create(print_key, __location__, "ACTION", &
2836 description="Controls the output of the total helium action", &
2837 print_level=medium_print_level, common_iter_levels=1)
2838 CALL section_add_subsection(subsection, print_key)
2839 CALL section_release(print_key)
2840
2841 ! Properties printed at HIGH print level
2842 !
2843 CALL cp_print_key_section_create(print_key, __location__, "COORDINATES", &
2844 description="Controls the output of helium coordinates", &
2845 print_level=high_print_level, common_iter_levels=1)
2846 CALL keyword_create(keyword, __location__, name="FORMAT", &
2847 description="Output file format for the coordinates", &
2848 usage="FORMAT (PDB|XYZ)", &
2849 default_i_val=fmt_id_pdb, &
2850 enum_c_vals=s2a("PDB", "XYZ"), &
2851 enum_i_vals=(/fmt_id_pdb, fmt_id_xyz/), &
2852 enum_desc=s2a("Bead coordinates and connectivity is written in PDB format", &
2853 "Only bead coordinates are written in XYZ format"))
2854 CALL section_add_keyword(print_key, keyword)
2855 CALL keyword_release(keyword)
2856 CALL section_add_subsection(subsection, print_key)
2857 CALL section_release(print_key)
2858 !
2859 CALL cp_print_key_section_create(print_key, __location__, "PERM", &
2860 description="Controls the output of the helium permutation state", &
2861 print_level=high_print_level, common_iter_levels=1)
2862 CALL keyword_create(keyword, __location__, name="FORMAT", &
2863 description="Output format for the permutation", &
2864 usage="FORMAT (CYCLE|PLAIN)", &
2865 default_i_val=perm_cycle, &
2866 enum_c_vals=s2a("CYCLE", "PLAIN"), &
2867 enum_i_vals=(/perm_cycle, perm_plain/), &
2868 enum_desc=s2a( &
2869 "Cycle notation with winding cycles enclosed"// &
2870 " in '[...]' and non-winding ones enclosed in '(...)'", &
2871 "Plain permutation output, i.e. P(1) ... P(N)"))
2872 CALL section_add_keyword(print_key, keyword)
2873 CALL keyword_release(keyword)
2874 CALL section_add_subsection(subsection, print_key)
2875 CALL section_release(print_key)
2876
2877 CALL cp_print_key_section_create(print_key, __location__, "FORCES", &
2878 description="Controls the output of the helium forces on the solute", &
2879 print_level=high_print_level, common_iter_levels=1)
2880 CALL section_add_subsection(subsection, print_key)
2881 CALL section_release(print_key)
2882
2883 ! Properties printed at DEBUG print level
2884 !
2885 CALL cp_print_key_section_create(print_key, __location__, "ACCEPTS", &
2886 description="Controls the output of the helium acceptance data", &
2887 print_level=debug_print_level, common_iter_levels=1)
2888 CALL section_add_subsection(subsection, print_key)
2889 CALL section_release(print_key)
2890 !
2891 CALL cp_print_key_section_create(print_key, __location__, "FORCES_INST", &
2892 description="Controls the output of the instantaneous helium forces on the solute", &
2893 print_level=debug_print_level, common_iter_levels=1)
2894 CALL section_add_subsection(subsection, print_key)
2895 CALL section_release(print_key)
2896
2897 CALL section_add_subsection(section, subsection)
2898 CALL section_release(subsection)
2899
2900 RETURN
2901 END SUBROUTINE create_helium_section
2902
2903END MODULE input_cp2k_motion
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public kapil2016
integer, save, public ceriotti2012
integer, save, public henkelman1999
integer, save, public ceriotti2010
integer, save, public henkelman2014
integer, save, public byrd1995
integer, save, public brieuc2016
integer, save, public ceriotti2014
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public add_last_numeric
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition cp_units.F:1150
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public propagator_cmd
integer, parameter, public default_cell_geo_opt_id
integer, parameter, public helium_solute_intpot_mwater
integer, parameter, public do_mc_virial
integer, parameter, public fix_xz
integer, parameter, public helium_forces_average
integer, parameter, public do_mc_gemc_nvt
integer, parameter, public helium_mdist_exponential
integer, parameter, public helium_sampling_ceperley
integer, parameter, public ls_3pnt
integer, parameter, public helium_cell_shape_octahedron
integer, parameter, public default_minimization_method_id
integer, parameter, public helium_solute_intpot_none
integer, parameter, public perm_cycle
integer, parameter, public propagator_rpmd
integer, parameter, public integrate_exact
integer, parameter, public default_ts_method_id
integer, parameter, public default_lbfgs_method_id
integer, parameter, public perm_plain
integer, parameter, public helium_forces_last
integer, parameter, public helium_mdist_gaussian
integer, parameter, public fix_y
integer, parameter, public fix_none
integer, parameter, public helium_mdist_quadratic
integer, parameter, public helium_mdist_uniform
integer, parameter, public fix_z
integer, parameter, public default_bfgs_method_id
integer, parameter, public default_cg_method_id
integer, parameter, public default_dimer_method_id
integer, parameter, public transformation_stage
integer, parameter, public helium_sampling_worm
integer, parameter, public matrix_init_cholesky
integer, parameter, public ls_2pnt
integer, parameter, public ls_none
integer, parameter, public default_cell_md_id
integer, parameter, public integrate_numeric
integer, parameter, public ls_fit
integer, parameter, public default_cell_direct_id
integer, parameter, public helium_mdist_singlev
integer, parameter, public ls_gold
integer, parameter, public propagator_pimd
integer, parameter, public do_mc_gemc_npt
integer, parameter, public helium_cell_shape_cube
integer, parameter, public fmt_id_pdb
integer, parameter, public gaussian
integer, parameter, public matrix_init_diagonal
integer, parameter, public fix_xy
integer, parameter, public do_mc_traditional
integer, parameter, public transformation_normal
integer, parameter, public helium_mdist_linear
integer, parameter, public helium_solute_intpot_nnp
integer, parameter, public fix_yz
integer, parameter, public fix_x
integer, parameter, public fmt_id_xyz
integer, parameter, public numerical
subroutine, public create_constraint_section(section)
Create the constraint section. This section is useful to impose constraints.
subroutine, public create_fe_section(section)
creates the free energy section
subroutine, public create_md_section(section)
...
subroutine, public add_format_keyword(keyword, section, pos, description)
creates the FORMAT keyword
subroutine, public create_motion_print_section(section)
creates the motionprint section
subroutine, public create_motion_section(section)
creates the motion section
subroutine, public create_band_section(section)
creates the section for a BAND run
builds the subsystem section of the input
subroutine, public create_rng_section(section)
Creates the random number restart section.
subroutine, public create_gle_section(section)
...
subroutine, public create_tmc_section(section)
creates the TreeMonteCarlo subsection
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
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