|
subroutine, public | valconf_copy (cout, cin) |
|
subroutine, public | write_valconf (c, s) |
|
subroutine, public | read_valconf (namespace, s, c) |
|
subroutine, public | valconf_unpolarized_to_polarized (conf) |
|
subroutine, public | atomhxc (namespace, functl, g, nspin, dens, v, extra) |
|
subroutine, public | atomxc (namespace, FUNCTL, AUTHOR, NR, MAXR, RMESH, NSPIN, DENS, EX, EC, DX, DC, V_XC) |
| Finds total exchange-correlation energy and potential for a ! spherical electron density distribution. ! This version implements the Local (spin) Density Approximation and ! the Generalized-Gradient-Aproximation with the explicit mesh ! functional method of White & Bird, PRB 50, 4954 (1994). ! Gradients are defined by numerical derivatives, using 2*NN+1 mesh ! points, where NN is a parameter defined below ! Coded by L.C.Balbas and J.M.Soler. December 1996. Version 0.5. ! ! CHARACTER*(*) FUNCTL : Functional to be used: ! LDA or LSD => Local (spin) Density Approximation ! GGA => Generalized Gradient Corrections ! Uppercase is optional ! CHARACTER*(*) AUTHOR : Parametrization desired: ! CA or PZ => LSD Perdew & Zunger, PRB 23, 5075 (1981) ! PW92 => LSD Perdew & Wang, PRB, 45, 13244 (1992). This is ! the local density limit of the next: ! PBE => GGA Perdew, Burke & Ernzerhof, PRL 77, 3865 (1996) ! Uppercase is optional ! INTEGER NR : Number of radial mesh points ! INTEGER MAXR : Physical first dimension of RMESH, DENS and V_XC ! REAL*8 RMESH(MAXR) : Radial mesh points ! INTEGER NSPIN : NSPIN=1 => unpolarized; NSPIN=2 => polarized ! REAL*8 DENS(MAXR,NSPIN) : Total (NSPIN=1) or spin (NSPIN=2) electron ! density at mesh points ! ************************* OUTPUT ********************************** ! REAL*8 EX : Total exchange energy ! REAL*8 EC : Total correlation energy ! REAL*8 DX : IntegralOf( rho * (eps_x - v_x) ) ! REAL*8 DC : IntegralOf( rho * (eps_c - v_c) ) ! REAL*8 V_XC(MAXR,NSPIN): (Spin) exch-corr potential ! ************************ UNITS ************************************ ! Distances in atomic units (Bohr). ! Densities in atomic units (electrons/Bohr**3) ! Energy unit depending of parameter EUNIT below ! ********* ROUTINES CALLED ***************************************** ! GGAXC, LDAXC ! More...
|
|
subroutine, public | vhrtre (rho, v, r, drdi, srdrdi, nr, a) |
| VHRTRE CONSTRUCTS THE ELECTROSTATIC POTENTIAL DUE TO A SUPPLIED ! ELECTRON DENSITY. THE NUMEROV METHOD IS USED TO INTEGRATE ! POISSONS EQN. ! ! DESCRIPTION OF ARGUMENTS: ! RHO....4*PI*R**2 * THE ELECTRON DENSITY FOR WHICH WE CALCULATING ! THE ELECTROSTATIC POTENTIAL ! V......THE ELECTROSTATIC POTENTIAL DUE TO THE ELECTRON DENSITY ! RHO. THE CONSTANTS OF INTEGRATION ARE FIXED SO THAT THE ! POTENTIAL TENDS TO A CONSTANT AT THE ORIGIN AND TO ! 2*Q/R AT R=R(NR), WHERE Q IS THE INTEGRATED CHARGE ! CONTAINED IN RHO(R) ! R......THE RADIAL MESH R(I) = B*(EXP(A(I-1))-1) ! NR.....THE NUMBER OF RADIAL MESH POINTS ! DRDI...DR(I)/DI ! SRDRDI.SQRT(DR/DI) ! A......THE PARAMETER APPEARING IN R(I) = B*(EXP(A(I-1))-1) ! More...
|
|
subroutine, public | egofv (namespace, h, s, n, e, g, y, l, z, a, b, rmax, nprin, nnode, dr, ierr) |
| egofv determines the eigenenergy and wavefunction corresponding ! to a particular l, principal quantum number and boundary condition. ! ! two fundamental techniques are used to locate the solution: ! 1) node counting and bisection ! 2) variational estimate based on a slope discontinuity in psi ! the arguments are defined as follows: ! h,s: g = (h-e*s)*g ! nr: maximum allowed number of radial points ! e: e is the energy found ! ne: number of energies found ! l: the angular momentum ! ncor: the number of lower-energy state ! ! the individual energies are resolved by performing a fixed number ! of bisections after a given eigenvalue has been isolated ! More...
|
|
subroutine | yofe (e, de, dr, rmax, h, s, y, nmax, l, ncor, nnode, z, a, b) |
|
subroutine | nrmlzg (namespace, g, s, n) |
|
subroutine | bcorgn (e, h, s, l, zdr, y2) |
|
subroutine | bcrmax (e, dr, rmax, h, s, n, yn, a, b) |
|
subroutine | numin (e, h, s, y, n, nnode, yn, g, gsg, x, knk) |
|
subroutine | numout (e, h, s, y, ncor, knk, nnode, y2, g, gsg, x) |
|
subroutine, public atomic_oct_m::atomxc |
( |
type(namespace_t), intent(in) |
namespace, |
|
|
character(len=*), intent(in) |
FUNCTL, |
|
|
character(len=*), intent(in) |
AUTHOR, |
|
|
integer, intent(in) |
NR, |
|
|
integer, intent(in) |
MAXR, |
|
|
real(real64), dimension(maxr), intent(in) |
RMESH, |
|
|
integer, intent(in) |
NSPIN, |
|
|
real(real64), dimension(maxr,nspin), intent(in) |
DENS, |
|
|
real(real64), intent(out) |
EX, |
|
|
real(real64), intent(out) |
EC, |
|
|
real(real64), intent(out) |
DX, |
|
|
real(real64), intent(out) |
DC, |
|
|
real(real64), dimension(maxr,nspin), intent(out) |
V_XC |
|
) |
| |
Finds total exchange-correlation energy and potential for a ! spherical electron density distribution. ! This version implements the Local (spin) Density Approximation and ! the Generalized-Gradient-Aproximation with the explicit mesh ! functional method of White & Bird, PRB 50, 4954 (1994). ! Gradients are defined by numerical derivatives, using 2*NN+1 mesh ! points, where NN is a parameter defined below ! Coded by L.C.Balbas and J.M.Soler. December 1996. Version 0.5. ! ! CHARACTER*(*) FUNCTL : Functional to be used: ! LDA or LSD => Local (spin) Density Approximation ! GGA => Generalized Gradient Corrections ! Uppercase is optional ! CHARACTER*(*) AUTHOR : Parametrization desired: ! CA or PZ => LSD Perdew & Zunger, PRB 23, 5075 (1981) ! PW92 => LSD Perdew & Wang, PRB, 45, 13244 (1992). This is ! the local density limit of the next: ! PBE => GGA Perdew, Burke & Ernzerhof, PRL 77, 3865 (1996) ! Uppercase is optional ! INTEGER NR : Number of radial mesh points ! INTEGER MAXR : Physical first dimension of RMESH, DENS and V_XC ! REAL*8 RMESH(MAXR) : Radial mesh points ! INTEGER NSPIN : NSPIN=1 => unpolarized; NSPIN=2 => polarized ! REAL*8 DENS(MAXR,NSPIN) : Total (NSPIN=1) or spin (NSPIN=2) electron ! density at mesh points ! ************************* OUTPUT ********************************** ! REAL*8 EX : Total exchange energy ! REAL*8 EC : Total correlation energy ! REAL*8 DX : IntegralOf( rho * (eps_x - v_x) ) ! REAL*8 DC : IntegralOf( rho * (eps_c - v_c) ) ! REAL*8 V_XC(MAXR,NSPIN): (Spin) exch-corr potential ! ************************ UNITS ************************************ ! Distances in atomic units (Bohr). ! Densities in atomic units (electrons/Bohr**3) ! Energy unit depending of parameter EUNIT below ! ********* ROUTINES CALLED ***************************************** ! GGAXC, LDAXC !
Definition at line 361 of file atomic.F90.