2023-07-18 11:53:38 +02:00
|
|
|
subroutine crRPA(TDA,doACFDT,exchange_kernel,singlet,triplet,nBas,nC,nO,nV,nR,nS,ENuc,EHF,ERI,dipole_int,e)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
! Crossed-ring channel of the random phase approximation
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
include 'quadrature.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
|
|
|
logical,intent(in) :: TDA
|
|
|
|
logical,intent(in) :: doACFDT
|
|
|
|
logical,intent(in) :: exchange_kernel
|
|
|
|
logical,intent(in) :: singlet
|
|
|
|
logical,intent(in) :: triplet
|
|
|
|
integer,intent(in) :: nBas
|
|
|
|
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
|
2023-07-18 11:53:38 +02:00
|
|
|
double precision,intent(in) :: EHF
|
|
|
|
double precision,intent(in) :: e(nBas)
|
2021-11-10 09:42:30 +01:00
|
|
|
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
|
|
|
|
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
integer :: ispin
|
2023-07-18 11:53:38 +02:00
|
|
|
logical :: dRPA
|
|
|
|
double precision,allocatable :: Aph(:,:)
|
|
|
|
double precision,allocatable :: Bph(:,:)
|
|
|
|
double precision,allocatable :: Om(:)
|
|
|
|
double precision,allocatable :: XpY(:,:)
|
|
|
|
double precision,allocatable :: XmY(:,:)
|
|
|
|
|
2023-07-31 16:01:12 +02:00
|
|
|
double precision :: EcRPA(nspin)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
! Hello world
|
|
|
|
|
|
|
|
write(*,*)
|
|
|
|
write(*,*)'***********************************************************'
|
2021-11-10 14:47:26 +01:00
|
|
|
write(*,*)'| Random phase approximation calculation: cr channel |'
|
2021-11-10 09:42:30 +01:00
|
|
|
write(*,*)'***********************************************************'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
! TDA
|
|
|
|
|
|
|
|
if(TDA) then
|
|
|
|
write(*,*) 'Tamm-Dancoff approximation activated!'
|
|
|
|
write(*,*)
|
|
|
|
end if
|
|
|
|
|
|
|
|
! Initialization
|
|
|
|
|
2023-07-18 11:53:38 +02:00
|
|
|
dRPA = .false.
|
|
|
|
|
2023-07-31 16:01:12 +02:00
|
|
|
EcRPA(:) = 0d0
|
|
|
|
EcRPA(:) = 0d0
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
! Memory allocation
|
|
|
|
|
2023-07-18 11:53:38 +02:00
|
|
|
allocate(Om(nS),XpY(nS,nS),XmY(nS,nS),Aph(nS,nS))
|
|
|
|
if(.not.TDA) allocate(Bph(nS,nS))
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
! Singlet manifold
|
|
|
|
|
|
|
|
if(singlet) then
|
|
|
|
|
|
|
|
ispin = 1
|
|
|
|
|
2023-07-18 11:53:38 +02:00
|
|
|
call phLR_A(ispin,dRPA,nBas,nC,nO,nV,nR,nS,-1d0,e,ERI,Aph)
|
|
|
|
if(.not.TDA) call phLR_B(ispin,dRPA,nBas,nC,nO,nV,nR,nS,-1d0,ERI,Bph)
|
|
|
|
|
2023-07-31 16:01:12 +02:00
|
|
|
call phLR(TDA,nS,Aph,Bph,EcRPA(ispin),Om,XpY,XmY)
|
2023-07-28 14:14:35 +02:00
|
|
|
call print_excitation_energies('crRPA@HF',ispin,nS,Om)
|
|
|
|
call phLR_transition_vectors(.true.,nBas,nC,nO,nV,nR,nS,dipole_int,Om,XpY,XmY)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
endif
|
|
|
|
|
|
|
|
! Triplet manifold
|
|
|
|
|
|
|
|
if(triplet) then
|
|
|
|
|
|
|
|
ispin = 2
|
|
|
|
|
2023-07-18 11:53:38 +02:00
|
|
|
call phLR_A(ispin,dRPA,nBas,nC,nO,nV,nR,nS,-1d0,e,ERI,Aph)
|
|
|
|
if(.not.TDA) call phLR_B(ispin,dRPA,nBas,nC,nO,nV,nR,nS,-1d0,ERI,Bph)
|
|
|
|
|
2023-07-31 16:01:12 +02:00
|
|
|
call phLR(TDA,nS,Aph,Bph,EcRPA(ispin),Om,XpY,XmY)
|
2023-07-28 14:14:35 +02:00
|
|
|
call print_excitation_energies('crRPA@HF',ispin,nS,Om)
|
|
|
|
call phLR_transition_vectors(.false.,nBas,nC,nO,nV,nR,nS,dipole_int,Om,XpY,XmY)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
endif
|
|
|
|
|
2023-07-18 11:53:38 +02:00
|
|
|
if(exchange_kernel) then
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2023-07-31 16:01:12 +02:00
|
|
|
EcRPA(1) = 0.5d0*EcRPA(1)
|
|
|
|
EcRPA(2) = 1.5d0*EcRPA(2)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2023-07-18 11:53:38 +02:00
|
|
|
end if
|
2021-11-10 09:42:30 +01:00
|
|
|
|
|
|
|
write(*,*)
|
|
|
|
write(*,*)'-------------------------------------------------------------------------------'
|
2023-07-31 16:01:12 +02:00
|
|
|
write(*,'(2X,A50,F20.10)') 'Tr@crRPA correlation energy (singlet) =',EcRPA(1)
|
|
|
|
write(*,'(2X,A50,F20.10)') 'Tr@crRPA correlation energy (triplet) =',EcRPA(2)
|
|
|
|
write(*,'(2X,A50,F20.10)') 'Tr@crRPA correlation energy =',EcRPA(1) + EcRPA(2)
|
|
|
|
write(*,'(2X,A50,F20.10)') 'Tr@crRPA total energy =',ENuc + EHF + EcRPA(1) + EcRPA(2)
|
2021-11-10 09:42:30 +01:00
|
|
|
write(*,*)'-------------------------------------------------------------------------------'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
! Compute the correlation energy via the adiabatic connection
|
|
|
|
|
2021-11-10 22:41:40 +01:00
|
|
|
if(doACFDT) then
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2021-11-10 22:41:40 +01:00
|
|
|
write(*,*) '-------------------------------------------------------'
|
|
|
|
write(*,*) 'Adiabatic connection version of crRPA correlation energy'
|
|
|
|
write(*,*) '-------------------------------------------------------'
|
|
|
|
write(*,*)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2023-07-31 16:01:12 +02:00
|
|
|
call crACFDT(exchange_kernel,dRPA,TDA,singlet,triplet,nBas,nC,nO,nV,nR,nS,ERI,e,EcRPA)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2021-11-10 22:41:40 +01:00
|
|
|
write(*,*)
|
|
|
|
write(*,*)'-------------------------------------------------------------------------------'
|
2023-07-31 16:01:12 +02:00
|
|
|
write(*,'(2X,A50,F20.10)') 'AC@crRPA correlation energy (singlet) =',EcRPA(1)
|
|
|
|
write(*,'(2X,A50,F20.10)') 'AC@crRPA correlation energy (triplet) =',EcRPA(2)
|
|
|
|
write(*,'(2X,A50,F20.10)') 'AC@crRPA correlation energy =',EcRPA(1) + EcRPA(2)
|
|
|
|
write(*,'(2X,A50,F20.10)') 'AC@crRPA total energy =',ENuc + EHF + EcRPA(1) + EcRPA(2)
|
2021-11-10 22:41:40 +01:00
|
|
|
write(*,*)'-------------------------------------------------------------------------------'
|
|
|
|
write(*,*)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2021-11-10 22:41:40 +01:00
|
|
|
end if
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2023-07-17 15:17:02 +02:00
|
|
|
end subroutine
|