10integer,
intent(in) :: ikp
11complex(8),
intent(out) :: vclcv(ncrmax,natmtot,nstsv)
12complex(8),
intent(out) :: vclvv(nstsv,nstsv)
14integer ik,jk,nst,ist1,ist2,ist3
15integer is,ia,ias,nrc,nrci,npc
16integer iv(3),ig,iq,ic,jc,m1,m2
22real(8),
allocatable :: vgqc(:,:),gqc(:),gclgq(:),jlgqrmt(:,:,:)
23complex(8),
allocatable :: apwalm(:,:,:,:),evecfv(:,:),evecsv(:,:)
24complex(8),
allocatable :: ylmgq(:,:),sfacgq(:,:)
25complex(4),
allocatable :: wfmt1(:,:,:,:),wfir1(:,:,:)
26complex(4),
allocatable :: wfmt2(:,:,:,:),wfir2(:,:,:)
27complex(4),
allocatable :: wfcr1(:,:),wfcr2(:,:)
28complex(4),
allocatable :: crhomt1(:,:,:),crhomt2(:,:),crhoir1(:,:)
29complex(4),
allocatable :: cvclmt(:,:),cvclir(:)
31complex(8),
external :: zcfinp,zcfmtinp
41allocate(crhomt1(
npcmtmax,natmtot,nstsv),crhoir1(
ngtc,nstsv))
51call match(
ngk(1,ikp),
vgkc(:,:,1,ikp),
gkc(:,1,ikp),
sfacgk(:,:,1,ikp),apwalm)
53call 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
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)
223 vclvv(ist1,ist2)=vclvv(ist1,ist2)-z1
232 do m2=-
ksp(ist1,is),
ksp(ist1,is)-1
235 vclcv(ic,ias,ist2)=vclcv(ic,ias,ist2)-z1
250deallocate(vgqc,gqc,gclgq,jlgqrmt)
251deallocate(apwalm,evecfv,evecsv,ylmgq,sfacgq)
252deallocate(wfmt1,wfir1,wfmt2,wfir2,wfcr1,wfcr2)
253deallocate(crhomt1,crhomt2,crhoir1)
254deallocate(cvclmt,cvclir)
259pure subroutine crho1(n,wf1,wf2,crho)
261integer,
intent(in) :: n
262complex(4),
intent(in) :: wf1(n),wf2(n)
263complex(4),
intent(out) :: crho(n)
264crho(1:n)=conjg(wf1(1:n))*wf2(1:n)
267pure subroutine crho2(n,wf11,wf12,wf21,wf22,crho)
269integer,
intent(in) :: n
270complex(4),
intent(in) :: wf11(n),wf12(n),wf21(n),wf22(n)
271complex(4),
intent(out) :: crho(n)
272crho(1:n)=conjg(wf11(1:n))*wf21(1:n)+conjg(wf12(1:n))*wf22(1:n)
real(8), dimension(:,:,:,:), allocatable vgkc
real(8), dimension(:,:,:), allocatable gkc
integer, dimension(:,:,:), allocatable igkig
integer, dimension(:,:,:), allocatable ivqiq
real(8), dimension(:,:,:), allocatable rlcmt
real(8), dimension(:,:,:,:), allocatable vgkl
real(8), dimension(:,:,:), allocatable wprcmt
integer, dimension(:,:,:), allocatable ivkik
complex(8), dimension(:,:,:,:), allocatable sfacgk