The Elk Code
 
Loading...
Searching...
No Matches
energy.f90
Go to the documentation of this file.
1
2! Copyright (C) 2002-2006 J. K. Dewhurst, S. Sharma 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: energy
8! !INTERFACE:
9subroutine energy
10! !USES:
11use modmain
12use moddftu
13use modtest
14! !DESCRIPTION:
15! Computes the total energy and its individual contributions. The kinetic
16! energy is given by
17! $$ T_s=\sum_i n_i\epsilon_i-\int\rho({\bf r})[v_{\rm C}({\bf r})
18! +v_{\rm xc}({\bf r})]d{\bf r}-\int {\bf m}({\bf r})\cdot
19! ({\bf B}_{\rm xc}({\bf r})+{\bf B}_{\rm ext}({\bf r}))d{\bf r}, $$
20! where $n_i$ are the occupation numbers and $\epsilon_i$ are the eigenvalues
21! of both the core and valence states; $\rho$ is the density; ${\bf m}$ is the
22! magnetisation density; $v_{\rm C}$ is the Coulomb potential; $v_{\rm xc}$
23! and ${\bf B}_{\rm xc}$ are the exchange-correlation potential and magnetic
24! field, respectively; and ${\bf B}_{\rm ext}$ is the external magnetic field.
25! The Hartree, electron-nuclear and nuclear-nuclear electrostatic energies are
26! combined into the Coulomb energy:
27! \begin{align*}
28! E_{\rm C}&=E_{\rm H}+E_{\rm en}+E_{\rm nn} \\
29! &=\frac{1}{2}V_{\rm C}+E_{\rm Mad},
30! \end{align*}
31! where
32! $$ V_{\rm C}=\int\rho({\bf r})v_{\rm C}({\bf r})d{\bf r} $$
33! is the Coulomb potential energy. The Madelung energy is given by
34! $$ E_{\rm Mad}=\frac{1}{2}\sum_{\alpha}z_{\alpha}R_{\alpha}, $$
35! where
36! $$ R_{\alpha}=\lim_{r\rightarrow 0}\left(v^{\rm C}_{\alpha;00}(r)Y_{00}
37! +\frac{z_{\alpha}}{r}\right) $$
38! for atom $\alpha$, with $v^{\rm C}_{\alpha;00}$ being the $l=0$ component of
39! the spherical harmonic expansion of $v_{\rm C}$ in the muffin-tin, and
40! $z_{\alpha}$ is the nuclear charge. Using the nuclear-nuclear energy
41! determined at the start of the calculation, the electron-nuclear and Hartree
42! energies can be isolated with
43! $$ E_{\rm en}=2\left(E_{\rm Mad}-E_{\rm nn}\right) $$
44! and
45! $$ E_{\rm H}=\frac{1}{2}(E_{\rm C}-E_{\rm en}). $$
46! Finally, the total energy is
47! $$ E=T_s+E_{\rm C}+E_{\rm xc}, $$
48! where $E_{\rm xc}$ is obtained either by integrating the
49! exchange-correlation energy density, or in the case of exact exchange, the
50! explicit calculation of the Fock exchange integral. The energy from the
51! external magnetic fields in the muffin-tins, {\tt bfcmt}, is always removed
52! from the total since these fields are non-physical: their field lines do not
53! close. The energy of the physical external field, {\tt bfieldc}, is also not
54! included in the total because this field, like those in the muffin-tins, is
55! used for breaking spin symmetry and taken to be infintesimal. If this field
56! is intended to be finite, then the associated energy, {\tt engybext}, should
57! be added to the total by hand. See {\tt potxc}, {\tt exxengy} and related
58! subroutines.
59!
60! !REVISION HISTORY:
61! Created May 2003 (JKD)
62!EOP
63!BOC
64implicit none
65! local variables
66integer ik,ist,idm,jdm
67integer is,ia,ias,n2,idu
68real(8) cb,sm,w,f
69complex(8) z1
70! allocatable arrays
71real(8), allocatable :: rfmt(:,:)
72complex(8), allocatable :: evecsv(:,:),kmat(:,:),c(:,:)
73! external functions
74real(8), external :: rfinp
75complex(8), external :: zdotc
76! coupling constant of the external field (g_e/4c)
77cb=gfacte/(4.d0*solsc)
78!-----------------------------------------------!
79! exchange-correlation potential energy !
80!-----------------------------------------------!
82!-----------------------------------------------------!
83! exchange-correlation effective field energy !
84!-----------------------------------------------------!
85engybxc=0.d0
86do idm=1,ndmag
87 engybxc=engybxc+rfinp(magmt(:,:,idm),magir(:,idm),bxcmt(:,:,idm),bxcir(:,idm))
88end do
89!------------------------------------------!
90! external magnetic field energies !
91!------------------------------------------!
92engybext=0.d0
93do idm=1,ndmag
94 if (ncmag) then
95 jdm=idm
96 else
97 jdm=3
98 end if
99! energy of physical global field
100 engybext=engybext+cb*momtot(idm)*bfieldc(jdm)
101end do
102!----------------------------------!
103! Coulomb potential energy !
104!----------------------------------!
106!-------------------------!
107! Madelung energy !
108!-------------------------!
109engymad=0.d0
110do ias=1,natmtot
111 is=idxis(ias)
112 engymad=engymad+0.5d0*spzn(is)*(vclmt(1,ias)-vcln(1,is))*y00
113end do
114!---------------------------------------------!
115! electron-nuclear interaction energy !
116!---------------------------------------------!
117engyen=2.d0*(engymad-engynn)
118!------------------------!
119! Hartree energy !
120!------------------------!
121engyhar=0.5d0*(engyvcl-engyen)
122!------------------------!
123! Coulomb energy !
124!------------------------!
126!-------------------------!
127! exchange energy !
128!-------------------------!
129if ((xctype(1) < 0).or.(task == 5)) then
130! exact exchange for OEP-EXX or Hartree-Fock on last self-consistent loop
131 if (tlast) then
132 call exxengy
133! mix exact and DFT exchange energies for hybrid functionals
134 if (hybrid) then
137 end if
138 else
139 engyx=0.d0
140 end if
141else
142! exchange energy from the density
144end if
145!----------------------------!
146! correlation energy !
147!----------------------------!
148if ((task == 5).and.(.not.hybrid)) then
149! zero correlation energy for pure Hartree-Fock
150 engyc=0.d0
151else
152! correlation energy from the density
154end if
155!----------------------!
156! DFT+U energy !
157!----------------------!
158engydu=0.d0
159if (dftu /= 0) then
160 do idu=1,ndftu
161 is=isldu(1,idu)
162 do ia=1,natoms(is)
163 engydu=engydu+engyadu(ia,idu)
164 end do
165 end do
166end if
167!-------------------------------------!
168! sum of occupied eigenvalues !
169!-------------------------------------!
170! core eigenvalues
171evalsum=0.d0
172do ias=1,natmtot
173 is=idxis(ias)
174 do ist=1,nstsp(is)
175 if (spcore(ist,is)) evalsum=evalsum+occcr(ist,ias)*evalcr(ist,ias)
176 end do
177end do
178! valence eigenvalues
179do ik=1,nkpt
180 evalsum=evalsum+wkpt(ik)*sum(occsv(1:nstsv,ik)*evalsv(1:nstsv,ik))
181end do
182!------------------------!
183! kinetic energy !
184!------------------------!
185! core electron kinetic energy
186call energykncr
187! total electron kinetic energy
188if (task == 5) then
189! Hartree-Fock case
191! kinetic energy from valence states
192 allocate(evecsv(nstsv,nstsv),kmat(nstsv,nstsv),c(nstsv,nstsv))
193 do ik=1,nkpt
194 w=wkpt(ik)
195 call getevecsv(filext,ik,vkl(:,ik),evecsv)
196 call getkmat(ik,kmat)
197 call zgemm('N','N',nstsv,nstsv,nstsv,zone,kmat,nstsv,evecsv,nstsv,zzero,c, &
198 nstsv)
199 do ist=1,nstsv
200 z1=zdotc(nstsv,evecsv(:,ist),1,c(:,ist),1)
201 engykn=engykn+w*occsv(ist,ik)*z1%re
202 end do
203 end do
204 deallocate(evecsv,kmat,c)
205else
206! Kohn-Sham case
207 allocate(rfmt(npmtmax,natmtot))
208! remove magnetic field contribution
209 sm=0.d0
210 do idm=1,ndmag
211 do ias=1,natmtot
212 is=idxis(ias)
213 call rfsht(nrcmt(is),nrcmti(is),bsmt(:,ias,idm),rfmt(:,ias))
214 end do
215 call rfmtctof(rfmt)
216 sm=sm+rfinp(magmt(:,:,idm),magir(:,idm),rfmt,bsir(:,idm))
217 end do
218! remove fixed tensor moment potential matrix contribution
219 if (ftmtype /= 0) then
220 n2=(lmmaxdm*nspinor)**2
221 do ias=1,natmtot
222 z1=zdotc(n2,dmatmt(:,:,:,:,ias),1,vmftm(:,:,:,:,ias),1)
223 sm=sm+z1%re
224 end do
225 end if
227 deallocate(rfmt)
228end if
229! remove vector potential energy term if required
230if (tafield.and.tlast) then
231 engykn=engykn+(0.5d0/solsc)*dot_product(afieldc(:),jtot(:))
232end if
233! remove spin-dependent vector potential energy term if required
234if (tafsp.and.tlast) call energyafsp
235!-------------------------------!
236! entropic contribution !
237!-------------------------------!
238entrpy=0.d0
239engyts=0.d0
240! non-zero only for the Fermi-Dirac smearing function
241if (stype == 3) then
242 sm=0.d0
243 do ik=1,nkpt
244 w=wkpt(ik)
245 do ist=1,nstsv
246 f=occsv(ist,ik)/occmax
247 if ((f > 0.d0).and.(f < 1.d0)) then
248 sm=sm+w*(f*log(f)+(1.d0-f)*log(1.d0-f))
249 end if
250 end do
251 end do
252! entropy
254! contribution to free energy
256end if
257!----------------------!
258! total energy !
259!----------------------!
261! add the DFT+U correction if required
262if (dftu /= 0) engytot=engytot+engydu
263! write total energy to test file
264call writetest(0,'total energy',tol=1.d-5,rv=engytot)
265end subroutine
266!EOC
267
subroutine energy
Definition energy.f90:10
subroutine energyafsp
Definition energyafsp.f90:7
subroutine energykncr
Definition energykncr.f90:7
subroutine exxengy
Definition exxengy.f90:7
subroutine getevecsv(fext, ikp, vpl, evecsv)
Definition getevecsv.f90:7
subroutine getkmat(ik, kmat)
Definition getkmat.f90:7
integer ndftu
Definition moddftu.f90:38
integer dftu
Definition moddftu.f90:32
integer, parameter lmmaxdm
Definition moddftu.f90:14
real(8), dimension(:,:), allocatable engyadu
Definition moddftu.f90:44
integer, dimension(2, maxdftu) isldu
Definition moddftu.f90:40
integer ftmtype
Definition moddftu.f90:70
real(8) engydu
Definition moddftu.f90:46
complex(8), dimension(:,:,:,:,:), allocatable dmatmt
Definition moddftu.f90:16
complex(8), dimension(:,:,:,:,:), allocatable vmftm
Definition moddftu.f90:82
real(8), dimension(:,:), allocatable evalcr
Definition modmain.f90:934
real(8), parameter y00
Definition modmain.f90:1233
real(8), dimension(:), allocatable wkpt
Definition modmain.f90:475
real(8), parameter gfacte
Definition modmain.f90:1276
real(8) hybridc
Definition modmain.f90:1151
real(8), dimension(3) bfieldc
Definition modmain.f90:269
real(8), dimension(3) jtot
Definition modmain.f90:748
real(8), dimension(:,:,:), allocatable bxcmt
Definition modmain.f90:636
complex(8), parameter zzero
Definition modmain.f90:1238
logical ncmag
Definition modmain.f90:240
integer nspinor
Definition modmain.f90:267
real(8), dimension(:,:,:), pointer, contiguous magmt
Definition modmain.f90:616
integer, dimension(maxspecies) natoms
Definition modmain.f90:36
real(8), dimension(:), pointer, contiguous rhoir
Definition modmain.f90:614
character(256) filext
Definition modmain.f90:1300
logical, dimension(maxstsp, maxspecies) spcore
Definition modmain.f90:127
real(8), dimension(:,:), allocatable exmt
Definition modmain.f90:630
real(8), dimension(3) afieldc
Definition modmain.f90:325
real(8) engykn
Definition modmain.f90:950
real(8) engykncr
Definition modmain.f90:952
real(8), dimension(:,:), allocatable ecmt
Definition modmain.f90:632
real(8) engyhar
Definition modmain.f90:958
real(8) engynn
Definition modmain.f90:954
integer, dimension(maxspecies) nrcmt
Definition modmain.f90:173
real(8), dimension(:,:), allocatable bxcir
Definition modmain.f90:636
real(8) engycl
Definition modmain.f90:960
complex(8), parameter zone
Definition modmain.f90:1238
integer, dimension(3) xctype
Definition modmain.f90:588
real(8) engyvcl
Definition modmain.f90:962
real(8) entrpy
Definition modmain.f90:976
real(8), dimension(:), allocatable vxcir
Definition modmain.f90:634
integer, dimension(maxatoms *maxspecies) idxis
Definition modmain.f90:44
logical hybrid
Definition modmain.f90:1149
real(8) engybext
Definition modmain.f90:970
logical tafield
Definition modmain.f90:322
integer, dimension(maxspecies) nstsp
Definition modmain.f90:113
real(8) engyen
Definition modmain.f90:956
real(8) swidth
Definition modmain.f90:892
logical tafsp
Definition modmain.f90:329
integer nkpt
Definition modmain.f90:461
real(8) evalsum
Definition modmain.f90:948
real(8) engyvxc
Definition modmain.f90:966
integer natmtot
Definition modmain.f90:40
real(8), dimension(3) momtot
Definition modmain.f90:738
real(8) engyts
Definition modmain.f90:978
real(8), dimension(:), allocatable vclir
Definition modmain.f90:624
real(8), parameter kboltz
Definition modmain.f90:1262
logical tlast
Definition modmain.f90:1050
real(8) engyx
Definition modmain.f90:972
integer task
Definition modmain.f90:1298
integer nstsv
Definition modmain.f90:886
real(8), dimension(:,:), pointer, contiguous magir
Definition modmain.f90:616
real(8) engymad
Definition modmain.f90:964
integer npmtmax
Definition modmain.f90:216
real(8), dimension(:,:), allocatable bsir
Definition modmain.f90:658
real(8) solsc
Definition modmain.f90:1252
real(8), dimension(:,:), allocatable vclmt
Definition modmain.f90:624
real(8), dimension(:,:), allocatable vkl
Definition modmain.f90:471
real(8) occmax
Definition modmain.f90:898
real(8) engytot
Definition modmain.f90:980
real(8), dimension(:,:), allocatable vcln
Definition modmain.f90:97
real(8), dimension(:,:), allocatable vxcmt
Definition modmain.f90:634
real(8) engyc
Definition modmain.f90:974
real(8), dimension(:), allocatable exir
Definition modmain.f90:630
real(8), dimension(:,:,:), pointer, contiguous bsmt
Definition modmain.f90:656
integer stype
Definition modmain.f90:888
real(8), dimension(:,:), pointer, contiguous rhomt
Definition modmain.f90:614
integer, dimension(maxspecies) nrcmti
Definition modmain.f90:211
real(8), dimension(:,:), allocatable occsv
Definition modmain.f90:902
integer ndmag
Definition modmain.f90:238
real(8), dimension(:), allocatable ecir
Definition modmain.f90:632
real(8), dimension(:,:), allocatable evalsv
Definition modmain.f90:918
real(8) engybxc
Definition modmain.f90:968
real(8), dimension(maxspecies) spzn
Definition modmain.f90:80
real(8), dimension(:,:), allocatable occcr
Definition modmain.f90:932
subroutine writetest(id, descr, nv, iv, iva, tol, rv, rva, zv, zva)
Definition modtest.f90:16
real(8) function rfinp(rfmt1, rfir1, rfmt2, rfir2)
Definition rfinp.f90:10
subroutine rfmtctof(rfmt)
Definition rfmtctof.f90:10
subroutine rfsht(nr, nri, rfmt1, rfmt2)
Definition rfsht.f90:7