Skip to content

Commit

Permalink
Also log the reading of wfn restart files (cp2k#2960)
Browse files Browse the repository at this point in the history
  • Loading branch information
mkrack authored Aug 31, 2023
1 parent f67586f commit edf7f2f
Show file tree
Hide file tree
Showing 4 changed files with 57 additions and 12 deletions.
7 changes: 5 additions & 2 deletions src/motion/simpar_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ SUBROUTINE read_md_section(simpar, motion_section, md_section)
iw = cp_print_key_unit_nr(logger, md_section, "PRINT%PROGRAM_RUN_INFO", extension=".log")

CALL read_md_low(simpar, motion_section, md_section)
IF (iw > 0) WRITE (iw, *)
IF (iw > 0) WRITE (UNIT=iw, FMT="(A)") ""

! Begin setup Langevin dynamics
IF (simpar%ensemble == langevin_ensemble) THEN
Expand All @@ -88,14 +88,17 @@ SUBROUTINE read_md_section(simpar, motion_section, md_section)
! Normalization factor using a normal Gaussian random number distribution
simpar%var_w = 2.0_dp*simpar%temp_ext*simpar%dt*(simpar%gamma + simpar%noisy_gamma)
IF (iw > 0) THEN
WRITE (UNIT=iw, FMT="(T2,A)") &
"LD| Parameters for Langevin dynamics"
tmp_r1 = cp_unit_from_cp2k(simpar%gamma, "fs^-1")
tmp_r2 = cp_unit_from_cp2k(simpar%noisy_gamma, "fs^-1")
tmp_r3 = cp_unit_from_cp2k(simpar%shadow_gamma, "fs^-1")
WRITE (UNIT=iw, FMT="(T2,A,T71,ES10.3)") &
"LD| Gamma [1/fs] ", tmp_r1, &
"LD| Noisy Gamma [1/fs]", tmp_r2, &
"LD| Shadow Gamma [1/fs]", tmp_r3, &
"LD| Variance [a.u.]", simpar%var_w
"LD| Variance [a.u.]", simpar%var_w, &
""
END IF
END IF

Expand Down
40 changes: 33 additions & 7 deletions src/qs_initial_guess.F
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,8 @@ MODULE qs_initial_guess
sparse_guess
USE input_cp2k_hfx, ONLY: ri_mo
USE input_section_types, ONLY: section_vals_get_subs_vals,&
section_vals_type
section_vals_type,&
section_vals_val_get
USE kinds, ONLY: default_path_length,&
dp
USE kpoint_io, ONLY: read_kpoints_restart
Expand Down Expand Up @@ -146,7 +147,7 @@ SUBROUTINE calculate_first_density_matrix(scf_env, qs_env)
INTEGER, DIMENSION(:), POINTER :: atom_list, elec_conf, nelec_kind, &
sort_kind
LOGICAL :: did_guess, do_hfx_ri_mo, do_kpoints, do_std_diag, exist, has_unit_metric, &
natom_mismatch, need_mos, need_wm, ofgpw, owns_ortho
natom_mismatch, need_mos, need_wm, ofgpw, owns_ortho, print_history_log, print_log
REAL(dp), ALLOCATABLE, DIMENSION(:, :) :: buff, buff2
REAL(dp), DIMENSION(:, :), POINTER :: pdata
REAL(KIND=dp) :: checksum, eps, length, maxocc, occ, &
Expand Down Expand Up @@ -313,8 +314,9 @@ SUBROUTINE calculate_first_density_matrix(scf_env, qs_env)
IF (do_kpoints) THEN
CPABORT("calculate_first_density_matrix: history_guess not implemented for k-points")
END IF
IF (para_env%is_source()) &
IF (para_env%is_source()) THEN
CALL wfn_restart_file_name(file_name, exist, dft_section, logger)
END IF
CALL para_env%bcast(exist)
CALL para_env%bcast(file_name)
nvec = qs_env%wf_history%memory_depth
Expand All @@ -323,7 +325,9 @@ SUBROUTINE calculate_first_density_matrix(scf_env, qs_env)
DO i = 1, nvec
j = i - 1
filename = TRIM(file_name)
IF (j /= 0) filename = TRIM(file_name)//".bak-"//ADJUSTL(cp_to_string(j))
IF (j /= 0) THEN
filename = TRIM(file_name)//".bak-"//ADJUSTL(cp_to_string(j))
END IF
IF (para_env%is_source()) &
INQUIRE (FILE=filename, exist=exist)
CALL para_env%bcast(exist)
Expand Down Expand Up @@ -365,8 +369,26 @@ SUBROUTINE calculate_first_density_matrix(scf_env, qs_env)
END IF
END IF

IF (density_guess == restart_guess) THEN
ounit = -1
print_log = .FALSE.
print_history_log = .FALSE.
IF (para_env%is_source()) THEN
CALL section_vals_val_get(dft_section, &
"SCF%PRINT%RESTART%LOG_PRINT_KEY", &
l_val=print_log)
CALL section_vals_val_get(dft_section, &
"SCF%PRINT%RESTART_HISTORY%LOG_PRINT_KEY", &
l_val=print_history_log)
IF (print_log .OR. print_history_log) THEN
ounit = cp_logger_get_default_io_unit(logger)
END IF
END IF

IF (density_guess == restart_guess) THEN
IF (ounit > 0) THEN
WRITE (UNIT=ounit, FMT="(/,T2,A)") &
"WFN_RESTART| Reading restart file"
END IF
IF (do_kpoints) THEN
natoms = SIZE(particle_set)
CALL read_kpoints_restart(rho_ao_kp, kpoints, work1, &
Expand All @@ -375,7 +397,7 @@ SUBROUTINE calculate_first_density_matrix(scf_env, qs_env)
ELSE
CALL read_mo_set_from_restart(mo_array, atomic_kind_set, qs_kind_set, particle_set, para_env, &
id_nr=id_nr, multiplicity=dft_control%multiplicity, dft_section=dft_section, &
natom_mismatch=natom_mismatch)
natom_mismatch=natom_mismatch, out_unit=ounit)

IF (natom_mismatch) THEN
density_guess = safe_density_guess
Expand Down Expand Up @@ -441,11 +463,15 @@ SUBROUTINE calculate_first_density_matrix(scf_env, qs_env)

IF (density_guess == history_guess) THEN
IF (not_read > 1) THEN
IF (ounit > 0) THEN
WRITE (UNIT=ounit, FMT="(/,T2,A)") &
"WFN_RESTART| Reading restart file history"
END IF
DO i = 1, last_read
j = last_read - i
CALL read_mo_set_from_restart(mo_array, atomic_kind_set, qs_kind_set, particle_set, para_env, &
id_nr=j, multiplicity=dft_control%multiplicity, &
dft_section=dft_section)
dft_section=dft_section, out_unit=ounit)

DO ispin = 1, nspin
IF (scf_control%level_shift /= 0.0_dp) THEN
Expand Down
17 changes: 14 additions & 3 deletions src/qs_mo_io.F
Original file line number Diff line number Diff line change
Expand Up @@ -486,10 +486,11 @@ END SUBROUTINE wfn_restart_file_name
!> \param dft_section ...
!> \param natom_mismatch ...
!> \param cdft ...
!> \param out_unit ...
! **************************************************************************************************
SUBROUTINE read_mo_set_from_restart(mo_array, atomic_kind_set, qs_kind_set, particle_set, &
para_env, id_nr, multiplicity, dft_section, natom_mismatch, &
cdft)
cdft, out_unit)

TYPE(mo_set_type), DIMENSION(:), INTENT(INOUT) :: mo_array
TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
Expand All @@ -500,18 +501,22 @@ SUBROUTINE read_mo_set_from_restart(mo_array, atomic_kind_set, qs_kind_set, part
TYPE(section_vals_type), POINTER :: dft_section
LOGICAL, INTENT(OUT), OPTIONAL :: natom_mismatch
LOGICAL, INTENT(IN), OPTIONAL :: cdft
INTEGER, INTENT(IN), OPTIONAL :: out_unit

CHARACTER(LEN=*), PARAMETER :: routineN = 'read_mo_set_from_restart'

CHARACTER(LEN=default_path_length) :: file_name
INTEGER :: handle, ispin, natom, nspin, restart_unit
INTEGER :: handle, ispin, my_out_unit, natom, &
nspin, restart_unit
LOGICAL :: exist, my_cdft
TYPE(cp_logger_type), POINTER :: logger

CALL timeset(routineN, handle)
logger => cp_get_default_logger()
my_cdft = .FALSE.
IF (PRESENT(cdft)) my_cdft = cdft
my_out_unit = -1
IF (PRESENT(out_unit)) my_out_unit = out_unit

nspin = SIZE(mo_array)
restart_unit = -1
Expand Down Expand Up @@ -548,7 +553,13 @@ SUBROUTINE read_mo_set_from_restart(mo_array, atomic_kind_set, qs_kind_set, part
END IF

! Close restart file
IF (para_env%is_source()) CALL close_file(unit_number=restart_unit)
IF (para_env%is_source()) THEN
IF (my_out_unit > 0) THEN
WRITE (UNIT=my_out_unit, FMT="(T2,A)") &
"WFN_RESTART| Restart file "//TRIM(file_name)//" read"
END IF
CALL close_file(unit_number=restart_unit)
END IF

! CDFT has no real dft_section and does not need to print
IF (.NOT. my_cdft) THEN
Expand Down
5 changes: 5 additions & 0 deletions tests/QS/regtest-ot-1/H2O-OT-ASPC-6.inp
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,11 @@
&OT ON
MINIMIZER DIIS
&END OT
&PRINT
&RESTART_HISTORY
LOG_PRINT_KEY
&END RESTART_HISTORY
&END PRINT
&END SCF
&XC
&XC_FUNCTIONAL Pade
Expand Down

0 comments on commit edf7f2f

Please sign in to comment.