Skip to content

Commit

Permalink
RI-HFX| Performance and memory management optimizations
Browse files Browse the repository at this point in the history
  • Loading branch information
abussy committed Nov 11, 2021
1 parent 4ef9989 commit d9068a4
Show file tree
Hide file tree
Showing 7 changed files with 563 additions and 374 deletions.
742 changes: 499 additions & 243 deletions src/hfx_ri.F

Large diffs are not rendered by default.

19 changes: 7 additions & 12 deletions src/hfx_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -571,7 +571,6 @@ MODULE hfx_types
!> \param dft_control ...
!> \param cell ...
!> \param do_exx ...
!> \param do_ot ...
!> \param nelectron_total ...
!> \par History
!> 09.2007 created [Manuel Guidon]
Expand All @@ -581,7 +580,7 @@ MODULE hfx_types
!> unknown at invocation time
! **************************************************************************************************
SUBROUTINE hfx_create(x_data, para_env, hfx_section, atomic_kind_set, qs_kind_set, &
particle_set, dft_control, cell, do_exx, do_ot, nelectron_total)
particle_set, dft_control, cell, do_exx, nelectron_total)
TYPE(hfx_type), DIMENSION(:, :), POINTER :: x_data
TYPE(cp_para_env_type) :: para_env
TYPE(section_vals_type), POINTER :: hfx_section
Expand All @@ -590,7 +589,7 @@ SUBROUTINE hfx_create(x_data, para_env, hfx_section, atomic_kind_set, qs_kind_se
TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
TYPE(dft_control_type), POINTER :: dft_control
TYPE(cell_type), POINTER :: cell
LOGICAL, OPTIONAL :: do_exx, do_ot
LOGICAL, OPTIONAL :: do_exx
INTEGER, OPTIONAL :: nelectron_total

CHARACTER(LEN=*), PARAMETER :: routineN = 'hfx_create'
Expand Down Expand Up @@ -971,12 +970,11 @@ SUBROUTINE hfx_create(x_data, para_env, hfx_section, atomic_kind_set, qs_kind_se

hf_sub_section => section_vals_get_subs_vals(hfx_section, "RI", i_rep_section=irep)
IF (actual_x_data%do_hfx_ri) THEN
CPASSERT(PRESENT(do_ot))
CPASSERT(PRESENT(nelectron_total))
ALLOCATE (actual_x_data%ri_data)
CALL hfx_ri_init_read_input_from_hfx(actual_x_data%ri_data, actual_x_data, hfx_section, &
hf_sub_section, qs_kind_set, &
particle_set, atomic_kind_set, dft_control, para_env, irep, do_ot, &
particle_set, atomic_kind_set, dft_control, para_env, irep, &
nelectron_total, my_do_exx)

END IF
Expand All @@ -1002,13 +1000,12 @@ END SUBROUTINE hfx_create
!> \param dft_control ...
!> \param para_env ...
!> \param irep ...
!> \param do_ot ...
!> \param nelectron_total ...
!> \param do_exx ...
! **************************************************************************************************
SUBROUTINE hfx_ri_init_read_input_from_hfx(ri_data, x_data, hfx_section, ri_section, qs_kind_set, &
particle_set, atomic_kind_set, dft_control, para_env, irep, &
do_ot, nelectron_total, do_exx)
nelectron_total, do_exx)
TYPE(hfx_ri_type), INTENT(INOUT) :: ri_data
TYPE(hfx_type), INTENT(INOUT) :: x_data
TYPE(section_vals_type), POINTER :: hfx_section, ri_section
Expand All @@ -1017,9 +1014,7 @@ SUBROUTINE hfx_ri_init_read_input_from_hfx(ri_data, x_data, hfx_section, ri_sect
TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
TYPE(dft_control_type), POINTER :: dft_control
TYPE(cp_para_env_type) :: para_env
INTEGER, INTENT(IN) :: irep
LOGICAL, INTENT(IN) :: do_ot
INTEGER, INTENT(IN) :: nelectron_total
INTEGER, INTENT(IN) :: irep, nelectron_total
LOGICAL, INTENT(IN) :: do_exx

CHARACTER(LEN=*), PARAMETER :: routineN = 'hfx_ri_init_read_input_from_hfx'
Expand Down Expand Up @@ -1077,8 +1072,8 @@ SUBROUTINE hfx_ri_init_read_input_from_hfx(ri_data, x_data, hfx_section, ri_sect
para_env, unit_nr, unit_nr_dbcsr, nelectron_total, &
t_c_filename=t_c_filename)

IF (ri_data%flavor == ri_mo .AND. .NOT. do_ot) THEN
CPABORT("RI_FLAVOR MO is not consistent with density mixing. Either use OT or RI_FLAVOR RHO.")
IF (dft_control%smear) THEN
CPABORT("RI_FLAVOR MO is not consistent with smearing. Please use RI_FLAVOR RHO.")
END IF

CALL timestop(handle)
Expand Down
66 changes: 33 additions & 33 deletions src/libint_2c_3c.F
Original file line number Diff line number Diff line change
Expand Up @@ -533,14 +533,14 @@ SUBROUTINE eri_3center_derivs(der_abc_1, der_abc_2, &
CALL cp_libint_get_3eri_derivs(li, lj, lk, lib, p_deriv, a_mysize)

IF (do_ext) THEN
DO k = 1, ncoc
p1 = (k - 1)*ncob
DO j = 1, ncob
p2 = (p1 + j - 1)*ncoa
DO i = 1, ncoa
p3 = p2 + i
DO i_deriv = 1, 3
DO k = 1, ncoc
p1 = (k - 1)*ncob
DO j = 1, ncob
p2 = (p1 + j - 1)*ncoa
DO i = 1, ncoa
p3 = p2 + i

DO i_deriv = 1, 3
der_abc_1(a_offset + i, b_offset + j, c_offset + k, i_deriv) = &
p_deriv(p3, permute_2(i_deriv))
der_abc_1_ext_prv(i_deriv) = MAX(der_abc_1_ext_prv(i_deriv), &
Expand All @@ -556,14 +556,14 @@ SUBROUTINE eri_3center_derivs(der_abc_1, der_abc_2, &
END DO
END DO
ELSE
DO k = 1, ncoc
p1 = (k - 1)*ncob
DO j = 1, ncob
p2 = (p1 + j - 1)*ncoa
DO i = 1, ncoa
p3 = p2 + i
DO i_deriv = 1, 3
DO k = 1, ncoc
p1 = (k - 1)*ncob
DO j = 1, ncob
p2 = (p1 + j - 1)*ncoa
DO i = 1, ncoa
p3 = p2 + i

DO i_deriv = 1, 3
der_abc_1(a_offset + i, b_offset + j, c_offset + k, i_deriv) = &
p_deriv(p3, permute_2(i_deriv))

Expand Down Expand Up @@ -597,14 +597,14 @@ SUBROUTINE eri_3center_derivs(der_abc_1, der_abc_2, &
CALL cp_libint_get_3eri_derivs(lj, li, lk, lib, p_deriv, a_mysize)

IF (do_ext) THEN
DO k = 1, ncoc
p1 = (k - 1)*ncoa
DO i = 1, ncoa
p2 = (p1 + i - 1)*ncob
DO j = 1, ncob
p3 = p2 + j
DO i_deriv = 1, 3
DO k = 1, ncoc
p1 = (k - 1)*ncoa
DO i = 1, ncoa
p2 = (p1 + i - 1)*ncob
DO j = 1, ncob
p3 = p2 + j

DO i_deriv = 1, 3
der_abc_1(a_offset + i, b_offset + j, c_offset + k, i_deriv) = &
p_deriv(p3, permute_1(i_deriv))

Expand All @@ -621,14 +621,14 @@ SUBROUTINE eri_3center_derivs(der_abc_1, der_abc_2, &
END DO
END DO
ELSE
DO k = 1, ncoc
p1 = (k - 1)*ncoa
DO i = 1, ncoa
p2 = (p1 + i - 1)*ncob
DO j = 1, ncob
p3 = p2 + j
DO i_deriv = 1, 3
DO k = 1, ncoc
p1 = (k - 1)*ncoa
DO i = 1, ncoa
p2 = (p1 + i - 1)*ncob
DO j = 1, ncob
p3 = p2 + j

DO i_deriv = 1, 3
der_abc_1(a_offset + i, b_offset + j, c_offset + k, i_deriv) = &
p_deriv(p3, permute_1(i_deriv))

Expand Down Expand Up @@ -1056,11 +1056,11 @@ SUBROUTINE eri_2center_derivs(der_ab, la_min, la_max, npgfa, zeta, rpgfa, ra, &
a_mysize(1) = ncoa*ncob
CALL cp_libint_get_2eri_derivs(li, lj, lib, p_deriv, a_mysize)

DO j = 1, ncob
p1 = (j - 1)*ncoa
DO i = 1, ncoa
p2 = p1 + i
DO i_deriv = 1, 3
DO i_deriv = 1, 3
DO j = 1, ncob
p1 = (j - 1)*ncoa
DO i = 1, ncoa
p2 = p1 + i
der_ab(a_offset + i, b_offset + j, i_deriv) = p_deriv(p2, permute(i_deriv))
END DO
END DO
Expand Down
4 changes: 2 additions & 2 deletions src/qs_environment.F
Original file line number Diff line number Diff line change
Expand Up @@ -413,7 +413,7 @@ SUBROUTINE qs_init(qs_env, para_env, root_section, globenv, cp_subsys, kpoint_en
IF (do_hfx) THEN
! Retrieve particle_set and atomic_kind_set (needed for both kinds of initialization)
CALL hfx_create(qs_env%x_data, para_env, hfx_section, atomic_kind_set, &
qs_kind_set, particle_set, dft_control, my_cell, do_ot=scf_control%use_ot, &
qs_kind_set, particle_set, dft_control, my_cell, &
nelectron_total=nelectron_total)
END IF

Expand All @@ -435,7 +435,7 @@ SUBROUTINE qs_init(qs_env, para_env, root_section, globenv, cp_subsys, kpoint_en

CALL hfx_create(qs_env%mp2_env%ri_rpa%x_data, para_env, hfx_section, atomic_kind_set, &
qs_kind_set, particle_set, dft_control, my_cell, do_exx=(.NOT. do_admm_rpa), &
do_ot=scf_control%use_ot, nelectron_total=nelectron_total)
nelectron_total=nelectron_total)

END IF
END IF
Expand Down

0 comments on commit d9068a4

Please sign in to comment.