4
1
mirror of https://github.com/pfloos/quack synced 2024-06-26 15:12:17 +02:00
quack/src/RPA/phRRPA.f90

145 lines
4.4 KiB
Fortran
Raw Normal View History

2023-11-11 23:00:00 +01:00
subroutine phRRPA(dotest,TDA,doACFDT,exchange_kernel,singlet,triplet,nBas,nC,nO,nV,nR,nS,ENuc,EHF,ERI,dipole_int,e)
2020-01-13 23:08:03 +01:00
! Perform a direct random phase approximation calculation
implicit none
include 'parameters.h'
include 'quadrature.h'
! Input variables
2023-11-11 23:00:00 +01:00
logical,intent(in) :: dotest
2020-09-24 16:39:15 +02:00
logical,intent(in) :: TDA
2020-01-14 21:27:34 +01:00
logical,intent(in) :: doACFDT
2020-01-16 21:39:00 +01:00
logical,intent(in) :: exchange_kernel
2020-09-24 11:56:06 +02:00
logical,intent(in) :: singlet
logical,intent(in) :: triplet
2020-01-13 23:08:03 +01:00
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)
2020-01-13 23:08:03 +01:00
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
2020-01-13 23:08:03 +01:00
! 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(:,:)
2020-01-13 23:08:03 +01:00
2023-07-31 16:01:12 +02:00
double precision :: EcRPA(nspin)
2020-01-13 23:08:03 +01:00
! Hello world
write(*,*)
write(*,*)'*********************************'
write(*,*)'* Restricted ph-RPA Calculation *'
write(*,*)'*********************************'
2020-01-13 23:08:03 +01:00
write(*,*)
2020-09-30 09:59:18 +02:00
! TDA
if(TDA) then
write(*,*) 'Tamm-Dancoff approximation activated!'
write(*,*)
end if
2020-01-13 23:08:03 +01:00
! Initialization
2023-07-18 11:53:38 +02:00
dRPA = .true.
2023-07-31 16:01:12 +02:00
EcRPA(:) = 0d0
2020-01-13 23:08:03 +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))
2020-01-13 23:08:03 +01:00
! Singlet manifold
2020-09-24 11:56:06 +02:00
if(singlet) then
2020-01-13 23:08:03 +01:00
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('phRPA@HF',ispin,nS,Om)
call phLR_transition_vectors(.true.,nBas,nC,nO,nV,nR,nS,dipole_int,Om,XpY,XmY)
2020-01-13 23:08:03 +01:00
endif
! Triplet manifold
2020-09-24 11:56:06 +02:00
if(triplet) then
2020-01-13 23:08:03 +01:00
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:35:14 +02:00
call print_excitation_energies('phRPA@HF',ispin,nS,Om)
2023-07-28 14:14:35 +02:00
call phLR_transition_vectors(.false.,nBas,nC,nO,nV,nR,nS,dipole_int,Om,XpY,XmY)
2020-01-13 23:08:03 +01:00
endif
2023-07-18 11:53:38 +02:00
if(exchange_kernel) then
2020-01-17 13:45:02 +01:00
2023-07-31 16:01:12 +02:00
EcRPA(1) = 0.5d0*EcRPA(1)
EcRPA(2) = 1.5d0*EcRPA(2)
2020-01-17 13:45:02 +01:00
2023-07-18 11:53:38 +02:00
end if
2020-01-17 13:45:02 +01:00
2020-01-13 23:08:03 +01:00
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
2023-11-11 23:00:00 +01:00
write(*,'(2X,A50,F20.10,A3)') 'Tr@phRRPA correlation energy (singlet) = ',EcRPA(1),' au'
write(*,'(2X,A50,F20.10,A3)') 'Tr@phRRPA correlation energy (triplet) = ',EcRPA(2),' au'
write(*,'(2X,A50,F20.10,A3)') 'Tr@phRRPA correlation energy = ',sum(EcRPA),' au'
write(*,'(2X,A50,F20.10,A3)') 'Tr@phRRPA total energy = ',ENuc + EHF + sum(EcRPA),' au'
2020-01-13 23:08:03 +01:00
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
2023-07-18 11:53:38 +02:00
deallocate(Om,XpY,XmY,Aph,Bph)
2020-01-14 16:36:11 +01:00
! Compute the correlation energy via the adiabatic connection
2020-01-13 23:08:03 +01:00
2020-03-13 09:18:18 +01:00
if(doACFDT) then
2023-07-18 11:53:38 +02:00
write(*,*) '--------------------------------------------------------'
write(*,*) 'Adiabatic connection version of phRPA correlation energy'
write(*,*) '--------------------------------------------------------'
2020-03-13 09:18:18 +01:00
write(*,*)
2023-07-31 16:01:12 +02:00
call phACFDT(exchange_kernel,dRPA,TDA,singlet,triplet,nBas,nC,nO,nV,nR,nS,ERI,e,EcRPA)
2020-03-13 09:18:18 +01:00
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
2023-11-11 23:00:00 +01:00
write(*,'(2X,A50,F20.10,A3)') 'AC@phRRPA correlation energy (singlet) = ',EcRPA(1),' au'
write(*,'(2X,A50,F20.10,A3)') 'AC@phRRPA correlation energy (triplet) = ',EcRPA(2),' au'
write(*,'(2X,A50,F20.10,A3)') 'AC@phRRPA correlation energy = ',sum(EcRPA),' au'
write(*,'(2X,A50,F20.10,A3)') 'AC@phRRPA total energy = ',ENuc + EHF + sum(EcRPA),' au'
2020-03-13 09:18:18 +01:00
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
end if
2020-01-13 23:08:03 +01:00
2023-11-11 23:00:00 +01:00
if(dotest) then
call dump_test_value('R','phRRPA correlation energy',sum(EcRPA))
end if
end subroutine