The Elk Code
 
Loading...
Searching...
No Matches
genspecies.f90
Go to the documentation of this file.
1
2! Copyright (C) 2009 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.
5
6subroutine genspecies(fnum)
7use modmain
8use modmpi
9implicit none
10! arguments
11integer, intent(in) :: fnum
12! local variables
13integer nz,nmax,nst,ist
14integer ne,nrm,nr,ir,it,i
15integer n(maxstsp),l(maxstsp),k(maxstsp)
16real(8) mass,zn,t1,t2,t3
17real(8) rm,rmin,rmax
18real(8) occ(maxstsp),eval(maxstsp)
19character(64) symb,name
20! allocatable arrays
21real(8), allocatable :: r(:),rho(:),vr(:),rwf(:,:,:)
22read(fnum,*,err=20) nz
23if (nz < 1) then
24 write(*,*)
25 write(*,'("Error(genspecies): nz < 1 : ",I8)') nz
26 write(*,*)
27 stop
28end if
29read(fnum,*,err=20) symb,name
30read(fnum,*,err=20) mass
31! convert from 'atomic mass units' to atomic units
32mass=mass*amu
33read(fnum,*,err=20) rm
34read(fnum,*,err=20) nst
35if ((nst < 1).or.(nst > maxstsp)) then
36 write(*,*)
37 write(*,'("Error(genspecies): nst out of range : ",I8)') nst
38 write(*,'(" for species ",A)') trim(name)
39 write(*,*)
40 stop
41end if
42ne=0
43nmax=1
44do ist=1,nst
45 read(fnum,*,err=20) n(ist),l(ist),k(ist),i
46 ne=ne+i
47 occ(ist)=i
48 nmax=max(nmax,n(ist))
49end do
50if (mp_mpi) then
51 write(*,'("Info(genspecies): running Z = ",I4,", (",A,")")') nz,trim(name)
52 if (ne /= nz) then
53 write(*,*)
54 write(*,'("Warning(genspecies): atom not neutral, electron number : ",&
55 &I4)') ne
56 end if
57end if
58! nuclear charge in units of e
59zn=-dble(nz)
60! minimum radial mesh point proportional to 1/sqrt(Z)
61rmin=2.d-6/sqrt(dble(nz))
62! default effective infinity
63rmax=100.d0
64! set the number of radial mesh points proportional to number of nodes
65nrm=100*(nmax+1)
66do it=1,2
67! number of points to effective infinity
68 t1=log(rm/rmin)
69 t2=log(rmax/rmin)
70 t3=dble(nrm)*t2/t1
71 nr=int(t3)
72 allocate(r(nr),rho(nr),vr(nr),rwf(nr,2,nst))
73! generate logarithmic radial mesh
74 t2=t1/dble(nrm-1)
75 do ir=1,nr
76 r(ir)=rmin*exp(dble(ir-1)*t2)
77 end do
78! solve the Kohn-Sham-Dirac equation for the atom
79 call atom(sol,.true.,zn,nst,n,l,k,occ,3,0,nr,r,eval,rho,vr,rwf)
80! recompute the effective infinity
81 do ir=nr,1,-1
82 if (rho(ir) > 1.d-20) then
83 rmax=1.75d0*r(ir)
84 exit
85 end if
86 end do
87 deallocate(r,rho,vr,rwf)
88end do
89! write the species file
90call writespecies(symb,name,zn,mass,rmin,rm,rmax,nrm,nst,n,l,k,occ,eval)
91return
9220 continue
93write(*,*)
94write(*,'("Error(genspecies): error reading species data")')
95write(*,*)
96stop
97end subroutine
98
subroutine atom(sol, ptnucl, zn, nst, n, l, k, occ, xctype, xcgrad, nr, r, eval, rho, vr, rwf)
Definition atom.f90:10
subroutine genspecies(fnum)
Definition genspecies.f90:7
real(8), parameter amu
Definition modmain.f90:1282
real(8), parameter sol
Definition modmain.f90:1250
logical mp_mpi
Definition modmpi.f90:17
subroutine writespecies(symb, name, zn, mass, rmin, rm, rmax, nrm, nst, n, l, k, occ, eval)