exciting-0.9.150
[exciting.git] / src / genvmat.f90
blob90dca276aa6c59208fd37021c75b523b26dc5cf7
2 ! Copyright (C) 2007 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.
6 subroutine genvmat(vmt,vir,vmat)
7 ! generates potential matrix elements for all states and k-points
8 use modmain
9 implicit none
10 ! arguments
11 real(8), intent(in) :: vmt(lmmaxvr,nrmtmax,natmtot)
12 real(8), intent(in) :: vir(ngrtot)
13 complex(8), intent(out) :: vmat(nstsv,nstsv,nkpt)
14 ! local variables
15 integer is,ia,ias,irc,ir
16 integer ik
17 ! local arrays
18 real(8), allocatable :: rfmt(:,:,:)
19 complex(8), allocatable :: apwalm(:,:,:,:)
20 complex(8), allocatable :: evecfv(:,:)
21 complex(8), allocatable :: evecsv(:,:)
22 complex(8), allocatable :: wfmt(:,:,:,:,:)
23 complex(8), allocatable :: wfir(:,:,:)
24 ! allocate local arrays
25 allocate(rfmt(lmmaxvr,nrcmtmax,natmtot))
26 allocate(apwalm(ngkmax,apwordmax,lmmaxapw,natmtot))
27 allocate(evecfv(nmatmax,nstfv))
28 allocate(evecsv(nstsv,nstsv))
29 allocate(wfmt(lmmaxvr,nrcmtmax,natmtot,nspinor,nstsv))
30 allocate(wfir(ngrtot,nspinor,nstsv))
31 ! convert muffin-tin potential to spherical coordinates
32 do is=1,nspecies
33 do ia=1,natoms(is)
34 ias=idxas(ia,is)
35 irc=0
36 do ir=1,nrmt(is),lradstp
37 irc=irc+1
38 call dgemv('N',lmmaxvr,lmmaxvr,1.d0,rbshtapw,lmmaxapw,vmt(1,ir,ias), &
39 1,0.d0,rfmt(1,irc,ias),1)
40 end do
41 end do
42 end do
43 ! loop over k-points
44 do ik=1,nkpt
45 ! get the eigenvectors and values from file
46 call getevalsv(vkl(1,ik),evalsv)
47 call getevecfv(vkl(1,ik),vgkl(1,1,ik,1),evecfv)
48 call getevecsv(vkl(1,ik),evecsv)
49 ! find the matching coefficients
50 call match(ngk(ik,1),gkc(1,ik,1),tpgkc(1,1,ik,1),sfacgk(1,1,ik,1),apwalm)
51 ! calculate the wavefunctions for all states
52 call genwfsv(.false.,ngk(ik,1),igkig(1,ik,1),evalsv,apwalm,evecfv,evecsv, &
53 wfmt,wfir)
54 call genvmatk(rfmt,vir,wfmt,wfir,vmat(1,1,ik))
55 end do
56 deallocate(apwalm,evecfv,evecsv,wfmt,wfir)
57 return
58 end subroutine