The Elk Code
dielectric.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2002-2009 S. Sharma, J. K. Dewhurst and C. Ambrosch-Draxl.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
5 
6 !BOP
7 ! !ROUTINE: dielectric
8 ! !INTERFACE:
9 subroutine dielectric
10 ! !USES:
11 use modmain
12 use modmpi
13 use modomp
14 use modtest
15 ! !DESCRIPTION:
16 ! Computes the dielectric tensor, optical conductivity and plasma frequency.
17 ! The formulae are taken from {\it Physica Scripta} {\bf T109}, 170 (2004).
18 !
19 ! !REVISION HISTORY:
20 ! Created November 2005 (SS and JKD)
21 ! Added plasma frequency and intraband contribution (S. Lebegue)
22 ! Complete rewrite, 2008 (JKD)
23 ! Fixed problem with plasma frequency, 2009 (Marty Blaber and JKD)
24 ! Parallelised, 2009 (M. Blaber)
25 !EOP
26 !BOC
27 implicit none
28 ! local variables
29 integer ik,jk,ist,jst
30 integer iw,ioc,i,j,nthd
31 real(8) w1,w2,wplas,x
32 real(8) ei,ej,eji,t1,t2
33 complex(8) eta,z1
34 character(256) fname
35 ! allocatable arrays
36 real(8), allocatable :: w(:)
37 complex(8), allocatable :: pmat(:,:,:),sigma(:)
38 ! external functions
39 real(8), external :: sdelta
40 ! initialise universal variables
41 call init0
42 call init1
43 ! read Fermi energy from file
44 call readefm
45 ! get the eigenvalues and occupation numbers from file
46 call readevalsv
47 call readoccsv
48 ! allocate local arrays
49 allocate(w(nwplot),sigma(nwplot))
50 ! generate energy grid (always non-negative)
51 w1=max(wplot(1),0.d0)
52 w2=max(wplot(2),w1)
53 t1=(w2-w1)/dble(nwplot)
54 do iw=1,nwplot
55  w(iw)=w1+t1*dble(iw-1)
56 end do
57 ! i divided by the complex relaxation time
58 eta=cmplx(0.d0,swidth,8)
59 ! loop over dielectric tensor components
60 do ioc=1,noptcomp
61  i=optcomp(1,ioc)
62  j=optcomp(2,ioc)
63  wplas=0.d0
64  sigma(:)=0.d0
65 ! parallel loop over non-reduced k-points
66  call holdthd(nkptnr,nthd)
67 !$OMP PARALLEL DEFAULT(SHARED) &
68 !$OMP PRIVATE(pmat,jk,ist,jst) &
69 !$OMP PRIVATE(ei,ej,eji,z1,t1,x) &
70 !$OMP REDUCTION(+:wplas,sigma) &
71 !$OMP NUM_THREADS(nthd)
72  allocate(pmat(nstsv,nstsv,3))
73 !$OMP DO SCHEDULE(DYNAMIC)
74  do ik=1,nkptnr
75 ! distribute among MPI processes
76  if (mod(ik-1,np_mpi) /= lp_mpi) cycle
77 !$OMP CRITICAL(dielectric_)
78  write(*,'("Info(dielectric): ",I6," of ",I6," k-points")') ik,nkptnr
79 !$OMP END CRITICAL(dielectric_)
80 ! equivalent reduced k-point
81  jk=ivkik(ivk(1,ik),ivk(2,ik),ivk(3,ik))
82 ! read in the momentum matrix elements
83  call getpmat(vkl(:,ik),pmat)
84 ! valance states
85  do ist=1,nstsv
86  ei=evalsv(ist,jk)
87 ! conduction states
88  do jst=1,nstsv
89  ej=evalsv(jst,jk)
90  eji=ej-ei
91  z1=pmat(ist,jst,i)*conjg(pmat(ist,jst,j))
92  if (abs(eji) > 1.d-8) then
93  t1=occsv(ist,jk)*(1.d0-occsv(jst,jk)/occmax)/eji
94  sigma(:)=sigma(:)+t1*(z1/(w(:)-eji+eta)+conjg(z1)/(w(:)+eji+eta))
95  end if
96 ! add to the plasma frequency
97  if (intraband) then
98  if (i == j) then
99  if (ist == jst) then
100  x=(ei-efermi)/swidth
101  t1=wkptnr*z1%re*sdelta(stype,x)/swidth
102  wplas=wplas+t1
103  end if
104  end if
105  end if
106  end do
107  end do
108  end do
109 !$OMP END DO
110  deallocate(pmat)
111 !$OMP END PARALLEL
112  call freethd(nthd)
113 ! multiply response function by prefactor
114  z1=zi*wkptnr/omega
115  sigma(:)=z1*sigma(:)
116 ! add response function and plasma frequency from each process and redistribute
117  if (np_mpi > 1) then
118  call mpi_allreduce(mpi_in_place,sigma,nwplot,mpi_double_complex,mpi_sum, &
119  mpicom,ierror)
120  call mpi_allreduce(mpi_in_place,wplas,1,mpi_double_precision,mpi_sum, &
121  mpicom,ierror)
122  end if
123 ! intraband contribution
124  if (intraband) then
125  if (i == j) then
126  wplas=sqrt(occmax*abs(wplas)*fourpi/omega)
127 ! write the plasma frequency to file
128  write(fname,'("PLASMA_",2I1,".OUT")') i,j
129  open(50,file=trim(fname),form='FORMATTED')
130  write(50,'(G18.10," : plasma frequency")') wplas
131  close(50)
132 ! add the intraband contribution to sigma
133  t1=wplas**2/fourpi
134  do iw=1,nwplot
135  sigma(iw)=sigma(iw)+t1/(swidth-zi*w(iw))
136  end do
137  end if
138  end if
139 ! write the optical conductivity to file
140  write(fname,'("SIGMA_",2I1,".OUT")') i,j
141  open(50,file=trim(fname),form='FORMATTED')
142  do iw=1,nwplot
143  write(50,'(2G18.10)') w(iw),dble(sigma(iw))
144  end do
145  write(50,*)
146  do iw=1,nwplot
147  write(50,'(2G18.10)') w(iw),aimag(sigma(iw))
148  end do
149  close(50)
150 ! write the dielectric function to file
151  write(fname,'("EPSILON_",2I1,".OUT")') i,j
152  open(50,file=trim(fname),form='FORMATTED')
153  t1=0.d0
154  if (i == j) t1=1.d0
155  do iw=1,nwplot
156  t2=t1-fourpi*aimag(sigma(iw)/(w(iw)+eta))
157  write(50,'(2G18.10)') w(iw),t2
158  end do
159  write(50,*)
160  do iw=1,nwplot
161  t2=fourpi*dble(sigma(iw)/(w(iw)+eta))
162  write(50,'(2G18.10)') w(iw),t2
163  end do
164  close(50)
165 ! end loop over tensor components
166 end do
167 if (mp_mpi) then
168  write(*,*)
169  write(*,'("Info(dielectric):")')
170  write(*,'(" dielectric tensor written to EPSILON_ij.OUT")')
171  write(*,'(" optical conductivity written to SIGMA_ij.OUT")')
172  if (intraband) then
173  write(*,'(" plasma frequency written to PLASMA_ij.OUT")')
174  end if
175  write(*,'(" for components")')
176  do ioc=1,noptcomp
177  write(*,'(" i = ",I1,", j = ",I1)') optcomp(1:2,ioc)
178  end do
179 end if
180 ! write sigma to test file if required
181 call writetest(121,'optical conductivity',nv=nwplot,tol=1.d-2,zva=sigma)
182 deallocate(w,sigma)
183 end subroutine
184 !EOC
185 
real(8) efermi
Definition: modmain.f90:907
subroutine writetest(id, descr, nv, iv, iva, tol, rv, rva, zv, zva)
Definition: modtest.f90:16
real(8), dimension(:,:), allocatable evalsv
Definition: modmain.f90:921
logical mp_mpi
Definition: modmpi.f90:17
real(8) omega
Definition: modmain.f90:20
subroutine getpmat(vpl, pmat)
Definition: getpmat.f90:7
Definition: modomp.f90:6
real(8) swidth
Definition: modmain.f90:895
integer, dimension(:,:,:), allocatable ivkik
Definition: modmain.f90:467
integer nkptnr
Definition: modmain.f90:463
subroutine readoccsv
Definition: readoccsv.f90:7
integer np_mpi
Definition: modmpi.f90:13
integer nstsv
Definition: modmain.f90:889
real(8), dimension(2) wplot
Definition: modmain.f90:1079
subroutine dielectric
Definition: dielectric.f90:10
logical intraband
Definition: modmain.f90:1095
subroutine readefm
Definition: readefm.f90:10
real(8) occmax
Definition: modmain.f90:901
integer, dimension(3, 27) optcomp
Definition: modmain.f90:1093
real(8), dimension(:,:), allocatable occsv
Definition: modmain.f90:905
subroutine init1
Definition: init1.f90:10
real(8), dimension(:,:), allocatable vkl
Definition: modmain.f90:471
integer noptcomp
Definition: modmain.f90:1091
integer stype
Definition: modmain.f90:891
Definition: modmpi.f90:6
integer lp_mpi
Definition: modmpi.f90:15
subroutine freethd(nthd)
Definition: modomp.f90:106
subroutine holdthd(nloop, nthd)
Definition: modomp.f90:78
complex(8), parameter zi
Definition: modmain.f90:1240
real(8) wkptnr
Definition: modmain.f90:477
subroutine init0
Definition: init0.f90:10
real(8), parameter fourpi
Definition: modmain.f90:1234
integer nwplot
Definition: modmain.f90:1073
subroutine readevalsv
Definition: readevalsv.f90:7
integer, dimension(:,:), allocatable ivk
Definition: modmain.f90:465
integer mpicom
Definition: modmpi.f90:11
integer ierror
Definition: modmpi.f90:19