Merge branch 'exx_fft' into 'develop'

EXX FFT decomposition

See merge request QEF/q-e!1809
This commit is contained in:
giannozz 2022-04-21 19:53:30 +00:00
commit 93a4fe3a84
2 changed files with 46 additions and 45 deletions

View File

@ -126,24 +126,24 @@ MODULE exx
!! onto the new (smaller) grid for \rho=\psi_{k+q}\psi^*_k and vice versa.
!! Set up fft descriptors, including parallel stuff: sticks, planes, etc.
!
USE gvecw, ONLY : ecutwfc
USE gvect, ONLY : ecutrho, ngm, g, gg, gstart, mill
USE cell_base, ONLY : at, bg, tpiba2
USE recvec_subs, ONLY : ggen, ggens
USE fft_base, ONLY : smap
USE fft_types, ONLY : fft_type_init
USE symm_base, ONLY : fft_fact
USE mp_exx, ONLY : nproc_egrp, negrp, intra_egrp_comm
USE mp_bands, ONLY : nproc_bgrp, intra_bgrp_comm, nyfft
USE gvecw, ONLY : ecutwfc
USE gvect, ONLY : ecutrho, ngm, g, gg, gstart, mill
USE cell_base, ONLY : at, bg, tpiba2
USE recvec_subs, ONLY : ggen, ggens
USE fft_base, ONLY : smap
USE fft_types, ONLY : fft_type_init
USE symm_base, ONLY : fft_fact
USE mp_exx, ONLY : nproc_egrp, negrp, intra_egrp_comm
USE mp_bands, ONLY : nproc_bgrp, intra_bgrp_comm, nyfft
!
USE klist, ONLY : nks, xk
USE mp_pools, ONLY : inter_pool_comm
USE mp, ONLY : mp_max, mp_sum
USE klist, ONLY : nks, xk
USE mp_pools, ONLY : inter_pool_comm
USE mp, ONLY : mp_max, mp_sum
!
USE control_flags, ONLY : tqr
USE realus, ONLY : qpointlist, tabxx, tabp
USE exx_band, ONLY : smap_exx
USE command_line_options, ONLY : nmany_
USE control_flags, ONLY : tqr
USE realus, ONLY : qpointlist, tabxx, tabp
USE exx_band, ONLY : smap_exx
USE command_line_options, ONLY : nmany_, pencil_decomposition_
!
IMPLICIT NONE
!
@ -193,7 +193,8 @@ MODULE exx
lpara = ( nproc_bgrp > 1 )
CALL fft_type_init( dfftt, smap, "rho", gamma_only, lpara, &
intra_bgrp_comm, at, bg, gcutmt, gcutmt/gkcut, &
fft_fact=fft_fact, nyfft=nyfft, nmany=nmany_ )
fft_fact=fft_fact, nyfft=nyfft, nmany=nmany_, &
use_pd=pencil_decomposition_ )
CALL ggens( dfftt, gamma_only, at, g, gg, mill, gcutmt, ngmt, gt, ggt )
gstart_t = gstart
npwt = n_plane_waves(ecutwfc/tpiba2, nks, xk, gt, ngmt)
@ -207,7 +208,8 @@ MODULE exx
lpara = ( nproc_egrp > 1 )
CALL fft_type_init( dfftt, smap_exx, "rho", gamma_only, lpara, &
intra_egrp_comm, at, bg, gcutmt, gcutmt/gkcut, &
fft_fact=fft_fact, nyfft=nyfft, nmany=nmany_ )
fft_fact=fft_fact, nyfft=nyfft, nmany=nmany_, &
use_pd=pencil_decomposition_ )
ngmt = dfftt%ngm
ngmt_g = ngmt
CALL mp_sum( ngmt_g, intra_egrp_comm )
@ -1594,9 +1596,9 @@ MODULE exx
ENDIF
!
CALL fwfft ('Rho', psi_rhoc_work_d, dfftt)
psi_rhoc_work = psi_rhoc_work_d
! >>>> add augmentation in G SPACE here
IF(okvan .and. .not. tqr) THEN
psi_rhoc_work = psi_rhoc_work_d
! contribution from one band added to real (in real space) part of rhoc
IF(jbnd>=jstart) &
CALL addusxx_g(dfftt, psi_rhoc_work, xkq, xkp, 'r', &
@ -1609,7 +1611,6 @@ MODULE exx
ENDIF
! >>>> charge density done
!
vc(:,ii) = 0._DP
vc_d(:,ii) = 0._DP
fac(:) = coulomb_fac(:,iq,current_k)
!
@ -4070,11 +4071,11 @@ end associate
CALL vexx_loc( nnpw, nbndproj, xitmp, mexx )
CALL MatSymm( 'S', 'L', mexx,nbndproj )
ELSE
! |xi> = Vx[phi]|phi>
CALL vexx( nnpw, nnpw, nbndproj, phi, xitmp, becpsi )
! mexx = <phi|Vx[phi]|phi>
CALL matcalc( 'exact', .TRUE., 0, nnpw, nbndproj, nbndproj, phi, xitmp, mexx, exxe )
! |xi> = -One * Vx[phi]|phi> * rmexx^T
! |xi> = Vx[phi]|phi>
CALL vexx( nnpw, nnpw, nbndproj, phi, xitmp, becpsi )
! mexx = <phi|Vx[phi]|phi>
CALL matcalc( 'exact', .TRUE., 0, nnpw, nbndproj, nbndproj, phi, xitmp, mexx, exxe )
! |xi> = -One * Vx[phi]|phi> * rmexx^T
ENDIF
!
CALL aceupdate( nbndproj, nnpw, xitmp, mexx )

View File

@ -954,24 +954,23 @@ MODULE exx_band
!! * is_exx = .TRUE. - change to the EXX data structure;
!! * is_exx = .FALSE. - change to the local data strucutre.
!
USE cell_base, ONLY : at, bg, tpiba2
USE cellmd, ONLY : lmovecell
USE wvfct, ONLY : npwx
USE gvect, ONLY : gcutm, ig_l2g, g, gg, ngm, ngm_g, mill, mill_d, &
gstart, gvect_init, deallocate_gvect_exx, gshells
USE gvect, ONLY : g_d, gg_d
USE gvecs, ONLY : gcutms, ngms, ngms_g, gvecs_init
USE gvecw, ONLY : gkcut, ecutwfc, gcutw
USE klist, ONLY : xk, nks, ngk
USE mp_bands, ONLY : intra_bgrp_comm, ntask_groups, nyfft
USE mp_exx, ONLY : intra_egrp_comm, me_egrp, exx_mode, nproc_egrp, &
negrp, root_egrp
USE io_global, ONLY : stdout
USE fft_base, ONLY : dfftp, dffts, smap, fft_base_info
USE fft_types, ONLY : fft_type_init
USE recvec_subs, ONLY : ggen, ggens
!
USE command_line_options, ONLY : nmany_
USE cell_base, ONLY : at, bg, tpiba2
USE cellmd, ONLY : lmovecell
USE wvfct, ONLY : npwx
USE gvect, ONLY : gcutm, ig_l2g, g, gg, ngm, ngm_g, mill, mill_d, &
gstart, gvect_init, deallocate_gvect_exx, gshells
USE gvect, ONLY : g_d, gg_d
USE gvecs, ONLY : gcutms, ngms, ngms_g, gvecs_init
USE gvecw, ONLY : gkcut, ecutwfc, gcutw
USE klist, ONLY : xk, nks, ngk
USE mp_bands, ONLY : intra_bgrp_comm, ntask_groups, nyfft
USE mp_exx, ONLY : intra_egrp_comm, me_egrp, exx_mode, nproc_egrp, &
negrp, root_egrp
USE io_global, ONLY : stdout
USE fft_base, ONLY : dfftp, dffts, smap, fft_base_info
USE fft_types, ONLY : fft_type_init
USE recvec_subs, ONLY : ggen, ggens
USE command_line_options, ONLY : nmany_, pencil_decomposition_
!
!
IMPLICIT NONE
@ -1025,9 +1024,10 @@ MODULE exx_band
CALL fft_type_init( dffts_exx, smap_exx, "wave", gamma_only, &
lpara, intra_egrp_comm, at, bg, gkcut, gcutms/gkcut, &
nyfft=ntask_groups, nmany=nmany_ )
nyfft=ntask_groups, nmany=nmany_, use_pd=pencil_decomposition_ )
CALL fft_type_init( dfftp_exx, smap_exx, "rho", gamma_only, &
lpara, intra_egrp_comm, at, bg, gcutm, nyfft=nyfft, nmany=nmany_ )
lpara, intra_egrp_comm, at, bg, gcutm, nyfft=nyfft, nmany=nmany_, &
use_pd=pencil_decomposition_ )
CALL fft_base_info( ionode, stdout )
ngs_ = dffts_exx%ngl( dffts_exx%mype + 1 )
ngm_ = dfftp_exx%ngl( dfftp_exx%mype + 1 )