Skip to content

Commit

Permalink
Added option in TP-XAS: write a full restart file from the XAS-SCF (#…
Browse files Browse the repository at this point in the history
  • Loading branch information
marci73 committed Feb 23, 2022
1 parent afe1d75 commit f2b1148
Show file tree
Hide file tree
Showing 5 changed files with 48 additions and 4 deletions.
9 changes: 9 additions & 0 deletions src/input_cp2k_dft.F
Original file line number Diff line number Diff line change
Expand Up @@ -7283,6 +7283,15 @@ SUBROUTINE create_xas_section(section)
CALL section_add_subsection(subsection, print_key)
CALL section_release(print_key)

CALL cp_print_key_section_create(print_key, __LOCATION__, "FULL_RESTART", &
description="Controls the dumping of a standard MO restart file "// &
"where coefficients and occupation numbers are those of the TP scheme,"// &
"i.e. with emptied core state.", &
print_level=high_print_level, common_iter_levels=3, each_iter_names=s2a("XAS_SCF"), &
add_last=add_last_numeric, each_iter_values=(/3/), filename="")
CALL section_add_subsection(subsection, print_key)
CALL section_release(print_key)

CALL cp_print_key_section_create(print_key, __LOCATION__, "CLS_FUNCTION_CUBES", &
description="Controls the printing of the relaxed orbitals ", &
print_level=high_print_level, common_iter_levels=3, add_last=add_last_numeric, filename="")
Expand Down
3 changes: 2 additions & 1 deletion src/qs_mo_io.F
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,8 @@ MODULE qs_mo_io
write_dm_binary_restart, &
write_mo_set_to_output_unit, &
write_mo_set_to_restart, &
read_mo_set_from_restart
read_mo_set_from_restart, &
write_mo_set_low

CONTAINS

Expand Down
24 changes: 22 additions & 2 deletions src/xas_restart.F
Original file line number Diff line number Diff line change
Expand Up @@ -47,12 +47,15 @@ MODULE xas_restart
default_string_length,&
dp
USE message_passing, ONLY: mp_bcast
USE particle_types, ONLY: particle_type
USE qs_density_matrices, ONLY: calculate_density_matrix
USE qs_environment_types, ONLY: get_qs_env,&
qs_environment_type
USE qs_kind_types, ONLY: qs_kind_type
USE qs_ks_types, ONLY: qs_ks_did_change
USE qs_mixing_utils, ONLY: mixing_init
USE qs_mo_io, ONLY: wfn_restart_file_name
USE qs_mo_io, ONLY: wfn_restart_file_name,&
write_mo_set_low
USE qs_mo_occupation, ONLY: set_mo_occupation
USE qs_mo_types, ONLY: get_mo_set,&
mo_set_p_type,&
Expand Down Expand Up @@ -293,10 +296,12 @@ SUBROUTINE xas_write_restart(xas_env, xas_section, qs_env, xas_method, iatom, is
TYPE(cp_fm_type), POINTER :: mo_coeff
TYPE(cp_logger_type), POINTER :: logger
TYPE(mo_set_p_type), DIMENSION(:), POINTER :: mos
TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set
TYPE(section_vals_type), POINTER :: print_key

CALL timeset(routineN, handle)
NULLIFY (mos, logger, print_key)
NULLIFY (mos, logger, print_key, particle_set, qs_kind_set)
logger => cp_get_default_logger()

CALL get_xas_env(xas_env=xas_env, occ_estate=occ_estate, xas_estate=xas_estate, &
Expand Down Expand Up @@ -350,6 +355,21 @@ SUBROUTINE xas_write_restart(xas_env, xas_section, qs_env, xas_method, iatom, is
CALL cp_print_key_finished_output(rst_unit, logger, xas_section, &
"PRINT%RESTART")
END IF

IF (BTEST(cp_print_key_should_output(logger%iter_info, &
xas_section, "PRINT%FULL_RESTART", used_print_key=print_key), &
cp_p_file)) THEN
rst_unit = cp_print_key_unit_nr(logger, xas_section, "PRINT%FULL_RESTART", &
extension="_full.rst", file_status="REPLACE", file_action="WRITE", &
file_form="UNFORMATTED", middle_name=TRIM(my_middle))

CALL get_qs_env(qs_env=qs_env, particle_set=particle_set, qs_kind_set=qs_kind_set)
CALL write_mo_set_low(mos, particle_set=particle_set, &
qs_kind_set=qs_kind_set, ires=rst_unit)
CALL cp_print_key_finished_output(rst_unit, logger, xas_section, "PRINT%FULL_RESTART")

END IF

CALL timestop(handle)

END SUBROUTINE xas_write_restart
Expand Down
10 changes: 9 additions & 1 deletion src/xas_tp_scf.F
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,7 @@ MODULE xas_tp_scf
localized_wfn_control_type,&
qs_loc_env_new_type
USE qs_mixing_utils, ONLY: self_consistency_check
USE qs_mo_io, ONLY: write_mo_set_to_restart
USE qs_mo_methods, ONLY: calculate_subspace_eigenvalues
USE qs_mo_occupation, ONLY: set_mo_occupation
USE qs_mo_types, ONLY: get_mo_set,&
Expand Down Expand Up @@ -156,17 +157,20 @@ SUBROUTINE xas_do_tp_scf(dft_control, xas_env, iatom, istate, scf_env, qs_env, &
TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: matrix_ks, matrix_s
TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: rho_ao_kp
TYPE(mo_set_p_type), DIMENSION(:), POINTER :: mos
TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
TYPE(qs_charges_type), POINTER :: qs_charges
TYPE(qs_energy_type), POINTER :: energy
TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set
TYPE(qs_ks_env_type), POINTER :: ks_env
TYPE(qs_rho_type), POINTER :: rho
TYPE(scf_control_type), POINTER :: scf_control
TYPE(section_vals_type), POINTER :: dft_section
TYPE(xas_control_type), POINTER :: xas_control

CALL timeset(routineN, handle)
NULLIFY (xas_control, matrix_s, matrix_ks, para_env, rho_ao_kp)
NULLIFY (rho, energy, scf_control, logger, ks_env, mos, atomic_kind_set)
NULLIFY (qs_charges)
NULLIFY (qs_charges, particle_set, qs_kind_set)

logger => cp_get_default_logger()
t1 = m_walltime()
Expand Down Expand Up @@ -331,6 +335,10 @@ SUBROUTINE xas_do_tp_scf(dft_control, xas_env, iatom, istate, scf_env, qs_env, &
CALL xas_write_restart(xas_env, xas_section, qs_env, xas_control%xas_method, &
iatom, istate)

dft_section => section_vals_get_subs_vals(qs_env%input, "DFT")
CALL get_qs_env(qs_env=qs_env, mos=mos, particle_set=particle_set, qs_kind_set=qs_kind_set)
CALL write_mo_set_to_restart(mos, particle_set, dft_section=dft_section, qs_kind_set=qs_kind_set)

IF (exit_loop) THEN
CALL timestop(handle2)
EXIT scf_loop
Expand Down
6 changes: 6 additions & 0 deletions tests/QS/regtest-gapw-4/CO_xastpxfh.inp
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,12 @@
XAS_SCF 4
&END
ADD_LAST NUMERIC
&END
&FULL_RESTART
&EACH
XAS_SCF 4
&END
ADD_LAST NUMERIC
&END
&XES_SPECTRUM
&END
Expand Down

0 comments on commit f2b1148

Please sign in to comment.