10 integer,
intent(in) :: ikp
13 integer nst1,nst2,ist,jst
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(:,:,:),wfcr(:,:)
26 complex(4),
allocatable :: wfmt2(:,:,:,:),wfir2(:,:,:)
27 complex(4),
allocatable :: crhomt(:,:),crhoir(:)
28 complex(4),
allocatable :: cvclmt(:,:),cvclir(:)
30 complex(8),
external :: zcfinp,zcfmtinp
37 call match(
ngk(1,ikp),
vgkc(:,:,1,ikp),
gkc(:,1,ikp),
sfacgk(:,:,1,ikp),apwalm)
47 call genwfsv_sp(.false.,.false.,nst1,idx,
ngdgc,
igfc,
ngk(1,ikp),
igkig(:,1,ikp), &
48 apwalm,evecfv,evecsv,wfmt1,
ngtc,wfir1)
65 iv(:)=modulo(iv(:),
ngridk(:))
68 if (any(mod(iv(:),
ngridk(:)) /= 0)) cycle
70 iq=
ivqiq(iv(1),iv(2),iv(3))
74 vgqc(1:3,ig)=
vgc(1:3,ig)+vc(1:3)
76 gqc(ig)=sqrt(vgqc(1,ig)**2+vgqc(2,ig)**2+vgqc(3,ig)**2)
87 call match(
ngk(1,ik),
vgkc(:,:,1,ik),
gkc(:,1,ik),
sfacgk(:,:,1,ik),apwalm)
99 call genwfsv_sp(.false.,.false.,nst2,idx,
ngdgc,
igfc,
ngk(1,ik),
igkig(:,1,ik), &
100 apwalm,evecfv,evecsv,wfmt2,
ngtc,wfir2)
107 call gencrho(.true.,.true.,
ngtc,wfmt2(:,:,:,jst),wfir2(:,:,jst), &
108 wfmt1(:,:,:,ist),wfir1(:,:,ist),crhomt,crhoir)
112 gclgq,
ngvc,jlgqrmt,ylmgq,sfacgq,crhoir,
npcmtmax,cvclmt,cvclir)
114 z1=zcfinp(crhomt,crhoir,cvclmt,cvclir)
120 deallocate(vgqc,gqc,gclgq,jlgqrmt)
121 deallocate(apwalm,evecfv,evecsv)
122 deallocate(ylmgq,sfacgq,wfmt2,wfir2)
136 do m=-
ksp(jst,is),
ksp(jst,is)-1
142 call crho2(npc,wfcr,wfcr(:,2),wfmt1(:,ias,1,ist), &
143 wfmt1(:,ias,2,ist),crhomt(:,ias))
145 call crho1(npc,wfcr,wfmt1(:,ias,1,ist),crhomt(:,ias))
147 call cfshtip(nrc,nrci,crhomt(:,ias))
150 crhomt(:,ias),cvclmt(:,ias))
151 z1=zcfmtinp(nrc,nrci,
wr2cmt(:,is),crhomt(:,ias),cvclmt(:,ias))
166 deallocate(wfmt1,wfir1,wfcr)
167 deallocate(crhomt,crhoir,cvclmt,cvclir)
171 pure subroutine crho1(n,wf1,wf2,crho)
173 integer,
intent(in) :: n
174 complex(4),
intent(in) :: wf1(n),wf2(n)
175 complex(4),
intent(out) :: crho(n)
176 crho(1:n)=conjg(wf1(1:n))*wf2(1:n)
179 pure subroutine crho2(n,wf11,wf12,wf21,wf22,crho)
181 integer,
intent(in) :: n
182 complex(4),
intent(in) :: wf11(n),wf12(n),wf21(n),wf22(n)
183 complex(4),
intent(out) :: crho(n)
184 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
real(8), dimension(:), allocatable wkpt
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