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