The Elk Code
 
Loading...
Searching...
No Matches
genhmlu.f90
Go to the documentation of this file.
1
2! Copyright (C) 2017 T. Mueller, 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 genhmlu(ik0,h)
7use modmain
8use modulr
9use modomp
10implicit none
11! arguments
12integer, intent(in) :: ik0
13complex(8), intent(out) :: h(nstulr,nstulr)
14! local variables
15integer ik,ist,jst,ispn,idm,nthd
16integer ikpa,jkpa,iq,ifq,ngk0,igk
17integer i1,i2,i3,j1,j2,j3,i,j
18! automatic arrays
19complex(8) zvir(ngtc),zbir(ngtc,ndmag),vmat(nstsv,nstsv)
20! allocatable arrays
21complex(8), allocatable :: apwalm(:,:,:,:),evecfv(:,:),evecsv(:,:)
22complex(4), allocatable :: wfmt(:,:,:,:),wfir(:,:,:),wfgk(:,:,:)
23complex(8), allocatable :: hdb(:,:,:)
24! central k-point
25ik=(ik0-1)*nkpa+1
26! number of G+k-vectors for central k-point
27ngk0=ngk(1,ik)
28! get the ground-state eigenvectors from file for central k-point
29allocate(evecfv(nmatmax,nstfv),evecsv(nstsv,nstsv))
30call getevecfv('.OUT',ik,vkl(:,ik),vgkl(:,:,:,ik),evecfv)
31call getevecsv('.OUT',ik,vkl(:,ik),evecsv)
32! find the matching coefficients
33allocate(apwalm(ngkmax,apwordmax,lmmaxapw,natmtot))
34call match(ngk0,vgkc(:,:,1,ik),gkc(:,1,ik),sfacgk(:,:,1,ik),apwalm)
35! calculate the wavefunctions for all states of the central k-point
36allocate(wfmt(npcmtmax,natmtot,nspinor,nstsv),wfgk(ngk0,nspinor,nstsv))
37call genwfsv_sp(.false.,.true.,nstsv,[0],ngridg,igfft,ngk0,igkig(:,1,ik), &
38 apwalm,evecfv,evecsv,wfmt,ngk0,wfgk)
39deallocate(apwalm,evecfv,evecsv)
40! determine the interstitial wavefunctions in real-space (without 1/sqrt(omega))
41allocate(wfir(ngtc,nspinor,nstsv))
42call holdthd(nstsv,nthd)
43!$OMP PARALLEL DO DEFAULT(SHARED) &
44!$OMP PRIVATE(ispn,igk) &
45!$OMP SCHEDULE(DYNAMIC) &
46!$OMP NUM_THREADS(nthd)
47do ist=1,nstsv
48 do ispn=1,nspinor
49 wfir(1:ngtc,ispn,ist)=0.e0
50 do igk=1,ngk0
51 wfir(igfc(igkig(igk,1,ik)),ispn,ist)=wfgk(igk,ispn,ist)
52 end do
53 call cfftifc(3,ngdgc,1,wfir(:,ispn,ist))
54 end do
55end do
56!$OMP END PARALLEL DO
57call freethd(nthd)
58! generate the matrix elements for all Q-vectors
59call holdthd(nfqrz,nthd)
60!$OMP PARALLEL DO DEFAULT(SHARED) &
61!$OMP PRIVATE(zvir,zbir,vmat) &
62!$OMP PRIVATE(iq,idm,ikpa,jkpa,j1,j2,j3) &
63!$OMP PRIVATE(jst,i,j,i1,i2,i3) &
64!$OMP SCHEDULE(DYNAMIC) &
65!$OMP NUM_THREADS(nthd)
66do ifq=1,nfqrz
67 iq=iqrzf(ifq)
68! multiply long-range interstitial potential by characteristic function and
69! convert to coarse grid
70 call zfirftoc(vsqir(:,ifq),zvir)
71 if (spinpol) then
72! convert interstitial magnetic field to coarse grid
73 do idm=1,ndmag
74 call zfirftoc(bsqir(:,idm,ifq),zbir(:,idm))
75 end do
76! calculate matrix elements for this Q-vector
77 call genzvbmatk(vsqmt(:,:,ifq),zvir,bsqmt(:,:,:,ifq),zbir,ngk0, &
78 igkig(:,1,ik),wfmt,wfir,wfgk,vmat)
79 else
80 call genzvmatk(vsqmt(:,:,ifq),zvir,ngk0,igkig(:,1,ik),wfmt,wfir,wfgk,vmat)
81 end if
82 do jkpa=1,nkpa
83 j1=ivq(1,jkpa); j2=ivq(2,jkpa); j3=ivq(3,jkpa)
84 do jst=1,nstsv
85 j=(jkpa-1)*nstsv+jst
86 do ikpa=1,jkpa-1
87 i=(ikpa-1)*nstsv+1
88 i1=ivq(1,ikpa)-j1; i2=ivq(2,ikpa)-j2; i3=ivq(3,ikpa)-j3
89 if (ivqiq(i1,i2,i3) == iq) then
90! copy matrix elements for κ_i - κ_j in Q-point set
91 h(i:i+nstsv-1,j)=vmat(1:nstsv,jst)
92 else if (ivqiq(-i1,-i2,-i3) == iq) then
93! otherwise use conjugate transpose
94 h(i:i+nstsv-1,j)=conjg(vmat(jst,1:nstsv))
95 end if
96 end do
97! copy only the upper triangular part for Q=0
98 if (ifq == 1) then
99 i=(jkpa-1)*nstsv+1
100 h(i:i+jst-1,j)=vmat(1:jst,jst)
101 end if
102 end do
103 end do
104end do
105!$OMP END PARALLEL DO
106call freethd(nthd)
107deallocate(wfmt,wfir,wfgk)
108! add the second-variational eigenvalues of k+κ to the diagonal but in the basis
109! of the states at k
110do ist=1,nstsv
111 h(ist,ist)=h(ist,ist)+evalsv(ist,ik)
112end do
113allocate(hdb(nstsv,nstsv,2:nkpa))
114call hdbulrk(ik0,hdb)
115do ikpa=2,nkpa
116 i=(ikpa-1)*nstsv+1
117 do jst=1,nstsv
118 j=i+jst-1
119 h(i:i+jst-1,j)=h(i:i+jst-1,j)+hdb(1:jst,jst,ikpa)
120 end do
121end do
122deallocate(hdb)
123end subroutine
124
subroutine cfftifc(nd, n, sgn, c)
subroutine genhmlu(ik0, h)
Definition genhmlu.f90:7
subroutine genwfsv_sp(tsh, tgp, nst, idx, ngridg_, igfft_, ngp, igpig, apwalm, evecfv, evecsv, wfmt, ld, wfir)
Definition genwfsv_sp.f90:8
subroutine genzvbmatk(zvmt, zvir, zbmt, zbir, ngp, igpig, wfmt, wfir, wfgp, vbmat)
Definition genzvbmatk.f90:7
subroutine genzvmatk(zvmt, zvir, ngp, igpig, wfmt, wfir, wfgp, vmat)
Definition genzvmatk.f90:7
subroutine getevecfv(fext, ikp, vpl, vgpl, evecfv)
Definition getevecfv.f90:10
subroutine getevecsv(fext, ikp, vpl, evecsv)
Definition getevecsv.f90:7
subroutine hdbulrk(ik0, hdb)
Definition hdbulrk.f90:7
subroutine match(ngp, vgpc, gpc, sfacgp, apwalm)
Definition match.f90:10
real(8), dimension(:,:,:,:), allocatable vgkc
Definition modmain.f90:505
integer, dimension(3) ngridg
Definition modmain.f90:386
real(8), dimension(:,:,:), allocatable gkc
Definition modmain.f90:507
integer nspinor
Definition modmain.f90:267
integer, dimension(3) ngdgc
Definition modmain.f90:388
integer nfqrz
Definition modmain.f90:539
integer, dimension(:,:), allocatable ivq
Definition modmain.f90:529
logical spinpol
Definition modmain.f90:228
integer, dimension(:,:), allocatable ngk
Definition modmain.f90:497
integer, dimension(:,:,:), allocatable igkig
Definition modmain.f90:501
integer, dimension(:,:,:), allocatable ivqiq
Definition modmain.f90:531
integer, dimension(:), allocatable igfc
Definition modmain.f90:410
integer lmmaxapw
Definition modmain.f90:199
integer apwordmax
Definition modmain.f90:760
integer natmtot
Definition modmain.f90:40
real(8), dimension(:,:,:,:), allocatable vgkl
Definition modmain.f90:503
integer npcmtmax
Definition modmain.f90:216
integer, dimension(:), allocatable igfft
Definition modmain.f90:406
integer nmatmax
Definition modmain.f90:848
integer, dimension(:), allocatable iqrzf
Definition modmain.f90:543
real(8), dimension(:,:), allocatable vkl
Definition modmain.f90:471
integer ngkmax
Definition modmain.f90:499
integer nstfv
Definition modmain.f90:884
complex(8), dimension(:,:,:,:), allocatable sfacgk
Definition modmain.f90:509
real(8), dimension(:,:), allocatable evalsv
Definition modmain.f90:918
subroutine holdthd(nloop, nthd)
Definition modomp.f90:78
subroutine freethd(nthd)
Definition modomp.f90:106
complex(8), dimension(:,:,:,:), pointer, contiguous bsqmt
Definition modulr.f90:84
complex(8), dimension(:,:,:), pointer, contiguous vsqmt
Definition modulr.f90:83
integer nkpa
Definition modulr.f90:24
complex(8), dimension(:,:,:), pointer, contiguous bsqir
Definition modulr.f90:84
complex(8), dimension(:,:), pointer, contiguous vsqir
Definition modulr.f90:83
subroutine zfirftoc(zfir, zfirc)
Definition zfirftoc.f90:7