The Elk Code
 
Loading...
Searching...
No Matches
gndstate.f90
Go to the documentation of this file.
1
2! Copyright (C) 2002-2013 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: gndstate
8! !INTERFACE:
9subroutine gndstate
10! !USES:
11use modmain
12use moddftu
13use modxcifc
14use modulr
15use modgw
16use modmpi
17use modomp
18use modvars
19use modramdisk
20! !DESCRIPTION:
21! Computes the self-consistent Kohn-Sham ground-state. General information is
22! written to the file {\tt INFO.OUT}. First- and second-variational
23! eigenvalues, eigenvectors and occupation numbers are written to the
24! unformatted files {\tt EVALFV.OUT}, {\tt EVALSV.OUT}, {\tt EVECFV.OUT},
25! {\tt EVECSV.OUT} and {\tt OCCSV.OUT}. The density, magnetisation, Kohn-Sham
26! potential and magnetic field are written to {\tt STATE.OUT}.
27!
28! !REVISION HISTORY:
29! Created October 2002 (JKD)
30! Added MPI, August 2010 (JKD)
31!EOP
32!BOC
33implicit none
34! local variables
35logical twrite
36integer ik,iscl0,nmix,nwork
37real(8) dv,etp,de,timetot
38character(64) str
39! allocatable arrays
40real(8), allocatable :: work(:)
41! initialise global variables
42call init0
43! initialise k- and G+k-vector-dependent variables
44call init1
45! initialise q-vector-dependent variables if required
46if ((xctype(1) < 0).or.ksgwrho) call init2
47! initialise GW variables if required
48if (ksgwrho) call init3
50if (task == 0) trdstate=.false.
51if (task == 1) trdstate=.true.
52! only the MPI master process should write files
53if (mp_mpi) then
54! write the real and reciprocal lattice vectors to file
55 call writelat
56! write symmetry matrices to file
57 call writesym
58! output the k-point set to file
59 call writekpts
60! write lattice vectors and atomic positions to file
61 open(50,file='GEOMETRY'//trim(filext),form='FORMATTED')
62 call writegeom(50)
63 close(50)
64! write interatomic distances to file
65 open(50,file='IADIST'//trim(filext),form='FORMATTED')
66 call writeiad(50)
67 close(50)
68! open INFO.OUT file
69 open(60,file='INFO'//trim(filext),form='FORMATTED')
70! write out general information to INFO.OUT
71 call writeinfo(60)
72 write(60,*)
73! open TOTENERGY.OUT
74 open(61,file='TOTENERGY'//trim(filext),form='FORMATTED')
75! open FERMIDOS.OUT
76 open(62,file='FERMIDOS'//trim(filext),form='FORMATTED')
77! open MOMENT.OUT if required
78 if (spinpol) open(63,file='MOMENT'//trim(filext),form='FORMATTED')
79! open GAP.OUT
80 open(64,file='GAP'//trim(filext),form='FORMATTED')
81! open RMSDVS.OUT
82 open(65,file='RMSDVS'//trim(filext),form='FORMATTED')
83! open DTOTENERGY.OUT
84 open(66,file='DTOTENERGY'//trim(filext),form='FORMATTED')
85! open MOMENTM.OUT
86 if (spinpol) open(68,file='MOMENTM'//trim(filext),form='FORMATTED')
87! open RESIDUAL.OUT
88 if (xctype(1) < 0) open(69,file='RESIDUAL'//trim(filext),form='FORMATTED')
89end if
90iscl=0
91if (trdstate) then
92! read the Kohn-Sham potential and fields from file
93 call readstate
94 if (mp_mpi) then
95 write(60,'("Potential read in from STATE.OUT")')
96 end if
97else
98! initialise the density and magnetisation from atomic data
99 call rhoinit
100 if (spinpol) call maginit
101! compute the Kohn-Sham potential and magnetic field
102 call potks(.true.)
103 if (mp_mpi) then
104 write(60,'("Kohn-Sham potential initialised from atomic data")')
105 end if
106end if
107if (mp_mpi) flush(60)
108call genvsig
109! size of mixing vector
110nmix=size(vmixer)
111! determine the size of the mixer work array
112nwork=-1
113call mixerifc(mixtype,nmix,vmixer,dv,nwork,vmixer)
114allocate(work(nwork))
115! initialise the mixer
116iscl=0
117call mixerifc(mixtype,nmix,vmixer,dv,nwork,work)
118if (mixsave.and.trdstate) then
119! read in starting loop and mixer work array from file if required
120 call readmix(iscl0,nwork,work)
121 iscl0=min(iscl0,mixsdb)
122else
123! default starting loop
124 iscl0=1
125end if
126! set the stop signal to .false.
127tstop=.false.
128! set last self-consistent loop flag
129tlast=.false.
130etp=0.d0
131! begin the self-consistent loop
132if (mp_mpi) then
133 call writebox(60,"Self-consistent loop started")
134end if
135do iscl=iscl0,maxscl
136 if (mp_mpi) then
137 write(str,'("Loop number : ",I0)') iscl
138 call writebox(60,trim(str))
139 end if
140 if (iscl >= maxscl) then
141 if (mp_mpi) then
142 write(60,*)
143 write(60,'("Reached self-consistent loops maximum")')
144 end if
145 if (maxscl > 1) then
146 write(*,*)
147 write(*,'("Warning(gndstate): failed to reach self-consistency after ", &
148 &I4," loops")') iscl
149 end if
150 tlast=.true.
151 end if
152 if (mp_mpi) flush(60)
153! always write the eigenvectors to disk on the last loop
154 if (tlast) wrtdsk=.true.
155! generate the core wavefunctions and densities
156 call gencore
157! find the new linearisation energies
158 call linengy
159! write out the linearisation energies
160 if (mp_mpi) call writelinen
161! generate the APW and local-orbital radial functions and integrals
162 call genapwlofr
163! generate the spin-orbit coupling radial functions
164 call gensocfr
165! generate the first- and second-variational eigenvectors and eigenvalues
166 call genevfsv
167! find the occupation numbers and Fermi energy
168 call occupy
169 if (mp_mpi) then
170 if (autoswidth) then
171 write(60,*)
172 write(60,'("New smearing width : ",G18.10)') swidth
173 end if
174! write the occupation numbers to file
175 do ik=1,nkpt
176 call putoccsv(filext,ik,occsv(:,ik))
177 end do
178! write eigenvalues to file
179 call writeeval
180! write the Fermi energy to file
181 call writefermi
182 end if
183! synchronise MPI processes
184 call mpi_barrier(mpicom,ierror)
185! generate the density and magnetisation
186 if (ksgwrho) then
187! density calculated from the GW approximation
188 call gwrhomag
189 else
190! density calculated directly from the Kohn-Sham states
191 call rhomag
192 end if
193! DFT+U or fixed tensor moment calculation
194 if ((dftu /= 0).or.(ftmtype /= 0)) then
195! generate the muffin-tin density matrix used for computing the potential matrix
196 call gendmatmt
197! write the FTM tensor moments to file
198 if (ftmtype /= 0) call writeftm
199! generate the DFT+U or FTM muffin-tin potential matrices
200 call genvmatmt
201 end if
202 if (dftu /= 0) then
203 if (mp_mpi) then
204! write the DFT+U matrices to file
205 call writedftu
206! calculate and write tensor moments to file
207 if (tmwrite) call writetm3
208 end if
209 end if
210! compute the Kohn-Sham potential and magnetic field before potential mixing
211 if (.not.mixrho) call potks(.true.)
212! mix the old density/magnetisation or potential/field with the new
213 call mixerifc(mixtype,nmix,vmixer,dv,nwork,work)
214! compute the Kohn-Sham potential and magnetic field after density mixing
215 if (mixrho) call potks(.true.)
216! calculate and add the fixed spin moment effective field (after mixing)
217 call bfieldfsm
218 call addbfsm
219! Fourier transform Kohn-Sham potential to G-space
220 call genvsig
221! reduce the external magnetic fields if required
222 if (reducebf < 1.d0) then
224 bfcmt(:,:,:)=bfcmt(:,:,:)*reducebf
225 end if
226! compute the paramagnetic current density and total current if required
227 if (tjr.and.tlast) then
228 call genjpr
229 call genjtot
230 end if
231! compute the energy components
232 call energy
233 if (mp_mpi) then
234! output energy components
235 call writeengy(60)
236 write(60,*)
237 write(60,'("Density of states at Fermi energy : ",G18.10)') fermidos
238 write(60,'(" (states/Hartree/unit cell)")')
239 write(60,*)
240 write(60,'("Estimated indirect band gap : ",G18.10)') bandgap(1)
241 write(60,'(" from k-point ",I6," to k-point ",I6)') ikgap(1),ikgap(2)
242 write(60,'("Estimated direct band gap : ",G18.10)') bandgap(2)
243 write(60,'(" at k-point ",I6)') ikgap(3)
244! write total energy to TOTENERGY.OUT
245 write(61,'(G24.14)') engytot
246 flush(61)
247! write DOS at Fermi energy to FERMIDOS.OUT
248 write(62,'(G18.10)') fermidos
249 flush(62)
250! output charges and moments
251 call writechg(60)
252 if (spinpol) then
253 call writemom(60)
254! write total moment to MOMENT.OUT
255 write(63,'(3G18.10)') momtot(1:ndmag)
256 flush(63)
257! write total moment magnitude to MOMENTM.OUT
258 write(68,'(G18.10)') momtotm
259 flush(68)
260 end if
261! write estimated Kohn-Sham indirect band gap
262 write(64,'(G24.14)') bandgap(1)
263 flush(64)
264! output effective fields for fixed spin moment calculations
265 if (fsmtype /= 0) call writefsm(60)
266! write the average electric field in each muffin-tin
267 if (tefield) call writeefield(60)
268! write the Tran-Blaha functional constant
269 if (xctype(2) == xc_mgga_x_tb09) then
270 write(60,*)
271 write(60,'("Tran-Blaha ''09 constant c : ",G18.10)') c_tb09
272 end if
273! check for existence of the WRITE file
274 call checkwrite(twrite)
275! check self-consistent loop number modulo nwrite
276 if (nwrite >= 1) then
277 if (mod(iscl,nwrite) == 0) twrite=.true.
278 end if
279! write STATE.OUT and mixer work array if required
280 if (twrite) then
281 call writestate
282 write(60,*)
283 write(60,'("Wrote STATE.OUT")')
284 if (mixsave) call writemix(nwork,work)
285 end if
286! write OEP step size and residual
287 if (xctype(1) < 0) then
288 write(60,*)
289 write(60,'("OEP iterative solver step size : ",G18.10)') tauoep
290 write(60,'("Magnitude of OEP residual : ",G18.10)') resoep
291 write(69,'(G18.10)') resoep
292 flush(69)
293 end if
294 end if
295! exit self-consistent loop if required
296 if (tlast) goto 10
297! check for convergence
298 if (iscl >= iscl0+1) then
299 de=abs(engytot-etp)
300 if (mp_mpi) then
301 write(60,*)
302 write(60,'("RMS change in Kohn-Sham potential (target) : ",G18.10," (",&
303 &G18.10,")")') dv,epspot
304 write(65,'(G18.10)') dv
305 flush(65)
306 write(60,'("Absolute change in total energy (target) : ",G18.10," (",&
307 &G18.10,")")') de,epsengy
308 write(66,'(G18.10)') de
309 flush(66)
310 if ((dv < epspot).and.(de < epsengy)) then
311 write(60,*)
312 write(60,'("Convergence targets achieved")')
313 tlast=.true.
314 end if
315 end if
316 end if
317! average the current and previous total energies and store
318 if (iscl == iscl0) etp=engytot
319 etp=0.75d0*engytot+0.25d0*etp
320! check for STOP file
321 call checkstop
322 if (tstop) tlast=.true.
323! broadcast tlast from master process to all other processes
324 call mpi_bcast(tlast,1,mpi_logical,0,mpicom,ierror)
325! output the current total CPU time
327 if (mp_mpi) then
328 write(60,*)
329 write(60,'("Time (CPU seconds) : ",F12.2)') timetot
330 end if
331! end the self-consistent loop
332end do
33310 continue
334! synchronise MPI processes
335call mpi_barrier(mpicom,ierror)
336if (mp_mpi) then
337 call writebox(60,"Self-consistent loop stopped")
338! write STATE.OUT and mixer work array only if maxscl > 1
339 if (maxscl > 1) then
340 call writestate
341 write(60,*)
342 write(60,'("Wrote STATE.OUT")')
343 if (mixsave) call writemix(nwork,work)
344 end if
345end if
346! compute forces if required
347if (tforce) then
348 call force
349! output forces to INFO.OUT
350 if (mp_mpi) call writeforces(60)
351end if
352! output the paramagnetic current
353if (tjr.and.mp_mpi) then
354 write(60,*)
355 write(60,'("Total paramagnetic current per unit cell")')
356 write(60,'(3G18.10)') jtot
357 write(60,'(" magnitude : ",G18.10)') jtotm
358end if
359! total time used
361if (mp_mpi) then
362! output timing information
363 write(60,*)
364 write(60,'("Timings (CPU seconds) :")')
365 write(60,'(" initialisation",T40,": ",F12.2)') timeinit
366 write(60,'(" Hamiltonian and overlap matrix set up",T40,": ",F12.2)') timemat
367 write(60,'(" first-variational eigenvalue equation",T40,": ",F12.2)') timefv
368 if (tevecsv) then
369 write(60,'(" second-variational calculation",T40,": ",F12.2)') timesv
370 end if
371 write(60,'(" charge density calculation",T40,": ",F12.2)') timerho
372 write(60,'(" potential calculation",T40,": ",F12.2)') timepot
373 if (tforce) then
374 write(60,'(" force calculation",T40,": ",F12.2)') timefor
375 end if
376 write(60,'(" total",T40,": ",F12.2)') timetot
377! close the INFO.OUT file
378 close(60)
379! close the TOTENERGY.OUT file
380 close(61)
381! close the FERMIDOS.OUT file
382 close(62)
383! close the MOMENT.OUT and MOMENTM.OUT files
384 if (spinpol) then
385 close(63); close(68)
386 end if
387! close the GAP.OUT file
388 close(64)
389! close the RMSDVS.OUT file
390 close(65)
391! close the DTOTENERGY.OUT file
392 close(66)
393! close the RESIDUAL.OUT file
394 if (xctype(1) < 0) close(69)
395! write to VARIABLES.OUT if required
396 if (wrtvars) call writegsvars
397end if
398deallocate(work)
400! synchronise MPI processes
401call mpi_barrier(mpicom,ierror)
402end subroutine
403!EOC
404
subroutine addbfsm
Definition addbfsm.f90:7
subroutine bfieldfsm
Definition bfieldfsm.f90:10
subroutine checkstop
Definition checkstop.f90:7
subroutine checkwrite(twrite)
Definition checkwrite.f90:7
subroutine energy
Definition energy.f90:10
subroutine force
Definition force.f90:10
subroutine genapwlofr
Definition genapwlofr.f90:7
subroutine gencore
Definition gencore.f90:10
subroutine gendmatmt
Definition gendmatmt.f90:7
subroutine genevfsv
Definition genevfsv.f90:7
subroutine genjpr
Definition genjpr.f90:7
subroutine genjtot
Definition genjtot.f90:7
subroutine gensocfr
Definition gensocfr.f90:7
subroutine genvmatmt
Definition genvmatmt.f90:10
subroutine genvsig
Definition genvsig.f90:10
subroutine gndstate
Definition gndstate.f90:10
subroutine gwrhomag
Definition gwrhomag.f90:7
subroutine init0
Definition init0.f90:10
subroutine init1
Definition init1.f90:10
subroutine init2
Definition init2.f90:7
subroutine init3
Definition init3.f90:7
subroutine linengy
Definition linengy.f90:10
subroutine maginit
Definition maginit.f90:7
subroutine mixerifc(mtype, n, v, dv, nwork, work)
Definition mixerifc.f90:7
logical tmwrite
Definition moddftu.f90:66
integer dftu
Definition moddftu.f90:32
integer ftmtype
Definition moddftu.f90:70
Definition modgw.f90:6
logical ksgwrho
Definition modgw.f90:38
real(8) resoep
Definition modmain.f90:1147
real(8) epsengy
Definition modmain.f90:1060
real(8), dimension(3) bfieldc
Definition modmain.f90:269
real(8), dimension(3) jtot
Definition modmain.f90:748
real(8) epspot
Definition modmain.f90:1058
integer nwrite
Definition modmain.f90:1056
logical autoswidth
Definition modmain.f90:894
logical mixrho
Definition modmain.f90:687
character(256) filext
Definition modmain.f90:1300
real(8) timepot
Definition modmain.f90:1222
real(8), dimension(3, maxatoms, maxspecies) bfcmt
Definition modmain.f90:273
logical spinpol
Definition modmain.f90:228
integer fsmtype
Definition modmain.f90:251
real(8) timefor
Definition modmain.f90:1224
integer, dimension(3) ikgap
Definition modmain.f90:914
integer, dimension(3) xctype
Definition modmain.f90:588
real(8), dimension(2) bandgap
Definition modmain.f90:912
integer mixsdb
Definition modmain.f90:704
real(8) jtotm
Definition modmain.f90:748
logical tjr
Definition modmain.f90:620
real(8) timerho
Definition modmain.f90:1220
integer mixtype
Definition modmain.f90:695
real(8) timemat
Definition modmain.f90:1214
real(8) timefv
Definition modmain.f90:1216
real(8) swidth
Definition modmain.f90:892
logical tefield
Definition modmain.f90:310
logical tstop
Definition modmain.f90:1052
integer nkpt
Definition modmain.f90:461
real(8), dimension(3) momtot
Definition modmain.f90:738
real(8) fermidos
Definition modmain.f90:910
real(8) tauoep
Definition modmain.f90:1141
logical trdstate
Definition modmain.f90:682
logical tlast
Definition modmain.f90:1050
integer task
Definition modmain.f90:1298
logical mixsave
Definition modmain.f90:700
real(8) c_tb09
Definition modmain.f90:678
real(8) momtotm
Definition modmain.f90:740
integer maxscl
Definition modmain.f90:1046
real(8) timeinit
Definition modmain.f90:1212
real(8) reducebf
Definition modmain.f90:279
real(8) engytot
Definition modmain.f90:980
logical tforce
Definition modmain.f90:986
real(8), dimension(:,:), allocatable occsv
Definition modmain.f90:902
real(8) timesv
Definition modmain.f90:1218
integer iscl
Definition modmain.f90:1048
integer ndmag
Definition modmain.f90:238
real(8), dimension(:), pointer, contiguous vmixer
Definition modmain.f90:689
logical tevecsv
Definition modmain.f90:920
integer ierror
Definition modmpi.f90:19
integer mpicom
Definition modmpi.f90:11
logical mp_mpi
Definition modmpi.f90:17
type(file_t), dimension(:), allocatable, private file
logical wrtdsk0
logical wrtdsk
logical wrtvars
Definition modvars.f90:9
subroutine occupy
Definition occupy.f90:10
subroutine potks(txc)
Definition potks.f90:10
subroutine putoccsv(fext, ik, occsvp)
Definition putoccsv.f90:7
subroutine readmix(iscl0, nwork, work)
Definition readmix.f90:7
subroutine readstate
Definition readstate.f90:10
subroutine rhoinit
Definition rhoinit.f90:10
subroutine rhomag
Definition rhomag.f90:7
subroutine writebox(fnum, str)
Definition writebox.f90:7
subroutine writechg(fnum)
Definition writechg.f90:7
subroutine writedftu
Definition writedftu.f90:7
subroutine writeefield(fnum)
subroutine writeengy(fnum)
Definition writeengy.f90:7
subroutine writeeval
Definition writeeval.f90:10
subroutine writefermi
subroutine writeforces(fnum)
subroutine writefsm(fnum)
Definition writefsm.f90:7
subroutine writeftm
Definition writeftm.f90:7
subroutine writegeom(fnum)
Definition writegeom.f90:10
subroutine writegsvars
subroutine writeiad(fnum)
Definition writeiad.f90:10
subroutine writeinfo(fnum)
Definition writeinfo.f90:10
subroutine writekpts
Definition writekpts.f90:10
subroutine writelat
Definition writelat.f90:7
subroutine writelinen
subroutine writemix(nwork, work)
Definition writemix.f90:7
subroutine writemom(fnum)
Definition writemom.f90:7
subroutine writestate
subroutine writesym
Definition writesym.f90:10
subroutine writetm3
Definition writetm3.f90:10