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