43real(8),
allocatable :: gwf2mt(:,:),gwf2ir(:)
44real(8),
allocatable :: rfmt(:),grfmt(:,:)
45real(8),
allocatable :: rfir(:),grfir(:)
46real(8),
allocatable :: elfmt(:,:),elfir(:)
47complex(8),
allocatable :: zfft1(:),zfft2(:)
82call symrf(
nrcmt,
nrcmti,
npcmt,
ngdgc,
ngtc,
ngvc,
nfgrzc,
igfc,
igrzfc,
npmtmax, &
105 call gradrfmt(nr,nri,
rlmt(:,-1,is),
wcrmt(:,:,is),
rhomt(:,ias),
npmtmax,grfmt)
108 call rbshtip(nr,nri,grfmt(:,i))
113 t1=grfmt(i,1)**2+grfmt(i,2)**2+grfmt(i,3)**2
115 t1=(1.d0/2.d0)*(gwf2mt(i,ias)-(1.d0/4.d0)*t1/r)
117 t2=(3.d0/5.d0)*((6.d0*
pi**2)**(2.d0/3.d0))*(r/2.d0)**(5.d0/3.d0)
119 elfmt(i,ias)=1.d0/(1.d0+(t1/t2)**2)
122 call rfshtip(nr,nri,elfmt(:,ias))
135 zfft2(ifg)=
vgc(i,ig)*
zi*zfft1(ifg)
143 grfir(ir)=grfir(ir)+rfir(ir)**2
149 t1=(1.d0/2.d0)*(gwf2ir(ir)-(1.d0/4.d0)*grfir(ir)/r)
151 t2=(3.d0/5.d0)*((6.d0*
pi**2)**(2.d0/3.d0))*(r/2.d0)**(5.d0/3.d0)
153 elfir(ir)=1.d0/(1.d0+(t1/t2)**2)
158 open(50,file=
'ELF1D.OUT',form=
'FORMATTED')
159 open(51,file=
'ELFLINES.OUT',form=
'FORMATTED')
160 call plot1d(50,51,1,elfmt,elfir)
164 write(*,
'("Info(elfplot):")')
165 write(*,
'(" 1D ELF plot written to ELF1D.OUT")')
166 write(*,
'(" vertex location lines written to ELFLINES.OUT")')
168 open(50,file=
'ELF2D.OUT',form=
'FORMATTED')
169 call plot2d(.false.,50,1,elfmt,elfir)
172 write(*,
'("Info(elfplot): 2D ELF plot written to ELF2D.OUT")')
174 open(50,file=
'ELF3D.OUT',form=
'FORMATTED')
175 call plot3d(50,1,elfmt,elfir)
178 write(*,
'("Info(elfplot): 3D ELF plot written to ELF3D.OUT")')
180deallocate(gwf2mt,gwf2ir,rfmt,grfmt,rfir,grfir)
181deallocate(elfmt,elfir,zfft1,zfft2)
subroutine gradrfmt(nr, nri, ri, wcr, rfmt, ld, grfmt)
subroutine gradwf2(ik, gwf2mt, gwf2ir)
subroutine gradwfcr2(gwf2mt)
integer, dimension(maxspecies) nrmti
real(8), dimension(:,:,:), allocatable wcrmt
integer, dimension(3) ngridg
integer, dimension(3) ngdgc
integer, dimension(maxspecies) nrmt
real(8), dimension(:), pointer, contiguous rhoir
integer, dimension(:), allocatable igrzf
integer, dimension(maxspecies) nrcmt
integer, dimension(:), allocatable igfc
integer, dimension(maxatoms *maxspecies) idxis
integer, dimension(maxspecies) npcmt
integer, dimension(maxspecies) npmt
real(8), dimension(:,:), allocatable vgc
integer, dimension(:), allocatable igrzfc
real(8), dimension(:,:), pointer, contiguous rhomt
integer, dimension(maxspecies) nrcmti
real(8), dimension(:,:,:), allocatable rlmt
subroutine plot1d(fnum1, fnum2, nf, rfmt, rfir)
subroutine plot2d(tproj, fnum, nf, rfmt, rfir)
subroutine plot3d(fnum, nf, rfmt, rfir)
subroutine rbsht(nr, nri, rfmt1, rfmt2)
subroutine rbshtip(nr, nri, rfmt)
subroutine rfirctof(rfirc, rfir)
subroutine rfmtctof(rfmt)
subroutine rfshtip(nr, nri, rfmt)
subroutine symrf(nrmt_, nrmti_, npmt_, ngridg_, ngtot_, ngvec_, nfgrz_, igfft_, igrzf_, ld, rfmt, rfir)
subroutine rzfftifc(nd, n, sgn, r, z)