The Elk Code
rhostatic.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2020 J. K. Dewhurst and S. Sharma.
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 rhostatic
7 use modmain
8 use modtddft
9 use modmpi
10 implicit none
11 ! local variables
12 integer is,ia,ias,np,i
13 real(8) t0,t1
14 ! allocatable arrays
15 real(8), allocatable :: jrmt0(:,:,:),jrir0(:,:)
16 ! external functions
17 real(8), external :: rfmtint,rfint
18 ! store original parameters
20 afieldc0(:)=afieldc(:)
22 tjr0=tjr
23 ! initialise global variables
24 call init0
25 ! only one self-consistent loop required
26 maxscl=1
27 ! read potential from STATE.OUT
28 trdstate=.true.
29 ! calculate current density with zero A-field
30 tjr=.true.
31 afieldc(:)=0.d0
32 ! switch off forces
33 tforce=.false.
34 ! run the ground-state calculation
35 call gndstate
36 ! store the current density
37 allocate(jrmt0(npmtmax,natmtot,3),jrir0(ngtot,3))
38 do i=1,3
39  do ias=1,natmtot
40  is=idxis(ias)
41  jrmt0(1:npmt(is),ias,i)=jrmt(1:npmt(is),ias,i)
42  end do
43  jrir0(1:ngtot,i)=jrir(1:ngtot,i)
44 end do
45 ! allocate static density and charge global arrays
46 if (allocated(rhosmt)) deallocate(rhosmt)
47 allocate(rhosmt(npmtmax,natmtot,3))
48 if (allocated(rhosir)) deallocate(rhosir)
49 allocate(rhosir(ngtot,3))
50 if (allocated(chgsmt)) deallocate(chgsmt)
51 allocate(chgsmt(natmtot,3))
52 ! magnitude of applied external A-field
53 t0=0.75d0*solsc
54 t1=solsc/t0
55 ! loop over three directions
56 do i=1,3
57  afieldc(:)=0.d0
58  afieldc(i)=t0
59 ! run the ground-state calculation
60  call gndstate
61 ! muffin-tin static density
62  do ias=1,natmtot
63  is=idxis(ias)
64  np=npmt(is)
65  rhosmt(1:np,ias,i)=rhomt(1:np,ias)+t1*(jrmt0(1:np,ias,i)-jrmt(1:np,ias,i))
66 ! compute the muffin-tin static charge
67  chgsmt(ias,i)=rfmtint(nrmt(is),nrmti(is),wr2mt(:,is),rhosmt(:,ias,i))
68  end do
69 ! interstitial static density
70  rhosir(1:ngtot,i)=rhoir(1:ngtot)+t1*(jrir0(1:ngtot,i)-jrir(1:ngtot,i))
71 ! compute the static charge
72  chgstot(i)=rfint(rhosmt(:,:,i),rhosir(:,i))
73 end do
74 if (mp_mpi) then
75 ! write static density and charges to binary file
76  open(100,file='RHOSTAT.OUT',form='UNFORMATTED',action='WRITE')
77  write(100) natmtot
78  write(100) npmtmax
79  write(100) ngtot
80  write(100) rhosmt,rhosir
81  write(100) chgsmt
82  write(100) chgstot
83  close(100)
84 ! write static charges to text file
85  open(50,file='CHGSTAT.OUT',form='FORMATTED',action='WRITE')
86  write(50,'("Muffin-tin static charges :")')
87  do is=1,nspecies
88  write(50,'(" species : ",I4," (",A,")")') is,trim(spsymb(is))
89  write(50,'(" core charge",T25,": ",G18.10)') chgcr(is)
90  do ia=1,natoms(is)
91  ias=idxas(ia,is)
92  write(50,'(" atom ",I4,T25,": ",3G18.10)') ia,chgsmt(ias,:)
93  end do
94  end do
95  write(50,*)
96  write(50,'("Total static charge",T25,": ",3G18.10)') chgstot(:)
97  close(50)
98 end if
99 deallocate(jrmt0,jrir0)
100 ! restore original input parameters
102 afieldc(:)=afieldc0(:)
104 tjr=tjr0
105 ! synchronise MPI processes
106 call mpi_barrier(mpicom,ierror)
107 end subroutine
108 
logical tjr
Definition: modmain.f90:620
subroutine gndstate
Definition: gndstate.f90:10
logical mp_mpi
Definition: modmpi.f90:17
integer ngtot
Definition: modmain.f90:390
logical tjr0
Definition: modmain.f90:620
real(8), dimension(:), pointer, contiguous rhoir
Definition: modmain.f90:614
integer, dimension(maxatoms, maxspecies) idxas
Definition: modmain.f90:42
integer, dimension(maxspecies) npmt
Definition: modmain.f90:213
logical tforce0
Definition: modmain.f90:989
real(8), dimension(:,:), pointer, contiguous rhomt
Definition: modmain.f90:614
integer maxscl0
Definition: modmain.f90:1049
logical tforce
Definition: modmain.f90:989
subroutine rhostatic
Definition: rhostatic.f90:7
real(8), dimension(maxspecies) chgcr
Definition: modmain.f90:716
real(8), dimension(:,:), allocatable rhosir
Definition: modtddft.f90:82
real(8), dimension(3) afieldc
Definition: modmain.f90:325
real(8) solsc
Definition: modmain.f90:1253
integer, dimension(maxspecies) natoms
Definition: modmain.f90:36
integer, dimension(maxatoms *maxspecies) idxis
Definition: modmain.f90:44
Definition: modmpi.f90:6
integer nspecies
Definition: modmain.f90:34
real(8), dimension(:,:), allocatable chgsmt
Definition: modtddft.f90:86
real(8), dimension(3) chgstot
Definition: modtddft.f90:84
logical trdstate
Definition: modmain.f90:682
integer npmtmax
Definition: modmain.f90:216
real(8), dimension(:,:,:), allocatable jrmt
Definition: modmain.f90:622
subroutine init0
Definition: init0.f90:10
integer natmtot
Definition: modmain.f90:40
real(8), dimension(3) afieldc0
Definition: modmain.f90:325
integer, dimension(maxspecies) nrmti
Definition: modmain.f90:211
real(8), dimension(:,:), allocatable jrir
Definition: modmain.f90:622
integer maxscl
Definition: modmain.f90:1049
character(64), dimension(maxspecies) spsymb
Definition: modmain.f90:78
integer mpicom
Definition: modmpi.f90:11
real(8), dimension(:,:), allocatable wr2mt
Definition: modmain.f90:183
integer ierror
Definition: modmpi.f90:19
real(8), dimension(:,:,:), allocatable rhosmt
Definition: modtddft.f90:82
integer, dimension(maxspecies) nrmt
Definition: modmain.f90:150