The Elk Code
 
Loading...
Searching...
No Matches
genolpq.f90
Go to the documentation of this file.
1
2! Copyright (C) 2019 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
6subroutine genolpq(nst,expqmt,ngpq,igpqig,wfmt,wfir,wfmtq,wfgpq,oq)
7use modmain
8use modomp
9implicit none
10! arguments
11integer, intent(in) :: nst
12complex(8), intent(in) :: expqmt(npcmtmax,natmtot)
13integer, intent(in) :: ngpq(nspnfv),igpqig(ngkmax,nspnfv)
14complex(8), intent(in) :: wfmt(npcmtmax,natmtot,nspinor,nst)
15complex(8), intent(in) :: wfir(ngtc,nspinor,nst)
16complex(8), intent(in) :: wfmtq(npcmtmax,natmtot,nspinor,nst)
17complex(8), intent(in) :: wfgpq(ngkmax,nspinor,nst)
18complex(8), intent(out) :: oq(nst,nst)
19! local variables
20integer jst,ispn,jspn
21integer is,ias,nrc,nrci,npc
22integer ld1,ld2,igpq,nthd
23real(8) t0
24! automatic arrays
25complex(8) wfmt1(npcmtmax),wfir1(ngtc),z(ngkmax)
26ld1=npcmtmax*natmtot*nspinor
27ld2=ngkmax*nspinor
28t0=sqrt(omega)
29! zero the matrix elements
30oq(1:nst,1:nst)=0.d0
31call holdthd(nst,nthd)
32!$OMP PARALLEL DEFAULT(SHARED) &
33!$OMP PRIVATE(wfmt1,wfir1,z) &
34!$OMP PRIVATE(jst,ispn,jspn,igpq) &
35!$OMP PRIVATE(ias,is,nrc,nrci,npc) &
36!$OMP NUM_THREADS(nthd)
37!---------------------------!
38! interstitial part !
39!---------------------------!
40!$OMP DO SCHEDULE(DYNAMIC)
41do jst=1,nst
42 do ispn=1,nspinor
43 jspn=jspnfv(ispn)
44! multiply wavefunction by characteristic function
45 wfir1(1:ngtc)=wfir(1:ngtc,ispn,jst)*cfrc(1:ngtc)
46! Fourier transform to G+p+q-space
47 call zfftifc(3,ngdgc,-1,wfir1)
48 do igpq=1,ngpq(jspn)
49 z(igpq)=wfir1(igfc(igpqig(igpq,jspn)))
50 end do
51 call zgemv('C',ngpq(jspn),nst,zone,wfgpq(1,ispn,1),ld2,z,1,zone,oq(1,jst),1)
52 end do
53end do
54!$OMP END DO
55! scale the matrix elements because of the real-space wavefunction normalisation
56!$OMP SINGLE
57oq(1:nst,1:nst)=t0*oq(1:nst,1:nst)
58!$OMP END SINGLE
59!-------------------------!
60! muffin-tin part !
61!-------------------------!
62!$OMP DO SCHEDULE(DYNAMIC)
63do jst=1,nst
64 do ispn=1,nspinor
65 do ias=1,natmtot
66 is=idxis(ias)
67 nrc=nrcmt(is)
68 nrci=nrcmti(is)
69 npc=npcmt(is)
70! multiply by local phase factor function exp(iq.r)
71 wfmt1(1:npc)=expqmt(1:npc,ias)*wfmt(1:npc,ias,ispn,jst)
72! apply the radial integral weights
73 call zfcmtwr(nrc,nrci,wr2cmt(:,is),wfmt1)
74! compute the inner products
75 call zgemv('C',npc,nst,zone,wfmtq(1,ias,ispn,1),ld1,wfmt1,1,zone, &
76 oq(1,jst),1)
77 end do
78 end do
79end do
80!$OMP END DO
81!$OMP END PARALLEL
82call freethd(nthd)
83end subroutine
84
subroutine genolpq(nst, expqmt, ngpq, igpqig, wfmt, wfir, wfmtq, wfgpq, oq)
Definition genolpq.f90:7
real(8), dimension(:), allocatable cfrc
Definition modmain.f90:438
integer, dimension(3) ngdgc
Definition modmain.f90:388
real(8) omega
Definition modmain.f90:20
integer, dimension(maxspecies) nrcmt
Definition modmain.f90:173
complex(8), parameter zone
Definition modmain.f90:1238
integer, dimension(:), allocatable igfc
Definition modmain.f90:410
integer, dimension(maxatoms *maxspecies) idxis
Definition modmain.f90:44
real(8), dimension(:,:), allocatable wr2cmt
Definition modmain.f90:189
integer, dimension(maxspecies) npcmt
Definition modmain.f90:214
integer, dimension(2) jspnfv
Definition modmain.f90:291
integer, dimension(maxspecies) nrcmti
Definition modmain.f90:211
subroutine holdthd(nloop, nthd)
Definition modomp.f90:78
subroutine freethd(nthd)
Definition modomp.f90:106
pure subroutine zfcmtwr(nr, nri, wr, zfmt)
Definition zfcmtwr.f90:7
subroutine zfftifc(nd, n, sgn, z)