11integer,
intent(in) :: ik
12real(8),
intent(inout) :: taumt_(npcmtmax,natmtot,nspinor),tauir_(ngtc,nspinor)
14integer ispn,jspn,nst,ist,jst
15integer is,ias,nrc,nrci
16integer npc,igk,ifg,i,nthd
21complex(8) gzfmt(npcmtmax,3),zfmt(npcmtmax),zfft(ngtc)
23complex(8),
allocatable :: apwalm(:,:,:,:,:),evecfv(:,:),evecsv(:,:)
24complex(8),
allocatable :: wfmt(:,:,:,:),wfgp(:,:,:)
30 sfacgk(:,:,ispn,ik),apwalm(:,:,:,:,ispn))
43allocate(wfmt(npcmtmax,natmtot,nspinor,nst),wfgp(
ngkmax,nspinor,nst))
44call genwfsv(.true.,.true.,nst,idx,
ngdgc,
igfc,
ngk(:,ik),
igkig(:,:,ik),apwalm, &
45 evecfv,evecsv,wfmt,
ngkmax,wfgp)
46deallocate(apwalm,evecfv,evecsv)
47call holdthd(max(nspinor*natmtot,2),nthd)
69 wfmt(:,ias,ispn,ist),npcmtmax,gzfmt)
72 call zbsht(nrc,nrci,gzfmt(:,i),zfmt)
74 taumt_(1:npc,ias,ispn)=taumt_(1:npc,ias,ispn) &
75 +wo*(dble(zfmt(1:npc))**2+aimag(zfmt(1:npc))**2)
94 zfft(ifg)=
vgkc(i,igk,jspn,ik)*
zi*wfgp(igk,ispn,ist)
97 tauir_(1:ngtc,ispn)=tauir_(1:ngtc,ispn) &
98 +wo*(dble(zfft(1:ngtc))**2+aimag(zfft(1:ngtc))**2)
subroutine gentauk(ik, taumt_, tauir_)
subroutine genwfsv(tsh, tgp, nst, idx, ngridg_, igfft_, ngp, igpig, apwalm, evecfv, evecsv, wfmt, ld, wfir)
subroutine getevecfv(fext, ikp, vpl, vgpl, evecfv)
subroutine getevecsv(fext, ikp, vpl, evecsv)
subroutine gradzfmt(nr, nri, ri, wcr, zfmt, ld, gzfmt)
subroutine match(ngp, vgpc, gpc, sfacgp, apwalm)
real(8), dimension(:,:,:,:), allocatable vgkc
real(8), dimension(:), allocatable wkpt
real(8), dimension(:,:,:), allocatable gkc
integer, dimension(3) ngdgc
integer, dimension(:,:), allocatable ngk
integer, dimension(:,:,:), allocatable igkig
integer, dimension(maxspecies) nrcmt
integer, dimension(:), allocatable igfc
integer, dimension(maxatoms *maxspecies) idxis
real(8), dimension(:,:,:), allocatable rlcmt
real(8), dimension(:,:,:), allocatable wcrcmt
real(8), dimension(:,:,:,:), allocatable vgkl
integer, dimension(maxspecies) npcmt
integer, dimension(2) jspnfv
real(8), dimension(:,:), allocatable vkl
complex(8), dimension(:,:,:,:), allocatable sfacgk
integer, dimension(maxspecies) nrcmti
real(8), dimension(:,:), allocatable occsv
subroutine holdthd(nloop, nthd)
subroutine zbsht(nr, nri, zfmt1, zfmt2)
subroutine zfftifc(nd, n, sgn, z)