! !--------------------------------------------------------------------------- subroutine ephwan2bloch ( nbnd, nrr, irvec, ndegen, epmatw, & xk, cufkk, cufkq, epmatf, nmodes) !--------------------------------------------------------------------------- ! #include "f_defs.h" USE kinds, only : DP implicit none ! ! input variables ! integer :: nbnd, nrr, irvec ( 3, nrr), ndegen (nrr), nmodes ! number of bands (possibly in tyhe optimal subspace) ! number of WS points ! coordinates of WS points ! degeneracy of WS points ! number of phonon modes complex(kind=DP) :: epmatw ( nbnd, nbnd, nrr, nmodes), cufkk (nbnd, nbnd), & cufkq (nbnd, nbnd) ! e-p matrix in Wanner representation ! rotation matrix U(k) ! rotation matrix U(k+q) real(kind=DP) :: xk(3) ! kpoint for the interpolation (WARNING: this must be in crystal coord!) ! ! output variables ! complex(kind=DP) :: epmatf (nbnd, nbnd, nmodes) ! e-p matrix in Bloch representation, fine grid ! ! work variables ! integer :: ibnd, jbnd, ir, imode real(kind=DP), parameter :: twopi = 6.28318530717959 real(kind=DP) :: rdotk complex(kind=DP) :: cfac, eptmp( nbnd, nbnd) complex(kind=DP), parameter :: ci = (0.d0,1.d0), & czero = (0.d0, 0.d0), cone = (1.d0, 0.d0) ! !---------------------------------------------------------- ! STEP 3: inverse Fourier transform of g to fine k mesh !---------------------------------------------------------- ! ! g~ (k') = sum_R 1/ndegen(R) e^{-ik'R} g (R) ! ! g~(k') is epmatf (nbnd, nbnd, ik ) ! every pool works with its own subset of k points on the fine grid ! epmatf = czero ! do ir = 1, nrr ! ! note xk is assumed to be already in cryst coord ! rdotk = twopi * dot_product ( xk, float(irvec(:, ir)) ) cfac = exp( ci*rdotk ) / float( ndegen(ir) ) ! do imode = 1, nmodes epmatf (:, :, imode) = epmatf (:, :, imode) + cfac * epmatw ( :, :, ir, imode) enddo ! enddo ! !---------------------------------------------------------- ! STEP 4: un-rotate to Bloch space, fine grid !---------------------------------------------------------- ! ! g (k') = U_q^\dagger (k') g~ (k') U_k (k') ! ! the two zgemm calls perform the following ops: ! epmatf = [ cufkq * epmatf ] * cufkk^\dagger ! do imode = 1, nmodes ! call zgemm ('n', 'n', nbnd, nbnd, nbnd, cone, cufkq, & nbnd, epmatf (:,:,imode), nbnd, czero, eptmp, nbnd) call zgemm ('n', 'c', nbnd, nbnd, nbnd, cone, eptmp, & nbnd, cufkk, nbnd, czero, epmatf(:,:,imode), nbnd) ! enddo ! ! return end subroutine ephwan2bloch !