2 ! Copyright (C) 2002-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.
13 ! Computes the self-consistent Kohn-Sham ground-state. General information is
14 ! written to the file {\tt INFO.OUT}. First- and second-variational
15 ! eigenvalues, eigenvectors and occupancies are written to the unformatted
16 ! files {\tt EVALFV.OUT}, {\tt EVALSV.OUT}, {\tt EVECFV.OUT}, {\tt EVECSV.OUT}
17 ! and {\tt OCCSV.OUT}.
20 ! Created October 2002 (JKD)
30 real(8), allocatable
:: v(:)
31 real(8), allocatable
:: work(:)
32 real(8), allocatable
:: evalfv(:,:)
33 complex(8), allocatable
:: evecfv(:,:,:)
34 complex(8), allocatable
:: evecsv(:,:)
35 ! require forces for structural optimisation
36 if ((task
.eq
.2).or
.(task
.eq
.3)) tforce
=.true
.
37 ! initialise global variables
40 ! initialise OEP variables if required
41 if (xctype
.lt
.0) call init2
42 ! write the real and reciprocal lattice vectors to file
44 ! write interatomic distances to file
45 call writeiad(.false
.)
46 ! write symmetry matrices to file
48 ! output the k-point set to file
50 ! write lattice vectors and atomic positions to file
51 call writegeom(.false
.)
53 open(60,file
='INFO'//trim(filext
),action
='WRITE',form
='FORMATTED')
55 open(61,file
='TOTENERGY'//trim(filext
),action
='WRITE',form
='FORMATTED')
57 open(62,file
='FERMIDOS'//trim(filext
),action
='WRITE',form
='FORMATTED')
58 ! open MOMENT.OUT if required
59 if (spinpol
) open(63,file
='MOMENT'//trim(filext
),action
='WRITE', &
61 ! open FORCEMAX.OUT if required
62 if (tforce
) open(64,file
='FORCEMAX'//trim(filext
),action
='WRITE', &
65 open(65,file
='RMSDVEFF'//trim(filext
),action
='WRITE',form
='FORMATTED')
66 ! write out general information to INFO.OUT
68 ! initialise or read the charge density and potentials from file
71 if ((task
.eq
.1).or
.(task
.eq
.3)) then
73 write(60,'("Potential read in from STATE.OUT")')
74 else if (task
.eq
.200) then
76 write(60,'("Supercell potential constructed from STATE.OUT")')
81 write(60,'("Density and potential initialised from atomic data")')
84 ! size of mixing vector
85 n
=lmmaxvr
*nrmtmax
*natmtot
+ngrtot
86 if (spinpol
) n
=n
*(1+ndmag
)
87 if (ldapu
.ne
.0) n
=n
+2*lmmaxlu
*lmmaxlu
*nspinor
*nspinor
*natmtot
88 ! allocate mixing arrays
90 ! determine the size of the mixer work array
92 call mixerifc(mixtype
,n
,v
,dv
,nwork
,v
)
97 ! set last iteration flag
99 ! delete any existing eigenvector files
100 if ((task
.eq
.0).or
.(task
.eq
.2)) call delevec
101 ! begin the self-consistent loop
103 write(60,'("+------------------------------+")')
104 write(60,'("| Self-consistent loop started |")')
105 write(60,'("+------------------------------+")')
108 write(60,'("+-------------------------+")')
109 write(60,'("| Iteration number : ",I4," |")') iscl
110 write(60,'("+-------------------------+")')
112 if (iscl
.ge
.maxscl
) then
114 write(60,'("Reached self-consistent loops maximum")')
118 ! generate the core wavefunctions and densities
120 ! find the new linearisation energies
122 ! write out the linearisation energies
124 ! generate the APW radial functions
126 ! generate the local-orbital radial functions
128 ! compute the overlap radial integrals
130 ! compute the Hamiltonian radial integrals
132 ! begin parallel loop over k-points
133 !$OMP PARALLEL DEFAULT(SHARED) &
134 !$OMP PRIVATE(evalfv,evecfv,evecsv)
137 ! every thread should allocate its own arrays
138 allocate(evalfv(nstfv
,nspnfv
))
139 allocate(evecfv(nmatmax
,nstfv
,nspnfv
))
140 allocate(evecsv(nstsv
,nstsv
))
141 ! solve the first- and second-variational secular equations
142 call seceqn(ik
,evalfv
,evecfv
,evecsv
)
143 ! write the eigenvalues/vectors to file
144 call putevalfv(ik
,evalfv
)
145 call putevalsv(ik
,evalsv(:,ik
))
146 call putevecfv(ik
,evecfv
)
147 call putevecsv(ik
,evecsv
)
148 deallocate(evalfv
,evecfv
,evecsv
)
152 ! find the occupation numbers and Fermi energy
154 ! write out the eigenvalues and occupation numbers
156 ! write the Fermi energy to file
158 ! set the charge density and magnetisation to zero
165 !$OMP PARALLEL DEFAULT(SHARED) &
166 !$OMP PRIVATE(evecfv,evecsv)
169 allocate(evecfv(nmatmax
,nstfv
,nspnfv
))
170 allocate(evecsv(nstsv
,nstsv
))
171 ! write the occupancies to file
172 call putoccsv(ik
,occsv(:,ik
))
173 ! get the eigenvectors from file
174 call getevecfv(vkl(:,ik
),vgkl(:,:,:,ik
),evecfv
)
175 call getevecsv(vkl(:,ik
),evecsv
)
176 ! add to the density and magnetisation
177 call rhovalk(ik
,evecfv
,evecsv
)
178 deallocate(evecfv
,evecsv
)
182 ! symmetrise the density
183 call symrf(lradstp
,rhomt
,rhoir
)
184 ! symmetrise the magnetisation
185 if (spinpol
) call symrvf(lradstp
,magmt
,magir
)
186 ! convert the density from a coarse to a fine radial mesh
188 ! convert the magnetisation from a coarse to a fine radial mesh
190 call rfmtctof(magmt(:,:,:,idm
))
192 ! add the core density to the total density
194 ! calculate the charges
196 ! calculate the moments
197 if (spinpol
) call moment
198 ! normalise the density
202 ! generate the LDA+U density matrix
204 ! generate the LDA+U potential matrix
206 ! write the LDA+U matrices to file
209 ! compute the effective potential
211 ! pack interstitial and muffin-tin effective potential and field into one array
212 call packeff(.true
.,n
,v
)
213 ! mix in the old potential and field with the new
214 call mixerifc(mixtype
,n
,v
,dv
,nwork
,work
)
215 ! unpack potential and field
216 call packeff(.false
.,n
,v
)
217 ! add the fixed spin moment effect field
218 if (fixspin
.ne
.0) call fsmfield
219 ! Fourier transform effective potential to G-space
221 ! reduce the external magnetic fields if required
222 if (reducebf
.lt
.1.d0
) then
223 bfieldc(:)=bfieldc(:)*reducebf
224 bfcmt(:,:,:)=bfcmt(:,:,:)*reducebf
226 ! compute the energy components
228 ! output energy components
231 write(60,'("Density of states at Fermi energy : ",G18.10)') fermidos
232 write(60,'(" (states/Hartree/unit cell)")')
233 ! write total energy to TOTENERGY.OUT and flush
234 write(61,'(G22.12)') engytot
236 ! write DOS at Fermi energy to FERMIDOS.OUT and flush
237 write(62,'(G18.10)') fermidos
239 ! output charges and moments
241 ! write total moment to MOMENT.OUT and flush
243 write(63,'(3G18.10)') momtot(1:ndmag
)
246 ! output effective fields for fixed spin moment calculations
247 if (fixspin
.ne
.0) call writefsm(60)
248 ! check for WRITE file
249 inquire(file
='WRITE',exist
=exist
)
252 write(60,'("WRITE file exists - writing STATE.OUT")')
254 open(50,file
='WRITE')
255 close(50,status
='DELETE')
257 ! write STATE.OUT file if required
258 if (nwrite
.ge
.1) then
259 if (mod(iscl
,nwrite
).eq
.0) then
262 write(60,'("Wrote STATE.OUT")')
265 ! exit self-consistent loop if last iteration is complete
267 ! check for convergence
270 write(60,'("RMS change in effective potential (target) : ",G18.10,&
271 &" (",G18.10,")")') dv
,epspot
272 if (dv
.lt
.epspot
) then
274 write(60,'("Potential convergence target achieved")')
277 write(65,'(G18.10)') dv
280 if (xctype
.lt
.0) then
282 write(60,'("Magnitude of OEP residual : ",G18.10)') resoep
284 ! check for STOP file
285 inquire(file
='STOP',exist
=exist
)
288 write(60,'("STOP file exists - stopping self-consistent loop")')
292 close(50,status
='DELETE')
294 ! output the current total CPU time
295 timetot
=timeinit
+timemat
+timefv
+timesv
+timerho
+timepot
+timefor
297 write(60,'("Time (CPU seconds) : ",F12.2)') timetot
298 ! end the self-consistent loop
302 write(60,'("+------------------------------+")')
303 write(60,'("| Self-consistent loop stopped |")')
304 write(60,'("+------------------------------+")')
305 ! write density and potentials to file only if maxscl > 1
306 if (maxscl
.gt
.1) then
309 write(60,'("Wrote STATE.OUT")')
311 !-----------------------!
313 !-----------------------!
314 if ((.not
.tstop
).and
.(tforce
)) then
316 ! output forces to INFO.OUT
318 ! write maximum force magnitude to FORCEMAX.OUT
319 write(64,'(G18.10)') forcemax
322 !---------------------------------------!
323 ! perform structural relaxation !
324 !---------------------------------------!
325 if ((.not
.tstop
).and
.((task
.eq
.2).or
.(task
.eq
.3))) then
327 write(60,'("Maximum force magnitude (target) : ",G18.10," (",G18.10,")")') &
330 ! check force convergence
331 if (forcemax
.le
.epsforce
) then
333 write(60,'("Force convergence target achieved")')
336 ! update the atomic positions if forces are not converged
339 write(60,'("+--------------------------+")')
340 write(60,'("| Updated atomic positions |")')
341 write(60,'("+--------------------------+")')
344 write(60,'("Species : ",I4," (",A,")")') is
,trim(spsymb(is
))
345 write(60,'(" atomic positions (lattice) :")')
347 write(60,'(I4," : ",3F14.8)') ia
,atposl(:,ia
,is
)
350 ! add blank line to TOTENERGY.OUT, FERMIDOS.OUT, MOMENT.OUT and RMSDVEFF.OUT
353 if (spinpol
) write (63,*)
355 ! begin new self-consistent loop with updated positions
359 ! output timing information
361 write(60,'("Timings (CPU seconds) :")')
362 write(60,'(" initialisation",T40,": ",F12.2)') timeinit
363 write(60,'(" Hamiltonian and overlap matrix set up",T40,": ",F12.2)') timemat
364 write(60,'(" first-variational secular equation",T40,": ",F12.2)') timefv
366 write(60,'(" second-variational calculation",T40,": ",F12.2)') timesv
368 write(60,'(" charge density calculation",T40,": ",F12.2)') timerho
369 write(60,'(" potential calculation",T40,": ",F12.2)') timepot
371 write(60,'(" force calculation",T40,": ",F12.2)') timefor
373 timetot
=timeinit
+timemat
+timefv
+timesv
+timerho
+timepot
+timefor
374 write(60,'(" total",T40,": ",F12.2)') timetot
376 write(60,'("+----------------------------------+")')
377 write(60,'("| EXCITING version ",I1.1,".",I1.1,".",I3.3," stopped |")') version
378 write(60,'("+----------------------------------+")')
379 ! close the INFO.OUT file
381 ! close the TOTENERGY.OUT file
383 ! close the FERMIDOS.OUT file
385 ! close the MOMENT.OUT file
386 if (spinpol
) close(63)
387 ! close the FORCEMAX.OUT file
388 if (tforce
) close(64)
389 ! close the RMSDVEFF.OUT file