MsSpec-DFM/New_libraries/DFM_library/PHYSICAL_PROPERTIES_LIBRARY/calc_energies.f90

316 lines
13 KiB
Fortran

!
!=======================================================================
!
MODULE CALC_ENERGIES
!
USE ACCURACY_REAL
!
CONTAINS
!
!=======================================================================
!
SUBROUTINE ENERGIES_3D(X,EC_TYPE,RS,T,I_SCREEN,K_SC, &
E_0,E_X,E_X_HF,E_C,E_XC,E_HF, &
E_GS,E_KIN,E_POT)
!
! This subroutine computes the different energies (per electron)
! involved in the 3D system --> 3D
!
! References: (1) G. Giuliani and G. Vignale, "Quantum Theory of the
! Electron Liquid", Cambridge Uiversity Press (2005)
!
! Input parameters:
!
! * X : dimensionless factor --> X = q / (2 * k_F)
! * EC_TYPE : type of correlation energy functional
! * RS : Wigner-Seitz radius (in units of a_0)
! * T : system temperature in SI
! * I_SCREEN : switch for screened (=1) or unscreened (=0) Coulomb
! * K_SC : screening momentum (in SI)
!
!
! Output parameters:
!
! * E_0 : energy of non-interacting electron in SI
! * E_X : exchange energy (1st order) in SI
! * E_X_HF : exchange energy (Hartree-Fock) in SI
! * E_C : correlation energy in SI
! * E_XC : exchange and correlation energy in SI
! * E_HF : Hartree-Fock energy in SI
! * E_GS : energy of the ground state in SI
! * E_KIN : kinetic energy in SI
! * E_POT : potential energy in SI
!
!
! Author : D. Sébilleau
! Last modified : 12 Nov 2020
!
!
USE REAL_NUMBERS, ONLY : ZERO,ONE,TWO,THREE,FOUR, &
HALF,THIRD,FOURTH
USE CONSTANTS_P1, ONLY : BOHR,E,EPS_0
USE CONSTANTS_P2, ONLY : HARTREE
USE FERMI_SI, ONLY : EF_SI,KF_SI
USE PI_ETC, ONLY : PI,PI_INV
USE CORRELATION_ENERGIES
!
IMPLICIT NONE
!
CHARACTER (LEN = 6) :: EC_TYPE
!
REAL (WP), INTENT(IN) :: X,RS,T
REAL (WP), INTENT(OUT) :: E_0,E_X,E_X_HF,E_C,E_XC
REAL (WP), INTENT(OUT) :: E_HF,E_GS,E_KIN,E_POT
REAL (WP) :: Y
REAL (WP) :: D_EC_1,D_EC_2,D_EX_1
REAL (WP) :: K_SC,R1,R2,FK
!
REAL (WP) :: LOG,ABS,ATAN
!
INTEGER :: I_SCREEN
!
Y = X + X ! q / k_F
!
IF(I_SCREEN == 1) THEN !
R1 = KF_SI / K_SC !
R2 = ONE / R1 !
END IF !
!
! Computing the Hartree-Fock function FK
!
IF(Y == ONE) THEN !
FK = HALF !
ELSE IF(Y == ZERO) THEN !
FK = ONE !
ELSE !
FK = HALF + FOURTH * (ONE - Y * Y) * & !
LOG(ABS((ONE + Y) / (ONE - Y))) / Y ! ref. (1) eq. (2.52)
END IF !
!
! Computing the correlation energy and its derivatives
!
CALL DERIVE_EC_3D(EC_TYPE,1,5,RS,T,D_EC_1,D_EC_2) !
!
! Changing to SI
!
D_EC_1 = D_EC_1 * HALF * HARTREE !
D_EC_2 = D_EC_2 * HALF * HARTREE !
!
E_0 = 0.6E0_WP *EF_SI ! ref. (1) eq. (1.83)
E_X = - 0.75E0_WP * E * E * PI_INV * KF_SI ! ref. (1) eq. (1.94)
!
IF(I_SCREEN == 1) THEN !
E_X = E_X * ( FOUR + R2 * R2 * LOG(ONE + FOUR * R1 * R1) & !
- FOUR * R2 * ATAN(TWO * R1) & ! ref. (1) ex. (1.12)
) ! page 66
END IF !
!
E_X_HF = - HALF * E * E * PI_INV * PI_INV * KF_SI * FK / EPS_0! ref. (1) eq. (2.51)
E_C = EC_3D(EC_TYPE,1,RS,T) * HALF * HARTREE !
!
E_XC = E_X + E_C !
E_HF = E_0 + E_X_HF ! ref. (1) eq. (2.49)
E_GS = E_0 + E_XC !
!
! Computing the derivative of the exchange energy
!
D_EX_1 = THREE * (E * E / (FOUR * PI * BOHR)) / (RS * RS) !
!
E_KIN = E_0 - E_XC - RS * (D_EX_1 + D_EC_1) ! ref. (1) eq. (1.57)
E_POT = TWO * E_XC + RS * (D_EX_1 + D_EC_1) ! ref. (1) eq. (1.56)
!
END SUBROUTINE ENERGIES_3D
!
!=======================================================================
!
SUBROUTINE ENERGIES_2D(X,EC_TYPE,RS,T,E_0,E_X,E_X_HF,E_C, &
E_XC,E_HF,E_GS,E_KIN,E_POT)
!
! This subroutine computes the different energies (per electron)
! involved in the 2D system --> 2D
!
! References: (1) G. Giuliani and G. Vignale, "Quantum Theory of the
! Electron Liquid", Cambridge Uiversity Press (2005)
!
! Input parameters:
!
! * X : dimensionless factor --> X = q / (2 * k_F)
! * EC_TYPE : type of correlation energy functional
! * RS : Wigner-Seitz radius (in units of a_0)
! * T : system temperature in SI
!
!
! Output parameters:
!
! * E_0 : energy of non-interacting electron in SI
! * E_X : exchange energy (1st order) in SI
! * E_X_HF : exchange energy (Hartree-Fock) in SI
! * E_C : correlation energy in SI
! * E_XC : exchange and correlation energy in SI
! * E_HF : Hartree-Fock energy in SI
! * E_GS : energy of the ground state in SI
! * E_KIN : kinetic energy in SI
! * E_POT : potential energy in SI
!
!
! Note: for the Hartree-Fock exchange energy, we make use
! of the fact that Gradshteyn-Ryzhik complete elliptic integrals
! K(k) and E(k) are related to Carlson's elliptic integrals through
!
! K(k) = RF(0,1-K^2,1)
! E(K) = RF(0,1-K^2,1) - 1/3 k^2 RD(0,1-K^2,1)
!
! as explained by W. H. Press and S. A. Tseukolsky,
! Comp. in Phys. Jan-Fev 1990, pp. 92-96
!
! Author : D. Sébilleau
!
! Last modified : 11 Jun 2020
!
!
USE REAL_NUMBERS, ONLY : ZERO,ONE,TWO,FOUR,EIGHT, &
HALF,THIRD,TTINY
USE CONSTANTS_P1, ONLY : BOHR,E,EPS_0
USE CONSTANTS_P2, ONLY : HARTREE
USE FERMI_SI, ONLY : EF_SI,KF_SI
USE PI_ETC, ONLY : PI,PI_INV
USE EXT_FUNCTIONS, ONLY : RF,RD ! Carlson's elliptic integrals
USE CORRELATION_ENERGIES
!
IMPLICIT NONE
!
CHARACTER (LEN = 6) :: EC_TYPE
!
REAL (WP), INTENT(IN) :: X,RS,T
REAL (WP), INTENT(OUT) :: E_0,E_X,E_X_HF,E_C,E_XC
REAL (WP), INTENT(OUT) :: E_HF,E_GS,E_KIN,E_POT
REAL (WP) :: Y,Y2
REAL (WP) :: D_EC_1,D_EC_2,D_EX_1,FK,F1
REAL (WP) :: O,O2
!
!
Y = X + X ! q / k_F
Y2 = Y * Y !
IF(Y == ZERO) THEN !
Y = TTINY !
END IF !
O = ONE / Y !
O2 = O * O !
!
! Computing the Hartree-Fock function FK
!
IF(Y <= ONE) THEN !
FK = RF(ZERO,ONE-Y2,ONE) - THIRD * Y2 * RD(ZERO,ONE-Y2,ONE) ! ref. (1) eq. (2.54)
ELSE !
F1 = RF(ZERO,ONE-O2,ONE) - THIRD * O2 * RD(ZERO,ONE-O2,ONE) !
FK = Y * (F1 - (ONE - O2) * RF(ZERO,ONE-O2,ONE)) ! ref. (1) eq. (2.54)
END IF !
!
! Computing the correlation energy and its derivatives
!
CALL DERIVE_EC_2D(EC_TYPE,5,RS,T,D_EC_1,D_EC_2) !
!
! Changing to SI
!
D_EC_1 = D_EC_1 * HALF * HARTREE !
D_EC_2 = D_EC_2 * HALF * HARTREE !
!
E_0 = HALF * EF_SI ! ref. (1) eq. (1.83)
E_X = - FOUR * THIRD * E * E * PI_INV * KF_SI ! ref. (1) eq. (1.94)
E_X_HF = - HALF * E * E * PI_INV * PI_INV * KF_SI*FK / EPS_0 ! ref. (1) eq. (2.53)
E_C = EC_2D(EC_TYPE,RS,T) * HALF * HARTREE !
!
E_XC = E_X + E_C !
E_HF = E_0 + E_X_HF ! ref. (1) eq. (2.49)
E_GS = E_0 + E_XC !
!
! Computing the derivative of the exchange energy
!
D_EX_1 = - EIGHT * THIRD * (E * E / (PI * BOHR)) !
!
E_KIN = E_0 - E_XC - RS * (D_EX_1 + D_EC_1) ! ref. (1) eq. (1.57)
E_POT = TWO * E_XC + RS * (D_EX_1 + D_EC_1) ! ref. (1) eq. (1.56)
!
END SUBROUTINE ENERGIES_2D
!
!=======================================================================
!
SUBROUTINE ENERGIES_1D(EC_TYPE,FF,RS,T,E_0,E_X,E_C,E_XC,E_HF, &
E_GS,E_KIN,E_POT)
!
! This subroutine computes the different energies (per electron)
! involved in the 1D system --> 1D
!
! References: (1) G. Giuliani and G. Vignale, "Quantum Theory of the
! Electron Liquid", Cambridge Uiversity Press (2005)
!
! Input parameters:
!
! * EC_TYPE : type of correlation energy functional
! * RS : Wigner-Seitz radius (in units of a_0)
! * T : system temperature in SI
! * FF : form factor
!
!
! Output parameters:
!
! * E_0 : energy of non-interacting electron in SI
! * E_X : exchange energy in SI
! * E_C : correlation energy in SI
! * E_XC : exchange and correlation energy in SI
! * E_HF : Hartree-Fock energy in SI
! * E_GS : energy of the ground state in SI
! * E_KIN : kinetic energy in SI
! * E_POT : potential energy in SI
!
!
! Author : D. Sébilleau
!
! Last modified : 12 Jun 2020
!
!
USE REAL_NUMBERS, ONLY : TWO,HALF,THIRD,FOURTH
USE CONSTANTS_P2, ONLY : HARTREE
USE FERMI_SI, ONLY : EF_SI
USE CORRELATION_ENERGIES
!
IMPLICIT NONE
!
CHARACTER (LEN = 6) :: EC_TYPE
!
REAL (WP), INTENT(IN) :: RS,T,FF
REAL (WP), INTENT(OUT) :: E_0,E_X,E_C,E_XC,E_HF
REAL (WP), INTENT(OUT) :: E_GS,E_KIN,E_POT
REAL (WP) :: D_EC_1,D_EC_2,D_EX_1
!
! Computing the correlation energy and its derivatives
!
CALL DERIVE_EC_1D(EC_TYPE,5,RS,T,D_EC_1,D_EC_2) !
!
! Changing to SI
!
D_EC_1 = D_EC_1 * HALF * HARTREE !
D_EC_2 = D_EC_2 * HALF * HARTREE !
!
E_0 = THIRD * EF_SI ! ref. (1) eq. (1.83)
E_X = - FOURTH * FF / RS * HALF * HARTREE ! ref. (1) eq. (1.97)
E_C = EC_1D(EC_TYPE,RS,T) * HALF * HARTREE !
!
E_XC = E_X + E_C !
E_HF = E_0 + E_X ! ref. (1) eq. (2.49)
E_GS = E_0 + E_XC !
!
! Computing the derivative of the exchange energy
!
D_EX_1 = FOURTH * FF / (RS * RS) * HALF * HARTREE !
!
E_KIN = E_0 - E_XC - RS * (D_EX_1 + D_EC_1) ! ref. (1) eq. (1.57)
E_POT = TWO * E_XC + RS * (D_EX_1 + D_EC_1) ! ref. (1) eq. (1.56)
!
RETURN
!
END
!
END MODULE CALC_ENERGIES