6 subroutine oepvclk(ikp,vclcv,vclvv)
10 integer,
intent(in) :: ikp
11 complex(8),
intent(out) :: vclcv(ncrmax,natmtot,nstsv)
12 complex(8),
intent(out) :: vclvv(nstsv,nstsv)
14 integer ik,jk,nst,ist1,ist2,ist3
15 integer is,ia,ias,nrc,nrci,npc
16 integer iv(3),ig,iq,ic,jc,m1,m2
22 real(8),
allocatable :: vgqc(:,:),gqc(:),gclgq(:),jlgqrmt(:,:,:)
23 complex(8),
allocatable :: apwalm(:,:,:,:),evecfv(:,:),evecsv(:,:)
24 complex(8),
allocatable :: ylmgq(:,:),sfacgq(:,:)
25 complex(4),
allocatable :: wfmt1(:,:,:,:),wfir1(:,:,:)
26 complex(4),
allocatable :: wfmt2(:,:,:,:),wfir2(:,:,:)
27 complex(4),
allocatable :: wfcr1(:,:),wfcr2(:,:)
28 complex(4),
allocatable :: crhomt1(:,:,:),crhomt2(:,:),crhoir1(:,:)
29 complex(4),
allocatable :: cvclmt(:,:),cvclir(:)
31 complex(8),
external :: zcfinp,zcfmtinp
41 allocate(crhomt1(
npcmtmax,natmtot,nstsv),crhoir1(
ngtc,nstsv))
51 call match(
ngk(1,ikp),
vgkc(:,:,1,ikp),
gkc(:,1,ikp),
sfacgk(:,:,1,ikp),apwalm)
53 call genwfsv_sp(.false.,.false.,nstsv,[0],
ngdgc,
igfc,
ngk(1,ikp),
igkig(:,1,ikp),&
54 apwalm,evecfv,evecsv,wfmt1,
ngtc,wfir1)
61 iv(:)=modulo(iv(:),
ngridk(:))
64 if (any(mod(iv(:),
ngridk(:)) /= 0)) cycle
66 iq=
ivqiq(iv(1),iv(2),iv(3))
70 vgqc(1:3,ig)=
vgc(1:3,ig)+vc(1:3)
72 gqc(ig)=sqrt(vgqc(1,ig)**2+vgqc(2,ig)**2+vgqc(3,ig)**2)
83 call match(
ngk(1,ik),
vgkc(:,:,1,ik),
gkc(:,1,ik),
sfacgk(:,:,1,ik),apwalm)
95 call genwfsv_sp(.false.,.false.,nst,idx,
ngdgc,
igfc,
ngk(1,ik),
igkig(:,1,ik), &
96 apwalm,evecfv,evecsv,wfmt2,
ngtc,wfir2)
100 call gencrho(.true.,.true.,
ngtc,wfmt2(:,:,:,ist3),wfir2(:,:,ist3), &
101 wfmt1(:,:,:,ist1),wfir1(:,:,ist1),crhomt1(:,:,ist1),crhoir1(:,ist1))
113 do m1=-
ksp(ist1,is),
ksp(ist1,is)-1
118 call crho2(npc,wfmt2(:,ias,1,ist3),wfmt2(:,ias,2,ist3),wfcr1, &
119 wfcr1(:,2),crhomt2(:,jc))
121 call crho1(npc,wfmt2(:,ias,1,ist3),wfcr1,crhomt2(:,jc))
124 call cfshtip(nrc,nrci,crhomt2(:,jc))
134 crhomt1(:,:,ist2),cvclmt)
136 gclgq,
ngvc,jlgqrmt,ylmgq,sfacgq,crhoir1(:,ist2),
npcmtmax,cvclmt,cvclir)
137 cvclir(:)=cvclir(:)*
cfrc(:)
143 z1=zcfinp(crhomt1(:,:,ist1),crhoir1(:,ist1),cvclmt,cvclir)
144 vclvv(ist1,ist2)=vclvv(ist1,ist2)-
wqptnr*z1
159 do m1=-
ksp(ist1,is),
ksp(ist1,is)-1
162 z1=zcfmtinp(nrc,nrci,
wr2cmt(:,is),crhomt2(:,jc),cvclmt(:,ias))
163 vclcv(ic,ias,ist2)=vclcv(ic,ias,ist2)-
wqptnr*z1
187 do m1=-
ksp(ist3,is),
ksp(ist3,is)-1
193 call crho2(npc,wfcr1,wfcr1(:,2),wfmt1(:,ias,1,ist1), &
194 wfmt1(:,ias,2,ist1),crhomt1(:,ias,ist1))
196 call crho1(npc,wfcr1,wfmt1(:,ias,1,ist1),crhomt1(:,ias,ist1))
198 call cfshtip(nrc,nrci,crhomt1(:,ias,ist1))
204 do m2=-
ksp(ist1,is),
ksp(ist1,is)-1
207 call crho2(npc,wfcr1,wfcr1(:,2),wfcr2,wfcr2(:,2),crhomt2(:,ic))
208 call cfshtip(nrc,nrci,crhomt2(:,ic))
216 crhomt1(:,ias,ist2),cvclmt)
222 z1=zcfmtinp(nrc,nrci,
wr2cmt(:,is),crhomt1(:,ias,ist1),cvclmt)
223 vclvv(ist1,ist2)=vclvv(ist1,ist2)-z1
232 do m2=-
ksp(ist1,is),
ksp(ist1,is)-1
234 z1=zcfmtinp(nrc,nrci,
wr2cmt(:,is),crhomt2(:,ic),cvclmt)
235 vclcv(ic,ias,ist2)=vclcv(ic,ias,ist2)-z1
250 deallocate(vgqc,gqc,gclgq,jlgqrmt)
251 deallocate(apwalm,evecfv,evecsv,ylmgq,sfacgq)
252 deallocate(wfmt1,wfir1,wfmt2,wfir2,wfcr1,wfcr2)
253 deallocate(crhomt1,crhomt2,crhoir1)
254 deallocate(cvclmt,cvclir)
258 pure subroutine crho1(n,wf1,wf2,crho)
260 integer,
intent(in) :: n
261 complex(4),
intent(in) :: wf1(n),wf2(n)
262 complex(4),
intent(out) :: crho(n)
263 crho(1:n)=conjg(wf1(1:n))*wf2(1:n)
266 pure subroutine crho2(n,wf11,wf12,wf21,wf22,crho)
268 integer,
intent(in) :: n
269 complex(4),
intent(in) :: wf11(n),wf12(n),wf21(n),wf22(n)
270 complex(4),
intent(out) :: crho(n)
271 crho(1:n)=conjg(wf11(1:n))*wf21(1:n)+conjg(wf12(1:n))*wf22(1:n)
subroutine gencvclmt(nrmt_, nrmti_, ld1, rl, wpr, ld2, crhomt, cvclmt)
integer, dimension(maxstsp, maxspecies) ksp
integer, dimension(maxspecies) npcmt
subroutine getevecsv(fext, ikp, vpl, evecsv)
pure subroutine gensfacgp(ngp, vgpc, ld, sfacgp)
real(8), dimension(:,:), allocatable evalsv
integer, dimension(maxatoms, maxspecies) idxas
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)
integer, dimension(:,:,:), allocatable ivkik
pure subroutine genylmv(t4pil, lmax, v, ylm)
complex(8), dimension(:,:,:,:), allocatable sfacgk
real(8), dimension(:,:), allocatable vkc
real(8), dimension(:,:), allocatable vgc
logical, dimension(maxstsp, maxspecies) spcore
pure subroutine gengclgq(treg, iq, ngq, gqc, gclgq)
integer, dimension(:,:), allocatable ngk
subroutine oepvclk(ikp, vclcv, vclvv)
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
pure subroutine wavefcr(tsh, lrstp, is, ia, ist, m, ld, wfcr)
integer, dimension(3) ngridk
real(8), dimension(:,:,:), allocatable wprcmt
integer, dimension(:,:,:), allocatable ivqiq
pure subroutine crho1(n, wf1, wf2, crho)
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)
integer, dimension(maxspecies) natoms
real(8), dimension(:,:), allocatable wr2cmt
subroutine cfshtip(nr, nri, cfmt)
real(8), dimension(:,:,:), allocatable gkc
integer, dimension(3) ngdgc
pure subroutine crho2(n, wf11, wf12, wf21, wf22, crho)
subroutine genjlgprmt(lmax, ngp, gpc, ld, jlgprmt)
integer, dimension(maxspecies) nstsp
pure subroutine cpotclmt(nr, nri, ld, rl, wpr, crhomt, cvclmt)
real(8), dimension(:), allocatable cfrc
integer, dimension(maxspecies) nrcmt
integer, dimension(maxspecies) nrcmti
integer, dimension(:,:,:), allocatable igkig
integer, dimension(:,:), allocatable ivk