SUBROUTINE fft6_g2r_coulomb_ex (f_g, f_r) ! 6-D fourier transform used for W(G,G') and G(G,G') ! which agrees with convention in FG's paper. USE io_files, ONLY : prefix, iunigk USE kinds, ONLY : DP USE cell_base, ONLY : omega, alat USE control_gw, ONLY : lgamma USE wvfct, ONLY : npw,npwx, igk USE qpoint, ONLY : xq, npwq, igkq, nksq, ikks, ikqs USE gvect, ONLY : ngm, nrxx, g, nr1, nr2, nr3, nrx1, nrx2, nrx3, nl USE gwsigma, ONLY : ngmsex, nrsex, nr1sex, nr2sex, nr3sex, nlsex IMPLICIT NONE INTEGER :: ios INTEGER :: ngmtmp INTEGER :: ig, igp, ir, irp COMPLEX(DP) :: czero INTEGER :: nr1tmp, nr2tmp, nr3tmp, nrtmp !Self-Energy Grid COMPLEX(DP), INTENT(INOUT) :: f_g (ngmsex,ngmsex) COMPLEX(DP), INTENT(INOUT) :: f_r (nrsex,nrsex) COMPLEX(DP) :: aux (nrsex) czero = (0.0d0, 0.0d0) f_r(:,:) = czero do ig = 1, ngmsex aux(:) = czero do igp = 1, ngmsex aux(nlsex(igp)) = f_g(ig,igp) enddo call cft3s (aux, nr1sex, nr2sex, nr3sex, nr1sex, nr2sex, nr3sex, +1) do irp = 1, nrsex f_r(ig, irp) = aux(irp) / omega enddo enddo ! the conjg/conjg is to calculate sum_G f(G) exp(-iGr) ! following the convention set in the paper ! [because the standard transform is sum_G f(G) exp(iGr) ] do irp = 1, nrsex aux = czero do ig = 1, ngmsex aux(nlsex(ig)) = conjg( f_r(ig,irp) ) enddo call cft3s (aux, nr1sex, nr2sex, nr3sex, nr1sex, nr2sex, nr3sex, +1) f_r(1:nrsex,irp) = conjg ( aux ) enddo END SUBROUTINE fft6_g2r_coulomb_ex