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