Skip to content

Commit

Permalink
Use aligned fft buffers in negf_integr_cc
Browse files Browse the repository at this point in the history
  • Loading branch information
Frederick Stein authored and fstein93 committed Mar 17, 2023
1 parent 6268640 commit ea2850b
Show file tree
Hide file tree
Showing 5 changed files with 65 additions and 58 deletions.
14 changes: 9 additions & 5 deletions src/negf_integr_cc.F
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,9 @@ MODULE negf_integr_cc
cp_fm_get_info,&
cp_fm_release,&
cp_fm_type
USE fft_tools, ONLY: fft_fw1d
USE fft_tools, ONLY: fft_alloc,&
fft_dealloc,&
fft_fw1d
USE kahan_sum, ONLY: accurate_sum
USE kinds, ONLY: dp,&
int_8
Expand Down Expand Up @@ -427,7 +429,8 @@ SUBROUTINE ccquad_refine_integral(cc_env)

CHARACTER(len=*), PARAMETER :: routineN = 'ccquad_refine_integral'

COMPLEX(kind=dp), ALLOCATABLE, DIMENSION(:, :, :) :: ztmp, ztmp_dct
COMPLEX(kind=dp), CONTIGUOUS, DIMENSION(:, :, :), &
POINTER :: ztmp, ztmp_dct
INTEGER :: handle, icol, ipoint, irow, ncols_local, nintervals, nintervals_half, &
nintervals_half_plus_1, nintervals_half_plus_2, nintervals_plus_2, nrows_local, stat
LOGICAL :: equiv
Expand Down Expand Up @@ -484,8 +487,8 @@ SUBROUTINE ccquad_refine_integral(cc_env)
! 1.0 / nintervals
rscale = 1.0_dp/rscale

ALLOCATE (ztmp(nintervals, nrows_local, ncols_local))
ALLOCATE (ztmp_dct(nintervals, nrows_local, ncols_local))
CALL fft_alloc(ztmp, [nintervals, nrows_local, ncols_local])
CALL fft_alloc(ztmp_dct, [nintervals, nrows_local, ncols_local])

!$OMP PARALLEL DO DEFAULT(NONE), PRIVATE(icol, ipoint, irow), &
!$OMP SHARED(cc_env, ncols_local, nintervals_half, nintervals_half_plus_1, nintervals_half_plus_2, nrows_local, ztmp)
Expand Down Expand Up @@ -527,7 +530,8 @@ SUBROUTINE ccquad_refine_integral(cc_env)
END DO
!$OMP END PARALLEL DO

DEALLOCATE (ztmp, ztmp_dct)
CALL fft_dealloc(ztmp)
CALL fft_dealloc(ztmp_dct)

CALL cp_fm_trace(cc_env%error_fm, cc_env%weights, cc_env%error)

Expand Down
13 changes: 5 additions & 8 deletions src/pw/fft/fft_lib.F
Original file line number Diff line number Diff line change
Expand Up @@ -13,14 +13,10 @@ MODULE fft_lib
fftsg_do_cleanup,&
fftsg_do_init,&
fftsg_get_lengths
USE fftw3_lib, ONLY: fftw31dm,&
fftw33d,&
fftw3_create_plan_1dm,&
fftw3_create_plan_3d,&
fftw3_destroy_plan,&
fftw3_do_cleanup,&
fftw3_do_init,&
fftw3_get_lengths
USE fftw3_lib, ONLY: &
fft_alloc => fftw_alloc, fft_dealloc => fftw_dealloc, fftw31dm, fftw33d, &
fftw3_create_plan_1dm, fftw3_create_plan_3d, fftw3_destroy_plan, fftw3_do_cleanup, &
fftw3_do_init, fftw3_get_lengths
#include "../../base/base_uses.f90"

IMPLICIT NONE
Expand All @@ -30,6 +26,7 @@ MODULE fft_lib

PUBLIC :: fft_do_cleanup, fft_do_init, fft_get_lengths, fft_create_plan_3d
PUBLIC :: fft_create_plan_1dm, fft_1dm, fft_library, fft_3d, fft_destroy_plan
PUBLIC :: fft_alloc, fft_dealloc

CONTAINS
! **************************************************************************************************
Expand Down
25 changes: 13 additions & 12 deletions src/pw/fft/fft_plan.F
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@
! **************************************************************************************************

MODULE fft_plan
USE ISO_C_BINDING, ONLY: C_PTR
USE ISO_C_BINDING, ONLY: C_NULL_PTR,&
C_PTR

IMPLICIT NONE
PRIVATE
Expand All @@ -25,24 +26,24 @@ MODULE fft_plan

TYPE fft_plan_type

INTEGER :: fft_type
INTEGER :: fsign
LOGICAL :: trans, fft_in_place, valid, separated_plans
INTEGER :: n, m
INTEGER, DIMENSION(3) :: n_3d
INTEGER :: fft_type = -1
INTEGER :: fsign = 0
LOGICAL :: trans = .FALSE., fft_in_place = .FALSE., valid = .FALSE., separated_plans = .FALSE.
INTEGER :: n = -1, m = -1
INTEGER, DIMENSION(3) :: n_3d = -1

! Handle for the FFTW plan
TYPE(C_PTR) :: fftw_plan
TYPE(C_PTR) :: fftw_plan = C_NULL_PTR

! Plan for the remaining rows for 1D FFT when number of threads does not divide the number of rows exactly
!$ TYPE(C_PTR) :: alt_fftw_plan
!$ LOGICAL :: need_alt_plan
!$ INTEGER :: num_threads_needed, num_rows, alt_num_rows
!$ TYPE(C_PTR) :: alt_fftw_plan = C_NULL_PTR
!$ LOGICAL :: need_alt_plan = .FALSE.
!$ INTEGER :: num_threads_needed = -1, num_rows = -1, alt_num_rows = -1

! Individual plans (used by hand-optimised 3D FFT)
TYPE(C_PTR) :: fftw_plan_nx, fftw_plan_ny, fftw_plan_nz
TYPE(C_PTR) :: fftw_plan_nx = C_NULL_PTR, fftw_plan_ny = C_NULL_PTR, fftw_plan_nz = C_NULL_PTR
! Plans for the remaining rows (when the number of threads does not divide the number of rows exactly)
TYPE(C_PTR) :: fftw_plan_nx_r, fftw_plan_ny_r, fftw_plan_nz_r
TYPE(C_PTR) :: fftw_plan_nx_r = C_NULL_PTR, fftw_plan_ny_r = C_NULL_PTR, fftw_plan_nz_r = C_NULL_PTR

END TYPE fft_plan_type

Expand Down
3 changes: 2 additions & 1 deletion src/pw/fft/fftw3_lib.F
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ MODULE fftw3_lib
C_INTPTR_T, &
C_LOC, &
C_NULL_CHAR, &
C_SIZE_T
C_SIZE_T, C_F_POINTER
#endif
USE cp_files, ONLY: get_unit_number
USE fft_kinds, ONLY: dp
Expand All @@ -36,6 +36,7 @@ MODULE fftw3_lib

PUBLIC :: fftw3_do_init, fftw3_do_cleanup, fftw3_get_lengths, fftw33d, fftw31dm
PUBLIC :: fftw3_destroy_plan, fftw3_create_plan_1dm, fftw3_create_plan_3d
PUBLIC :: fftw_alloc, fftw_dealloc

#if defined ( __FFTW3 )
#include "fftw3.f03"
Expand Down
68 changes: 36 additions & 32 deletions src/pw/fft_tools.F
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,8 @@ MODULE fft_tools
USE cp_log_handling, ONLY: cp_logger_get_default_io_unit
USE fast, ONLY: zero_c
USE fft_lib, ONLY: &
fft_1dm, fft_3d, fft_create_plan_1dm, fft_create_plan_3d, fft_destroy_plan, &
fft_do_cleanup, fft_do_init, fft_get_lengths, fft_library
fft_1dm, fft_3d, fft_alloc, fft_create_plan_1dm, fft_create_plan_3d, fft_dealloc, &
fft_destroy_plan, fft_do_cleanup, fft_do_init, fft_get_lengths, fft_library
USE fft_plan, ONLY: fft_plan_type
USE kinds, ONLY: dp,&
dp_size,&
Expand Down Expand Up @@ -69,59 +69,62 @@ MODULE fft_tools
INTEGER :: lg = 0, mg = 0
INTEGER :: nbx = 0, nbz = 0
INTEGER :: nmray = 0, nyzray = 0
TYPE(mp_comm_type) :: gs_group
TYPE(mp_cart_type) :: rs_group
TYPE(mp_comm_type) :: gs_group = mp_comm_type()
TYPE(mp_cart_type) :: rs_group = mp_cart_type()
INTEGER, DIMENSION(2) :: g_pos = 0, r_pos = 0, r_dim = 0
INTEGER :: numtask = 0
END TYPE fft_scratch_sizes

TYPE fft_scratch_type
INTEGER :: fft_scratch_id
INTEGER :: tf_type
LOGICAL :: in_use
TYPE(mp_comm_type) :: group
INTEGER, DIMENSION(3) :: nfft
INTEGER :: fft_scratch_id = -1
INTEGER :: tf_type = -1
LOGICAL :: in_use = .FALSE.
TYPE(mp_comm_type) :: group = mp_comm_type()
INTEGER, DIMENSION(3) :: nfft = -1
! to be used in cube_transpose_* routines
TYPE(mp_cart_type), DIMENSION(2) :: cart_sub_comm
INTEGER, DIMENSION(2) :: dim, pos
TYPE(mp_cart_type), DIMENSION(2) :: cart_sub_comm = mp_cart_type()
INTEGER, DIMENSION(2) :: dim = -1, pos = -1
! to be used in fft3d_s
COMPLEX(KIND=dp), DIMENSION(:, :, :), POINTER &
:: ziptr, zoptr
:: ziptr => NULL(), zoptr => NULL()
! to be used in fft3d_ps : block distribution
COMPLEX(KIND=dp), DIMENSION(:, :), POINTER &
:: p1buf, p2buf, p3buf, p4buf, p5buf, p6buf, p7buf
:: p1buf => NULL(), p2buf => NULL(), p3buf => NULL(), p4buf => NULL(), &
p5buf => NULL(), p6buf => NULL(), p7buf => NULL()
! to be used in fft3d_ps : plane distribution
COMPLEX(KIND=dp), DIMENSION(:, :), POINTER &
:: r1buf, r2buf
:: r1buf => NULL(), r2buf => NULL()
COMPLEX(KIND=dp), DIMENSION(:, :, :), POINTER &
:: tbuf
:: tbuf => NULL()
! to be used in fft3d_pb
COMPLEX(KIND=dp), DIMENSION(:, :), POINTER &
:: a1buf, a2buf, a3buf, a4buf, a5buf, a6buf
:: a1buf => NULL(), a2buf => NULL(), a3buf => NULL(), &
a4buf => NULL(), a5buf => NULL(), a6buf => NULL()
! to be used in communication routines
INTEGER, DIMENSION(:), POINTER :: scount, rcount, sdispl, rdispl
INTEGER, DIMENSION(:, :), POINTER :: pgcube
INTEGER, DIMENSION(:), POINTER :: xzcount, yzcount, xzdispl, yzdispl
INTEGER :: in, mip
REAL(KIND=dp) :: rsratio
INTEGER, DIMENSION(:), POINTER :: scount => NULL(), rcount => NULL(), sdispl => NULL(), rdispl => NULL()
INTEGER, DIMENSION(:, :), POINTER :: pgcube => NULL()
INTEGER, DIMENSION(:), POINTER :: xzcount => NULL(), yzcount => NULL(), xzdispl => NULL(), yzdispl => NULL()
INTEGER :: in = -1, mip = -1
REAL(KIND=dp) :: rsratio = 0.0_dp
COMPLEX(KIND=dp), DIMENSION(:), POINTER &
:: xzbuf, yzbuf
:: xzbuf => NULL(), yzbuf => NULL()
COMPLEX(KIND=sp), DIMENSION(:), POINTER &
:: xzbuf_sgl, yzbuf_sgl
:: xzbuf_sgl => NULL(), yzbuf_sgl => NULL()
COMPLEX(KIND=dp), DIMENSION(:, :), POINTER &
:: rbuf1, rbuf2, rbuf3, rbuf4, rbuf5, rbuf6, rr
:: rbuf1 => NULL(), rbuf2 => NULL(), rbuf3 => NULL(), rbuf4 => NULL(), &
rbuf5 => NULL(), rbuf6 => NULL(), rr => NULL()
COMPLEX(KIND=sp), DIMENSION(:, :), POINTER &
:: ss, tt
INTEGER, DIMENSION(:, :), POINTER :: pgrid
INTEGER, DIMENSION(:), POINTER :: xcor, zcor, pzcoord
TYPE(fft_scratch_sizes) :: sizes
TYPE(fft_plan_type), DIMENSION(6) :: fft_plan
INTEGER :: last_tick
:: ss => NULL(), tt => NULL()
INTEGER, DIMENSION(:, :), POINTER :: pgrid => NULL()
INTEGER, DIMENSION(:), POINTER :: xcor => NULL(), zcor => NULL(), pzcoord => NULL()
TYPE(fft_scratch_sizes) :: sizes = fft_scratch_sizes()
TYPE(fft_plan_type), DIMENSION(6) :: fft_plan = fft_plan_type()
INTEGER :: last_tick = -1
END TYPE fft_scratch_type

TYPE fft_scratch_pool_type
TYPE(fft_scratch_type), POINTER :: fft_scratch
TYPE(fft_scratch_pool_type), POINTER :: fft_scratch_next
TYPE(fft_scratch_type), POINTER :: fft_scratch => NULL()
TYPE(fft_scratch_pool_type), POINTER :: fft_scratch_next => NULL()
END TYPE fft_scratch_pool_type

INTEGER, SAVE :: init_fft_pool = 0
Expand All @@ -134,6 +137,7 @@ MODULE fft_tools

PRIVATE
PUBLIC :: init_fft, fft3d, finalize_fft
PUBLIC :: fft_alloc, fft_dealloc
PUBLIC :: fft_radix_operations, fft_fw1d
PUBLIC :: FWFFT, BWFFT
PUBLIC :: FFT_RADIX_CLOSEST, FFT_RADIX_NEXT
Expand Down

0 comments on commit ea2850b

Please sign in to comment.