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