4
1
mirror of https://github.com/pfloos/quack synced 2024-06-02 03:15:31 +02:00
quack/src/RPA/ppRPA.f90

142 lines
4.5 KiB
Fortran
Raw Normal View History

2021-11-10 22:41:40 +01:00
subroutine ppRPA(TDA,doACFDT,exchange_kernel,singlet,triplet,eta,nBas,nC,nO,nV,nR,ENuc,ERHF,ERI,e)
2019-10-05 23:09:20 +02:00
! Perform pp-RPA calculation
implicit none
include 'parameters.h'
! Input variables
2021-10-18 22:05:26 +02:00
logical,intent(in) :: TDA
2021-11-10 22:41:40 +01:00
logical,intent(in) :: doACFDT
logical,intent(in) :: exchange_kernel
2021-10-18 22:05:26 +02:00
logical,intent(in) :: singlet
logical,intent(in) :: triplet
2021-11-10 22:41:40 +01:00
double precision,intent(in) :: eta
2019-10-05 23:09:20 +02:00
integer,intent(in) :: nBas
integer,intent(in) :: nC
integer,intent(in) :: nO
integer,intent(in) :: nV
integer,intent(in) :: nR
double precision,intent(in) :: ENuc
double precision,intent(in) :: ERHF
double precision,intent(in) :: e(nBas)
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
! Local variables
integer :: ispin
2021-11-10 22:41:40 +01:00
integer :: nS
integer :: nOOs,nOOt
integer :: nVVs,nVVt
double precision,allocatable :: Omega1s(:),Omega1t(:)
double precision,allocatable :: X1s(:,:),X1t(:,:)
double precision,allocatable :: Y1s(:,:),Y1t(:,:)
double precision,allocatable :: Omega2s(:),Omega2t(:)
double precision,allocatable :: X2s(:,:),X2t(:,:)
double precision,allocatable :: Y2s(:,:),Y2t(:,:)
2019-10-05 23:09:20 +02:00
double precision :: Ec_ppRPA(nspin)
2021-11-10 22:41:40 +01:00
double precision :: EcAC(nspin)
2019-10-05 23:09:20 +02:00
! Hello world
write(*,*)
2019-10-05 23:32:17 +02:00
write(*,*)'****************************************'
write(*,*)'| particle-particle RPA calculation |'
write(*,*)'****************************************'
2019-10-05 23:09:20 +02:00
write(*,*)
! Initialization
Ec_ppRPA(:) = 0d0
2021-11-10 22:41:40 +01:00
EcAC(:) = 0d0
2019-10-05 23:09:20 +02:00
2021-11-10 22:41:40 +01:00
! Useful quantities
2019-10-05 23:09:20 +02:00
2021-11-10 22:41:40 +01:00
nS = nO*nV
2019-10-05 23:09:20 +02:00
2021-11-10 22:41:40 +01:00
nOOs = nO*(nO+1)/2
nVVs = nV*(nV+1)/2
2019-10-05 23:09:20 +02:00
2021-11-10 22:41:40 +01:00
nOOt = nO*(nO-1)/2
nVVt = nV*(nV-1)/2
2019-10-07 22:31:45 +02:00
2021-11-10 22:41:40 +01:00
! Memory allocation
2019-10-07 22:31:45 +02:00
2021-11-10 22:41:40 +01:00
allocate(Omega1s(nVVs),X1s(nVVs,nVVs),Y1s(nOOs,nVVs), &
Omega2s(nOOs),X2s(nVVs,nOOs),Y2s(nOOs,nOOs))
allocate(Omega1t(nVVt),X1t(nVVt,nVVt),Y1t(nOOt,nVVt), &
Omega2t(nOOt),X2t(nVVt,nOOt),Y2t(nOOt,nOOt))
! Singlet manifold
2019-10-07 22:31:45 +02:00
2021-11-10 22:41:40 +01:00
if(singlet) then
2019-10-07 22:31:45 +02:00
2021-11-10 22:41:40 +01:00
ispin = 1
2019-10-07 22:31:45 +02:00
2021-11-10 22:41:40 +01:00
call linear_response_pp(ispin,TDA,nBas,nC,nO,nV,nR,nOOs,nVVs,1d0,e,ERI, &
Omega1s,X1s,Y1s,Omega2s,X2s,Y2s,Ec_ppRPA(ispin))
2019-10-05 23:09:20 +02:00
2021-11-10 22:41:40 +01:00
call print_excitation('pp-RPA (N+2)',ispin,nVVs,Omega1s)
call print_excitation('pp-RPA (N-2)',ispin,nOOs,Omega2s)
2019-10-07 22:31:45 +02:00
2019-10-05 23:09:20 +02:00
endif
! Triplet manifold
2021-10-18 22:05:26 +02:00
if(triplet) then
2019-10-05 23:09:20 +02:00
ispin = 2
2021-11-10 22:41:40 +01:00
call linear_response_pp(ispin,TDA,nBas,nC,nO,nV,nR,nOOt,nVVt,1d0,e,ERI, &
Omega1t,X1t,Y1t,Omega2t,X2t,Y2t,Ec_ppRPA(ispin))
2019-10-07 22:31:45 +02:00
2021-11-10 22:41:40 +01:00
call print_excitation('pp-RPA (N+2)',ispin,nVVt,Omega1t)
call print_excitation('pp-RPA (N-2)',ispin,nOOt,Omega2t)
2019-10-07 22:31:45 +02:00
2019-10-05 23:09:20 +02:00
endif
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
2020-03-21 22:50:43 +01:00
write(*,'(2X,A50,F20.10)') 'Tr@ppRPA correlation energy (singlet) =',Ec_ppRPA(1)
write(*,'(2X,A50,F20.10)') 'Tr@ppRPA correlation energy (triplet) =',3d0*Ec_ppRPA(2)
write(*,'(2X,A50,F20.10)') 'Tr@ppRPA correlation energy =',Ec_ppRPA(1) + 3d0*Ec_ppRPA(2)
write(*,'(2X,A50,F20.10)') 'Tr@ppRPA total energy =',ENuc + ERHF + Ec_ppRPA(1) + 3d0*Ec_ppRPA(2)
2019-10-05 23:09:20 +02:00
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
2021-11-10 22:41:40 +01:00
! Compute the correlation energy via the adiabatic connection
if(doACFDT) then
write(*,*) '---------------------------------------------------------'
write(*,*) 'Adiabatic connection version of pp-RPA correlation energy'
write(*,*) '---------------------------------------------------------'
write(*,*)
call ACFDT_Tmatrix(exchange_kernel,.false.,.false.,.false.,TDA,.false.,singlet,triplet,eta,nBas,nC,nO,nV,nR,nS, &
ERI,e,e,EcAC)
if(exchange_kernel) then
EcAC(1) = 0.5d0*EcAC(1)
EcAC(2) = 1.5d0*EcAC(1)
end if
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
write(*,'(2X,A50,F20.10,A3)') 'AC@ppRPA correlation energy (singlet) =',EcAC(1),' au'
write(*,'(2X,A50,F20.10,A3)') 'AC@ppRPA correlation energy (triplet) =',EcAC(2),' au'
write(*,'(2X,A50,F20.10,A3)') 'AC@ppRPA correlation energy =',EcAC(1) + EcAC(2),' au'
write(*,'(2X,A50,F20.10,A3)') 'AC@ppRPA total energy =',ENuc + ERHF + EcAC(1) + EcAC(2),' au'
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
end if
2019-10-05 23:09:20 +02:00
end subroutine ppRPA