The Elk Code
hartfock.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2007 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 subroutine hartfock
7 use modmain
8 use modmpi
9 use modomp
10 implicit none
11 ! local variables
12 integer ik,lp,nthd
13 real(8) etp,de
14 character(64) str
15 ! allocatable arrays
16 real(8), allocatable :: vmt(:,:),vir(:),bmt(:,:,:),bir(:,:)
17 complex(8), allocatable :: evecsv(:,:)
18 ! initialise universal variables
19 call init0
20 call init1
21 call init2
22 ! read the charge density from file
23 call readstate
24 ! Fourier transform Kohn-Sham potential to G-space
25 call genvsig
26 ! generate the core wavefunctions and densities
27 call gencore
28 ! find the new linearisation energies
29 call linengy
30 ! generate the APW and local-orbital radial functions and integrals
31 call genapwlofr
32 ! generate the spin-orbit coupling radial functions
33 call gensocfr
34 ! generate the first- and second-variational eigenvectors and eigenvalues
35 call genevfsv
36 ! find the occupation numbers and Fermi energy
37 call occupy
38 ! generate the kinetic matrix elements in the first-variational basis
39 call genkmat(.true.,.true.)
40 ! allocate local arrays
41 allocate(vmt(npcmtmax,natmtot),vir(ngtc))
42 if (hybrid.and.spinpol) then
43  allocate(bmt(npcmtmax,natmtot,ndmag),bir(ngtc,ndmag))
44 else
45  allocate(bmt(1,1,1),bir(1,1))
46 end if
47 ! only the MPI master process should write files
48 if (mp_mpi) then
49 ! open HF_INFO.OUT file
50  open(60,file='HF_INFO'//trim(filext),form='FORMATTED')
51 ! open TOTENERGY.OUT
52  open(61,file='TOTENERGY'//trim(filext),form='FORMATTED')
53 ! open FERMIDOS.OUT
54  open(62,file='FERMIDOS'//trim(filext),form='FORMATTED')
55 ! open MOMENT.OUT if required
56  if (spinpol) open(63,file='MOMENT'//trim(filext),form='FORMATTED')
57 ! open GAP.OUT
58  open(64,file='GAP'//trim(filext),form='FORMATTED')
59 ! open DTOTENERGY.OUT
60  open(66,file='DTOTENERGY'//trim(filext),form='FORMATTED')
61 ! open MOMENTM.OUT
62  if (spinpol) open(68,file='MOMENTM'//trim(filext),form='FORMATTED')
63 ! write out general information to HF_INFO.OUT
64  call writeinfo(60)
65 end if
66 ! set last self-consistent loop flag
67 tlast=.false.
68 etp=0.d0
69 ! begin the self-consistent loop
70 if (mp_mpi) then
71  call writebox(60,"Self-consistent loop started")
72 end if
73 do iscl=1,maxscl
74  if (mp_mpi) then
75  write(str,'("Loop number : ",I0)') iscl
76  call writebox(60,trim(str))
77  flush(60)
78  write(*,'("Info(hartfock): self-consistent loop number : ",I4)') iscl
79  end if
80  if (iscl >= maxscl) then
81  if (mp_mpi) then
82  write(60,*)
83  write(60,'("Reached self-consistent loops maximum")')
84  end if
85  tlast=.true.
86  end if
87 ! reset the OpenMP thread variables
88  call omp_reset
89 ! compute the Hartree-Fock local potentials
90  call hflocal(vmt,vir,bmt,bir)
91 ! synchronise MPI processes
92  call mpi_barrier(mpicom,ierror)
93  call holdthd(nkpt/np_mpi,nthd)
94 !$OMP PARALLEL DEFAULT(SHARED) &
95 !$OMP PRIVATE(evecsv) &
96 !$OMP NUM_THREADS(nthd)
97  allocate(evecsv(nstsv,nstsv))
98 !$OMP DO SCHEDULE(DYNAMIC)
99  do ik=1,nkpt
100 ! distribute among MPI processes
101  if (mod(ik-1,np_mpi) /= lp_mpi) cycle
102  call getevecsv(filext,ik,vkl(:,ik),evecsv)
103 ! solve the Hartree-Fock eigenvalue equation
104  call eveqnhf(ik,vmt,vir,bmt,bir,evecsv)
105 ! write the eigenvalues/vectors to file
106  call putevalsv(filext,ik,evalsv(:,ik))
107  call putevecsv(filext,ik,evecsv)
108  end do
109 !$OMP END DO
110  deallocate(evecsv)
111 !$OMP END PARALLEL
112  call freethd(nthd)
113 ! synchronise MPI processes
114  call mpi_barrier(mpicom,ierror)
115 ! broadcast eigenvalue array to every process
116  do ik=1,nkpt
117  lp=mod(ik-1,np_mpi)
118  call mpi_bcast(evalsv(:,ik),nstsv,mpi_double_precision,lp,mpicom,ierror)
119  end do
120 ! find the occupation numbers and Fermi energy
121  call occupy
122  if (mp_mpi) then
123 ! write the occupation numbers to file
124  do ik=1,nkpt
125  call putoccsv(filext,ik,occsv(:,ik))
126  end do
127 ! write out the eigenvalues and occupation numbers
128  call writeeval
129 ! write the Fermi energy to file
130  call writeefm
131  end if
132 ! generate the density and magnetisation
133  call rhomag
134 ! compute the energy components
135  call energy
136  if (mp_mpi) then
137 ! output energy components
138  call writeengy(60)
139  write(60,*)
140  write(60,'("Density of states at Fermi energy : ",G18.10)') fermidos
141  write(60,'(" (states/Hartree/unit cell)")')
142  write(60,*)
143  write(60,'("Estimated indirect band gap : ",G18.10)') bandgap(1)
144  write(60,'(" from k-point ",I6," to k-point ",I6)') ikgap(1),ikgap(2)
145  write(60,'("Estimated direct band gap : ",G18.10)') bandgap(2)
146  write(60,'(" at k-point ",I6)') ikgap(3)
147 ! write total energy to TOTENERGY.OUT
148  write(61,'(G24.14)') engytot
149  flush(61)
150 ! write DOS at Fermi energy to FERMIDOS.OUT
151  write(62,'(G18.10)') fermidos
152  flush(62)
153 ! output charges and moments
154  call writechg(60)
155  if (spinpol) then
156  call writemom(60)
157 ! write total moment to MOMENT.OUT
158  write(63,'(3G18.10)') momtot(1:ndmag)
159  flush(63)
160 ! write total moment magnitude to MOMENTM.OUT
161  write(68,'(G18.10)') momtotm
162  flush(68)
163  end if
164 ! write estimated Hartree-Fock indirect band gap
165  write(64,'(G24.14)') bandgap(1)
166  flush(64)
167  end if
168  if (tlast) goto 10
169 ! compute the change in total energy and check for convergence
170  if (iscl >= 2) then
171  de=abs(engytot-etp)
172  if (mp_mpi) then
173  write(60,*)
174  write(60,'("Absolute change in total energy (target) : ",G18.10," (",&
175  &G18.10,")")') de,epsengy
176  end if
177  if (de < epsengy) then
178  if (mp_mpi) then
179  write(60,*)
180  write(60,'("Energy convergence target achieved")')
181  end if
182  tlast=.true.
183  end if
184  if (mp_mpi) then
185  write(66,'(G18.10)') de
186  flush(66)
187  end if
188  end if
189  etp=engytot
190 ! check for STOP file
191  call checkstop
192  if (tstop) tlast=.true.
193 ! broadcast tlast from master process to all other processes
194  call mpi_bcast(tlast,1,mpi_logical,0,mpicom,ierror)
195 end do
196 10 continue
197 if (mp_mpi) then
198  call writebox(60,"Self-consistent loop stopped")
199  if (maxscl > 1) then
200  call writestate
201  write(60,*)
202  write(60,'("Wrote STATE.OUT")')
203  end if
204 end if
205 !-----------------------!
206 ! compute forces !
207 !-----------------------!
208 if (tforce) then
209  call force
210 ! output forces to HF_INFO.OUT
211  if (mp_mpi) call writeforces(60)
212 end if
213 if (mp_mpi) then
214 ! close the HF_INFO.OUT file
215  close(60)
216 ! close the TOTENERGY.OUT file
217  close(61)
218 ! close the FERMIDOS.OUT file
219  close(62)
220 ! close the MOMENT.OUT and MOMENTM.OUT files
221  if (spinpol) then
222  close(63); close(68)
223  end if
224 ! close the GAP.OUT file
225  close(64)
226 ! close the DTOTENERGY.OUT file
227  close(66)
228 end if
229 deallocate(vmt,vir,bmt,bir)
230 end subroutine
231 
subroutine genevfsv
Definition: genevfsv.f90:7
subroutine getevecsv(fext, ikp, vpl, evecsv)
Definition: getevecsv.f90:7
real(8), dimension(3) momtot
Definition: modmain.f90:738
integer npcmtmax
Definition: modmain.f90:216
integer, dimension(3) ikgap
Definition: modmain.f90:917
character(256) filext
Definition: modmain.f90:1301
real(8), dimension(:,:), allocatable evalsv
Definition: modmain.f90:921
logical mp_mpi
Definition: modmpi.f90:17
subroutine occupy
Definition: occupy.f90:10
integer ngtc
Definition: modmain.f90:392
subroutine putevalsv(fext, ik, evalsv_)
Definition: putevalsv.f90:7
logical spinpol
Definition: modmain.f90:228
logical hybrid
Definition: modmain.f90:1152
integer nkpt
Definition: modmain.f90:461
integer ndmag
Definition: modmain.f90:238
real(8) momtotm
Definition: modmain.f90:740
subroutine writeinfo(fnum)
Definition: writeinfo.f90:10
integer iscl
Definition: modmain.f90:1051
subroutine gencore
Definition: gencore.f90:10
Definition: modomp.f90:6
logical tstop
Definition: modmain.f90:1055
real(8) fermidos
Definition: modmain.f90:913
subroutine writestate
Definition: writestate.f90:10
subroutine rhomag
Definition: rhomag.f90:7
subroutine genvsig
Definition: genvsig.f90:10
subroutine genapwlofr
Definition: genapwlofr.f90:7
subroutine checkstop
Definition: checkstop.f90:7
subroutine gensocfr
Definition: gensocfr.f90:7
integer np_mpi
Definition: modmpi.f90:13
subroutine hartfock
Definition: hartfock.f90:7
subroutine linengy
Definition: linengy.f90:10
logical tforce
Definition: modmain.f90:989
integer nstsv
Definition: modmain.f90:889
logical tlast
Definition: modmain.f90:1053
subroutine energy
Definition: energy.f90:10
real(8) engytot
Definition: modmain.f90:983
subroutine init2
Definition: init2.f90:7
real(8), dimension(:,:), allocatable occsv
Definition: modmain.f90:905
subroutine init1
Definition: init1.f90:10
real(8), dimension(:,:), allocatable vkl
Definition: modmain.f90:471
subroutine hflocal(vmt, vir, bmt, bir)
Definition: hflocal.f90:7
Definition: modmpi.f90:6
subroutine writechg(fnum)
Definition: writechg.f90:7
subroutine force
Definition: force.f90:10
subroutine writebox(fnum, str)
Definition: writebox.f90:7
subroutine readstate
Definition: readstate.f90:10
subroutine omp_reset
Definition: modomp.f90:71
subroutine writeforces(fnum)
Definition: writeforces.f90:7
integer lp_mpi
Definition: modmpi.f90:15
subroutine freethd(nthd)
Definition: modomp.f90:106
subroutine holdthd(nloop, nthd)
Definition: modomp.f90:78
subroutine putevecsv(fext, ik, evecsv)
Definition: putevecsv.f90:7
subroutine genkmat(tfv, tvclcr)
Definition: genkmat.f90:10
subroutine putoccsv(fext, ik, occsvp)
Definition: putoccsv.f90:7
subroutine init0
Definition: init0.f90:10
integer natmtot
Definition: modmain.f90:40
subroutine writeeval
Definition: writeeval.f90:10
real(8) epsengy
Definition: modmain.f90:1063
real(8), dimension(2) bandgap
Definition: modmain.f90:915
subroutine writemom(fnum)
Definition: writemom.f90:7
integer maxscl
Definition: modmain.f90:1049
subroutine eveqnhf(ikp, vmt, vir, bmt, bir, evecsvp)
Definition: eveqnhf.f90:7
integer mpicom
Definition: modmpi.f90:11
subroutine writeefm
Definition: writeefm.f90:10
integer ierror
Definition: modmpi.f90:19
subroutine writeengy(fnum)
Definition: writeengy.f90:7