12integer ispn,ik,ist,nthd
13integer is,ias,nrc,nrci,npc
14integer np,ngp(nspnfv),iu,i
18complex(8) ylmk(lmmaxo),sfack(natmtot)
20integer,
allocatable :: igpig(:,:)
21real(8),
allocatable :: vpl(:,:),jlkr(:,:)
22complex(8),
allocatable :: wfmt(:,:,:,:),wfir(:,:,:)
23complex(8),
allocatable :: expmt(:,:),wf(:,:,:)
37allocate(igpig(
ngkmax,nspnfv))
46 write(*,
'("Info(writew90unk): ",I6," of ",I6," k-points")') ik,
nkptnr
50 igpig,wfmt,
ngtot,wfir)
53 kc=sqrt(vc(1)**2+vc(2)**2+vc(3)**2)
57 call genexpmt(1,jlkr,ylmk,1,sfack,expmt)
67 wfmt(1:npc,ias,ispn,ist)=wfmt(1:npc,ias,ispn,ist)*expmt(1:npc,ias)
68 call zfshtip(nrc,nrci,wfmt(:,ias,ispn,ist))
71 call zfpts(np,vpl,wfmt(:,:,ispn,ist),wfir(:,ispn,ist),wf(:,ispn,ist))
75 write(fname,
'("UNK",I5.5,".NC")') ik
77 write(fname,
'("UNK",I5.5,".1")') ik
79 open(newunit=iu,file=trim(fname),form=
'UNFORMATTED',action=
'WRITE')
82 write(iu) (wf(i,1,ist),i=1,np)
84 write(iu) (wf(i,2,ist),i=1,np)
90deallocate(igpig,jlkr,wfmt,wfir,wf,expmt)
94write(*,
'("Info(writew90unk): created the UNKkkkkk.s files")')
subroutine genexpmt(ngp, jlgpr, ylmgp, ld, sfacgp, expmt)
subroutine genjlgpr(ngp, gpc, jlgpr)
pure subroutine gensfacgp(ngp, vgpc, ld, sfacgp)
subroutine genwfsvp(tsh, tgp, nst, idx, ngridg_, igfft_, vpl, ngp, igpig, wfmt, ld, wfir)
pure subroutine genylmv(t4pil, lmax, v, ylm)
integer, dimension(3) ngridg
integer, dimension(maxspecies) nrcmt
integer, dimension(maxatoms *maxspecies) idxis
integer, dimension(maxspecies) npcmt
integer, dimension(:), allocatable igfft
integer, dimension(3) np3d
real(8), dimension(:,:), allocatable vkl
real(8), dimension(:,:), allocatable vkc
integer, dimension(maxspecies) nrcmti
subroutine holdthd(nloop, nthd)
integer, dimension(:), allocatable idxw90
pure subroutine plotpt3d(vpl)
subroutine zfpts(np, vrl, zfmt, zfir, fp)
subroutine zfshtip(nr, nri, zfmt)