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