42#include "./base/base_uses.f90"
47 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
48 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'input_cp2k_check'
68 INTEGER,
INTENT(IN),
OPTIONAL :: output_unit
70 CHARACTER(len=*),
PARAMETER :: routinen =
'check_cp2k_input'
72 INTEGER :: handle, iforce_eval, nforce_eval, &
74 LOGICAL :: explicit, explicit_embed, explicit_mix
78 CALL timeset(routinen, handle)
79 cpassert(
ASSOCIATED(input_file))
80 cpassert(input_file%ref_count > 0)
82 IF (
PRESENT(output_unit)) &
83 CALL handle_ext_restart(input_declaration, input_file, para_env, output_unit)
92 DO iforce_eval = 1, nforce_eval
94 i_rep_section=iforce_eval)
96 IF (explicit_mix)
EXIT
98 DO iforce_eval = 1, nforce_eval
100 i_rep_section=iforce_eval)
102 IF (explicit_embed)
EXIT
107 IF (((explicit .AND. (nforce_eval == 1)) .OR. (.NOT. explicit .AND. (nforce_eval > 1))) .AND. run_type /=
negf_run)
THEN
108 IF ((explicit_mix .AND. (nforce_eval == 1)) .OR. (.NOT. explicit_mix .AND. (nforce_eval > 1)))
THEN
109 IF ((explicit_embed .AND. (nforce_eval == 1)) .OR. (.NOT. explicit_embed .AND. (nforce_eval > 1)))
THEN
110 CALL cp_abort(__location__, &
111 "Error multiple force_env without RESPA or MIXED or EMBED, or RESPA with one single "// &
112 "or MIXED with only two force_env section.")
116 DO iforce_eval = 1, nforce_eval
127 CALL timestop(handle)
139 CHARACTER(LEN=512) :: wrn_msg
140 INTEGER :: ifun, nfun, shortcut
151 IF (.NOT.
ASSOCIATED(xc_fun))
EXIT
156 WRITE (wrn_msg,
'(A)')
"User requested a shortcut while defining an explicit XC functional. "// &
157 "This is not recommended as it could lead to spurious behaviour. Please check input parameters."
161 SELECT CASE (shortcut)
180 r_val=0.3998335231_dp)
182 r_val=0.0000000000_dp)
191 r_val=0.6001664769_dp)
276 cpabort(
"unknown shortcut "//trim(adjustl(
cp_to_string(shortcut))))
289 SUBROUTINE handle_ext_restart(input_declaration, input_file, para_env, output_unit)
293 INTEGER,
INTENT(IN) :: output_unit
295 CHARACTER(len=*),
PARAMETER :: routinen =
'handle_ext_restart'
297 CHARACTER(default_path_length) :: r_file_path
301 CALL timeset(routinen, handle)
306 IF (r_file_path /=
" ")
THEN
308 CHARACTER(default_path_length) :: binary_restart_file
309 CHARACTER(default_string_length) :: path
310 CHARACTER(LEN=default_string_length), &
311 DIMENSION(:),
POINTER :: restarted_infos
312 INTEGER :: ensemble, i_rep_val, &
313 iforce_eval, myi, n_rep_val, &
314 nforce_eval1, nforce_eval2
315 INTEGER,
DIMENSION(:),
POINTER :: ivec, iwalkers_status, iwork, &
317 LOGICAL :: bsse_check, check, explicit1, explicit2, &
318 flag, flag2, qmmm_check, subsys_check
320 REAL(kind=
dp),
DIMENSION(:),
POINTER :: vec, work
322 section, section1, section2, &
325 NULLIFY (restarted_infos, iwalkers_status, rwalkers_status, vec, ivec, work, iwork)
332 NULLIFY (restart_file)
334 CALL parser_create(cpparser, file_name=r_file_path, para_env=para_env)
337 default_units=default_units)
347 IF (nforce_eval1 /= nforce_eval2)
THEN
348 cpabort(
"Restart and input file MUST have the number of force_env sections")
351 CALL handle_defaults_restart(r_section)
354 DO iforce_eval = 1, nforce_eval1
356 i_rep_section=iforce_eval)
358 i_rep_section=iforce_eval)
362 subsys_check = (
ASSOCIATED(section1) .EQV.
ASSOCIATED(section2))
363 IF (subsys_check)
THEN
364 IF (
ASSOCIATED(section1))
THEN
369 CALL set_restart_info(
"CELL", restarted_infos)
376 CALL set_restart_info(
"COORDINATES", restarted_infos)
388 CALL set_restart_info(
"RANDOM NUMBER GENERATOR", restarted_infos)
395 CALL set_restart_info(
"VELOCITIES", restarted_infos)
403 IF (check_restart(section1, section2,
"SHELL_COORD")) &
404 CALL set_restart_info(
"SHELL COORDINATES", restarted_infos)
410 IF (check_restart(section1, section2,
"CORE_COORD")) &
411 CALL set_restart_info(
"CORE COORDINATES", restarted_infos)
417 IF (check_restart(section1, section2,
"SHELL_VELOCITY")) &
418 CALL set_restart_info(
"SHELL VELOCITIES", restarted_infos)
424 IF (check_restart(section1, section2,
"CORE_VELOCITY")) &
425 CALL set_restart_info(
"CORE VELOCITIES", restarted_infos)
429 CALL cp_abort(__location__, &
430 "Error while reading the restart file. Two force_eval have incompatible"// &
431 " subsys.One of them has an allocated subsys while the other has not! Check your"// &
432 " input file or whether the restart file is compatible with the input!")
440 qmmm_check = (explicit1 .AND. explicit2)
441 IF (flag .AND. qmmm_check)
THEN
442 CALL set_restart_info(
"QMMM TRANSLATION VECTOR", restarted_infos)
454 bsse_check = (explicit1 .AND. explicit2)
455 IF (flag .AND. bsse_check)
THEN
458 CALL set_restart_info(
"BSSE FRAGMENT ENERGIES", restarted_infos)
464 IF (check_restart(input_file, restart_file,
"MOTION%MD"))
THEN
471 CALL set_restart_info(
"MD COUNTERS", restarted_infos)
474 IF (check_restart(input_file, restart_file,
"MOTION%GEO_OPT"))
THEN
478 CALL set_restart_info(
"GEO_OPT COUNTERS", restarted_infos)
480 IF (check_restart(input_file, restart_file,
"MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT"))
THEN
481 CALL section_vals_val_get(restart_file,
"MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT%STEP_START_VAL", &
483 CALL section_vals_val_set(input_file,
"MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT%STEP_START_VAL", &
485 CALL set_restart_info(
"ROT_OPT COUNTERS", restarted_infos)
489 IF (check_restart(input_file, restart_file,
"MOTION%GEO_OPT"))
THEN
493 CALL set_restart_info(
"CELL_OPT COUNTERS", restarted_infos)
496 IF (check_restart(input_file, restart_file,
"OPTIMIZE_INPUT"))
THEN
499 CALL set_restart_info(
"OPTIMIZE_INPUT ITERATION NUMBER", restarted_infos)
502 IF (check_restart(input_file, restart_file,
"MOTION%PINT"))
THEN
506 CALL set_restart_info(
"PINT ITERATION NUMBER", restarted_infos)
510 IF (flag2 .AND. check_restart(input_file, restart_file,
"MOTION%FREE_ENERGY%METADYN"))
THEN
512 "MOTION%FREE_ENERGY%METADYN%STEP_START_VAL", i_val=myi)
514 "MOTION%FREE_ENERGY%METADYN%STEP_START_VAL", i_val=myi)
516 "MOTION%FREE_ENERGY%METADYN%NHILLS_START_VAL", i_val=myi)
518 "MOTION%FREE_ENERGY%METADYN%NHILLS_START_VAL", i_val=myi)
521 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_NUMBER", i_val=myi)
523 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_NUMBER", i_val=myi)
525 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_STEP", i_val=myi)
527 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_STEP", i_val=myi)
529 CALL set_restart_info(
"METADYNAMIC COUNTERS", restarted_infos)
535 IF (check_restart(input_file, restart_file,
"MOTION%MD"))
THEN
538 CALL set_restart_info(
"MD AVERAGES", restarted_infos)
543 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%BAND"))
THEN
546 CALL set_restart_info(
"BAND CALCULATION", restarted_infos)
550 IF (flag .AND. check_restart(input_file, restart_file,
"OPTIMIZE_INPUT%VARIABLE"))
THEN
553 CALL set_restart_info(
"OPTIMIZE_INPUT: VARIABLES", restarted_infos)
557 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%MD%BAROSTAT"))
THEN
559 "MOTION%MD%BAROSTAT%MASS")
563 "MOTION%MD%BAROSTAT%VELOCITY")
566 CALL set_restart_info(
"BAROSTAT", restarted_infos)
569 flag = check_restart(input_file, restart_file,
"MOTION%MD")
574 check = check_restart(input_file, restart_file,
"MOTION%MD%BAROSTAT")
575 CALL restart_thermostat(flag, input_file, restart_file,
"MOTION%MD%BAROSTAT%THERMOSTAT", &
577 IF (flag .AND. check)
CALL set_restart_info(
"THERMOSTAT OF BAROSTAT", restarted_infos)
581 check = check_restart(input_file, restart_file,
"MOTION%MD%SHELL")
584 CALL restart_thermostat(flag, input_file, restart_file,
"MOTION%MD%SHELL%THERMOSTAT")
585 CALL set_restart_info(
"SHELL THERMOSTAT", restarted_infos)
589 CALL restart_thermostat(flag, input_file, restart_file,
"MOTION%MD%THERMOSTAT")
590 IF (flag)
CALL set_restart_info(
"PARTICLE THERMOSTAT", restarted_infos)
593 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%CONSTRAINT"))
THEN
596 CALL set_restart_info(
"CONSTRAINTS/RESTRAINTS", restarted_infos)
600 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%FREE_ENERGY%METADYN"))
THEN
602 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_POS")
606 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE")
610 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT")
614 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT")
619 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS0")
623 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP")
627 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS")
631 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_FS")
634 CALL set_restart_info(
"METADYNAMICS", restarted_infos)
638 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%MD"))
THEN
639 CALL section_vals_val_get(input_file,
"MOTION%MD%TEMPERATURE_ANNEALING", r_val=myt, explicit=explicit1)
640 IF ((.NOT. explicit1) .OR. (abs(1._dp - myt) <= 1.e-10_dp))
THEN
641 CALL cp_warn(__location__, &
642 "I'm about to override the input temperature "// &
643 "with the temperature found in external restart "// &
644 "but TEMPERATURE_ANNEALING isn't explicitly given or it is set to 1.")
650 CALL cp_warn(__location__, &
651 "I'm not going to override the input temperature "// &
652 "since the temperature isn't explicitly given in the external restart.")
657 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS"))
THEN
658 CALL section_vals_val_get(restart_file,
"MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS%WALKERS_STATUS", &
659 i_vals=rwalkers_status)
660 ALLOCATE (iwalkers_status(
SIZE(rwalkers_status)))
661 iwalkers_status = rwalkers_status
662 CALL section_vals_val_set(input_file,
"MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS%WALKERS_STATUS", &
663 i_vals_ptr=iwalkers_status)
664 CALL set_restart_info(
"WALKERS INFO", restarted_infos)
668 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%GEO_OPT%TRANSITION_STATE%DIMER"))
THEN
670 "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%DIMER_VECTOR")
673 CALL set_restart_info(
"DIMER TRANSITION STATE SEARCH", restarted_infos)
677 DO i_rep_val = 1, n_rep_val
679 IF (path /=
" ")
THEN
682 CALL set_restart_info(
"USER RESTART: "//trim(path), restarted_infos)
690 "FORCE_EVAL%DFT%REAL_TIME_PROPAGATION")
694 CALL set_restart_info(
"REAL TIME PROPAGATION", restarted_infos)
702 CALL set_restart_info(
"PINT BEAD POSITIONS", restarted_infos)
708 CALL set_restart_info(
"PINT BEAD VELOCITIES", restarted_infos)
716 CALL set_restart_info(
"PINT NOSE THERMOSTAT", restarted_infos)
722 CALL set_restart_info(
"PINT GLE THERMOSTAT", restarted_infos)
731 IF (.NOT. explicit1)
THEN
737 CALL set_restart_info(
"HELIUM BEAD POSITIONS", restarted_infos)
744 IF (.NOT. explicit1)
THEN
750 CALL set_restart_info(
"HELIUM PERMUTATION STATE", restarted_infos)
757 IF (.NOT. explicit1)
THEN
763 CALL set_restart_info(
"HELIUM FORCES ON SOLUTE", restarted_infos)
770 IF (.NOT. explicit1)
THEN
776 CALL set_restart_info(
"HELIUM RNG STATE", restarted_infos)
784 IF (.NOT. explicit1)
THEN
790 CALL set_restart_info(
"HELIUM DENSITIES", restarted_infos)
795 CALL release_restart_info(restarted_infos, r_file_path, binary_restart_file, &
799 CALL timestop(handle)
800 END SUBROUTINE handle_ext_restart
808 SUBROUTINE set_restart_info(label, restarted_infos)
810 CHARACTER(LEN=*),
INTENT(IN) :: label
811 CHARACTER(LEN=default_string_length), &
812 DIMENSION(:),
POINTER :: restarted_infos
817 IF (
ASSOCIATED(restarted_infos)) isize =
SIZE(restarted_infos)
819 CALL reallocate(restarted_infos, 1, isize)
820 restarted_infos(isize) = trim(label)
822 END SUBROUTINE set_restart_info
832 SUBROUTINE release_restart_info(restarted_infos, r_file_path, &
833 binary_restart_file, output_unit)
834 CHARACTER(LEN=default_string_length), &
835 DIMENSION(:),
POINTER :: restarted_infos
836 CHARACTER(LEN=*),
INTENT(IN) :: r_file_path, binary_restart_file
837 INTEGER,
INTENT(IN) :: output_unit
841 IF (output_unit > 0 .AND.
ASSOCIATED(restarted_infos))
THEN
842 WRITE (output_unit,
'(1X,79("*"))')
843 WRITE (output_unit,
'(1X,"*",T30,A,T80,"*")')
" RESTART INFORMATION "
844 WRITE (output_unit,
'(1X,79("*"))')
845 WRITE (output_unit,
'(1X,"*",T80,"*")')
847 WRITE (output_unit,
'(1X,"*",A,T26,A,T80,"*")')
" RESTART FILE NAME: ", &
848 r_file_path(53*(i - 1) + 1:53*i)
849 DO i = 2, ceiling(real(len_trim(r_file_path), kind=dp)/53.0_dp)
850 WRITE (output_unit,
'(T1,1X,"*",T26,A,T80,"*")') r_file_path(53*(i - 1) + 1:53*i)
852 IF (len_trim(binary_restart_file) > 0)
THEN
854 WRITE (output_unit,
'(1X,"*",A,T26,A,T80,"*")')
" BINARY RESTART FILE: ", &
855 binary_restart_file(53*(i - 1) + 1:53*i)
856 DO i = 2, ceiling(real(len_trim(binary_restart_file), kind=dp)/53.0_dp)
857 WRITE (output_unit,
'(T1,1X,"*",T26,A,T80,"*")') binary_restart_file(53*(i - 1) + 1:53*i)
860 WRITE (output_unit,
'(1X,"*",T80,"*")')
861 WRITE (output_unit,
'(1X,"*", A,T80,"*")')
" RESTARTED QUANTITIES: "
862 DO j = 1,
SIZE(restarted_infos)
863 DO i = 1, ceiling(real(len_trim(restarted_infos(j)), kind=dp)/53.0_dp)
864 WRITE (output_unit,
'(T1,1X,"*",T26,A,T80,"*")') restarted_infos(j) (53*(i - 1) + 1:53*i)
867 WRITE (output_unit,
'(1X,79("*"),/)')
869 IF (
ASSOCIATED(restarted_infos))
THEN
870 DEALLOCATE (restarted_infos)
872 END SUBROUTINE release_restart_info
883 SUBROUTINE restart_thermostat(flag, input_file, restart_file, path, check)
884 LOGICAL,
INTENT(IN) :: flag
885 TYPE(section_vals_type),
POINTER :: input_file, restart_file
886 CHARACTER(LEN=*),
INTENT(IN) :: path
887 LOGICAL,
INTENT(IN),
OPTIONAL :: check
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
894 check_loc = check_restart(input_file, restart_file, trim(path))
895 skip_other_checks =
PRESENT(check)
896 IF (skip_other_checks) check_loc = check
897 IF (flag .AND. check_loc)
THEN
900 CALL section_vals_val_get(input_file, trim(path)//
"%TYPE", i_val=input_type)
901 CALL section_vals_val_get(restart_file, trim(path)//
"%TYPE", i_val=restart_type)
903 IF (input_type == do_thermo_same_as_part)
THEN
904 CALL section_vals_val_get(input_file,
"MOTION%MD%THERMOSTAT%TYPE", i_val=input_type)
907 IF (skip_other_checks)
THEN
908 input_region = do_region_global
909 restart_region = do_region_global
912 CALL section_vals_val_get(input_file, trim(path)//
"%REGION", i_val=input_region)
913 CALL section_vals_val_get(restart_file, trim(path)//
"%REGION", i_val=restart_region)
916 IF ((input_type == restart_type) .AND. (input_region == restart_region))
THEN
917 SELECT CASE (input_type)
918 CASE (do_thermo_nose)
919 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%COORD")
920 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%COORD", section)
922 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%VELOCITY")
923 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%VELOCITY", section)
925 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%MASS")
926 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%MASS", section)
928 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%FORCE")
929 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%FORCE", section)
930 CASE (do_thermo_csvr)
931 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%CSVR%THERMOSTAT_ENERGY")
932 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%CSVR%THERMOSTAT_ENERGY", section)
933 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%CSVR%RNG_INIT")
934 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%CSVR%RNG_INIT", section)
936 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%GLE%THERMOSTAT_ENERGY")
937 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%GLE%THERMOSTAT_ENERGY", section)
938 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%GLE%RNG_INIT")
939 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%GLE%RNG_INIT", section)
940 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%GLE%S")
941 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%GLE%S", section)
943 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%AD_LANGEVIN%CHI")
944 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%AD_LANGEVIN%CHI", section)
945 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%AD_LANGEVIN%MASS")
946 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%AD_LANGEVIN%MASS", section)
949 IF (input_type /= restart_type) &
950 CALL cp_warn(__location__, &
951 "Requested to restart thermostat: "//trim(path)//
". The thermostat "// &
952 "specified in the input file and the information present in the restart "// &
953 "file do not match the same type of thermostat! Restarting is not possible! "// &
954 "Thermostat will not be restarted! ")
955 IF (input_region /= restart_region) &
956 CALL cp_warn(__location__, &
957 "Requested to restart thermostat: "//trim(path)//
". The thermostat "// &
958 "specified in the input file and the information present in the restart "// &
959 "file do not match the same type of REGION! Restarting is not possible! "// &
960 "Thermostat will not be restarted! ")
963 END SUBROUTINE restart_thermostat
973 FUNCTION check_restart(input_file, restart_file, tag_section)
RESULT(do_restart)
974 TYPE(section_vals_type),
POINTER :: input_file, restart_file
975 CHARACTER(LEN=*),
INTENT(IN) :: tag_section
976 LOGICAL :: do_restart
978 CHARACTER(len=*),
PARAMETER :: routinen =
'check_restart'
981 LOGICAL :: explicit1, explicit2
982 TYPE(section_vals_type),
POINTER :: work_section
984 CALL timeset(routinen, handle)
985 NULLIFY (work_section)
986 work_section => section_vals_get_subs_vals(input_file, trim(tag_section))
987 CALL section_vals_get(work_section, explicit=explicit1)
988 work_section => section_vals_get_subs_vals(restart_file, trim(tag_section))
989 CALL section_vals_get(work_section, explicit=explicit2)
991 do_restart = explicit1 .AND. explicit2
992 CALL timestop(handle)
993 END FUNCTION check_restart
1002 TYPE(section_vals_type),
POINTER :: input_file
1004 CHARACTER(len=*),
PARAMETER :: routinen =
'remove_restart_info'
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, &
1012 CALL timeset(routinen, handle)
1014 NULLIFY (work_section)
1015 section_to_delete => section_vals_get_subs_vals(input_file,
"EXT_RESTART")
1016 CALL section_vals_remove_values(section_to_delete)
1017 sections1 => section_vals_get_subs_vals(input_file,
"FORCE_EVAL")
1018 CALL section_vals_get(sections1, n_repetition=nforce_eval1)
1020 DO iforce_eval = 1, nforce_eval1
1021 section1 => section_vals_get_subs_vals3(sections1,
"SUBSYS", i_rep_section=iforce_eval)
1022 section_to_delete => section_vals_get_subs_vals(section1,
"COORD")
1023 CALL section_vals_remove_values(section_to_delete)
1024 section_to_delete => section_vals_get_subs_vals(section1,
"VELOCITY")
1025 CALL section_vals_remove_values(section_to_delete)
1028 motion_section => section_vals_get_subs_vals(input_file,
"MOTION")
1029 md_section => section_vals_get_subs_vals(motion_section,
"MD")
1030 CALL section_vals_get(md_section, explicit=explicit1)
1032 CALL section_vals_val_unset(md_section,
"STEP_START_VAL")
1033 CALL section_vals_val_unset(md_section,
"TIME_START_VAL")
1034 CALL section_vals_val_unset(md_section,
"ECONS_START_VAL")
1036 work_section => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN")
1037 CALL section_vals_get(work_section, explicit=explicit1)
1039 CALL section_vals_val_unset(motion_section,
"FREE_ENERGY%METADYN%STEP_START_VAL")
1040 CALL section_vals_val_unset(motion_section,
"FREE_ENERGY%METADYN%NHILLS_START_VAL")
1042 section_to_delete => section_vals_get_subs_vals(motion_section,
"BAND%REPLICA")
1043 CALL section_vals_remove_values(section_to_delete)
1044 section_to_delete => section_vals_get_subs_vals(md_section,
"AVERAGES%RESTART_AVERAGES")
1045 CALL section_vals_remove_values(section_to_delete)
1046 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%COORD")
1047 CALL section_vals_remove_values(section_to_delete)
1048 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%VELOCITY")
1049 CALL section_vals_remove_values(section_to_delete)
1050 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%MASS")
1051 CALL section_vals_remove_values(section_to_delete)
1052 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%FORCE")
1053 CALL section_vals_remove_values(section_to_delete)
1054 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%MASS")
1055 CALL section_vals_remove_values(section_to_delete)
1056 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%VELOCITY")
1057 CALL section_vals_remove_values(section_to_delete)
1058 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%COORD")
1059 CALL section_vals_remove_values(section_to_delete)
1060 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%VELOCITY")
1061 CALL section_vals_remove_values(section_to_delete)
1062 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%MASS")
1063 CALL section_vals_remove_values(section_to_delete)
1064 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%FORCE")
1065 CALL section_vals_remove_values(section_to_delete)
1066 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%COORD")
1067 CALL section_vals_remove_values(section_to_delete)
1068 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%VELOCITY")
1069 CALL section_vals_remove_values(section_to_delete)
1070 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%MASS")
1071 CALL section_vals_remove_values(section_to_delete)
1072 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%FORCE")
1073 CALL section_vals_remove_values(section_to_delete)
1075 section_to_delete => section_vals_get_subs_vals(motion_section,
"CONSTRAINT%FIX_ATOM_RESTART")
1076 CALL section_vals_remove_values(section_to_delete)
1077 section_to_delete => section_vals_get_subs_vals(motion_section,
"CONSTRAINT%COLVAR_RESTART")
1078 CALL section_vals_remove_values(section_to_delete)
1080 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_POS")
1081 CALL section_vals_remove_values(section_to_delete)
1082 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE")
1083 CALL section_vals_remove_values(section_to_delete)
1084 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT")
1085 CALL section_vals_remove_values(section_to_delete)
1086 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT")
1087 CALL section_vals_remove_values(section_to_delete)
1088 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_SS0")
1089 CALL section_vals_remove_values(section_to_delete)
1090 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP")
1091 CALL section_vals_remove_values(section_to_delete)
1092 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_SS")
1093 CALL section_vals_remove_values(section_to_delete)
1094 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_FS")
1095 CALL section_vals_remove_values(section_to_delete)
1096 CALL timestop(handle)
1104 SUBROUTINE handle_defaults_restart(r_section)
1105 TYPE(section_vals_type),
POINTER :: r_section
1107 CHARACTER(len=*),
PARAMETER :: routinen =
'handle_defaults_restart'
1109 INTEGER :: handle, ik, nval
1110 LOGICAL :: restart_default
1111 TYPE(keyword_type),
POINTER :: keyword
1112 TYPE(section_type),
POINTER :: section
1114 CALL timeset(routinen, handle)
1115 NULLIFY (keyword, section)
1116 CALL section_vals_get(r_section, section=section)
1117 CALL section_vals_val_get(r_section,
"RESTART_DEFAULT", l_val=restart_default)
1118 DO ik = -1, section%n_keywords
1119 keyword => section%keywords(ik)%keyword
1120 IF (
ASSOCIATED(keyword))
THEN
1121 IF (keyword%type_of_var == logical_t .AND. keyword%names(1) (1:8) ==
"RESTART_")
THEN
1122 IF (trim(keyword%names(1)) ==
"RESTART_DEFAULT") cycle
1123 CALL section_vals_val_get(r_section, keyword%names(1), n_rep_val=nval)
1126 CALL section_vals_val_set(r_section, keyword%names(1), l_val=restart_default)
1131 CALL timestop(handle)
1133 END SUBROUTINE handle_defaults_restart
various routines to log and control the output. The idea is that decisions about where to log should ...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_release(parser)
releases the parser
subroutine, public parser_create(parser, file_name, unit_nr, para_env, end_section_label, separator_chars, comment_char, continuation_char, quote_char, section_char, parse_white_lines, initial_variables, apply_preprocessing)
Start a parser run. Initial variables allow to @SET stuff before opening the file.
subroutine, public cp_unit_set_release(unit_set)
releases the given unit set
subroutine, public cp_unit_set_create(unit_set, name)
initializes the given unit set
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
integer, parameter, public default_path_length
Utility routines for the memory handling.
Interface to the message passing library MPI.
stores the default units to be used
stores all the informations relevant to an mpi environment