(git:30099c3)
Loading...
Searching...
No Matches
input_cp2k_check.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2026 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief checks the input and perform some automatic "magic" on it
10!> \par History
11!> 01.2006 created [fawzi]
12!> \author fawzi
13! **************************************************************************************************
19 USE cp_units, ONLY: cp_unit_set_create,&
22 USE input_constants, ONLY: &
30 USE input_section_types, ONLY: &
35 USE input_val_types, ONLY: logical_t
36 USE kinds, ONLY: default_path_length,&
38 dp
42#include "./base/base_uses.f90"
43
44 IMPLICIT NONE
45 PRIVATE
46
47 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
48 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_check'
49
51
52CONTAINS
53
54! **************************************************************************************************
55!> \brief performs further checks on an input that parsed successfully
56!> \param input_declaration ...
57!> \param input_file the parsed input
58!> \param para_env ...
59!> \param output_unit ...
60!> \author fawzi
61!> \note
62!> at the moment does nothing
63! **************************************************************************************************
64 SUBROUTINE check_cp2k_input(input_declaration, input_file, para_env, output_unit)
65 TYPE(section_type), POINTER :: input_declaration
66 TYPE(section_vals_type), POINTER :: input_file
67 TYPE(mp_para_env_type), POINTER :: para_env
68 INTEGER, INTENT(IN), OPTIONAL :: output_unit
69
70 CHARACTER(len=*), PARAMETER :: routinen = 'check_cp2k_input'
71
72 INTEGER :: force_eval_method, handle, iforce_eval, &
73 nforce_eval, run_type
74 LOGICAL :: apply_ext_potential, do_center, &
75 explicit, explicit_embed, explicit_mix
76 TYPE(section_vals_type), POINTER :: section, section1, section2, section3, &
77 section4, sections
78
79 CALL timeset(routinen, handle)
80 cpassert(ASSOCIATED(input_file))
81 cpassert(input_file%ref_count > 0)
82 ! ext_restart
83 IF (PRESENT(output_unit)) &
84 CALL handle_ext_restart(input_declaration, input_file, para_env, output_unit)
85
86 ! checks on force_eval section
87 sections => section_vals_get_subs_vals(input_file, "FORCE_EVAL")
88 CALL section_vals_get(sections, n_repetition=nforce_eval)
89
90 ! multiple force_eval only if present RESPA, or MIXED or EMBED calculation is performed
91 section2 => section_vals_get_subs_vals(input_file, "MOTION%MD%RESPA")
92 CALL section_vals_get(section2, explicit=explicit)
93 DO iforce_eval = 1, nforce_eval
94 section3 => section_vals_get_subs_vals(sections, "MIXED", &
95 i_rep_section=iforce_eval)
96 CALL section_vals_get(section3, explicit=explicit_mix)
97 IF (explicit_mix) EXIT
98 END DO
99 DO iforce_eval = 1, nforce_eval
100 section4 => section_vals_get_subs_vals(sections, "EMBED", &
101 i_rep_section=iforce_eval)
102 CALL section_vals_get(section4, explicit=explicit_embed)
103 IF (explicit_embed) EXIT
104 END DO
105 ! also allow multiple force_eval for NEGF run
106 CALL section_vals_val_get(input_file, "GLOBAL%RUN_TYPE", i_val=run_type)
107
108 IF (((explicit .AND. (nforce_eval == 1)) .OR. (.NOT. explicit .AND. (nforce_eval > 1))) .AND. run_type /= negf_run) THEN
109 IF ((explicit_mix .AND. (nforce_eval == 1)) .OR. (.NOT. explicit_mix .AND. (nforce_eval > 1))) THEN
110 IF ((explicit_embed .AND. (nforce_eval == 1)) .OR. (.NOT. explicit_embed .AND. (nforce_eval > 1))) THEN
111 CALL cp_abort(__location__, &
112 "Error multiple force_env without RESPA or MIXED or EMBED, or RESPA with one single "// &
113 "or MIXED with only two force_env section.")
114 END IF
115 END IF
116 END IF
117 DO iforce_eval = 1, nforce_eval
118 section => section_vals_get_subs_vals3(sections, "DFT", i_rep_section=iforce_eval)
119 ! xc: expand and fix default for tddfpt
120 section1 => section_vals_get_subs_vals(section, "XC")
121 section2 => section_vals_get_subs_vals(section, "XC%XC_FUNCTIONAL")
122 CALL xc_functionals_expand(section2, section1)
123 section1 => section_vals_get_subs_vals(section, "XAS_TDP%KERNEL")
124 section2 => section_vals_get_subs_vals(section, "XAS_TDP%KERNEL%XC_FUNCTIONAL")
125 CALL xc_functionals_expand(section2, section1)
126 section1 => section_vals_get_subs_vals(sections, "PROPERTIES%RIXS%XAS_TDP%KERNEL")
127 section2 => section_vals_get_subs_vals(sections, "PROPERTIES%RIXS%XAS_TDP%KERNEL%XC_FUNCTIONAL")
128 CALL xc_functionals_expand(section2, section1)
129 section1 => section_vals_get_subs_vals(section, "ACTIVE_SPACE%XC")
130 section2 => section_vals_get_subs_vals(section, "ACTIVE_SPACE%XC%XC_FUNCTIONAL")
131 CALL xc_functionals_expand(section2, section1)
132 END DO
133
134 ! additional checks for a MiMiC run
135 IF (run_type == mimic_run) THEN
136 ! disable CENTER_COORDINATES
137 CALL section_vals_val_get(sections, "SUBSYS%TOPOLOGY%CENTER_COORDINATES%_SECTION_PARAMETERS_", &
138 l_val=do_center)
139 IF (do_center) THEN
140 CALL section_vals_val_set(sections, &
141 "SUBSYS%TOPOLOGY%CENTER_COORDINATES%_SECTION_PARAMETERS_", &
142 l_val=.false.)
143 cpwarn("Turning off CENTER_COORDINATES for a MiMiC run.")
144 END IF
145
146 ! do not allow the use of external potential
147 section => section_vals_get_subs_vals(sections, "DFT%EXTERNAL_POTENTIAL")
148 CALL section_vals_get(section, explicit=apply_ext_potential)
149 IF (apply_ext_potential) &
150 cpabort("The EXTERNAL_POTENTIAL section is not allowed for the MiMiC runtype.")
151
152 ! force eval methods supported with MiMiC
153 CALL section_vals_val_get(sections, "METHOD", i_val=force_eval_method)
154 IF (force_eval_method /= do_qs) &
155 cpabort("At the moment, only Quickstep method is supported with MiMiC.")
156 END IF
157
158 CALL timestop(handle)
159 END SUBROUTINE check_cp2k_input
160
161! **************************************************************************************************
162!> \brief expand a shortcutted functional section
163!> \param functionals the functional section to expand
164!> \param xc_section ...
165!> \author fawzi
166! **************************************************************************************************
167 SUBROUTINE xc_functionals_expand(functionals, xc_section)
168 TYPE(section_vals_type), POINTER :: functionals, xc_section
169
170 CHARACTER(LEN=512) :: wrn_msg
171 INTEGER :: ifun, nfun, shortcut
172 TYPE(section_vals_type), POINTER :: xc_fun
173
174 CALL section_vals_val_get(functionals, "_SECTION_PARAMETERS_", &
175 i_val=shortcut)
176
177 ifun = 0
178 nfun = 0
179 DO
180 ifun = ifun + 1
181 xc_fun => section_vals_get_subs_vals2(functionals, i_section=ifun)
182 IF (.NOT. ASSOCIATED(xc_fun)) EXIT
183 nfun = nfun + 1
184 END DO
185!
186 IF (shortcut /= xc_funct_no_shortcut .AND. shortcut /= xc_none .AND. nfun > 0) THEN
187 WRITE (wrn_msg, '(A)') "User requested a shortcut while defining an explicit XC functional. "// &
188 "This is not recommended as it could lead to spurious behaviour. Please check input parameters."
189 cpwarn(wrn_msg)
190 END IF
191
192 SELECT CASE (shortcut)
194 ! nothing to expand
195 CASE (xc_funct_pbe0)
196 CALL section_vals_val_set(functionals, "PBE%_SECTION_PARAMETERS_", &
197 l_val=.true.)
198 CALL section_vals_val_set(functionals, "PBE%SCALE_X", &
199 r_val=0.75_dp)
200 CALL section_vals_val_set(functionals, "PBE%SCALE_C", &
201 r_val=1.0_dp)
202 ! Hartree Fock Exact Exchange
203 CALL section_vals_val_set(xc_section, "HF%FRACTION", &
204 r_val=0.25_dp)
205 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
207 CASE (xc_funct_beefvdw)
208 CALL section_vals_val_set(functionals, "PBE%_SECTION_PARAMETERS_", & !40% PBEc
209 l_val=.true.)
210 CALL section_vals_val_set(functionals, "PBE%SCALE_C", &
211 r_val=0.3998335231_dp)
212 CALL section_vals_val_set(functionals, "PBE%SCALE_X", & !no PBEx
213 r_val=0.0000000000_dp)
214
215 !PW92 correlation functional from libxc is required.
216 !The cp2k-native PW92 gives disagreeing results (in the 0.01E_H
217 !decimal) and yields inconsistent forces in a DEBUG run.
218 !(rk, 6.3.2014)
219 CALL section_vals_val_set(functionals, "LDA_C_PW%_SECTION_PARAMETERS_", & !60%LDA
220 l_val=.true.)
221 CALL section_vals_val_set(functionals, "LDA_C_PW%SCALE", &
222 r_val=0.6001664769_dp)
223
224 CALL section_vals_val_set(functionals, "BEEF%_SECTION_PARAMETERS_", & !BEEF exchange
225 l_val=.true.)
226
227 !NONLOCAL, LMKLL.
228 CALL section_vals_val_set(xc_section, "VDW_POTENTIAL%DISPERSION_FUNCTIONAL", &
229 i_val=xc_vdw_fun_nonloc)
230 CALL section_vals_val_set(xc_section, "VDW_POTENTIAL%NON_LOCAL%TYPE", &
231 i_val=vdw_nl_lmkll)
232 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
234 CASE (xc_funct_b3lyp)
235 CALL section_vals_val_set(functionals, "BECKE88%_SECTION_PARAMETERS_", &
236 l_val=.true.)
237 CALL section_vals_val_set(functionals, "BECKE88%SCALE_X", &
238 r_val=0.72_dp)
239 CALL section_vals_val_set(functionals, "LYP%_SECTION_PARAMETERS_", &
240 l_val=.true.)
241 CALL section_vals_val_set(functionals, "LYP%SCALE_C", &
242 r_val=0.81_dp)
243 CALL section_vals_val_set(functionals, "VWN%_SECTION_PARAMETERS_", &
244 l_val=.true.)
245 CALL section_vals_val_set(functionals, "VWN%FUNCTIONAL_TYPE", &
246 i_val=do_vwn5)
247 CALL section_vals_val_set(functionals, "VWN%SCALE_C", &
248 r_val=0.19_dp)
249 CALL section_vals_val_set(functionals, "XALPHA%_SECTION_PARAMETERS_", &
250 l_val=.true.)
251 CALL section_vals_val_set(functionals, "XALPHA%SCALE_X", &
252 r_val=0.08_dp)
253 ! Hartree Fock Exact Exchange
254 CALL section_vals_val_set(xc_section, "HF%FRACTION", &
255 r_val=0.20_dp)
256 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
258 CASE (xc_funct_blyp)
259 CALL section_vals_val_set(functionals, "BECKE88%_SECTION_PARAMETERS_", &
260 l_val=.true.)
261 CALL section_vals_val_set(functionals, "LYP%_SECTION_PARAMETERS_", &
262 l_val=.true.)
263 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
265 CASE (xc_funct_bp)
266 CALL section_vals_val_set(functionals, "BECKE88%_SECTION_PARAMETERS_", &
267 l_val=.true.)
268 CALL section_vals_val_set(functionals, "P86C%_SECTION_PARAMETERS_", &
269 l_val=.true.)
270 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
272 CASE (xc_funct_pade)
273 CALL section_vals_val_set(functionals, "PADE%_SECTION_PARAMETERS_", &
274 l_val=.true.)
275 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
277 CASE (xc_funct_pbe)
278 CALL section_vals_val_set(functionals, "PBE%_SECTION_PARAMETERS_", &
279 l_val=.true.)
280 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
282 CASE (xc_funct_xwpbe)
283 CALL section_vals_val_set(functionals, "XWPBE%_SECTION_PARAMETERS_", &
284 l_val=.true.)
285 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
287 CASE (xc_funct_tpss)
288 CALL section_vals_val_set(functionals, "TPSS%_SECTION_PARAMETERS_", &
289 l_val=.true.)
290 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
292 CASE (xc_funct_olyp)
293 CALL section_vals_val_set(functionals, "OPTX%_SECTION_PARAMETERS_", &
294 l_val=.true.)
295 CALL section_vals_val_set(functionals, "LYP%_SECTION_PARAMETERS_", &
296 l_val=.true.)
297 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
299 CASE (xc_funct_hcth120)
300 CALL section_vals_val_set(functionals, "HCTH%_SECTION_PARAMETERS_", &
301 l_val=.true.)
302 CALL section_vals_val_set(functionals, "HCTH%PARAMETER_SET", &
303 i_val=120)
304 CALL section_vals_val_set(functionals, "_SECTION_PARAMETERS_", &
306 CASE default
307 cpabort("unknown shortcut "//trim(adjustl(cp_to_string(shortcut))))
308 END SELECT
309 END SUBROUTINE xc_functionals_expand
310
311! **************************************************************************************************
312!> \brief Replaces the requested sections in the input with those found
313!> in the external restart (EXT_RESTART%RESTART_FILE_NAME).
314!> \param input_declaration ...
315!> \param input_file the input file to initialize
316!> \param para_env ...
317!> \param output_unit ...
318!> \author fawzi
319! **************************************************************************************************
320 SUBROUTINE handle_ext_restart(input_declaration, input_file, para_env, output_unit)
321 TYPE(section_type), POINTER :: input_declaration
322 TYPE(section_vals_type), POINTER :: input_file
323 TYPE(mp_para_env_type), POINTER :: para_env
324 INTEGER, INTENT(IN) :: output_unit
325
326 CHARACTER(len=*), PARAMETER :: routinen = 'handle_ext_restart'
327
328 CHARACTER(default_path_length) :: r_file_path
329 INTEGER :: handle
330 TYPE(section_vals_type), POINTER :: r_section
331
332 CALL timeset(routinen, handle)
333 ! Handle restart file
334 r_section => section_vals_get_subs_vals(input_file, "EXT_RESTART")
335 CALL section_vals_val_get(r_section, "RESTART_FILE_NAME", c_val=r_file_path)
336
337 IF (r_file_path /= " ") THEN
338 block
339 CHARACTER(default_path_length) :: binary_restart_file
340 CHARACTER(default_string_length) :: path
341 CHARACTER(LEN=default_string_length), &
342 DIMENSION(:), POINTER :: restarted_infos
343 INTEGER :: ensemble, i_rep_val, &
344 iforce_eval, myi, n_rep_val, &
345 nforce_eval1, nforce_eval2
346 INTEGER, DIMENSION(:), POINTER :: ivec, iwalkers_status, iwork, &
347 rwalkers_status
348 LOGICAL :: bsse_check, check, explicit1, explicit2, &
349 flag, flag2, qmmm_check, subsys_check
350 REAL(kind=dp) :: myt
351 REAL(kind=dp), DIMENSION(:), POINTER :: vec, work
352 TYPE(section_vals_type), POINTER :: rep_sections, restart_file, &
353 section, section1, section2, &
354 sections1, sections2
355
356 NULLIFY (restarted_infos, iwalkers_status, rwalkers_status, vec, ivec, work, iwork)
357 CALL section_vals_val_get(r_section, "BINARY_RESTART_FILE_NAME", c_val=binary_restart_file)
358
359 block
360 TYPE(cp_parser_type) :: cpparser
361 TYPE(cp_unit_set_type) :: default_units
362 ! parse the input
363 NULLIFY (restart_file)
364 CALL section_vals_create(restart_file, input_declaration)
365 CALL parser_create(cpparser, file_name=r_file_path, para_env=para_env)
366 CALL cp_unit_set_create(default_units, "OUTPUT")
367 CALL section_vals_parse(restart_file, cpparser, root_section=.false., &
368 default_units=default_units)
369 CALL cp_unit_set_release(default_units)
370 CALL parser_release(cpparser)
371 END block
372
373 ! Restart and input files same number of force_env sections
374 sections1 => section_vals_get_subs_vals(restart_file, "FORCE_EVAL")
375 CALL section_vals_get(sections1, n_repetition=nforce_eval1)
376 sections2 => section_vals_get_subs_vals(input_file, "FORCE_EVAL")
377 CALL section_vals_get(sections2, n_repetition=nforce_eval2)
378 IF (nforce_eval1 /= nforce_eval2) THEN
379 cpabort("Restart and input file MUST have the number of force_env sections")
380 END IF
381 ! Handle default restarts
382 CALL handle_defaults_restart(r_section)
383
384 ! Real restart of force_evals
385 DO iforce_eval = 1, nforce_eval1
386 section1 => section_vals_get_subs_vals3(sections1, "SUBSYS", &
387 i_rep_section=iforce_eval)
388 section2 => section_vals_get_subs_vals3(sections2, "SUBSYS", &
389 i_rep_section=iforce_eval)
390 ! Some care needs to be handled when treating multiple force_eval
391 ! Both subsys need to be consistently associated or not
392 ! Mixed stuff will be rejected for safety reason..
393 subsys_check = (ASSOCIATED(section1) .EQV. ASSOCIATED(section2))
394 IF (subsys_check) THEN
395 IF (ASSOCIATED(section1)) THEN
396 CALL section_vals_val_get(r_section, "RESTART_CELL", l_val=flag)
397 IF (flag) THEN
398 section => section_vals_get_subs_vals(section1, "CELL")
399 CALL section_vals_set_subs_vals(section2, "CELL", section)
400 CALL set_restart_info("CELL", restarted_infos)
401 END IF
402
403 CALL section_vals_val_get(r_section, "RESTART_POS", l_val=flag)
404 IF (flag) THEN
405 section => section_vals_get_subs_vals(section1, "COORD")
406 CALL section_vals_set_subs_vals(section2, "COORD", section)
407 CALL set_restart_info("COORDINATES", restarted_infos)
408 ! Copy over also the information on the multiple_unit_cell
409 CALL section_vals_val_get(section1, "TOPOLOGY%MULTIPLE_UNIT_CELL", i_vals=ivec)
410 ALLOCATE (iwork(3))
411 iwork = ivec
412 CALL section_vals_val_set(section2, "TOPOLOGY%MULTIPLE_UNIT_CELL", i_vals_ptr=iwork)
413 END IF
414
415 CALL section_vals_val_get(r_section, "RESTART_RANDOMG", l_val=flag)
416 IF (flag) THEN
417 section => section_vals_get_subs_vals(section1, "RNG_INIT")
418 CALL section_vals_set_subs_vals(section2, "RNG_INIT", section)
419 CALL set_restart_info("RANDOM NUMBER GENERATOR", restarted_infos)
420 END IF
421
422 CALL section_vals_val_get(r_section, "RESTART_VEL", l_val=flag)
423 IF (flag) THEN
424 section => section_vals_get_subs_vals(section1, "VELOCITY")
425 CALL section_vals_set_subs_vals(section2, "VELOCITY", section)
426 CALL set_restart_info("VELOCITIES", restarted_infos)
427 END IF
428
429 ! Core-Shell information "restarted" only when strictly necessary
430 CALL section_vals_val_get(r_section, "RESTART_SHELL_POS", l_val=flag)
431 IF (flag) THEN
432 section => section_vals_get_subs_vals(section1, "SHELL_COORD")
433 CALL section_vals_set_subs_vals(section2, "SHELL_COORD", section)
434 IF (check_restart(section1, section2, "SHELL_COORD")) &
435 CALL set_restart_info("SHELL COORDINATES", restarted_infos)
436 END IF
437 CALL section_vals_val_get(r_section, "RESTART_CORE_POS", l_val=flag)
438 IF (flag) THEN
439 section => section_vals_get_subs_vals(section1, "CORE_COORD")
440 CALL section_vals_set_subs_vals(section2, "CORE_COORD", section)
441 IF (check_restart(section1, section2, "CORE_COORD")) &
442 CALL set_restart_info("CORE COORDINATES", restarted_infos)
443 END IF
444 CALL section_vals_val_get(r_section, "RESTART_SHELL_VELOCITY", l_val=flag)
445 IF (flag) THEN
446 section => section_vals_get_subs_vals(section1, "SHELL_VELOCITY")
447 CALL section_vals_set_subs_vals(section2, "SHELL_VELOCITY", section)
448 IF (check_restart(section1, section2, "SHELL_VELOCITY")) &
449 CALL set_restart_info("SHELL VELOCITIES", restarted_infos)
450 END IF
451 CALL section_vals_val_get(r_section, "RESTART_CORE_VELOCITY", l_val=flag)
452 IF (flag) THEN
453 section => section_vals_get_subs_vals(section1, "CORE_VELOCITY")
454 CALL section_vals_set_subs_vals(section2, "CORE_VELOCITY", section)
455 IF (check_restart(section1, section2, "CORE_VELOCITY")) &
456 CALL set_restart_info("CORE VELOCITIES", restarted_infos)
457 END IF
458 END IF
459 ELSE
460 CALL cp_abort(__location__, &
461 "Error while reading the restart file. Two force_eval have incompatible"// &
462 " subsys.One of them has an allocated subsys while the other has not! Check your"// &
463 " input file or whether the restart file is compatible with the input!")
464 END IF
465 ! QMMM restarts
466 CALL section_vals_val_get(r_section, "RESTART_QMMM", l_val=flag)
467 section1 => section_vals_get_subs_vals3(sections1, "QMMM", i_rep_section=iforce_eval)
468 section2 => section_vals_get_subs_vals3(sections2, "QMMM", i_rep_section=iforce_eval)
469 CALL section_vals_get(section1, explicit=explicit1)
470 CALL section_vals_get(section2, explicit=explicit2)
471 qmmm_check = (explicit1 .AND. explicit2)
472 IF (flag .AND. qmmm_check) THEN
473 CALL set_restart_info("QMMM TRANSLATION VECTOR", restarted_infos)
474 CALL section_vals_val_get(section1, "INITIAL_TRANSLATION_VECTOR", r_vals=vec)
475 ALLOCATE (work(3))
476 work = vec
477 CALL section_vals_val_set(section2, "INITIAL_TRANSLATION_VECTOR", r_vals_ptr=work)
478 END IF
479 ! BSSE restarts
480 CALL section_vals_val_get(r_section, "RESTART_BSSE", l_val=flag)
481 section1 => section_vals_get_subs_vals3(sections1, "BSSE", i_rep_section=iforce_eval)
482 section2 => section_vals_get_subs_vals3(sections2, "BSSE", i_rep_section=iforce_eval)
483 CALL section_vals_get(section1, explicit=explicit1)
484 CALL section_vals_get(section2, explicit=explicit2)
485 bsse_check = (explicit1 .AND. explicit2)
486 IF (flag .AND. bsse_check) THEN
487 section => section_vals_get_subs_vals(section1, "FRAGMENT_ENERGIES")
488 CALL section_vals_set_subs_vals(section2, "FRAGMENT_ENERGIES", section)
489 CALL set_restart_info("BSSE FRAGMENT ENERGIES", restarted_infos)
490 END IF
491 END DO
492
493 CALL section_vals_val_get(r_section, "RESTART_COUNTERS", l_val=flag)
494 IF (flag) THEN
495 IF (check_restart(input_file, restart_file, "MOTION%MD")) THEN
496 CALL section_vals_val_get(restart_file, "MOTION%MD%STEP_START_VAL", i_val=myi)
497 CALL section_vals_val_set(input_file, "MOTION%MD%STEP_START_VAL", i_val=myi)
498 CALL section_vals_val_get(restart_file, "MOTION%MD%TIME_START_VAL", r_val=myt)
499 CALL section_vals_val_set(input_file, "MOTION%MD%TIME_START_VAL", r_val=myt)
500 CALL section_vals_val_get(restart_file, "MOTION%MD%ECONS_START_VAL", r_val=myt)
501 CALL section_vals_val_set(input_file, "MOTION%MD%ECONS_START_VAL", r_val=myt)
502 CALL set_restart_info("MD COUNTERS", restarted_infos)
503 END IF
504 !
505 IF (check_restart(input_file, restart_file, "MOTION%GEO_OPT")) THEN
506 ! GEO_OPT
507 CALL section_vals_val_get(restart_file, "MOTION%GEO_OPT%STEP_START_VAL", i_val=myi)
508 CALL section_vals_val_set(input_file, "MOTION%GEO_OPT%STEP_START_VAL", i_val=myi)
509 CALL set_restart_info("GEO_OPT COUNTERS", restarted_infos)
510 ! ROT_OPT
511 IF (check_restart(input_file, restart_file, "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT")) THEN
512 CALL section_vals_val_get(restart_file, "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT%STEP_START_VAL", &
513 i_val=myi)
514 CALL section_vals_val_set(input_file, "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT%STEP_START_VAL", &
515 i_val=myi)
516 CALL set_restart_info("ROT_OPT COUNTERS", restarted_infos)
517 END IF
518 END IF
519 !
520 IF (check_restart(input_file, restart_file, "MOTION%GEO_OPT")) THEN
521 ! CELL_OPT
522 CALL section_vals_val_get(restart_file, "MOTION%CELL_OPT%STEP_START_VAL", i_val=myi)
523 CALL section_vals_val_set(input_file, "MOTION%CELL_OPT%STEP_START_VAL", i_val=myi)
524 CALL set_restart_info("CELL_OPT COUNTERS", restarted_infos)
525 END IF
526 !
527 IF (check_restart(input_file, restart_file, "OPTIMIZE_INPUT")) THEN
528 CALL section_vals_val_get(restart_file, "OPTIMIZE_INPUT%ITER_START_VAL", i_val=myi)
529 CALL section_vals_val_set(input_file, "OPTIMIZE_INPUT%ITER_START_VAL", i_val=myi)
530 CALL set_restart_info("OPTIMIZE_INPUT ITERATION NUMBER", restarted_infos)
531 END IF
532 !
533 IF (check_restart(input_file, restart_file, "MOTION%PINT")) THEN
534 ! PINT
535 CALL section_vals_val_get(restart_file, "MOTION%PINT%ITERATION", i_val=myi)
536 CALL section_vals_val_set(input_file, "MOTION%PINT%ITERATION", i_val=myi)
537 CALL set_restart_info("PINT ITERATION NUMBER", restarted_infos)
538 END IF
539 !
540 CALL section_vals_val_get(r_section, "RESTART_METADYNAMICS", l_val=flag2)
541 IF (flag2 .AND. check_restart(input_file, restart_file, "MOTION%FREE_ENERGY%METADYN")) THEN
542 CALL section_vals_val_get(restart_file, &
543 "MOTION%FREE_ENERGY%METADYN%STEP_START_VAL", i_val=myi)
544 CALL section_vals_val_set(input_file, &
545 "MOTION%FREE_ENERGY%METADYN%STEP_START_VAL", i_val=myi)
546 CALL section_vals_val_get(restart_file, &
547 "MOTION%FREE_ENERGY%METADYN%NHILLS_START_VAL", i_val=myi)
548 CALL section_vals_val_set(input_file, &
549 "MOTION%FREE_ENERGY%METADYN%NHILLS_START_VAL", i_val=myi)
550 !RG Adaptive hills
551 CALL section_vals_val_get(restart_file, &
552 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_NUMBER", i_val=myi)
553 CALL section_vals_val_set(input_file, &
554 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_NUMBER", i_val=myi)
555 CALL section_vals_val_get(restart_file, &
556 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_STEP", i_val=myi)
557 CALL section_vals_val_set(input_file, &
558 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_STEP", i_val=myi)
559 !RG Adaptive hills
560 CALL set_restart_info("METADYNAMIC COUNTERS", restarted_infos)
561 END IF
562 END IF
563
564 CALL section_vals_val_get(r_section, "RESTART_AVERAGES", l_val=flag)
565 IF (flag) THEN
566 IF (check_restart(input_file, restart_file, "MOTION%MD")) THEN
567 rep_sections => section_vals_get_subs_vals(restart_file, "MOTION%MD%AVERAGES%RESTART_AVERAGES")
568 CALL section_vals_set_subs_vals(input_file, "MOTION%MD%AVERAGES%RESTART_AVERAGES", rep_sections)
569 CALL set_restart_info("MD AVERAGES", restarted_infos)
570 END IF
571 END IF
572
573 CALL section_vals_val_get(r_section, "RESTART_BAND", l_val=flag)
574 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%BAND")) THEN
575 rep_sections => section_vals_get_subs_vals(restart_file, "MOTION%BAND%REPLICA")
576 CALL section_vals_set_subs_vals(input_file, "MOTION%BAND%REPLICA", rep_sections)
577 CALL set_restart_info("BAND CALCULATION", restarted_infos)
578 END IF
579
580 CALL section_vals_val_get(r_section, "RESTART_OPTIMIZE_INPUT_VARIABLES", l_val=flag)
581 IF (flag .AND. check_restart(input_file, restart_file, "OPTIMIZE_INPUT%VARIABLE")) THEN
582 rep_sections => section_vals_get_subs_vals(restart_file, "OPTIMIZE_INPUT%VARIABLE")
583 CALL section_vals_set_subs_vals(input_file, "OPTIMIZE_INPUT%VARIABLE", rep_sections)
584 CALL set_restart_info("OPTIMIZE_INPUT: VARIABLES", restarted_infos)
585 END IF
586
587 CALL section_vals_val_get(r_section, "RESTART_BAROSTAT", l_val=flag)
588 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%MD%BAROSTAT")) THEN
589 section => section_vals_get_subs_vals(restart_file, &
590 "MOTION%MD%BAROSTAT%MASS")
591 CALL section_vals_set_subs_vals(input_file, "MOTION%MD%BAROSTAT%MASS", &
592 section)
593 section => section_vals_get_subs_vals(restart_file, &
594 "MOTION%MD%BAROSTAT%VELOCITY")
595 CALL section_vals_set_subs_vals(input_file, "MOTION%MD%BAROSTAT%VELOCITY", &
596 section)
597 CALL set_restart_info("BAROSTAT", restarted_infos)
598 END IF
599
600 flag = check_restart(input_file, restart_file, "MOTION%MD")
601 IF (flag) THEN
602 CALL section_vals_val_get(input_file, "MOTION%MD%ENSEMBLE", i_val=ensemble)
603 IF (ensemble == npt_i_ensemble .OR. ensemble == npt_f_ensemble .OR. ensemble == npt_ia_ensemble) THEN
604 CALL section_vals_val_get(r_section, "RESTART_BAROSTAT_THERMOSTAT", l_val=flag)
605 check = check_restart(input_file, restart_file, "MOTION%MD%BAROSTAT")
606 CALL restart_thermostat(flag, input_file, restart_file, "MOTION%MD%BAROSTAT%THERMOSTAT", &
607 check=check)
608 IF (flag .AND. check) CALL set_restart_info("THERMOSTAT OF BAROSTAT", restarted_infos)
609 END IF
610 END IF
611
612 check = check_restart(input_file, restart_file, "MOTION%MD%SHELL")
613 IF (check) THEN
614 CALL section_vals_val_get(r_section, "RESTART_SHELL_THERMOSTAT", l_val=flag)
615 CALL restart_thermostat(flag, input_file, restart_file, "MOTION%MD%SHELL%THERMOSTAT")
616 CALL set_restart_info("SHELL THERMOSTAT", restarted_infos)
617 END IF
618
619 CALL section_vals_val_get(r_section, "RESTART_THERMOSTAT", l_val=flag)
620 CALL restart_thermostat(flag, input_file, restart_file, "MOTION%MD%THERMOSTAT")
621 IF (flag) CALL set_restart_info("PARTICLE THERMOSTAT", restarted_infos)
622
623 CALL section_vals_val_get(r_section, "RESTART_CONSTRAINT", l_val=flag)
624 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%CONSTRAINT")) THEN
625 section => section_vals_get_subs_vals(restart_file, "MOTION%CONSTRAINT")
626 CALL section_vals_set_subs_vals(input_file, "MOTION%CONSTRAINT", section)
627 CALL set_restart_info("CONSTRAINTS/RESTRAINTS", restarted_infos)
628 END IF
629
630 CALL section_vals_val_get(r_section, "RESTART_METADYNAMICS", l_val=flag)
631 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%FREE_ENERGY%METADYN")) THEN
632 section => section_vals_get_subs_vals(restart_file, &
633 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_POS")
634 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_POS", &
635 section)
636 section => section_vals_get_subs_vals(restart_file, &
637 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE")
638 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE", &
639 section)
640 section => section_vals_get_subs_vals(restart_file, &
641 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT")
642 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT", &
643 section)
644 section => section_vals_get_subs_vals(restart_file, &
645 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT")
646 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT", &
647 section)
648 ! Extended Lagrangian
649 section => section_vals_get_subs_vals(restart_file, &
650 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS0")
651 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS0", &
652 section)
653 section => section_vals_get_subs_vals(restart_file, &
654 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP")
655 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP", &
656 section)
657 section => section_vals_get_subs_vals(restart_file, &
658 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS")
659 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS", &
660 section)
661 section => section_vals_get_subs_vals(restart_file, &
662 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_FS")
663 CALL section_vals_set_subs_vals(input_file, "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_FS", &
664 section)
665 CALL set_restart_info("METADYNAMICS", restarted_infos)
666 END IF
667
668 CALL section_vals_val_get(r_section, "RESTART_TEMPERATURE_ANNEALING", l_val=flag)
669 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%MD")) THEN
670 CALL section_vals_val_get(input_file, "MOTION%MD%TEMPERATURE_ANNEALING", r_val=myt, explicit=explicit1)
671 IF ((.NOT. explicit1) .OR. (abs(1._dp - myt) <= 1.e-10_dp)) THEN
672 CALL cp_warn(__location__, &
673 "I'm about to override the input temperature "// &
674 "with the temperature found in external restart "// &
675 "but TEMPERATURE_ANNEALING isn't explicitly given or it is set to 1.")
676 END IF
677 CALL section_vals_val_get(restart_file, "MOTION%MD%TEMPERATURE", r_val=myt, explicit=explicit1)
678 IF (explicit1) THEN
679 CALL section_vals_val_get(input_file, "MOTION%MD%TEMPERATURE", r_val=myt)
680 ELSE
681 CALL cp_warn(__location__, &
682 "I'm not going to override the input temperature "// &
683 "since the temperature isn't explicitly given in the external restart.")
684 END IF
685 END IF
686
687 CALL section_vals_val_get(r_section, "RESTART_WALKERS", l_val=flag)
688 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS")) THEN
689 CALL section_vals_val_get(restart_file, "MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS%WALKERS_STATUS", &
690 i_vals=rwalkers_status)
691 ALLOCATE (iwalkers_status(SIZE(rwalkers_status)))
692 iwalkers_status = rwalkers_status
693 CALL section_vals_val_set(input_file, "MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS%WALKERS_STATUS", &
694 i_vals_ptr=iwalkers_status)
695 CALL set_restart_info("WALKERS INFO", restarted_infos)
696 END IF
697
698 CALL section_vals_val_get(r_section, "RESTART_DIMER", l_val=flag)
699 IF (flag .AND. check_restart(input_file, restart_file, "MOTION%GEO_OPT%TRANSITION_STATE%DIMER")) THEN
700 section => section_vals_get_subs_vals(restart_file, &
701 "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%DIMER_VECTOR")
702 CALL section_vals_set_subs_vals(input_file, "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%DIMER_VECTOR", &
703 section)
704 CALL set_restart_info("DIMER TRANSITION STATE SEARCH", restarted_infos)
705 END IF
706
707 CALL section_vals_val_get(r_section, "CUSTOM_PATH", n_rep_val=n_rep_val)
708 DO i_rep_val = 1, n_rep_val
709 CALL section_vals_val_get(r_section, "CUSTOM_PATH", i_rep_val=i_rep_val, c_val=path)
710 IF (path /= " ") THEN
711 section => section_vals_get_subs_vals(restart_file, path)
712 CALL section_vals_set_subs_vals(input_file, path, section)
713 CALL set_restart_info("USER RESTART: "//trim(path), restarted_infos)
714 END IF
715 END DO
716
717 CALL section_vals_val_get(r_section, "RESTART_RTP", l_val=flag)
718 ! IF(flag.AND.check_restart(input_file, restart_file, "FORCE_EVAL%DFT%REAL_TIME_PROPAGATION")) THEN
719 IF (flag) THEN
720 section => section_vals_get_subs_vals(restart_file, &
721 "FORCE_EVAL%DFT%REAL_TIME_PROPAGATION")
722 CALL section_vals_val_get(section, "INITIAL_WFN", i_val=myi)
723 CALL section_vals_val_set(input_file, "FORCE_EVAL%DFT%REAL_TIME_PROPAGATION%INITIAL_WFN", &
724 i_val=myi)
725 CALL set_restart_info("REAL TIME PROPAGATION", restarted_infos)
726 END IF
727
728 ! PIMD
729 CALL section_vals_val_get(r_section, "RESTART_PINT_POS", l_val=flag)
730 IF (flag) THEN
731 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%BEADS%COORD")
732 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%BEADS%COORD", section)
733 CALL set_restart_info("PINT BEAD POSITIONS", restarted_infos)
734 END IF
735 CALL section_vals_val_get(r_section, "RESTART_PINT_VEL", l_val=flag)
736 IF (flag) THEN
737 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%BEADS%VELOCITY")
738 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%BEADS%VELOCITY", section)
739 CALL set_restart_info("PINT BEAD VELOCITIES", restarted_infos)
740 END IF
741 CALL section_vals_val_get(r_section, "RESTART_PINT_NOSE", l_val=flag)
742 IF (flag) THEN
743 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%NOSE%COORD")
744 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%NOSE%COORD", section)
745 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%NOSE%VELOCITY")
746 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%NOSE%VELOCITY", section)
747 CALL set_restart_info("PINT NOSE THERMOSTAT", restarted_infos)
748 END IF
749 CALL section_vals_val_get(r_section, "RESTART_PINT_GLE", l_val=flag)
750 IF (flag) THEN
751 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%GLE")
752 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%GLE", section)
753 CALL set_restart_info("PINT GLE THERMOSTAT", restarted_infos)
754 END IF
755
756 ! PIMC
757 !
758 CALL section_vals_val_get(r_section, "RESTART_HELIUM_POS", l_val=flag)
759 IF (flag) THEN
760 CALL section_vals_val_get(input_file, "MOTION%PINT%HELIUM%NUM_ENV", &
761 explicit=explicit1)
762 IF (.NOT. explicit1) THEN
763 CALL section_vals_val_get(restart_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
764 CALL section_vals_val_set(input_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
765 END IF
766 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%HELIUM%COORD")
767 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%HELIUM%COORD", section)
768 CALL set_restart_info("HELIUM BEAD POSITIONS", restarted_infos)
769 END IF
770 !
771 CALL section_vals_val_get(r_section, "RESTART_HELIUM_PERMUTATION", l_val=flag)
772 IF (flag) THEN
773 CALL section_vals_val_get(input_file, "MOTION%PINT%HELIUM%NUM_ENV", &
774 explicit=explicit1)
775 IF (.NOT. explicit1) THEN
776 CALL section_vals_val_get(restart_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
777 CALL section_vals_val_set(input_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
778 END IF
779 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%HELIUM%PERM")
780 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%HELIUM%PERM", section)
781 CALL set_restart_info("HELIUM PERMUTATION STATE", restarted_infos)
782 END IF
783 !
784 CALL section_vals_val_get(r_section, "RESTART_HELIUM_FORCE", l_val=flag)
785 IF (flag) THEN
786 CALL section_vals_val_get(input_file, "MOTION%PINT%HELIUM%NUM_ENV", &
787 explicit=explicit1)
788 IF (.NOT. explicit1) THEN
789 CALL section_vals_val_get(restart_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
790 CALL section_vals_val_set(input_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
791 END IF
792 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%HELIUM%FORCE")
793 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%HELIUM%FORCE", section)
794 CALL set_restart_info("HELIUM FORCES ON SOLUTE", restarted_infos)
795 END IF
796 !
797 CALL section_vals_val_get(r_section, "RESTART_HELIUM_RNG", l_val=flag)
798 IF (flag) THEN
799 CALL section_vals_val_get(input_file, "MOTION%PINT%HELIUM%NUM_ENV", &
800 explicit=explicit1)
801 IF (.NOT. explicit1) THEN
802 CALL section_vals_val_get(restart_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
803 CALL section_vals_val_set(input_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
804 END IF
805 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%HELIUM%RNG_STATE")
806 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%HELIUM%RNG_STATE", section)
807 CALL set_restart_info("HELIUM RNG STATE", restarted_infos)
808 END IF
809 !
810 !
811 CALL section_vals_val_get(r_section, "RESTART_HELIUM_DENSITIES", l_val=flag)
812 IF (flag) THEN
813 CALL section_vals_val_get(input_file, "MOTION%PINT%HELIUM%NUM_ENV", &
814 explicit=explicit1)
815 IF (.NOT. explicit1) THEN
816 CALL section_vals_val_get(restart_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
817 CALL section_vals_val_set(input_file, "MOTION%PINT%HELIUM%NUM_ENV", i_val=myi)
818 END IF
819 section => section_vals_get_subs_vals(restart_file, "MOTION%PINT%HELIUM%RHO")
820 CALL section_vals_set_subs_vals(input_file, "MOTION%PINT%HELIUM%RHO", section)
821 CALL set_restart_info("HELIUM DENSITIES", restarted_infos)
822 END IF
823 !
824 CALL section_vals_val_set(r_section, "RESTART_FILE_NAME", c_val=" ")
825 CALL section_vals_release(restart_file)
826 CALL release_restart_info(restarted_infos, r_file_path, binary_restart_file, &
827 output_unit)
828 END block
829 END IF
830 CALL timestop(handle)
831 END SUBROUTINE handle_ext_restart
832
833! **************************************************************************************************
834!> \brief store information on the restarted quantities
835!> \param label ...
836!> \param restarted_infos ...
837!> \author Teodoro Laino [tlaino] 09.2008 - University of Zurich
838! **************************************************************************************************
839 SUBROUTINE set_restart_info(label, restarted_infos)
840
841 CHARACTER(LEN=*), INTENT(IN) :: label
842 CHARACTER(LEN=default_string_length), &
843 DIMENSION(:), POINTER :: restarted_infos
844
845 INTEGER :: isize
846
847 isize = 0
848 IF (ASSOCIATED(restarted_infos)) isize = SIZE(restarted_infos)
849 isize = isize + 1
850 CALL reallocate(restarted_infos, 1, isize)
851 restarted_infos(isize) = trim(label)
852
853 END SUBROUTINE set_restart_info
854
855! **************************************************************************************************
856!> \brief dumps on output the information on the information effectively restarted
857!> \param restarted_infos ...
858!> \param r_file_path ...
859!> \param binary_restart_file ...
860!> \param output_unit ...
861!> \author Teodoro Laino [tlaino] 09.2008 - University of Zurich
862! **************************************************************************************************
863 SUBROUTINE release_restart_info(restarted_infos, r_file_path, &
864 binary_restart_file, output_unit)
865 CHARACTER(LEN=default_string_length), &
866 DIMENSION(:), POINTER :: restarted_infos
867 CHARACTER(LEN=*), INTENT(IN) :: r_file_path, binary_restart_file
868 INTEGER, INTENT(IN) :: output_unit
869
870 INTEGER :: i, j
871
872 IF (output_unit > 0 .AND. ASSOCIATED(restarted_infos)) THEN
873 WRITE (output_unit, '(1X,79("*"))')
874 WRITE (output_unit, '(1X,"*",T30,A,T80,"*")') " RESTART INFORMATION "
875 WRITE (output_unit, '(1X,79("*"))')
876 WRITE (output_unit, '(1X,"*",T80,"*")')
877 i = 1
878 WRITE (output_unit, '(1X,"*",A,T26,A,T80,"*")') " RESTART FILE NAME: ", &
879 r_file_path(53*(i - 1) + 1:53*i)
880 DO i = 2, ceiling(real(len_trim(r_file_path), kind=dp)/53.0_dp)
881 WRITE (output_unit, '(T1,1X,"*",T26,A,T80,"*")') r_file_path(53*(i - 1) + 1:53*i)
882 END DO
883 IF (len_trim(binary_restart_file) > 0) THEN
884 i = 1
885 WRITE (output_unit, '(1X,"*",A,T26,A,T80,"*")') " BINARY RESTART FILE: ", &
886 binary_restart_file(53*(i - 1) + 1:53*i)
887 DO i = 2, ceiling(real(len_trim(binary_restart_file), kind=dp)/53.0_dp)
888 WRITE (output_unit, '(T1,1X,"*",T26,A,T80,"*")') binary_restart_file(53*(i - 1) + 1:53*i)
889 END DO
890 END IF
891 WRITE (output_unit, '(1X,"*",T80,"*")')
892 WRITE (output_unit, '(1X,"*", A,T80,"*")') " RESTARTED QUANTITIES: "
893 DO j = 1, SIZE(restarted_infos)
894 DO i = 1, ceiling(real(len_trim(restarted_infos(j)), kind=dp)/53.0_dp)
895 WRITE (output_unit, '(T1,1X,"*",T26,A,T80,"*")') restarted_infos(j) (53*(i - 1) + 1:53*i)
896 END DO
897 END DO
898 WRITE (output_unit, '(1X,79("*"),/)')
899 END IF
900 IF (ASSOCIATED(restarted_infos)) THEN
901 DEALLOCATE (restarted_infos)
902 END IF
903 END SUBROUTINE release_restart_info
904
905! **************************************************************************************************
906!> \brief Possibly restart thermostats information
907!> \param flag ...
908!> \param input_file the input file to initialize
909!> \param restart_file ...
910!> \param path ...
911!> \param check ...
912!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
913! **************************************************************************************************
914 SUBROUTINE restart_thermostat(flag, input_file, restart_file, path, check)
915 LOGICAL, INTENT(IN) :: flag
916 TYPE(section_vals_type), POINTER :: input_file, restart_file
917 CHARACTER(LEN=*), INTENT(IN) :: path
918 LOGICAL, INTENT(IN), OPTIONAL :: check
919
920 INTEGER :: input_region, input_type, &
921 restart_region, restart_type
922 LOGICAL :: check_loc, skip_other_checks
923 TYPE(section_vals_type), POINTER :: section
924
925 check_loc = check_restart(input_file, restart_file, trim(path))
926 skip_other_checks = PRESENT(check)
927 IF (skip_other_checks) check_loc = check
928 IF (flag .AND. check_loc) THEN
929 ! Let's check if the thermostat type is different otherwise it does not make any
930 ! sense to do any kind of restart
931 CALL section_vals_val_get(input_file, trim(path)//"%TYPE", i_val=input_type)
932 CALL section_vals_val_get(restart_file, trim(path)//"%TYPE", i_val=restart_type)
933
934 IF (input_type == do_thermo_same_as_part) THEN
935 CALL section_vals_val_get(input_file, "MOTION%MD%THERMOSTAT%TYPE", i_val=input_type)
936 END IF
937
938 IF (skip_other_checks) THEN
939 input_region = do_region_global
940 restart_region = do_region_global
941 ELSE
942 ! Also the regions must be the same..
943 CALL section_vals_val_get(input_file, trim(path)//"%REGION", i_val=input_region)
944 CALL section_vals_val_get(restart_file, trim(path)//"%REGION", i_val=restart_region)
945 END IF
946
947 IF ((input_type == restart_type) .AND. (input_region == restart_region)) THEN
948 SELECT CASE (input_type)
949 CASE (do_thermo_nose)
950 section => section_vals_get_subs_vals(restart_file, trim(path)//"%NOSE%COORD")
951 CALL section_vals_set_subs_vals(input_file, trim(path)//"%NOSE%COORD", section)
952
953 section => section_vals_get_subs_vals(restart_file, trim(path)//"%NOSE%VELOCITY")
954 CALL section_vals_set_subs_vals(input_file, trim(path)//"%NOSE%VELOCITY", section)
955
956 section => section_vals_get_subs_vals(restart_file, trim(path)//"%NOSE%MASS")
957 CALL section_vals_set_subs_vals(input_file, trim(path)//"%NOSE%MASS", section)
958
959 section => section_vals_get_subs_vals(restart_file, trim(path)//"%NOSE%FORCE")
960 CALL section_vals_set_subs_vals(input_file, trim(path)//"%NOSE%FORCE", section)
961 CASE (do_thermo_csvr)
962 section => section_vals_get_subs_vals(restart_file, trim(path)//"%CSVR%THERMOSTAT_ENERGY")
963 CALL section_vals_set_subs_vals(input_file, trim(path)//"%CSVR%THERMOSTAT_ENERGY", section)
964 section => section_vals_get_subs_vals(restart_file, trim(path)//"%CSVR%RNG_INIT")
965 CALL section_vals_set_subs_vals(input_file, trim(path)//"%CSVR%RNG_INIT", section)
966 CASE (do_thermo_gle)
967 section => section_vals_get_subs_vals(restart_file, trim(path)//"%GLE%THERMOSTAT_ENERGY")
968 CALL section_vals_set_subs_vals(input_file, trim(path)//"%GLE%THERMOSTAT_ENERGY", section)
969 section => section_vals_get_subs_vals(restart_file, trim(path)//"%GLE%RNG_INIT")
970 CALL section_vals_set_subs_vals(input_file, trim(path)//"%GLE%RNG_INIT", section)
971 section => section_vals_get_subs_vals(restart_file, trim(path)//"%GLE%S")
972 CALL section_vals_set_subs_vals(input_file, trim(path)//"%GLE%S", section)
973 CASE (do_thermo_al)
974 section => section_vals_get_subs_vals(restart_file, trim(path)//"%AD_LANGEVIN%CHI")
975 CALL section_vals_set_subs_vals(input_file, trim(path)//"%AD_LANGEVIN%CHI", section)
976 section => section_vals_get_subs_vals(restart_file, trim(path)//"%AD_LANGEVIN%MASS")
977 CALL section_vals_set_subs_vals(input_file, trim(path)//"%AD_LANGEVIN%MASS", section)
978 END SELECT
979 ELSE
980 IF (input_type /= restart_type) &
981 CALL cp_warn(__location__, &
982 "Requested to restart thermostat: "//trim(path)//". The thermostat "// &
983 "specified in the input file and the information present in the restart "// &
984 "file do not match the same type of thermostat! Restarting is not possible! "// &
985 "Thermostat will not be restarted! ")
986 IF (input_region /= restart_region) &
987 CALL cp_warn(__location__, &
988 "Requested to restart thermostat: "//trim(path)//". The thermostat "// &
989 "specified in the input file and the information present in the restart "// &
990 "file do not match the same type of REGION! Restarting is not possible! "// &
991 "Thermostat will not be restarted! ")
992 END IF
993 END IF
994 END SUBROUTINE restart_thermostat
995
996! **************************************************************************************************
997!> \brief Checks if there are the proper conditions to do a restart
998!> \param input_file the input file to initialize
999!> \param restart_file ...
1000!> \param tag_section ...
1001!> \return ...
1002!> \author teo
1003! **************************************************************************************************
1004 FUNCTION check_restart(input_file, restart_file, tag_section) RESULT(do_restart)
1005 TYPE(section_vals_type), POINTER :: input_file, restart_file
1006 CHARACTER(LEN=*), INTENT(IN) :: tag_section
1007 LOGICAL :: do_restart
1008
1009 CHARACTER(len=*), PARAMETER :: routinen = 'check_restart'
1010
1011 INTEGER :: handle
1012 LOGICAL :: explicit1, explicit2
1013 TYPE(section_vals_type), POINTER :: work_section
1014
1015 CALL timeset(routinen, handle)
1016 NULLIFY (work_section)
1017 work_section => section_vals_get_subs_vals(input_file, trim(tag_section))
1018 CALL section_vals_get(work_section, explicit=explicit1)
1019 work_section => section_vals_get_subs_vals(restart_file, trim(tag_section))
1020 CALL section_vals_get(work_section, explicit=explicit2)
1021
1022 do_restart = explicit1 .AND. explicit2
1023 CALL timestop(handle)
1024 END FUNCTION check_restart
1025
1026! **************************************************************************************************
1027!> \brief Removes section used to restart a calculation from an
1028!> input file in memory
1029!> \param input_file the input file to initialize
1030!> \author teo
1031! **************************************************************************************************
1032 SUBROUTINE remove_restart_info(input_file)
1033 TYPE(section_vals_type), POINTER :: input_file
1034
1035 CHARACTER(len=*), PARAMETER :: routinen = 'remove_restart_info'
1036
1037 INTEGER :: handle, iforce_eval, nforce_eval1
1038 LOGICAL :: explicit1
1039 TYPE(section_vals_type), POINTER :: md_section, motion_section, section1, &
1040 section_to_delete, sections1, &
1041 work_section
1042
1043 CALL timeset(routinen, handle)
1044
1045 NULLIFY (work_section)
1046 section_to_delete => section_vals_get_subs_vals(input_file, "EXT_RESTART")
1047 CALL section_vals_remove_values(section_to_delete)
1048 sections1 => section_vals_get_subs_vals(input_file, "FORCE_EVAL")
1049 CALL section_vals_get(sections1, n_repetition=nforce_eval1)
1050
1051 DO iforce_eval = 1, nforce_eval1
1052 section1 => section_vals_get_subs_vals3(sections1, "SUBSYS", i_rep_section=iforce_eval)
1053 section_to_delete => section_vals_get_subs_vals(section1, "COORD")
1054 CALL section_vals_remove_values(section_to_delete)
1055 section_to_delete => section_vals_get_subs_vals(section1, "VELOCITY")
1056 CALL section_vals_remove_values(section_to_delete)
1057 END DO
1058
1059 motion_section => section_vals_get_subs_vals(input_file, "MOTION")
1060 md_section => section_vals_get_subs_vals(motion_section, "MD")
1061 CALL section_vals_get(md_section, explicit=explicit1)
1062 IF (explicit1) THEN
1063 CALL section_vals_val_unset(md_section, "STEP_START_VAL")
1064 CALL section_vals_val_unset(md_section, "TIME_START_VAL")
1065 CALL section_vals_val_unset(md_section, "ECONS_START_VAL")
1066 END IF
1067 work_section => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN")
1068 CALL section_vals_get(work_section, explicit=explicit1)
1069 IF (explicit1) THEN
1070 CALL section_vals_val_unset(motion_section, "FREE_ENERGY%METADYN%STEP_START_VAL")
1071 CALL section_vals_val_unset(motion_section, "FREE_ENERGY%METADYN%NHILLS_START_VAL")
1072 END IF
1073 section_to_delete => section_vals_get_subs_vals(motion_section, "BAND%REPLICA")
1074 CALL section_vals_remove_values(section_to_delete)
1075 section_to_delete => section_vals_get_subs_vals(md_section, "AVERAGES%RESTART_AVERAGES")
1076 CALL section_vals_remove_values(section_to_delete)
1077 section_to_delete => section_vals_get_subs_vals(md_section, "THERMOSTAT%NOSE%COORD")
1078 CALL section_vals_remove_values(section_to_delete)
1079 section_to_delete => section_vals_get_subs_vals(md_section, "THERMOSTAT%NOSE%VELOCITY")
1080 CALL section_vals_remove_values(section_to_delete)
1081 section_to_delete => section_vals_get_subs_vals(md_section, "THERMOSTAT%NOSE%MASS")
1082 CALL section_vals_remove_values(section_to_delete)
1083 section_to_delete => section_vals_get_subs_vals(md_section, "THERMOSTAT%NOSE%FORCE")
1084 CALL section_vals_remove_values(section_to_delete)
1085 section_to_delete => section_vals_get_subs_vals(md_section, "BAROSTAT%MASS")
1086 CALL section_vals_remove_values(section_to_delete)
1087 section_to_delete => section_vals_get_subs_vals(md_section, "BAROSTAT%VELOCITY")
1088 CALL section_vals_remove_values(section_to_delete)
1089 section_to_delete => section_vals_get_subs_vals(md_section, "BAROSTAT%THERMOSTAT%NOSE%COORD")
1090 CALL section_vals_remove_values(section_to_delete)
1091 section_to_delete => section_vals_get_subs_vals(md_section, "BAROSTAT%THERMOSTAT%NOSE%VELOCITY")
1092 CALL section_vals_remove_values(section_to_delete)
1093 section_to_delete => section_vals_get_subs_vals(md_section, "BAROSTAT%THERMOSTAT%NOSE%MASS")
1094 CALL section_vals_remove_values(section_to_delete)
1095 section_to_delete => section_vals_get_subs_vals(md_section, "BAROSTAT%THERMOSTAT%NOSE%FORCE")
1096 CALL section_vals_remove_values(section_to_delete)
1097 section_to_delete => section_vals_get_subs_vals(md_section, "SHELL%THERMOSTAT%NOSE%COORD")
1098 CALL section_vals_remove_values(section_to_delete)
1099 section_to_delete => section_vals_get_subs_vals(md_section, "SHELL%THERMOSTAT%NOSE%VELOCITY")
1100 CALL section_vals_remove_values(section_to_delete)
1101 section_to_delete => section_vals_get_subs_vals(md_section, "SHELL%THERMOSTAT%NOSE%MASS")
1102 CALL section_vals_remove_values(section_to_delete)
1103 section_to_delete => section_vals_get_subs_vals(md_section, "SHELL%THERMOSTAT%NOSE%FORCE")
1104 CALL section_vals_remove_values(section_to_delete)
1105 ! Constrained/Restrained section
1106 section_to_delete => section_vals_get_subs_vals(motion_section, "CONSTRAINT%FIX_ATOM_RESTART")
1107 CALL section_vals_remove_values(section_to_delete)
1108 section_to_delete => section_vals_get_subs_vals(motion_section, "CONSTRAINT%COLVAR_RESTART")
1109 CALL section_vals_remove_values(section_to_delete)
1110 ! Free energies restarts
1111 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%SPAWNED_HILLS_POS")
1112 CALL section_vals_remove_values(section_to_delete)
1113 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE")
1114 CALL section_vals_remove_values(section_to_delete)
1115 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT")
1116 CALL section_vals_remove_values(section_to_delete)
1117 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT")
1118 CALL section_vals_remove_values(section_to_delete)
1119 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%EXT_LAGRANGE_SS0")
1120 CALL section_vals_remove_values(section_to_delete)
1121 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP")
1122 CALL section_vals_remove_values(section_to_delete)
1123 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%EXT_LAGRANGE_SS")
1124 CALL section_vals_remove_values(section_to_delete)
1125 section_to_delete => section_vals_get_subs_vals(motion_section, "FREE_ENERGY%METADYN%EXT_LAGRANGE_FS")
1126 CALL section_vals_remove_values(section_to_delete)
1127 CALL timestop(handle)
1128 END SUBROUTINE remove_restart_info
1129
1130! **************************************************************************************************
1131!> \brief This subroutine controls the defaults for the restartable quantities..
1132!> \param r_section ...
1133!> \author teo - University of Zurich - 09.2007 [tlaino]
1134! **************************************************************************************************
1135 SUBROUTINE handle_defaults_restart(r_section)
1136 TYPE(section_vals_type), POINTER :: r_section
1137
1138 CHARACTER(len=*), PARAMETER :: routinen = 'handle_defaults_restart'
1139
1140 INTEGER :: handle, ik, nval
1141 LOGICAL :: restart_default
1142 TYPE(keyword_type), POINTER :: keyword
1143 TYPE(section_type), POINTER :: section
1144
1145 CALL timeset(routinen, handle)
1146 NULLIFY (keyword, section)
1147 CALL section_vals_get(r_section, section=section)
1148 CALL section_vals_val_get(r_section, "RESTART_DEFAULT", l_val=restart_default)
1149 DO ik = -1, section%n_keywords
1150 keyword => section%keywords(ik)%keyword
1151 IF (ASSOCIATED(keyword)) THEN
1152 IF (keyword%type_of_var == logical_t .AND. keyword%names(1) (1:8) == "RESTART_") THEN
1153 IF (trim(keyword%names(1)) == "RESTART_DEFAULT") cycle
1154 CALL section_vals_val_get(r_section, keyword%names(1), n_rep_val=nval)
1155 IF (nval == 0) THEN
1156 ! User didn't specify any value, use the value of the RESTART_DEFAULT keyword..
1157 CALL section_vals_val_set(r_section, keyword%names(1), l_val=restart_default)
1158 END IF
1159 END IF
1160 END IF
1161 END DO
1162 CALL timestop(handle)
1163
1164 END SUBROUTINE handle_defaults_restart
1165
1166END MODULE input_cp2k_check
various routines to log and control the output. The idea is that decisions about where to log should ...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_release(parser)
releases the parser
subroutine, public parser_create(parser, file_name, unit_nr, para_env, end_section_label, separator_chars, comment_char, continuation_char, quote_char, section_char, parse_white_lines, initial_variables, apply_preprocessing)
Start a parser run. Initial variables allow to @SET stuff before opening the file.
unit conversion facility
Definition cp_units.F:30
subroutine, public cp_unit_set_release(unit_set)
releases the given unit set
Definition cp_units.F:1298
subroutine, public cp_unit_set_create(unit_set, name)
initializes the given unit set
Definition cp_units.F:1227
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_thermo_nose
integer, parameter, public xc_funct_tpss
integer, parameter, public xc_funct_xwpbe
integer, parameter, public xc_funct_bp
integer, parameter, public xc_funct_olyp
integer, parameter, public xc_funct_pbe
integer, parameter, public xc_funct_no_shortcut
integer, parameter, public npt_i_ensemble
integer, parameter, public xc_vdw_fun_nonloc
integer, parameter, public xc_funct_pbe0
integer, parameter, public xc_funct_beefvdw
integer, parameter, public xc_funct_pade
integer, parameter, public xc_funct_blyp
integer, parameter, public do_thermo_al
integer, parameter, public do_thermo_csvr
integer, parameter, public mimic_run
integer, parameter, public vdw_nl_lmkll
integer, parameter, public do_thermo_gle
integer, parameter, public npt_ia_ensemble
integer, parameter, public npt_f_ensemble
integer, parameter, public do_region_global
integer, parameter, public negf_run
integer, parameter, public do_qs
integer, parameter, public xc_funct_b3lyp
integer, parameter, public xc_none
integer, parameter, public xc_funct_hcth120
integer, parameter, public do_thermo_same_as_part
checks the input and perform some automatic "magic" on it
subroutine, public check_cp2k_input(input_declaration, input_file, para_env, output_unit)
performs further checks on an input that parsed successfully
subroutine, public remove_restart_info(input_file)
Removes section used to restart a calculation from an input file in memory.
subroutine, public xc_functionals_expand(functionals, xc_section)
expand a shortcutted functional section
represents keywords in an input
routines that parse the input
recursive subroutine, public section_vals_parse(section_vals, parser, default_units, root_section)
...
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_unset(section_vals, keyword_name, i_rep_section, i_rep_val)
unsets (removes) the requested value (if it is a keyword repetitions removes the repetition,...
recursive subroutine, public section_vals_create(section_vals, section)
creates a object where to store the values of a section
subroutine, public section_vals_val_set(section_vals, keyword_name, i_rep_section, i_rep_val, val, l_val, i_val, r_val, c_val, l_vals_ptr, i_vals_ptr, r_vals_ptr, c_vals_ptr)
sets the requested value
type(section_vals_type) function, pointer, public section_vals_get_subs_vals2(section_vals, i_section, i_rep_section)
returns the values of the n-th non default subsection (null if no such section exists (not so many no...
subroutine, public section_vals_remove_values(section_vals)
removes the values of a repetition of the section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
type(section_vals_type) function, pointer, public section_vals_get_subs_vals3(section_vals, subsection_name, i_rep_section)
returns the values of the n-th non default subsection (null if no such section exists (not so many no...
subroutine, public section_vals_set_subs_vals(section_vals, subsection_name, new_section_vals, i_rep_section)
replaces of the requested subsection with the one given
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
recursive subroutine, public section_vals_release(section_vals)
releases the given object
a wrapper for basic fortran types.
integer, parameter, public logical_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Utility routines for the memory handling.
Interface to the message passing library MPI.
input constants for xc
integer, parameter, public do_vwn5
stores the default units to be used
Definition cp_units.F:149
represent a keyword in the input
represent a section of the input file
stores all the informations relevant to an mpi environment