27 integer,
intent(in) :: ikp
28 complex(8),
intent(out) :: vcl1223(nstsv,nstsv,nstsv,nkpt)
30 integer ik,ist1,ist2,ist3
35 real(8),
allocatable :: vgqc(:,:),gqc(:),gclgq(:),jlgqrmt(:,:,:)
36 complex(8),
allocatable :: apwalm(:,:,:,:),evecfv(:,:),evecsv(:,:)
37 complex(8),
allocatable :: ylmgq(:,:),sfacgq(:,:)
38 complex(4),
allocatable :: wfmt1(:,:,:,:),wfir1(:,:,:)
39 complex(4),
allocatable :: wfmt2(:,:,:,:),wfir2(:,:,:)
40 complex(4),
allocatable :: crhomt(:,:,:),crhoir(:,:)
41 complex(4),
allocatable :: cvclmt(:,:),cvclir(:)
43 complex(8),
external :: zcfinp
58 call match(
ngk(1,ikp),
vgkc(:,:,1,ikp),
gkc(:,1,ikp),
sfacgk(:,:,1,ikp),apwalm)
60 call genwfsv_sp(.false.,.false.,nstsv,[0],
ngdgc,
igfc,
ngk(1,ikp),
igkig(:,1,ikp),&
61 apwalm,evecfv,evecsv,wfmt2,
ngtc,wfir2)
66 iv(:)=modulo(iv(:),
ngridk(:))
69 if (any(mod(iv(:),
ngridk(:)) /= 0)) cycle
71 iq=
ivqiq(iv(1),iv(2),iv(3))
75 vgqc(1:3,ig)=
vgc(1:3,ig)+vc(1:3)
77 gqc(ig)=sqrt(vgqc(1,ig)**2+vgqc(2,ig)**2+vgqc(3,ig)**2)
88 call match(
ngk(1,ik),
vgkc(:,:,1,ik),
gkc(:,1,ik),
sfacgk(:,:,1,ik),apwalm)
93 call genwfsv_sp(.false.,.false.,nstsv,[0],
ngdgc,
igfc,
ngk(1,ik),
igkig(:,1,ik),&
94 apwalm,evecfv,evecsv,wfmt1,
ngtc,wfir1)
101 call gencrho(.true.,.true.,
ngtc,wfmt2(:,:,:,ist2),wfir2(:,:,ist2), &
102 wfmt1(:,:,:,ist1),wfir1(:,:,ist1),crhomt(:,:,ist1),crhoir(:,ist1))
107 crhomt(:,:,ist3),cvclmt)
109 gclgq,
ngvc,jlgqrmt,ylmgq,sfacgq,crhoir(:,ist3),
npcmtmax,cvclmt,cvclir)
112 z1=zcfinp(crhomt(:,:,ist1),crhoir(:,ist1),cvclmt,cvclir)
113 vcl1223(ist1,ist3,ist2,ik)=
wqptnr*z1
120 vcl1223(ist3,ist1,1:nstsv,ik)=conjg(vcl1223(ist1,ist3,1:nstsv,ik))
125 deallocate(vgqc,gqc,gclgq,jlgqrmt)
126 deallocate(apwalm,evecfv,evecsv,ylmgq,sfacgq)
127 deallocate(wfmt1,wfmt2,wfir1,wfir2)
128 deallocate(crhomt,crhoir,cvclmt,cvclir)
subroutine gencvclmt(nrmt_, nrmti_, ld1, rl, wpr, ld2, crhomt, cvclmt)
integer, dimension(maxspecies) npcmt
subroutine getevecsv(fext, ikp, vpl, evecsv)
pure subroutine gensfacgp(ngp, vgpc, ld, sfacgp)
subroutine getevecfv(fext, ikp, vpl, vgpl, evecfv)
subroutine gencrho(tsh, tspc, ngt, wfmt1, wfir1, wfmt2, wfir2, crhomt, crhoir)
subroutine match(ngp, vgpc, gpc, sfacgp, apwalm)
pure subroutine genylmv(t4pil, lmax, v, ylm)
complex(8), dimension(:,:,:,:), allocatable sfacgk
real(8), dimension(:,:), allocatable vkc
real(8), dimension(:,:), allocatable vgc
pure subroutine gengclgq(treg, iq, ngq, gqc, gclgq)
subroutine genvcl1223(ikp, vcl1223)
integer, dimension(:,:), allocatable ngk
subroutine genwfsv_sp(tsh, tgp, nst, idx, ngridg_, igfft_, ngp, igpig, apwalm, evecfv, evecsv, wfmt, ld, wfir)
real(8), dimension(:,:,:,:), allocatable vgkl
integer, dimension(:), allocatable igfc
real(8), dimension(:,:,:), allocatable rlcmt
integer, dimension(3) ngridk
real(8), dimension(:,:,:), allocatable wprcmt
integer, dimension(:,:,:), allocatable ivqiq
real(8), dimension(:,:,:,:), allocatable vgkc
integer, dimension(3) ngridq
real(8), dimension(:,:), allocatable vkl
subroutine cpotcoul(nrmt_, nrmti_, npmt_, ld1, rl, ngridg_, igfft_, ngp, gpc, gclgp, ld2, jlgprmt, ylmgp, sfacgp, crhoir, ld3, cvclmt, cvclir)
real(8), dimension(:,:,:), allocatable gkc
integer, dimension(3) ngdgc
subroutine genjlgprmt(lmax, ngp, gpc, ld, jlgprmt)
real(8), dimension(:), allocatable cfrc
integer, dimension(maxspecies) nrcmt
integer, dimension(maxspecies) nrcmti
integer, dimension(:,:,:), allocatable igkig
integer, dimension(:,:), allocatable ivk