exciting-0.9.150
[exciting.git] / src / rdmminc.f90
blob95c143463482dcb48202456e9e9f31ba619f885a
2 ! Copyright (C) 2007 J. K. Dewhurst, S. Sharma and E. K. U. Gross.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
6 subroutine rdmminc
7 ! minimises the total energy w.r.t. evecsv using steepest descent
8 use modmain
9 implicit none
10 integer it,ik,idm
11 real(8) sum,sp,ds
12 ! parameter to check energy convergence
13 real(8), parameter :: eps=1.d-10
14 ! allocatable arrays
15 complex(8), allocatable :: evecfv(:,:)
16 complex(8), allocatable :: evecsv(:,:)
17 ! allocate arrays
18 allocate(evecfv(nmatmax,nstfv))
19 allocate(evecsv(nstsv,nstsv))
20 sp=0.d0
21 ds=0.d0
22 open(61,file='RDMC_ENERGY.OUT',action='WRITE',form='FORMATTED')
23 if (spinpol) then
24 open(62,file='RDMC_MOMENT.OUT',action='WRITE',form='FORMATTED')
25 end if
26 write(*,*)
27 ! begin iteration loop
28 do it=1,maxitc
29 write(*,'("Info(rdmminc): iteration ",I4," of ",I4)') it,maxitc
30 ! vary evecsv and orthogonalise it
31 call rdmvaryc(sum)
32 ! zero the density
33 rhomt(:,:,:)=0.d0
34 rhoir(:)=0.d0
35 ! zero the magnetisation
36 if (spinpol) then
37 magmt(:,:,:,:)=0.d0
38 magir(:,:)=0.d0
39 end if
40 do ik=1,nkpt
41 ! get the eigenvectors and values from file
42 call getevecfv(vkl(1,ik),vgkl(1,1,ik,1),evecfv)
43 call getevecsv(vkl(1,ik),evecsv)
44 ! calculate the density
45 call rhovalk(ik,evecfv,evecsv)
46 end do
47 ! symmetrise the density
48 call symrf(lradstp,rhomt,rhoir)
49 ! convert the muffin-tin density from coarse to a fine grid
50 call rfmtctof(rhomt)
51 if (spinpol) then
52 ! symmetrise the magnetisation
53 call symrvf(lradstp,magmt,magir)
54 ! convert the magnetisation from a coarse to a fine radial mesh
55 do idm=1,ndmag
56 call rfmtctof(magmt(1,1,1,idm))
57 end do
58 end if
59 ! add core density to the valence density
60 call addrhocr
61 ! calculate the charges
62 call charge
63 ! calculate the magnetic moment
64 if (spinpol) then
65 call moment
66 write(62,'(I6,3G18.10)') it,momtot(1:ndmag)
67 call flushifc(62)
68 end if
69 ! normalise the density
70 call rhonorm
71 ! calculate the Coulomb potential
72 call potcoul
73 ! calculate Coulomb matrix elements
74 call genvmat(vclmt,vclir,vclmat)
75 ! calculate derivative of kinetic energy w.r.t. evecsv
76 call rdmdkdc
77 ! calculate the energy
78 call rdmenergy
79 ! check for convergence of derivative of energy w.r.t. evecsv
80 if (it.gt.1) then
81 ds=sp-sum
82 sp=sum
83 end if
84 ! write energy and convergence factor to a file
85 write(61,'(I6,2G18.10)') it,engytot,ds
86 call flushifc(61)
87 ! end iteration loop
88 end do
89 close(61)
90 close(62)
91 deallocate(evecfv,evecsv)
92 return
93 end subroutine