30integer iw,ioc,i,j,nthd
32real(8) ei,ej,eji,t1,t2
36real(8),
allocatable :: w(:)
37complex(8),
allocatable :: pmat(:,:,:),sigma(:)
39real(8),
external :: sdelta
55 w(iw)=w1+t1*dble(iw-1)
78 write(*,
'("Info(dielectric): ",I6," of ",I6," k-points")') ik,
nkptnr
91 z1=pmat(ist,jst,i)*conjg(pmat(ist,jst,j))
92 if (abs(eji) > 1.d-8)
then
94 sigma(:)=sigma(:)+t1*(z1/(w(:)-eji+eta)+conjg(z1)/(w(:)+eji+eta))
118 call mpi_allreduce(mpi_in_place,sigma,
nwplot,mpi_double_complex,mpi_sum, &
120 call mpi_allreduce(mpi_in_place,wplas,1,mpi_double_precision,mpi_sum, &
128 write(fname,
'("PLASMA_",2I1,".OUT")') i,j
129 open(50,file=trim(fname),form=
'FORMATTED')
130 write(50,
'(G18.10," : plasma frequency")') wplas
135 sigma(iw)=sigma(iw)+t1/(
swidth-
zi*w(iw))
140 write(fname,
'("SIGMA_",2I1,".OUT")') i,j
141 open(50,file=trim(fname),form=
'FORMATTED')
143 write(50,
'(2G18.10)') w(iw),dble(sigma(iw))
147 write(50,
'(2G18.10)') w(iw),aimag(sigma(iw))
151 write(fname,
'("EPSILON_",2I1,".OUT")') i,j
152 open(50,file=trim(fname),form=
'FORMATTED')
156 t2=t1-
fourpi*aimag(sigma(iw)/(w(iw)+eta))
157 write(50,
'(2G18.10)') w(iw),t2
161 t2=
fourpi*dble(sigma(iw)/(w(iw)+eta))
162 write(50,
'(2G18.10)') w(iw),t2
169 write(*,
'("Info(dielectric):")')
170 write(*,
'(" dielectric tensor written to EPSILON_ij.OUT")')
171 write(*,
'(" optical conductivity written to SIGMA_ij.OUT")')
173 write(*,
'(" plasma frequency written to PLASMA_ij.OUT")')
175 write(*,
'(" for components")')
177 write(*,
'(" i = ",I1,", j = ",I1)')
optcomp(1:2,ioc)
181call writetest(121,
'optical conductivity',nv=
nwplot,tol=1.d-2,zva=sigma)
subroutine getpmat(vpl, pmat)
integer, dimension(3, 27) optcomp
integer, dimension(:,:), allocatable ivk
real(8), parameter fourpi
real(8), dimension(2) wplot
real(8), dimension(:,:), allocatable vkl
integer, dimension(:,:,:), allocatable ivkik
real(8), dimension(:,:), allocatable occsv
real(8), dimension(:,:), allocatable evalsv
subroutine holdthd(nloop, nthd)
subroutine writetest(id, descr, nv, iv, iva, tol, rv, rva, zv, zva)
real(8) function sdelta(stype, x)