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
133 CALL timestop(handle)
145 CHARACTER(LEN=512) :: wrn_msg
146 INTEGER :: ifun, nfun, shortcut
157 IF (.NOT.
ASSOCIATED(xc_fun))
EXIT
162 WRITE (wrn_msg,
'(A)')
"User requested a shortcut while defining an explicit XC functional. "// &
163 "This is not recommended as it could lead to spurious behaviour. Please check input parameters."
167 SELECT CASE (shortcut)
186 r_val=0.3998335231_dp)
188 r_val=0.0000000000_dp)
197 r_val=0.6001664769_dp)
282 cpabort(
"unknown shortcut "//trim(adjustl(
cp_to_string(shortcut))))
295 SUBROUTINE handle_ext_restart(input_declaration, input_file, para_env, output_unit)
299 INTEGER,
INTENT(IN) :: output_unit
301 CHARACTER(len=*),
PARAMETER :: routinen =
'handle_ext_restart'
303 CHARACTER(default_path_length) :: r_file_path
307 CALL timeset(routinen, handle)
312 IF (r_file_path /=
" ")
THEN
314 CHARACTER(default_path_length) :: binary_restart_file
315 CHARACTER(default_string_length) :: path
316 CHARACTER(LEN=default_string_length), &
317 DIMENSION(:),
POINTER :: restarted_infos
318 INTEGER :: ensemble, i_rep_val, &
319 iforce_eval, myi, n_rep_val, &
320 nforce_eval1, nforce_eval2
321 INTEGER,
DIMENSION(:),
POINTER :: ivec, iwalkers_status, iwork, &
323 LOGICAL :: bsse_check, check, explicit1, explicit2, &
324 flag, flag2, qmmm_check, subsys_check
326 REAL(kind=
dp),
DIMENSION(:),
POINTER :: vec, work
328 section, section1, section2, &
331 NULLIFY (restarted_infos, iwalkers_status, rwalkers_status, vec, ivec, work, iwork)
338 NULLIFY (restart_file)
340 CALL parser_create(cpparser, file_name=r_file_path, para_env=para_env)
343 default_units=default_units)
353 IF (nforce_eval1 /= nforce_eval2)
THEN
354 cpabort(
"Restart and input file MUST have the number of force_env sections")
357 CALL handle_defaults_restart(r_section)
360 DO iforce_eval = 1, nforce_eval1
362 i_rep_section=iforce_eval)
364 i_rep_section=iforce_eval)
368 subsys_check = (
ASSOCIATED(section1) .EQV.
ASSOCIATED(section2))
369 IF (subsys_check)
THEN
370 IF (
ASSOCIATED(section1))
THEN
375 CALL set_restart_info(
"CELL", restarted_infos)
382 CALL set_restart_info(
"COORDINATES", restarted_infos)
394 CALL set_restart_info(
"RANDOM NUMBER GENERATOR", restarted_infos)
401 CALL set_restart_info(
"VELOCITIES", restarted_infos)
409 IF (check_restart(section1, section2,
"SHELL_COORD")) &
410 CALL set_restart_info(
"SHELL COORDINATES", restarted_infos)
416 IF (check_restart(section1, section2,
"CORE_COORD")) &
417 CALL set_restart_info(
"CORE COORDINATES", restarted_infos)
423 IF (check_restart(section1, section2,
"SHELL_VELOCITY")) &
424 CALL set_restart_info(
"SHELL VELOCITIES", restarted_infos)
430 IF (check_restart(section1, section2,
"CORE_VELOCITY")) &
431 CALL set_restart_info(
"CORE VELOCITIES", restarted_infos)
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 " input file or whether the restart file is compatible with the input!")
446 qmmm_check = (explicit1 .AND. explicit2)
447 IF (flag .AND. qmmm_check)
THEN
448 CALL set_restart_info(
"QMMM TRANSLATION VECTOR", restarted_infos)
460 bsse_check = (explicit1 .AND. explicit2)
461 IF (flag .AND. bsse_check)
THEN
464 CALL set_restart_info(
"BSSE FRAGMENT ENERGIES", restarted_infos)
470 IF (check_restart(input_file, restart_file,
"MOTION%MD"))
THEN
477 CALL set_restart_info(
"MD COUNTERS", restarted_infos)
480 IF (check_restart(input_file, restart_file,
"MOTION%GEO_OPT"))
THEN
484 CALL set_restart_info(
"GEO_OPT COUNTERS", restarted_infos)
486 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", &
489 CALL section_vals_val_set(input_file,
"MOTION%GEO_OPT%TRANSITION_STATE%DIMER%ROT_OPT%STEP_START_VAL", &
491 CALL set_restart_info(
"ROT_OPT COUNTERS", restarted_infos)
495 IF (check_restart(input_file, restart_file,
"MOTION%GEO_OPT"))
THEN
499 CALL set_restart_info(
"CELL_OPT COUNTERS", restarted_infos)
502 IF (check_restart(input_file, restart_file,
"OPTIMIZE_INPUT"))
THEN
505 CALL set_restart_info(
"OPTIMIZE_INPUT ITERATION NUMBER", restarted_infos)
508 IF (check_restart(input_file, restart_file,
"MOTION%PINT"))
THEN
512 CALL set_restart_info(
"PINT ITERATION NUMBER", restarted_infos)
516 IF (flag2 .AND. check_restart(input_file, restart_file,
"MOTION%FREE_ENERGY%METADYN"))
THEN
518 "MOTION%FREE_ENERGY%METADYN%STEP_START_VAL", i_val=myi)
520 "MOTION%FREE_ENERGY%METADYN%STEP_START_VAL", i_val=myi)
522 "MOTION%FREE_ENERGY%METADYN%NHILLS_START_VAL", i_val=myi)
524 "MOTION%FREE_ENERGY%METADYN%NHILLS_START_VAL", i_val=myi)
527 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_NUMBER", i_val=myi)
529 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_NUMBER", i_val=myi)
531 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_STEP", i_val=myi)
533 "MOTION%FREE_ENERGY%METADYN%OLD_HILL_STEP", i_val=myi)
535 CALL set_restart_info(
"METADYNAMIC COUNTERS", restarted_infos)
541 IF (check_restart(input_file, restart_file,
"MOTION%MD"))
THEN
544 CALL set_restart_info(
"MD AVERAGES", restarted_infos)
549 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%BAND"))
THEN
552 CALL set_restart_info(
"BAND CALCULATION", restarted_infos)
556 IF (flag .AND. check_restart(input_file, restart_file,
"OPTIMIZE_INPUT%VARIABLE"))
THEN
559 CALL set_restart_info(
"OPTIMIZE_INPUT: VARIABLES", restarted_infos)
563 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%MD%BAROSTAT"))
THEN
565 "MOTION%MD%BAROSTAT%MASS")
569 "MOTION%MD%BAROSTAT%VELOCITY")
572 CALL set_restart_info(
"BAROSTAT", restarted_infos)
575 flag = check_restart(input_file, restart_file,
"MOTION%MD")
580 check = check_restart(input_file, restart_file,
"MOTION%MD%BAROSTAT")
581 CALL restart_thermostat(flag, input_file, restart_file,
"MOTION%MD%BAROSTAT%THERMOSTAT", &
583 IF (flag .AND. check)
CALL set_restart_info(
"THERMOSTAT OF BAROSTAT", restarted_infos)
587 check = check_restart(input_file, restart_file,
"MOTION%MD%SHELL")
590 CALL restart_thermostat(flag, input_file, restart_file,
"MOTION%MD%SHELL%THERMOSTAT")
591 CALL set_restart_info(
"SHELL THERMOSTAT", restarted_infos)
595 CALL restart_thermostat(flag, input_file, restart_file,
"MOTION%MD%THERMOSTAT")
596 IF (flag)
CALL set_restart_info(
"PARTICLE THERMOSTAT", restarted_infos)
599 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%CONSTRAINT"))
THEN
602 CALL set_restart_info(
"CONSTRAINTS/RESTRAINTS", restarted_infos)
606 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%FREE_ENERGY%METADYN"))
THEN
608 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_POS")
612 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE")
616 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT")
620 "MOTION%FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT")
625 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS0")
629 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP")
633 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_SS")
637 "MOTION%FREE_ENERGY%METADYN%EXT_LAGRANGE_FS")
640 CALL set_restart_info(
"METADYNAMICS", restarted_infos)
644 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%MD"))
THEN
645 CALL section_vals_val_get(input_file,
"MOTION%MD%TEMPERATURE_ANNEALING", r_val=myt, explicit=explicit1)
646 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 "but TEMPERATURE_ANNEALING isn't explicitly given or it is set to 1.")
656 CALL cp_warn(__location__, &
657 "I'm not going to override the input temperature "// &
658 "since the temperature isn't explicitly given in the external restart.")
663 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 i_vals=rwalkers_status)
666 ALLOCATE (iwalkers_status(
SIZE(rwalkers_status)))
667 iwalkers_status = rwalkers_status
668 CALL section_vals_val_set(input_file,
"MOTION%FREE_ENERGY%METADYN%MULTIPLE_WALKERS%WALKERS_STATUS", &
669 i_vals_ptr=iwalkers_status)
670 CALL set_restart_info(
"WALKERS INFO", restarted_infos)
674 IF (flag .AND. check_restart(input_file, restart_file,
"MOTION%GEO_OPT%TRANSITION_STATE%DIMER"))
THEN
676 "MOTION%GEO_OPT%TRANSITION_STATE%DIMER%DIMER_VECTOR")
679 CALL set_restart_info(
"DIMER TRANSITION STATE SEARCH", restarted_infos)
683 DO i_rep_val = 1, n_rep_val
685 IF (path /=
" ")
THEN
688 CALL set_restart_info(
"USER RESTART: "//trim(path), restarted_infos)
696 "FORCE_EVAL%DFT%REAL_TIME_PROPAGATION")
700 CALL set_restart_info(
"REAL TIME PROPAGATION", restarted_infos)
708 CALL set_restart_info(
"PINT BEAD POSITIONS", restarted_infos)
714 CALL set_restart_info(
"PINT BEAD VELOCITIES", restarted_infos)
722 CALL set_restart_info(
"PINT NOSE THERMOSTAT", restarted_infos)
728 CALL set_restart_info(
"PINT GLE THERMOSTAT", restarted_infos)
737 IF (.NOT. explicit1)
THEN
743 CALL set_restart_info(
"HELIUM BEAD POSITIONS", restarted_infos)
750 IF (.NOT. explicit1)
THEN
756 CALL set_restart_info(
"HELIUM PERMUTATION STATE", restarted_infos)
763 IF (.NOT. explicit1)
THEN
769 CALL set_restart_info(
"HELIUM FORCES ON SOLUTE", restarted_infos)
776 IF (.NOT. explicit1)
THEN
782 CALL set_restart_info(
"HELIUM RNG STATE", restarted_infos)
790 IF (.NOT. explicit1)
THEN
796 CALL set_restart_info(
"HELIUM DENSITIES", restarted_infos)
801 CALL release_restart_info(restarted_infos, r_file_path, binary_restart_file, &
805 CALL timestop(handle)
806 END SUBROUTINE handle_ext_restart
814 SUBROUTINE set_restart_info(label, restarted_infos)
816 CHARACTER(LEN=*),
INTENT(IN) :: label
817 CHARACTER(LEN=default_string_length), &
818 DIMENSION(:),
POINTER :: restarted_infos
823 IF (
ASSOCIATED(restarted_infos)) isize =
SIZE(restarted_infos)
825 CALL reallocate(restarted_infos, 1, isize)
826 restarted_infos(isize) = trim(label)
828 END SUBROUTINE set_restart_info
838 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
847 IF (output_unit > 0 .AND.
ASSOCIATED(restarted_infos))
THEN
848 WRITE (output_unit,
'(1X,79("*"))')
849 WRITE (output_unit,
'(1X,"*",T30,A,T80,"*")')
" RESTART INFORMATION "
850 WRITE (output_unit,
'(1X,79("*"))')
851 WRITE (output_unit,
'(1X,"*",T80,"*")')
853 WRITE (output_unit,
'(1X,"*",A,T26,A,T80,"*")')
" RESTART FILE NAME: ", &
854 r_file_path(53*(i - 1) + 1:53*i)
855 DO i = 2, ceiling(real(len_trim(r_file_path), kind=dp)/53.0_dp)
856 WRITE (output_unit,
'(T1,1X,"*",T26,A,T80,"*")') r_file_path(53*(i - 1) + 1:53*i)
858 IF (len_trim(binary_restart_file) > 0)
THEN
860 WRITE (output_unit,
'(1X,"*",A,T26,A,T80,"*")')
" BINARY RESTART FILE: ", &
861 binary_restart_file(53*(i - 1) + 1:53*i)
862 DO i = 2, ceiling(real(len_trim(binary_restart_file), kind=dp)/53.0_dp)
863 WRITE (output_unit,
'(T1,1X,"*",T26,A,T80,"*")') binary_restart_file(53*(i - 1) + 1:53*i)
866 WRITE (output_unit,
'(1X,"*",T80,"*")')
867 WRITE (output_unit,
'(1X,"*", A,T80,"*")')
" RESTARTED QUANTITIES: "
868 DO j = 1,
SIZE(restarted_infos)
869 DO i = 1, ceiling(real(len_trim(restarted_infos(j)), kind=dp)/53.0_dp)
870 WRITE (output_unit,
'(T1,1X,"*",T26,A,T80,"*")') restarted_infos(j) (53*(i - 1) + 1:53*i)
873 WRITE (output_unit,
'(1X,79("*"),/)')
875 IF (
ASSOCIATED(restarted_infos))
THEN
876 DEALLOCATE (restarted_infos)
878 END SUBROUTINE release_restart_info
889 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
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
900 check_loc = check_restart(input_file, restart_file, trim(path))
901 skip_other_checks =
PRESENT(check)
902 IF (skip_other_checks) check_loc = check
903 IF (flag .AND. check_loc)
THEN
906 CALL section_vals_val_get(input_file, trim(path)//
"%TYPE", i_val=input_type)
907 CALL section_vals_val_get(restart_file, trim(path)//
"%TYPE", i_val=restart_type)
909 IF (input_type == do_thermo_same_as_part)
THEN
910 CALL section_vals_val_get(input_file,
"MOTION%MD%THERMOSTAT%TYPE", i_val=input_type)
913 IF (skip_other_checks)
THEN
914 input_region = do_region_global
915 restart_region = do_region_global
918 CALL section_vals_val_get(input_file, trim(path)//
"%REGION", i_val=input_region)
919 CALL section_vals_val_get(restart_file, trim(path)//
"%REGION", i_val=restart_region)
922 IF ((input_type == restart_type) .AND. (input_region == restart_region))
THEN
923 SELECT CASE (input_type)
924 CASE (do_thermo_nose)
925 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%COORD")
926 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%COORD", section)
928 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%VELOCITY")
929 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%VELOCITY", section)
931 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%MASS")
932 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%MASS", section)
934 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%NOSE%FORCE")
935 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%NOSE%FORCE", section)
936 CASE (do_thermo_csvr)
937 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%CSVR%THERMOSTAT_ENERGY")
938 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%CSVR%THERMOSTAT_ENERGY", section)
939 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%CSVR%RNG_INIT")
940 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%CSVR%RNG_INIT", section)
942 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%GLE%THERMOSTAT_ENERGY")
943 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%GLE%THERMOSTAT_ENERGY", section)
944 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%GLE%RNG_INIT")
945 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%GLE%RNG_INIT", section)
946 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%GLE%S")
947 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%GLE%S", section)
949 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%AD_LANGEVIN%CHI")
950 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%AD_LANGEVIN%CHI", section)
951 section => section_vals_get_subs_vals(restart_file, trim(path)//
"%AD_LANGEVIN%MASS")
952 CALL section_vals_set_subs_vals(input_file, trim(path)//
"%AD_LANGEVIN%MASS", section)
955 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 "Thermostat will not be restarted! ")
961 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 "Thermostat will not be restarted! ")
969 END SUBROUTINE restart_thermostat
979 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
984 CHARACTER(len=*),
PARAMETER :: routinen =
'check_restart'
987 LOGICAL :: explicit1, explicit2
988 TYPE(section_vals_type),
POINTER :: work_section
990 CALL timeset(routinen, handle)
991 NULLIFY (work_section)
992 work_section => section_vals_get_subs_vals(input_file, trim(tag_section))
993 CALL section_vals_get(work_section, explicit=explicit1)
994 work_section => section_vals_get_subs_vals(restart_file, trim(tag_section))
995 CALL section_vals_get(work_section, explicit=explicit2)
997 do_restart = explicit1 .AND. explicit2
998 CALL timestop(handle)
999 END FUNCTION check_restart
1008 TYPE(section_vals_type),
POINTER :: input_file
1010 CHARACTER(len=*),
PARAMETER :: routinen =
'remove_restart_info'
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, &
1018 CALL timeset(routinen, handle)
1020 NULLIFY (work_section)
1021 section_to_delete => section_vals_get_subs_vals(input_file,
"EXT_RESTART")
1022 CALL section_vals_remove_values(section_to_delete)
1023 sections1 => section_vals_get_subs_vals(input_file,
"FORCE_EVAL")
1024 CALL section_vals_get(sections1, n_repetition=nforce_eval1)
1026 DO iforce_eval = 1, nforce_eval1
1027 section1 => section_vals_get_subs_vals3(sections1,
"SUBSYS", i_rep_section=iforce_eval)
1028 section_to_delete => section_vals_get_subs_vals(section1,
"COORD")
1029 CALL section_vals_remove_values(section_to_delete)
1030 section_to_delete => section_vals_get_subs_vals(section1,
"VELOCITY")
1031 CALL section_vals_remove_values(section_to_delete)
1034 motion_section => section_vals_get_subs_vals(input_file,
"MOTION")
1035 md_section => section_vals_get_subs_vals(motion_section,
"MD")
1036 CALL section_vals_get(md_section, explicit=explicit1)
1038 CALL section_vals_val_unset(md_section,
"STEP_START_VAL")
1039 CALL section_vals_val_unset(md_section,
"TIME_START_VAL")
1040 CALL section_vals_val_unset(md_section,
"ECONS_START_VAL")
1042 work_section => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN")
1043 CALL section_vals_get(work_section, explicit=explicit1)
1045 CALL section_vals_val_unset(motion_section,
"FREE_ENERGY%METADYN%STEP_START_VAL")
1046 CALL section_vals_val_unset(motion_section,
"FREE_ENERGY%METADYN%NHILLS_START_VAL")
1048 section_to_delete => section_vals_get_subs_vals(motion_section,
"BAND%REPLICA")
1049 CALL section_vals_remove_values(section_to_delete)
1050 section_to_delete => section_vals_get_subs_vals(md_section,
"AVERAGES%RESTART_AVERAGES")
1051 CALL section_vals_remove_values(section_to_delete)
1052 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%COORD")
1053 CALL section_vals_remove_values(section_to_delete)
1054 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%VELOCITY")
1055 CALL section_vals_remove_values(section_to_delete)
1056 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%MASS")
1057 CALL section_vals_remove_values(section_to_delete)
1058 section_to_delete => section_vals_get_subs_vals(md_section,
"THERMOSTAT%NOSE%FORCE")
1059 CALL section_vals_remove_values(section_to_delete)
1060 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%MASS")
1061 CALL section_vals_remove_values(section_to_delete)
1062 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%VELOCITY")
1063 CALL section_vals_remove_values(section_to_delete)
1064 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%COORD")
1065 CALL section_vals_remove_values(section_to_delete)
1066 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%VELOCITY")
1067 CALL section_vals_remove_values(section_to_delete)
1068 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%MASS")
1069 CALL section_vals_remove_values(section_to_delete)
1070 section_to_delete => section_vals_get_subs_vals(md_section,
"BAROSTAT%THERMOSTAT%NOSE%FORCE")
1071 CALL section_vals_remove_values(section_to_delete)
1072 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%COORD")
1073 CALL section_vals_remove_values(section_to_delete)
1074 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%VELOCITY")
1075 CALL section_vals_remove_values(section_to_delete)
1076 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%MASS")
1077 CALL section_vals_remove_values(section_to_delete)
1078 section_to_delete => section_vals_get_subs_vals(md_section,
"SHELL%THERMOSTAT%NOSE%FORCE")
1079 CALL section_vals_remove_values(section_to_delete)
1081 section_to_delete => section_vals_get_subs_vals(motion_section,
"CONSTRAINT%FIX_ATOM_RESTART")
1082 CALL section_vals_remove_values(section_to_delete)
1083 section_to_delete => section_vals_get_subs_vals(motion_section,
"CONSTRAINT%COLVAR_RESTART")
1084 CALL section_vals_remove_values(section_to_delete)
1086 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_POS")
1087 CALL section_vals_remove_values(section_to_delete)
1088 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_SCALE")
1089 CALL section_vals_remove_values(section_to_delete)
1090 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_HEIGHT")
1091 CALL section_vals_remove_values(section_to_delete)
1092 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%SPAWNED_HILLS_INVDT")
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_SS0")
1095 CALL section_vals_remove_values(section_to_delete)
1096 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_VVP")
1097 CALL section_vals_remove_values(section_to_delete)
1098 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_SS")
1099 CALL section_vals_remove_values(section_to_delete)
1100 section_to_delete => section_vals_get_subs_vals(motion_section,
"FREE_ENERGY%METADYN%EXT_LAGRANGE_FS")
1101 CALL section_vals_remove_values(section_to_delete)
1102 CALL timestop(handle)
1110 SUBROUTINE handle_defaults_restart(r_section)
1111 TYPE(section_vals_type),
POINTER :: r_section
1113 CHARACTER(len=*),
PARAMETER :: routinen =
'handle_defaults_restart'
1115 INTEGER :: handle, ik, nval
1116 LOGICAL :: restart_default
1117 TYPE(keyword_type),
POINTER :: keyword
1118 TYPE(section_type),
POINTER :: section
1120 CALL timeset(routinen, handle)
1121 NULLIFY (keyword, section)
1122 CALL section_vals_get(r_section, section=section)
1123 CALL section_vals_val_get(r_section,
"RESTART_DEFAULT", l_val=restart_default)
1124 DO ik = -1, section%n_keywords
1125 keyword => section%keywords(ik)%keyword
1126 IF (
ASSOCIATED(keyword))
THEN
1127 IF (keyword%type_of_var == logical_t .AND. keyword%names(1) (1:8) ==
"RESTART_")
THEN
1128 IF (trim(keyword%names(1)) ==
"RESTART_DEFAULT") cycle
1129 CALL section_vals_val_get(r_section, keyword%names(1), n_rep_val=nval)
1132 CALL section_vals_val_set(r_section, keyword%names(1), l_val=restart_default)
1137 CALL timestop(handle)
1139 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