10integer,
intent(in) :: ikp
13integer nst1,nst2,ist,jst
22real(8),
allocatable :: vgqc(:,:),gqc(:),gclgq(:),jlgqrmt(:,:,:)
23complex(8),
allocatable :: apwalm(:,:,:,:),evecfv(:,:),evecsv(:,:)
24complex(8),
allocatable :: ylmgq(:,:),sfacgq(:,:)
25complex(4),
allocatable :: wfmt1(:,:,:,:),wfir1(:,:,:),wfcr(:,:)
26complex(4),
allocatable :: wfmt2(:,:,:,:),wfir2(:,:,:)
27complex(4),
allocatable :: crhomt(:,:),crhoir(:)
28complex(4),
allocatable :: cvclmt(:,:),cvclir(:)
30complex(8),
external :: zcfinp,zcfmtinp
37call match(
ngk(1,ikp),
vgkc(:,:,1,ikp),
gkc(:,1,ikp),
sfacgk(:,:,1,ikp),apwalm)
47call 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)
120deallocate(vgqc,gqc,gclgq,jlgqrmt)
121deallocate(evecfv,evecsv)
122deallocate(apwalm,ylmgq,sfacgq)
123deallocate(wfmt2,wfir2)
137 do m=-
ksp(jst,is),
ksp(jst,is)-1
143 call crho2(npc,wfcr,wfcr(:,2),wfmt1(:,ias,1,ist), &
144 wfmt1(:,ias,2,ist),crhomt(:,ias))
146 call crho1(npc,wfcr,wfmt1(:,ias,1,ist),crhomt(:,ias))
148 call cfshtip(nrc,nrci,crhomt(:,ias))
151 crhomt(:,ias),cvclmt(:,ias))
167deallocate(wfmt1,wfir1,wfcr)
168deallocate(crhomt,crhoir,cvclmt,cvclir)
173pure subroutine crho1(n,wf1,wf2,crho)
175integer,
intent(in) :: n
176complex(4),
intent(in) :: wf1(n),wf2(n)
177complex(4),
intent(out) :: crho(n)
178crho(1:n)=conjg(wf1(1:n))*wf2(1:n)
181pure subroutine crho2(n,wf11,wf12,wf21,wf22,crho)
183integer,
intent(in) :: n
184complex(4),
intent(in) :: wf11(n),wf12(n),wf21(n),wf22(n)
185complex(4),
intent(out) :: crho(n)
186crho(1:n)=conjg(wf11(1:n))*wf21(1:n)+conjg(wf12(1:n))*wf22(1:n)
subroutine cfshtip(nr, nri, cfmt)
pure subroutine cpotclmt(nr, nri, ld, rl, wpr, crhomt, cvclmt)
subroutine cpotcoul(nrmt_, nrmti_, npmt_, ld1, rl, ngridg_, igfft_, ngp, gpc, gclgp, ld2, jlgprmt, ylmgp, sfacgp, crhoir, ld3, cvclmt, cvclir)
pure subroutine crho2(n, wf11, wf12, wf21, wf22, crho)
pure subroutine crho1(n, wf1, wf2, crho)
subroutine gencrho(tsh, tspc, ngt, wfmt1, wfir1, wfmt2, wfir2, crhomt, crhoir)
subroutine gencvclmt(nrmt_, nrmti_, ld1, rl, wpr, ld2, crhomt, cvclmt)
pure subroutine gengclgq(treg, iq, ngq, gqc, gclgq)
subroutine genjlgprmt(lmax, ngp, gpc, ld, jlgprmt)
pure subroutine gensfacgp(ngp, vgpc, ld, sfacgp)
subroutine genwfsv_sp(tsh, tgp, nst, idx, ngridg_, igfft_, ngp, igpig, apwalm, evecfv, evecsv, wfmt, ld, wfir)
pure subroutine genylmv(t4pil, lmax, v, ylm)
subroutine getevecfv(fext, ikp, vpl, vgpl, evecfv)
subroutine getevecsv(fext, ikp, vpl, evecsv)
subroutine match(ngp, vgpc, gpc, sfacgp, apwalm)
real(8), dimension(:,:,:,:), allocatable vgkc
real(8), dimension(:), allocatable wkpt
real(8), dimension(:,:,:), allocatable gkc
real(8), dimension(:), allocatable cfrc
integer, dimension(3) ngdgc
integer, dimension(maxspecies) natoms
logical, dimension(maxstsp, maxspecies) spcore
integer, dimension(maxatoms, maxspecies) idxas
integer, dimension(:,:), allocatable ngk
integer, dimension(:,:,:), allocatable igkig
integer, dimension(maxspecies) nrcmt
integer, dimension(:,:), allocatable ivk
integer, dimension(:,:,:), allocatable ivqiq
integer, dimension(:), allocatable igfc
integer, dimension(maxspecies) nstsp
real(8), dimension(:,:,:), allocatable rlcmt
real(8), dimension(:,:), allocatable wr2cmt
real(8), dimension(:,:,:,:), allocatable vgkl
integer, dimension(3) ngridk
real(8), dimension(:,:,:), allocatable wprcmt
integer, dimension(maxspecies) npcmt
integer, dimension(maxstsp, maxspecies) ksp
real(8), dimension(:,:), allocatable vkl
real(8), dimension(:,:), allocatable vgc
integer, dimension(:,:,:), allocatable ivkik
real(8), dimension(:,:), allocatable vkc
complex(8), dimension(:,:,:,:), allocatable sfacgk
integer, dimension(maxspecies) nrcmti
integer, dimension(3) ngridq
real(8), dimension(:,:), allocatable evalsv
pure subroutine wavefcr(tsh, lrstp, is, ia, ist, m, ld, wfcr)
pure complex(8) function zcfmtinp(nr, nri, wr, cfmt1, cfmt2)