6 subroutine eveqnhf(ikp,vmt,vir,bmt,bir,evecsvp)
11 integer,
intent(in) :: ikp
12 real(8),
intent(in) :: vmt(npcmtmax,natmtot),vir(ngtc)
13 real(8),
intent(in) :: bmt(npcmtmax,natmtot,ndmag),bir(ngtc,ndmag)
14 complex(8),
intent(inout) :: evecsvp(nstsv,nstsv)
17 integer ist1,ist2,ist3,jst3
18 integer iv(3),iq,ig,nthd
23 real(8) vgqc(3,ngvc),gqc(ngvc),gclgq(ngvc)
25 real(8),
allocatable :: jlgqrmt(:,:,:)
26 complex(8),
allocatable :: apwalm(:,:,:,:),evecfv(:,:),evecsv(:,:)
27 complex(8),
allocatable :: ylmgq(:,:),sfacgq(:,:)
28 complex(8),
allocatable :: h(:,:),v(:,:),kmat(:,:)
29 complex(4),
allocatable :: wfmt1(:,:,:,:),wfir1(:,:,:)
30 complex(4),
allocatable :: wfmt2(:,:,:,:),wfir2(:,:,:)
31 complex(4),
allocatable :: crhomt(:,:,:),crhoir(:,:)
32 complex(4),
allocatable :: cvclmt(:,:),cvclir(:)
34 complex(8),
external :: zcfinp
36 write(*,
'("Info(eveqnhf): ",I0," of ",I0," k-points")') ikp,
nkpt 42 allocate(ylmgq(
lmmaxo,ngvc),sfacgq(ngvc,natmtot))
43 allocate(h(nstsv,nstsv),v(nstsv,nstsv))
44 allocate(wfmt1(npcmtmax,natmtot,
nspinor,nstsv),wfir1(ngtc,
nspinor,nstsv))
45 allocate(wfmt2(npcmtmax,natmtot,
nspinor,nstsv),wfir2(ngtc,
nspinor,nstsv))
46 allocate(crhomt(npcmtmax,natmtot,nstsv),crhoir(ngtc,nstsv))
50 call match(
ngk(1,ikp),
vgkc(:,:,1,ikp),
gkc(:,1,ikp),
sfacgk(:,:,1,ikp),apwalm)
52 call genwfsv_sp(.false.,.true.,nstsv,[0],
ngdgc,
igfc,
ngk(1,ikp),
igkig(:,1,ikp), &
53 apwalm,evecfv,evecsvp,wfmt1,ngtc,wfir1)
59 call genvbmatk(vmt,vir,bmt,bir,
ngk(1,ikp),
igkig(:,1,ikp),wfmt1,ngtc,wfir1,h)
61 call genvmatk(vmt,vir,
ngk(1,ikp),
igkig(:,1,ikp),wfmt1,ngtc,wfir1,h)
68 allocate(kmat(nstsv,nstsv))
70 call zgemm(
'N',
'N',nstsv,nstsv,nstsv,
zone,kmat,nstsv,evecsvp,nstsv,
zzero,v, &
72 call zgemm(
'C',
'N',nstsv,nstsv,nstsv,
zone,evecsvp,nstsv,v,nstsv,
zone,h,nstsv)
83 iv(1:3)=
ivk(1:3,ikp)-
ivk(1:3,ik)
84 iv(1:3)=modulo(iv(1:3),
ngridk(1:3))
86 iv(1:3)=iv(1:3)*
ngridq(1:3)
87 if (any(mod(iv(1:3),
ngridk(1:3)) /= 0)) cycle
88 iv(1:3)=iv(1:3)/
ngridk(1:3)
89 iq=
ivqiq(iv(1),iv(2),iv(3))
90 vc(1:3)=
vkc(1:3,ikp)-
vkc(1:3,ik)
93 vgqc(1:3,ig)=
vgc(1:3,ig)+vc(1:3)
95 gqc(ig)=sqrt(vgqc(1,ig)**2+vgqc(2,ig)**2+vgqc(3,ig)**2)
102 call gengclgq(.true.,iq,ngvc,gqc,gclgq)
106 call match(
ngk(1,ik),
vgkc(:,:,1,ik),
gkc(:,1,ik),
sfacgk(:,:,1,ik),apwalm)
118 call genwfsv_sp(.false.,.false.,nst,idx,
ngdgc,
igfc,
ngk(1,ik),
igkig(:,1,ik), &
119 apwalm,evecfv,evecsv,wfmt2,ngtc,wfir2)
125 allocate(cvclmt(npcmtmax,natmtot),cvclir(ngtc))
131 call gencrho(.true.,.true.,ngtc,wfmt2(:,:,:,ist3),wfir2(:,:,ist3), &
132 wfmt1(:,:,:,ist1),wfir1(:,:,ist1),crhomt(:,:,ist1),crhoir(:,ist1))
140 crhomt(:,:,ist2),cvclmt)
142 gclgq,ngvc,jlgqrmt,ylmgq,sfacgq,crhoir(:,ist2),npcmtmax,cvclmt,cvclir)
143 cvclir(:)=cvclir(:)*
cfrc(:)
145 z1=zcfinp(crhomt(:,:,ist1),crhoir(:,ist1),cvclmt,cvclir)
146 v(ist1,ist2)=v(ist1,ist2)-t1*z1
151 deallocate(cvclmt,cvclir)
156 deallocate(jlgqrmt,ylmgq,sfacgq,apwalm,evecfv)
157 deallocate(wfmt1,wfir1,wfmt2,wfir2,crhomt,crhoir)
168 evecsv(:,:)=evecsvp(:,:)
169 call zgemm(
'N',
'N',nstsv,nstsv,nstsv,
zone,evecsv,nstsv,h,nstsv,
zzero,evecsvp, &
171 deallocate(evecsv,h,v)
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)
real(8), dimension(:,:), allocatable evalsv
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
complex(8), parameter zone
subroutine getkmat(ik, kmat)
subroutine eveqnzh(n, ld, a, w)
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)
integer, dimension(:,:), allocatable ngk
subroutine genvmatk(vmt, vir, ngp, igpig, wfmt, ld, wfgp, vmat)
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 occsv
real(8), dimension(:,:,:), allocatable wprcmt
integer, dimension(:,:,:), allocatable ivqiq
real(8), dimension(:,:,:,:), allocatable vgkc
complex(8), parameter zzero
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 holdthd(nloop, nthd)
subroutine genjlgprmt(lmax, ngp, gpc, ld, jlgprmt)
subroutine cftwfir(ngp, igpig, wfir)
real(8), dimension(:), allocatable cfrc
integer, dimension(maxspecies) nrcmt
integer, dimension(maxspecies) nrcmti
subroutine genvbmatk(vmt, vir, bmt, bir, ngp, igpig, wfmt, ld, wfgp, vbmat)
integer, dimension(:,:,:), allocatable igkig
subroutine eveqnhf(ikp, vmt, vir, bmt, bir, evecsvp)
integer, dimension(:,:), allocatable ivk