2023-11-13 18:36:09 +01:00
|
|
|
subroutine RG0T0eh(dotest,doACFDT,exchange_kernel,doXBS,dophBSE,dophBSE2,TDA_T,TDA,dBSE,dTDA,doppBSE, &
|
2024-09-11 10:13:11 +02:00
|
|
|
singlet,triplet,linearize,eta,regularize,nBas,nOrb,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,dipole_int,eHF)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
! Perform ehG0T0 calculation
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
include 'quadrature.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
2023-11-13 18:36:09 +01:00
|
|
|
logical,intent(in) :: dotest
|
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
logical,intent(in) :: doACFDT
|
|
|
|
logical,intent(in) :: exchange_kernel
|
|
|
|
logical,intent(in) :: doXBS
|
2023-07-18 22:17:42 +02:00
|
|
|
logical,intent(in) :: dophBSE
|
|
|
|
logical,intent(in) :: dophBSE2
|
|
|
|
logical,intent(in) :: doppBSE
|
2023-06-29 18:54:00 +02:00
|
|
|
logical,intent(in) :: TDA_T
|
|
|
|
logical,intent(in) :: TDA
|
|
|
|
logical,intent(in) :: dBSE
|
|
|
|
logical,intent(in) :: dTDA
|
|
|
|
logical,intent(in) :: singlet
|
|
|
|
logical,intent(in) :: triplet
|
|
|
|
logical,intent(in) :: linearize
|
|
|
|
double precision,intent(in) :: eta
|
|
|
|
logical,intent(in) :: regularize
|
|
|
|
|
|
|
|
integer,intent(in) :: nBas
|
2024-09-11 10:13:11 +02:00
|
|
|
integer,intent(in) :: nOrb
|
2023-06-29 18:54:00 +02:00
|
|
|
integer,intent(in) :: nC
|
|
|
|
integer,intent(in) :: nO
|
|
|
|
integer,intent(in) :: nV
|
|
|
|
integer,intent(in) :: nR
|
|
|
|
integer,intent(in) :: nS
|
|
|
|
double precision,intent(in) :: ENuc
|
|
|
|
double precision,intent(in) :: ERHF
|
2024-09-11 10:13:11 +02:00
|
|
|
double precision,intent(in) :: ERI(nOrb,nOrb,nOrb,nOrb)
|
|
|
|
double precision,intent(in) :: dipole_int(nOrb,nOrb,ncart)
|
|
|
|
double precision,intent(in) :: eHF(nOrb)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
2023-07-23 23:10:57 +02:00
|
|
|
logical :: print_T = .true.
|
2023-07-18 22:17:42 +02:00
|
|
|
logical :: dRPA = .false.
|
2023-06-29 18:54:00 +02:00
|
|
|
integer :: ispin
|
2023-07-23 23:10:57 +02:00
|
|
|
integer :: isp_W
|
2023-06-29 18:54:00 +02:00
|
|
|
double precision :: EcRPA
|
|
|
|
double precision :: EcBSE(nspin)
|
|
|
|
double precision :: EcAC(nspin)
|
|
|
|
double precision :: EcGM
|
2023-07-18 22:17:42 +02:00
|
|
|
double precision,allocatable :: Aph(:,:)
|
|
|
|
double precision,allocatable :: Bph(:,:)
|
2023-07-12 14:13:45 +02:00
|
|
|
double precision,allocatable :: Sig(:)
|
2023-06-29 18:54:00 +02:00
|
|
|
double precision,allocatable :: Z(:)
|
2023-07-18 22:17:42 +02:00
|
|
|
double precision,allocatable :: Om(:)
|
|
|
|
double precision,allocatable :: XpY(:,:)
|
|
|
|
double precision,allocatable :: XmY(:,:)
|
2023-08-01 21:32:57 +02:00
|
|
|
double precision,allocatable :: rhoL(:,:,:)
|
|
|
|
double precision,allocatable :: rhoR(:,:,:)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2023-09-07 14:01:58 +02:00
|
|
|
double precision,allocatable :: eGTlin(:)
|
2023-07-17 13:35:24 +02:00
|
|
|
double precision,allocatable :: eGT(:)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2023-07-23 23:10:57 +02:00
|
|
|
double precision,allocatable :: KA_sta(:,:)
|
|
|
|
double precision,allocatable :: KB_sta(:,:)
|
|
|
|
double precision,allocatable :: OmRPA(:)
|
|
|
|
double precision,allocatable :: XpY_RPA(:,:)
|
|
|
|
double precision,allocatable :: XmY_RPA(:,:)
|
|
|
|
double precision,allocatable :: rho_RPA(:,:,:)
|
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
! Output variables
|
|
|
|
|
|
|
|
! Hello world
|
|
|
|
|
|
|
|
write(*,*)
|
2023-11-13 18:36:09 +01:00
|
|
|
write(*,*)'*********************************'
|
|
|
|
write(*,*)'* Restricted G0T0eh Calculation *'
|
|
|
|
write(*,*)'*********************************'
|
2023-06-29 18:54:00 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
! Initialization
|
|
|
|
|
|
|
|
EcRPA = 0d0
|
|
|
|
|
|
|
|
! TDA for T
|
|
|
|
|
|
|
|
if(TDA_T) then
|
|
|
|
write(*,*) 'Tamm-Dancoff approximation for eh T-matrix!'
|
|
|
|
write(*,*)
|
|
|
|
end if
|
|
|
|
|
|
|
|
! TDA
|
|
|
|
|
|
|
|
if(TDA) then
|
|
|
|
write(*,*) 'Tamm-Dancoff approximation activated!'
|
|
|
|
write(*,*)
|
|
|
|
end if
|
|
|
|
|
|
|
|
! Memory allocation
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
allocate(Aph(nS,nS),Bph(nS,nS),Sig(nOrb),Z(nOrb),Om(nS),XpY(nS,nS),XmY(nS,nS), &
|
|
|
|
rhoL(nOrb,nOrb,nS),rhoR(nOrb,nOrb,nS),eGT(nOrb),eGTlin(nOrb))
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2023-07-23 23:10:57 +02:00
|
|
|
!---------------------------------
|
2023-07-27 10:11:35 +02:00
|
|
|
! Compute (triplet) RPA screening
|
2023-07-23 23:10:57 +02:00
|
|
|
!---------------------------------
|
|
|
|
|
|
|
|
ispin = 2
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
call phLR_A(ispin,dRPA,nOrb,nC,nO,nV,nR,nS,1d0,eHF,ERI,Aph)
|
|
|
|
if(.not.TDA_T) call phLR_B(ispin,dRPA,nOrb,nC,nO,nV,nR,nS,1d0,ERI,Bph)
|
2023-07-23 23:10:57 +02:00
|
|
|
|
2023-07-18 22:17:42 +02:00
|
|
|
call phLR(TDA_T,nS,Aph,Bph,EcRPA,Om,XpY,XmY)
|
|
|
|
|
2023-11-22 10:07:23 +01:00
|
|
|
if(print_T) call print_excitation_energies('phRPA@RHF','triplet',nS,Om)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
!--------------------------!
|
|
|
|
! Compute spectral weights !
|
|
|
|
!--------------------------!
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
call RGTeh_excitation_density(nOrb,nC,nO,nR,nS,ERI,XpY,XmY,rhoL,rhoR)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
!------------------------!
|
|
|
|
! Compute GW self-energy !
|
|
|
|
!------------------------!
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
if(regularize) call GTeh_regularization(nOrb,nC,nO,nV,nR,nS,eHF,Om,rhoL,rhoR)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
call RGTeh_self_energy_diag(eta,nOrb,nC,nO,nV,nR,nS,eHF,Om,rhoL,rhoR,EcGM,Sig,Z)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
!-----------------------------------!
|
|
|
|
! Solve the quasi-particle equation !
|
|
|
|
!-----------------------------------!
|
|
|
|
|
|
|
|
! Linearized or graphical solution?
|
|
|
|
|
2023-09-07 14:01:58 +02:00
|
|
|
eGTlin(:) = eHF(:) + Z(:)*Sig(:)
|
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
if(linearize) then
|
|
|
|
|
|
|
|
write(*,*) ' *** Quasiparticle energies obtained by linearization *** '
|
|
|
|
write(*,*)
|
|
|
|
|
2023-09-07 14:01:58 +02:00
|
|
|
eGT(:) = eGTlin(:)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2023-11-27 10:17:14 +01:00
|
|
|
write(*,*) ' *** Quasiparticle energies obtained by root search *** '
|
2023-06-29 18:54:00 +02:00
|
|
|
write(*,*)
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
call RGTeh_QP_graph(eta,nOrb,nC,nO,nV,nR,nS,eHF,Om,rhoL,rhoR,eGTlin,eHF,eGT,Z)
|
2023-07-27 16:43:15 +02:00
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
end if
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
! call RGTeh_plot_self_energy(nOrb,nC,nO,nV,nR,nS,eHF,eHF,Om,rhoL,rhoR)
|
2023-08-24 00:02:23 +02:00
|
|
|
|
2023-07-21 20:38:49 +02:00
|
|
|
! Compute the RPA correlation energy based on the G0T0eh quasiparticle energies
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
call phLR_A(ispin,dRPA,nOrb,nC,nO,nV,nR,nS,1d0,eGT,ERI,Aph)
|
|
|
|
if(.not.TDA_T) call phLR_B(ispin,dRPA,nOrb,nC,nO,nV,nR,nS,1d0,ERI,Bph)
|
2023-07-18 22:17:42 +02:00
|
|
|
|
|
|
|
call phLR(TDA_T,nS,Aph,Bph,EcRPA,Om,XpY,XmY)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
!--------------!
|
|
|
|
! Dump results !
|
|
|
|
!--------------!
|
|
|
|
|
2024-09-11 10:13:11 +02:00
|
|
|
call print_RG0T0eh(nOrb,nO,eHF,ENuc,ERHF,Sig,Z,eGT,EcRPA,EcGM)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2023-11-13 18:36:09 +01:00
|
|
|
! Testing zone
|
|
|
|
|
|
|
|
if(dotest) then
|
|
|
|
|
2023-11-14 14:31:27 +01:00
|
|
|
call dump_test_value('R','G0T0eh correlation energy',EcRPA)
|
|
|
|
call dump_test_value('R','G0T0eh HOMO energy',eGT(nO))
|
|
|
|
call dump_test_value('R','G0T0eh LUMO energy',eGT(nO+1))
|
2023-11-13 18:36:09 +01:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
end subroutine
|