The Elk Code
gentauk.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2011 J. K. Dewhurst, S. Sharma and E. K. U. Gross.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
5 
6 subroutine gentauk(ik,taumt_,tauir_)
7 use modmain
8 use modomp
9 implicit none
10 ! arguments
11 integer, intent(in) :: ik
12 real(8), intent(inout) :: taumt_(npcmtmax,natmtot,nspinor),tauir_(ngtc,nspinor)
13 ! local variables
14 integer ispn,jspn,nst,ist,jst
15 integer is,ias,nrc,nrci
16 integer npc,igk,ifg,i,nthd
17 real(8) wo
18 ! automatic arrays
19 integer idx(nstsv)
20 ! automatic arrays
21 complex(8) gzfmt(npcmtmax,3),zfmt(npcmtmax),zfft(ngtc)
22 ! allocatable arrays
23 complex(8), allocatable :: apwalm(:,:,:,:,:),evecfv(:,:),evecsv(:,:)
24 complex(8), allocatable :: wfmt(:,:,:,:),wfgp(:,:,:)
25 allocate(apwalm(ngkmax,apwordmax,lmmaxapw,natmtot,nspnfv))
26 allocate(evecfv(nmatmax,nstfv),evecsv(nstsv,nstsv))
27 ! find the matching coefficients
28 do ispn=1,nspnfv
29  call match(ngk(ispn,ik),vgkc(:,:,ispn,ik),gkc(:,ispn,ik), &
30  sfacgk(:,:,ispn,ik),apwalm(:,:,:,:,ispn))
31 end do
32 ! get the eigenvectors from file
33 call getevecfv(filext,ik,vkl(:,ik),vgkl(:,:,:,ik),evecfv)
34 call getevecsv(filext,ik,vkl(:,ik),evecsv)
35 ! count and index the occupied states
36 nst=0
37 do ist=1,nstsv
38  if (abs(occsv(ist,ik)) < epsocc) cycle
39  nst=nst+1
40  idx(nst)=ist
41 end do
42 ! calculate the second-variational wavefunctions for occupied states
43 allocate(wfmt(npcmtmax,natmtot,nspinor,nst),wfgp(ngkmax,nspinor,nst))
44 call genwfsv(.true.,.true.,nst,idx,ngdgc,igfc,ngk(:,ik),igkig(:,:,ik),apwalm, &
45  evecfv,evecsv,wfmt,ngkmax,wfgp)
46 deallocate(apwalm,evecfv,evecsv)
47 call holdthd(nspinor*natmtot+1,nthd)
48 !$OMP PARALLEL DEFAULT(SHARED) &
49 !$OMP PRIVATE(gzfmt,zfmt,zfft) &
50 !$OMP PRIVATE(ispn,jspn,ias,is) &
51 !$OMP PRIVATE(nrc,nrci,npc,ist,jst) &
52 !$OMP PRIVATE(wo,i,igk,ifg) &
53 !$OMP NUM_THREADS(nthd)
54 !-------------------------!
55 ! muffin-tin part !
56 !-------------------------!
57 !$OMP DO COLLAPSE(2) SCHEDULE(DYNAMIC)
58 do ispn=1,nspinor
59  do ias=1,natmtot
60  is=idxis(ias)
61  nrc=nrcmt(is)
62  nrci=nrcmti(is)
63  npc=npcmt(is)
64  do ist=1,nst
65  jst=idx(ist)
66  wo=0.5d0*wkpt(ik)*occsv(jst,ik)
67 ! compute the gradient of the wavefunction
68  call gradzfmt(nrc,nrci,rlcmt(:,-1,is),wcrcmt(:,:,is), &
69  wfmt(:,ias,ispn,ist),npcmtmax,gzfmt)
70  do i=1,3
71 ! convert gradient to spherical coordinates
72  call zbsht(nrc,nrci,gzfmt(:,i),zfmt)
73 ! add to total in muffin-tin
74  taumt_(1:npc,ias,ispn)=taumt_(1:npc,ias,ispn) &
75  +wo*(dble(zfmt(1:npc))**2+aimag(zfmt(1:npc))**2)
76  end do
77  end do
78  end do
79 end do
80 !$OMP END DO NOWAIT
81 !---------------------------!
82 ! interstitial part !
83 !---------------------------!
84 !$OMP SINGLE
85 do ist=1,nst
86  jst=idx(ist)
87  wo=0.5d0*wkpt(ik)*occsv(jst,ik)/omega
88  do ispn=1,nspinor
89  jspn=jspnfv(ispn)
90  do i=1,3
91  zfft(1:ngtc)=0.d0
92  do igk=1,ngk(jspn,ik)
93  ifg=igfc(igkig(igk,jspn,ik))
94  zfft(ifg)=vgkc(i,igk,jspn,ik)*zi*wfgp(igk,ispn,ist)
95  end do
96  call zfftifc(3,ngdgc,1,zfft)
97  tauir_(1:ngtc,ispn)=tauir_(1:ngtc,ispn) &
98  +wo*(dble(zfft(1:ngtc))**2+aimag(zfft(1:ngtc))**2)
99  end do
100  end do
101 end do
102 !$OMP END SINGLE
103 !$OMP END PARALLEL
104 call freethd(nthd)
105 deallocate(wfmt,wfgp)
106 end subroutine
107 
integer nmatmax
Definition: modmain.f90:853
integer, dimension(maxspecies) npcmt
Definition: modmain.f90:214
subroutine getevecsv(fext, ikp, vpl, evecsv)
Definition: getevecsv.f90:7
character(256) filext
Definition: modmain.f90:1301
subroutine genwfsv(tsh, tgp, nst, idx, ngridg_, igfft_, ngp, igpig, apwalm, evecfv, evecsv, wfmt, ld, wfir)
Definition: genwfsv.f90:11
integer lmmaxapw
Definition: modmain.f90:199
integer ngkmax
Definition: modmain.f90:499
subroutine getevecfv(fext, ikp, vpl, vgpl, evecfv)
Definition: getevecfv.f90:10
real(8) omega
Definition: modmain.f90:20
subroutine match(ngp, vgpc, gpc, sfacgp, apwalm)
Definition: match.f90:10
subroutine gentauk(ik, taumt_, tauir_)
Definition: gentauk.f90:7
Definition: modomp.f90:6
subroutine gradzfmt(nr, nri, ri, wcr, zfmt, ld, gzfmt)
Definition: gradzfmt.f90:10
real(8) epsocc
Definition: modmain.f90:903
complex(8), dimension(:,:,:,:), allocatable sfacgk
Definition: modmain.f90:509
integer, dimension(:,:), allocatable ngk
Definition: modmain.f90:497
subroutine zfftifc(nd, n, sgn, z)
Definition: zfftifc_fftw.f90:7
real(8), dimension(:), allocatable wkpt
Definition: modmain.f90:475
real(8), dimension(:,:,:,:), allocatable vgkl
Definition: modmain.f90:503
integer, dimension(:), allocatable igfc
Definition: modmain.f90:410
real(8), dimension(:,:,:), allocatable rlcmt
Definition: modmain.f90:181
real(8), dimension(:,:), allocatable occsv
Definition: modmain.f90:905
real(8), dimension(:,:,:,:), allocatable vgkc
Definition: modmain.f90:505
real(8), dimension(:,:), allocatable vkl
Definition: modmain.f90:471
integer apwordmax
Definition: modmain.f90:760
integer, dimension(maxatoms *maxspecies) idxis
Definition: modmain.f90:44
real(8), dimension(:,:,:), allocatable wcrcmt
Definition: modmain.f90:193
subroutine zbsht(nr, nri, zfmt1, zfmt2)
Definition: zbsht.f90:10
real(8), dimension(:,:,:), allocatable gkc
Definition: modmain.f90:507
integer, dimension(3) ngdgc
Definition: modmain.f90:388
subroutine freethd(nthd)
Definition: modomp.f90:106
subroutine holdthd(nloop, nthd)
Definition: modomp.f90:78
complex(8), parameter zi
Definition: modmain.f90:1240
integer, dimension(maxspecies) nrcmt
Definition: modmain.f90:173
integer, dimension(maxspecies) nrcmti
Definition: modmain.f90:211
integer, dimension(:,:,:), allocatable igkig
Definition: modmain.f90:501
integer nstfv
Definition: modmain.f90:887
integer, dimension(2) jspnfv
Definition: modmain.f90:291
integer nspnfv
Definition: modmain.f90:289