Skip to content

Commit

Permalink
XAS_TDP| clean-up + performance upgrade
Browse files Browse the repository at this point in the history
  • Loading branch information
abussy committed Nov 16, 2020
1 parent d8fd13a commit 96643d5
Show file tree
Hide file tree
Showing 8 changed files with 325 additions and 235 deletions.
2 changes: 1 addition & 1 deletion src/hfx_load_balance_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ MODULE hfx_load_balance_methods
PRIVATE

PUBLIC :: hfx_load_balance, &
hfx_update_load_balance, &
hfx_update_load_balance, reshuffle, &
collect_load_balance_info, cost_model, p1_energy, p2_energy, p3_energy

CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'hfx_load_balance_methods'
Expand Down
6 changes: 2 additions & 4 deletions src/input_cp2k_dft.F
Original file line number Diff line number Diff line change
Expand Up @@ -8101,8 +8101,7 @@ SUBROUTINE create_xas_tdp_section(section)
description="Whether spin-orbit coupling should be added. "// &
"Note: only applies for spin-restricted calculations with "// &
"singlet and triplet excitations OR spin-unrestricted "// &
"calculations with both spin-conserving and spin-flip."// &
"Only tested with CIS", &
"calculations with both spin-conserving and spin-flip.", &
usage="SOC {logical}", &
default_l_val=.FALSE., &
lone_keyword_l_val=.TRUE.)
Expand All @@ -8124,8 +8123,7 @@ SUBROUTINE create_xas_tdp_section(section)
"a given atomic kind. This keyword can/should be repeated "// &
"for each excited kind. The default grid dimensions are "// &
"those set for the GAPW ground state calculation. These "// &
"grids are used for the xc-kernel calculations and/or for "// &
"spin-orbit coupling. "// &
"grids are used for the xc-kernel integration. "// &
"Usage: GRID < KIND > < LEBEDEV_GRID > < RADIAL_GRID >", &
usage="GRID {string} {integer} {integer}", &
n_var=3, type_of_var=char_t, repeats=.TRUE.)
Expand Down
139 changes: 60 additions & 79 deletions src/xas_tdp_atom.F

Large diffs are not rendered by default.

10 changes: 5 additions & 5 deletions src/xas_tdp_integrals.F
Original file line number Diff line number Diff line change
Expand Up @@ -1039,16 +1039,16 @@ END SUBROUTINE get_opt_3c_dist2d
! **************************************************************************************************
!> \brief Computes the RI exchange 3-center integrals (ab|c), where c is from the RI_XAS basis and
!> centered on excited atoms and kind. The operator used is that of the RI metric
!> \param ex_atom the excited atom on which the third center is
!> \param ex_atoms excited atoms on which the third center is located
!> \param xas_tdp_env ...
!> \param xas_tdp_control ...
!> \param qs_env ...
!> \note This routine is called once for each excited atom. Because there are many different a,b
!> pairs involved, load balance is ok. This allows memory saving
! **************************************************************************************************
SUBROUTINE compute_ri_3c_exchange(ex_atom, xas_tdp_env, xas_tdp_control, qs_env)
SUBROUTINE compute_ri_3c_exchange(ex_atoms, xas_tdp_env, xas_tdp_control, qs_env)
INTEGER, INTENT(IN) :: ex_atom
INTEGER, DIMENSION(:), INTENT(IN) :: ex_atoms
TYPE(xas_tdp_env_type), POINTER :: xas_tdp_env
TYPE(xas_tdp_control_type), POINTER :: xas_tdp_control
TYPE(qs_environment_type), POINTER :: qs_env
Expand Down Expand Up @@ -1083,7 +1083,7 @@ SUBROUTINE compute_ri_3c_exchange(ex_atom, xas_tdp_env, xas_tdp_control, qs_env)
CALL build_xas_tdp_ovlp_nl(ab_list, basis_set_orb, basis_set_orb, qs_env)
CALL build_xas_tdp_3c_nl(ac_list, basis_set_orb, basis_set_ri, &
xas_tdp_control%ri_m_potential%potential_type, qs_env, &
excited_atoms=[ex_atom], x_range=xas_tdp_control%ri_m_potential%cutoff_radius)
excited_atoms=ex_atoms, x_range=xas_tdp_control%ri_m_potential%cutoff_radius)
CALL get_opt_3c_dist2d(xas_tdp_env%opt_dist2d_ex, ab_list, ac_list, basis_set_orb, &
basis_set_orb, basis_set_ri, qs_env)
Expand All @@ -1095,7 +1095,7 @@ SUBROUTINE compute_ri_3c_exchange(ex_atom, xas_tdp_env, xas_tdp_control, qs_env)
ext_dist2d=xas_tdp_env%opt_dist2d_ex)
CALL build_xas_tdp_3c_nl(ac_list, basis_set_orb, basis_set_ri, &
xas_tdp_control%ri_m_potential%potential_type, qs_env, &
excited_atoms=[ex_atom], x_range=xas_tdp_control%ri_m_potential%cutoff_radius, &
excited_atoms=ex_atoms, x_range=xas_tdp_control%ri_m_potential%cutoff_radius, &
ext_dist2d=xas_tdp_env%opt_dist2d_ex)
! Allocate, init and compute the integrals.
Expand Down
56 changes: 35 additions & 21 deletions src/xas_tdp_kernel.F
Original file line number Diff line number Diff line change
Expand Up @@ -18,11 +18,12 @@ MODULE xas_tdp_kernel
USE cp_para_types, ONLY: cp_para_env_type
USE dbcsr_api, ONLY: &
dbcsr_add, dbcsr_complete_redistribute, dbcsr_copy, dbcsr_create, dbcsr_desymmetrize, &
dbcsr_distribution_release, dbcsr_distribution_type, dbcsr_finalize, dbcsr_get_block_p, &
dbcsr_get_info, dbcsr_get_stored_coordinates, dbcsr_iterator_blocks_left, &
dbcsr_iterator_next_block, dbcsr_iterator_start, dbcsr_iterator_stop, dbcsr_iterator_type, &
dbcsr_multiply, dbcsr_p_type, dbcsr_put_block, dbcsr_release, dbcsr_reserve_block2d, &
dbcsr_set, dbcsr_transposed, dbcsr_type, dbcsr_type_no_symmetry, dbcsr_type_symmetric
dbcsr_distribution_get, dbcsr_distribution_new, dbcsr_distribution_release, &
dbcsr_distribution_type, dbcsr_finalize, dbcsr_get_block_p, dbcsr_get_info, &
dbcsr_get_stored_coordinates, dbcsr_iterator_blocks_left, dbcsr_iterator_next_block, &
dbcsr_iterator_start, dbcsr_iterator_stop, dbcsr_iterator_type, dbcsr_multiply, &
dbcsr_p_type, dbcsr_put_block, dbcsr_release, dbcsr_reserve_block2d, dbcsr_set, &
dbcsr_transposed, dbcsr_type, dbcsr_type_no_symmetry, dbcsr_type_symmetric
USE dbcsr_tensor_api, ONLY: dbcsr_t_get_block,&
dbcsr_t_iterator_blocks_left,&
dbcsr_t_iterator_next_block,&
Expand Down Expand Up @@ -666,20 +667,22 @@ SUBROUTINE ondiag_ex(ondiag_ex_ker, contr1_int, dist, blk_size, donor_state, xas
TYPE(xas_tdp_control_type), POINTER :: xas_tdp_control
TYPE(qs_environment_type), POINTER :: qs_env
INTEGER :: blk, iblk, iso, jblk, jso, nblk, ndo_mo, &
ndo_so, nsgfa, nsgfp, ri_atom, source
INTEGER, DIMENSION(:), POINTER :: ri_blk_size
INTEGER :: blk, group, iblk, iso, jblk, jso, nblk, &
ndo_mo, ndo_so, nsgfa, nsgfp, ri_atom, &
source
INTEGER, DIMENSION(:), POINTER :: col_dist, col_dist_work, ri_blk_size, &
row_dist, row_dist_work
INTEGER, DIMENSION(:, :), POINTER :: pgrid
LOGICAL :: do_roks, do_uks, found
REAL(dp), ALLOCATABLE, DIMENSION(:, :) :: coeffs, ri_coeffs
REAL(dp), DIMENSION(:, :), POINTER :: aIQ, pblock, PQ
TYPE(cp_para_env_type), POINTER :: para_env
TYPE(dbcsr_distribution_type) :: opt_dbcsr_dist
TYPE(dbcsr_distribution_type) :: opt_dbcsr_dist, work_dbcsr_dist
TYPE(dbcsr_iterator_type) :: iter
TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: matrix_s
TYPE(dbcsr_type) :: abIJ, abIJ_std_dist, mats_desymm, &
work_mat
TYPE(dbcsr_type) :: abIJ, mats_desymm, work_mat
NULLIFY (para_env, matrix_s, pblock, aIQ)
NULLIFY (para_env, matrix_s, pblock, aIQ, row_dist, col_dist, row_dist_work, col_dist_work, pgrid)
! We want to compute (ab|I_sigma J_tau) = (ab|P) * (P|Q)^-1 * (Q|I_sigma J_tau)
! Already have (cJ_tau|P) stored in contr1_int. Need to further contract the
Expand Down Expand Up @@ -709,11 +712,23 @@ SUBROUTINE ondiag_ex(ondiag_ex_ker, contr1_int, dist, blk_size, donor_state, xas
CALL dbcsr_create(abIJ, template=mats_desymm, name="(ab|IJ)", dist=opt_dbcsr_dist)
CALL dbcsr_complete_redistribute(mats_desymm, abIJ)
CALL dbcsr_create(abIJ_std_dist, template=mats_desymm)
CALL dbcsr_release(mats_desymm)
CALL dbcsr_create(work_mat, name="WORK", matrix_type=dbcsr_type_no_symmetry, dist=dist, &
! Create a work distribution based on opt_dbcsr_dist, but for full size matrices
CALL dbcsr_distribution_get(opt_dbcsr_dist, row_dist=row_dist, col_dist=col_dist, group=group, &
pgrid=pgrid)
ALLOCATE (row_dist_work(ndo_so*nblk))
ALLOCATE (col_dist_work(ndo_so*nblk))
DO iso = 1, ndo_so
row_dist_work((iso - 1)*nblk + 1:iso*nblk) = row_dist(:)
col_dist_work((iso - 1)*nblk + 1:iso*nblk) = col_dist(:)
END DO
CALL dbcsr_distribution_new(work_dbcsr_dist, group=group, pgrid=pgrid, row_dist=row_dist_work, &
col_dist=col_dist_work)
CALL dbcsr_create(work_mat, name="WORK", matrix_type=dbcsr_type_no_symmetry, dist=work_dbcsr_dist, &
row_blk_size=blk_size, col_blk_size=blk_size)
! Loop over donor spin-orbitals. End matrix is symmetric => span only upper half
Expand Down Expand Up @@ -748,16 +763,14 @@ SUBROUTINE ondiag_ex(ondiag_ex_ker, contr1_int, dist, blk_size, donor_state, xas
CALL dbcsr_set(abIJ, 0.0_dp)
CALL contract3_RI_to_doMOs(xas_tdp_env%ri_3c_ex, ri_coeffs(:, jso), abIJ, ri_atom)
! Need (ab|IJ) in the standard dbcsr distribution
CALL dbcsr_complete_redistribute(abIJ, abIJ_std_dist)
CALL dbcsr_iterator_start(iter, abIJ_std_dist)
! Loop over (ab|IJ) and copy into work. OK because dist are made to match
CALL dbcsr_iterator_start(iter, abIJ)
DO WHILE (dbcsr_iterator_blocks_left(iter))
CALL dbcsr_iterator_next_block(iter, row=iblk, column=jblk, blk=blk)
IF (iso == jso .AND. jblk < iblk) CYCLE
CALL dbcsr_get_block_p(abIJ_std_dist, iblk, jblk, pblock, found)
CALL dbcsr_get_block_p(abIJ, iblk, jblk, pblock, found)
IF (found) THEN
CALL dbcsr_put_block(work_mat, (iso - 1)*nblk + iblk, (jso - 1)*nblk + jblk, pblock)
Expand Down Expand Up @@ -786,7 +799,8 @@ SUBROUTINE ondiag_ex(ondiag_ex_ker, contr1_int, dist, blk_size, donor_state, xas
CALL dbcsr_release(work_mat)
CALL dbcsr_release(abIJ)
CALL dbcsr_distribution_release(opt_dbcsr_dist)
CALL dbcsr_release(abIJ_std_dist)
CALL dbcsr_distribution_release(work_dbcsr_dist)
DEALLOCATE (col_dist_work, row_dist_work)
END SUBROUTINE ondiag_ex
Expand Down

0 comments on commit 96643d5

Please sign in to comment.