The Elk Code
dhmlalo.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2013 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 pure subroutine dhmlalo(is,ias,ngp,ngpq,apwalm,apwalmq,dapwalm,dapwalmq,ld,dh)
7 use modmain
8 use modphonon
9 implicit none
10 ! arguments
11 integer, intent(in) :: is,ias,ngp,ngpq
12 complex(8), intent(in) :: apwalm(ngkmax,apwordmax,lmmaxapw)
13 complex(8), intent(in) :: apwalmq(ngkmax,apwordmax,lmmaxapw)
14 complex(8), intent(in) :: dapwalm(ngkmax,apwordmax,lmmaxapw)
15 complex(8), intent(in) :: dapwalmq(ngkmax,apwordmax,lmmaxapw)
16 integer, intent(in) :: ld
17 complex(8), intent(inout) :: dh(ld,*)
18 ! local variables
19 integer io,ilo
20 integer l0,l1,l2,l3
21 integer lm1,lm3,lma,lmb
22 integer i0,j0,i,j
23 complex(8) z1
24 do ilo=1,nlorb(is)
25  l1=lorbl(ilo,is)
26  do lm1=l1**2+1,(l1+1)**2
27  i=idxlo(lm1,ilo,ias)
28  i0=ngpq+i
29  j0=ngp+i
30  do l3=0,lmaxapw
31  if (mod(l1+l3,2) == 0) then; l0=0; else; l0=1; end if
32  do lm3=l3**2+1,(l3+1)**2
33  do io=1,apword(l3,is)
34  z1=0.d0
35  do l2=l0,lmaxo,2
36  lma=l2**2+1; lmb=lma+2*l2
37  z1=z1+sum(gntyyy(lma:lmb,lm3,lm1)*dhloa(lma:lmb,io,l3,ilo,ias))
38  end do
39  if (abs(z1%re)+abs(z1%im) > 1.d-12) then
40  do i=1,ngpq
41  dh(i,j0)=dh(i,j0)+conjg(z1*apwalmq(i,io,lm3))
42  end do
43  do j=1,ngp
44  dh(i0,j)=dh(i0,j)+z1*apwalm(j,io,lm3)
45  end do
46  end if
47  end do
48  end do
49  end do
50  if (ias == iasph) then
51  do l3=0,lmaxapw
52  if (mod(l1+l3,2) == 0) then; l0=0; else; l0=1; end if
53  do lm3=l3**2+1,(l3+1)**2
54  do io=1,apword(l3,is)
55  z1=0.d0
56  do l2=l0,lmaxo,2
57  lma=l2**2+1; lmb=lma+2*l2
58  z1=z1+sum(gntyry(lma:lmb,lm3,lm1)*hloa(lma:lmb,io,l3,ilo,ias))
59  end do
60  if (abs(z1%re)+abs(z1%im) > 1.d-12) then
61  do i=1,ngpq
62  dh(i,j0)=dh(i,j0)+conjg(z1*dapwalmq(i,io,lm3))
63  end do
64  do j=1,ngp
65  dh(i0,j)=dh(i0,j)+z1*dapwalm(j,io,lm3)
66  end do
67  end if
68  end do
69  end do
70  end do
71  end if
72  end do
73 end do
74 end subroutine
75 
integer, dimension(maxspecies) nlorb
Definition: modmain.f90:786
integer, dimension(:,:,:), allocatable idxlo
Definition: modmain.f90:855
integer lmmaxapw
Definition: modmain.f90:199
integer ngkmax
Definition: modmain.f90:499
integer iasph
Definition: modphonon.f90:15
integer lmaxo
Definition: modmain.f90:201
complex(8), dimension(:,:,:,:,:), allocatable dhloa
Definition: modphonon.f90:122
real(8), dimension(:,:,:), allocatable gntyyy
Definition: modphonon.f90:126
integer lmaxapw
Definition: modmain.f90:197
integer, dimension(0:maxlapw, maxspecies) apword
Definition: modmain.f90:758
complex(8), dimension(:,:,:), allocatable gntyry
Definition: modmain.f90:867
real(8), dimension(:,:,:,:,:), allocatable hloa
Definition: modmain.f90:863
integer apwordmax
Definition: modmain.f90:760
integer, dimension(maxlorb, maxspecies) lorbl
Definition: modmain.f90:796
pure subroutine dhmlalo(is, ias, ngp, ngpq, apwalm, apwalmq, dapwalm, dapwalmq, ld, dh)
Definition: dhmlalo.f90:7