Skip to content

Commit

Permalink
Revise TDA basis set info output (cp2k#3430)
Browse files Browse the repository at this point in the history
  • Loading branch information
juerghutter authored May 24, 2024
1 parent e3f64b7 commit 7c26275
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 19 deletions.
7 changes: 6 additions & 1 deletion src/basis_set_output.F
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@ SUBROUTINE print_basis_set_file(qs_env, base_section)
INTEGER, SAVE :: ncalls = 0
TYPE(cp_logger_type), POINTER :: logger
TYPE(gto_basis_set_type), POINTER :: aux_fit_basis, lri_aux_basis, orb_basis, &
p_lri_aux_basis, ri_aux_basis, ri_hfx_basis, ri_hxc_basis, ri_xas_basis
p_lri_aux_basis, ri_aux_basis, ri_hfx_basis, ri_hxc_basis, ri_xas_basis, tda_hfx_basis
TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set
TYPE(qs_kind_type), POINTER :: qs_kind

Expand Down Expand Up @@ -96,6 +96,7 @@ SUBROUTINE print_basis_set_file(qs_env, base_section)
CALL get_qs_kind(qs_kind, basis_set=p_lri_aux_basis, basis_type="P_LRI_AUX")
CALL get_qs_kind(qs_kind, basis_set=aux_fit_basis, basis_type="AUX_FIT")
CALL get_qs_kind(qs_kind, basis_set=ri_xas_basis, basis_type="RI_XAS")
CALL get_qs_kind(qs_kind, basis_set=tda_hfx_basis, basis_type="TDA_HFX")
IF (ounit > 0) THEN
IF (ASSOCIATED(orb_basis)) THEN
bname = "local_orbital"
Expand Down Expand Up @@ -129,6 +130,10 @@ SUBROUTINE print_basis_set_file(qs_env, base_section)
bname = "local_ri_hfx"
CALL basis_out(ri_hfx_basis, element_symbol, bname, iunit)
END IF
IF (ASSOCIATED(tda_hfx_basis)) THEN
bname = "local_tda_hfx"
CALL basis_out(tda_hfx_basis, element_symbol, bname, iunit)
END IF
END IF
END DO

Expand Down
3 changes: 3 additions & 0 deletions src/min_basis_set.F
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,9 @@ SUBROUTINE create_minbas_set(qs_env, unit_nr, basis_type, primitive)
nprim = -1
END IF

IF (unit_nr > 0) THEN
WRITE (unit_nr, '(T2,A,T60,A21)') "Generate MINBAS set", ADJUSTR(TRIM(btype))
END IF
! check for or generate reference basis
CALL get_qs_env(qs_env=qs_env, qs_kind_set=qs_kind_set)
CALL get_qs_env(qs_env, dft_control=dft_control)
Expand Down
21 changes: 3 additions & 18 deletions src/qs_tddfpt2_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -66,8 +66,7 @@ MODULE qs_tddfpt2_methods
USE qs_kernel_types, ONLY: full_kernel_env_type,&
kernel_env_type,&
release_kernel_env
USE qs_kind_types, ONLY: get_qs_kind_set,&
qs_kind_type
USE qs_kind_types, ONLY: qs_kind_type
USE qs_mo_types, ONLY: mo_set_type
USE qs_scf_methods, ONLY: eigensolver
USE qs_scf_types, ONLY: qs_scf_env_type
Expand Down Expand Up @@ -238,7 +237,7 @@ SUBROUTINE tddfpt(qs_env, calc_forces)
END IF

CALL tddfpt_header(log_unit)
CALL kernel_info(qs_env, log_unit, dft_control, tddfpt_control, xc_section)
CALL kernel_info(log_unit, dft_control, tddfpt_control, xc_section)
! obtain occupied and virtual (unoccupied) ground-state Kohn-Sham orbitals
NULLIFY (gs_mos)

Expand Down Expand Up @@ -743,25 +742,20 @@ END SUBROUTINE tddfpt_input

! **************************************************************************************************
!> \brief ...
!> \param qs_env ...
!> \param log_unit ...
!> \param dft_control ...
!> \param tddfpt_control ...
!> \param xc_section ...
! **************************************************************************************************
SUBROUTINE kernel_info(qs_env, log_unit, dft_control, tddfpt_control, xc_section)
TYPE(qs_environment_type), POINTER :: qs_env
SUBROUTINE kernel_info(log_unit, dft_control, tddfpt_control, xc_section)
INTEGER, INTENT(IN) :: log_unit
TYPE(dft_control_type), POINTER :: dft_control
TYPE(tddfpt2_control_type), POINTER :: tddfpt_control
TYPE(section_vals_type), POINTER :: xc_section

CHARACTER(LEN=4) :: ktype
INTEGER :: nbas_admm, nbas_hfxsr, nbas_lri
LOGICAL :: lsd
TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set

CALL get_qs_env(qs_env, qs_kind_set=qs_kind_set)
lsd = (dft_control%nspins > 1)
IF (tddfpt_control%kernel == tddfpt_kernel_full) THEN
ktype = "FULL"
Expand All @@ -770,10 +764,7 @@ SUBROUTINE kernel_info(qs_env, log_unit, dft_control, tddfpt_control, xc_section
CALL xc_write(log_unit, xc_section, lsd)
IF (tddfpt_control%do_hfx) THEN
IF (tddfpt_control%do_admm) THEN
CALL get_qs_kind_set(qs_kind_set, nsgf=nbas_admm, basis_type="AUX_FIT")
WRITE (log_unit, "(T2,A,T62,A19)") "KERNEL|", "ADMM Exact Exchange"
WRITE (log_unit, "(T2,A,T41,A,T72,I9)") &
"KERNEL|", "Number of ADMM basis functions", nbas_admm
IF (tddfpt_control%admm_xc_correction) THEN
WRITE (log_unit, "(T2,A,T60,A21)") "KERNEL|", "Apply ADMM Kernel XC Correction"
END IF
Expand All @@ -785,19 +776,13 @@ SUBROUTINE kernel_info(qs_env, log_unit, dft_control, tddfpt_control, xc_section
END IF
END IF
IF (tddfpt_control%do_hfxsr) THEN
CALL get_qs_kind_set(qs_kind_set, nsgf=nbas_hfxsr, basis_type="TDA_HFX")
WRITE (log_unit, "(T2,A,T43,A38)") "KERNEL|", "Short range HFX approximation"
WRITE (log_unit, "(T2,A,T38,A,T72,I9)") &
"KERNEL|", "Number of TDA-X SR basis functions", nbas_hfxsr
END IF
IF (tddfpt_control%do_hfxlr) THEN
WRITE (log_unit, "(T2,A,T43,A38)") "KERNEL|", "Long range HFX approximation"
END IF
IF (tddfpt_control%do_lrigpw) THEN
CALL get_qs_kind_set(qs_kind_set, nsgf=nbas_lri, basis_type="P_LRI_AUX")
WRITE (log_unit, "(T2,A,T42,A39)") "KERNEL|", "LRI approximation of transition density"
WRITE (log_unit, "(T2,A,T39,A,T72,I9)") &
"KERNEL|", "Number of TDA-LRI basis functions", nbas_hfxsr
END IF
END IF
ELSE IF (tddfpt_control%kernel == tddfpt_kernel_stda) THEN
Expand Down

0 comments on commit 7c26275

Please sign in to comment.