10integer,
intent(in) :: ik
11real(8),
intent(inout) :: jrmt_(npcmtmax,natmtot,3),jrir_(ngtc,3)
13integer ispn,jspn,nst,ist,jst
14integer is,ia,ias,nrc,nrci,npc
20complex(8) gwfmt(npcmtmax,3),zfmt1(npcmtmax),zfmt2(npcmtmax)
22complex(8),
allocatable :: apwalm(:,:,:,:,:),evecfv(:,:,:),evecsv(:,:)
23complex(8),
allocatable :: wfmt(:,:,:,:),wfgk(:,:,:),zfft1(:),zfft2(:)
29 sfacgk(:,:,ispn,ik),apwalm(:,:,:,:,ispn))
43call genwfsv(.true.,.true.,nst,idx,
ngdgc,
igfc,
ngk(:,ik),
igkig(:,:,ik),apwalm, &
44 evecfv,evecsv,wfmt,
ngkmax,wfgk)
45deallocate(apwalm,evecfv,evecsv)
61 wfmt(:,ias,ispn,ist),npcmtmax,gwfmt)
63 call zbsht(nrc,nrci,wfmt(:,ias,ispn,ist),zfmt1)
64 zfmt1(1:npc)=conjg(zfmt1(1:npc))
67 call zbsht(nrc,nrci,gwfmt(:,i),zfmt2)
69 rfmt(1:npc)=aimag(zfmt1(1:npc)*zfmt2(1:npc))
70 jrmt_(1:npc,ias,i)=jrmt_(1:npc,ias,i)+wo*rfmt(1:npc)
80allocate(zfft1(ngtc),zfft2(ngtc))
90 zfft1(ifg)=wfgk(igk,ispn,ist)
93 zfft1(1:ngtc)=conjg(zfft1(1:ngtc))
99 zfft2(ifg)=
vgkc(i,igk,jspn,ik)*
zi*wfgk(igk,ispn,ist)
102 jrir_(1:ngtc,i)=jrir_(1:ngtc,i)+wo*aimag(zfft1(1:ngtc)*zfft2(1:ngtc))
106deallocate(wfgk,zfft1,zfft2)
subroutine genjprk(ik, jrmt_, jrir_)
subroutine genwfsv(tsh, tgp, nst, idx, ngridg_, igfft_, ngp, igpig, apwalm, evecfv, evecsv, wfmt, ld, wfir)
subroutine getevecfv(fext, ikp, vpl, vgpl, evecfv)
subroutine getevecsv(fext, ikp, vpl, evecsv)
subroutine gradzfmt(nr, nri, ri, wcr, zfmt, ld, gzfmt)
subroutine match(ngp, vgpc, gpc, sfacgp, apwalm)
real(8), dimension(:,:,:,:), allocatable vgkc
real(8), dimension(:), allocatable wkpt
real(8), dimension(:,:,:), allocatable gkc
integer, dimension(3) ngdgc
integer, dimension(maxspecies) natoms
integer, dimension(maxatoms, maxspecies) idxas
integer, dimension(:,:), allocatable ngk
integer, dimension(:,:,:), allocatable igkig
integer, dimension(maxspecies) nrcmt
integer, dimension(:), allocatable igfc
real(8), dimension(:,:,:), allocatable rlcmt
real(8), dimension(:,:,:), allocatable wcrcmt
real(8), dimension(:,:,:,:), allocatable vgkl
integer, dimension(maxspecies) npcmt
integer, dimension(2) jspnfv
real(8), dimension(:,:), allocatable vkl
complex(8), dimension(:,:,:,:), allocatable sfacgk
integer, dimension(maxspecies) nrcmti
real(8), dimension(:,:), allocatable occsv
subroutine zbsht(nr, nri, zfmt1, zfmt2)
subroutine zfftifc(nd, n, sgn, z)