4
1
mirror of https://github.com/pfloos/quack synced 2024-06-21 20:52:21 +02:00
quack/src/RPA/RPA.f90

139 lines
4.5 KiB
Fortran
Raw Normal View History

2020-10-07 22:51:30 +02:00
subroutine RPA(TDA,doACFDT,exchange_kernel,singlet,triplet,eta,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,dipole_int,eHF)
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
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-23 21:22:41 +01:00
double precision,intent(in) :: eta
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
double precision,intent(in) :: ERHF
2020-09-24 11:56:06 +02:00
double precision,intent(in) :: eHF(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
double precision,allocatable :: Omega(:,:)
double precision,allocatable :: XpY(:,:,:)
2020-01-14 14:44:01 +01:00
double precision,allocatable :: XmY(:,:,:)
2020-01-13 23:08:03 +01:00
double precision :: rho
double precision :: EcRPA(nspin)
2020-01-14 22:56:20 +01:00
double precision :: EcAC(nspin)
2020-01-13 23:08:03 +01:00
! Hello world
write(*,*)
write(*,*)'***********************************************'
2020-09-24 11:56:06 +02:00
write(*,*)'| Random-phase approximation calculation |'
2020-01-13 23:08:03 +01:00
write(*,*)'***********************************************'
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
EcRPA(:) = 0d0
2020-01-14 22:56:20 +01:00
EcAC(:) = 0d0
2020-01-13 23:08:03 +01:00
! Memory allocation
2020-01-14 14:44:01 +01:00
allocate(Omega(nS,nspin),XpY(nS,nS,nspin),XmY(nS,nS,nspin))
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
2020-09-24 16:39:15 +02:00
call linear_response(ispin,.true.,TDA,.false.,eta,nBas,nC,nO,nV,nR,nS,1d0,eHF,ERI,rho,Omega(:,ispin), &
2020-01-14 14:44:01 +01:00
EcRPA(ispin),Omega(:,ispin),XpY(:,:,ispin),XmY(:,:,ispin))
2020-09-24 11:56:06 +02:00
call print_excitation('RPA@HF ',ispin,nS,Omega(:,ispin))
call print_transition_vectors(.true.,nBas,nC,nO,nV,nR,nS,dipole_int,Omega(:,ispin),XpY(:,:,ispin),XmY(:,:,ispin))
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
2020-09-24 16:39:15 +02:00
call linear_response(ispin,.true.,TDA,.false.,eta,nBas,nC,nO,nV,nR,nS,1d0,eHF,ERI,rho,Omega(:,ispin), &
2020-01-14 14:44:01 +01:00
EcRPA(ispin),Omega(:,ispin),XpY(:,:,ispin),XmY(:,:,ispin))
2020-09-24 11:56:06 +02:00
call print_excitation('RPA@HF ',ispin,nS,Omega(:,ispin))
call print_transition_vectors(.false.,nBas,nC,nO,nV,nR,nS,dipole_int,Omega(:,ispin),XpY(:,:,ispin),XmY(:,:,ispin))
2020-01-13 23:08:03 +01:00
endif
2020-01-17 13:45:02 +01:00
if(exchange_kernel) then
EcRPA(1) = 0.5d0*EcRPA(1)
2020-09-24 11:56:06 +02:00
EcRPA(2) = 1.5d0*EcRPA(2)
2020-01-17 13:45:02 +01:00
end if
2020-01-13 23:08:03 +01:00
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
2020-01-23 21:22:41 +01:00
write(*,'(2X,A50,F20.10)') 'Tr@RPA correlation energy (singlet) =',EcRPA(1)
write(*,'(2X,A50,F20.10)') 'Tr@RPA correlation energy (triplet) =',EcRPA(2)
write(*,'(2X,A50,F20.10)') 'Tr@RPA correlation energy =',EcRPA(1) + EcRPA(2)
write(*,'(2X,A50,F20.10)') 'Tr@RPA total energy =',ENuc + ERHF + EcRPA(1) + EcRPA(2)
2020-01-13 23:08:03 +01:00
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
2020-01-14 16:36:11 +01:00
! Compute the correlation energy via the adiabatic connection
2020-01-25 15:49:09 +01:00
! Switch off ACFDT for RPA as the trace formula is equivalent
2020-01-13 23:08:03 +01:00
2020-03-13 09:18:18 +01:00
if(doACFDT) then
write(*,*) '------------------------------------------------------'
write(*,*) 'Adiabatic connection version of RPA correlation energy'
write(*,*) '------------------------------------------------------'
write(*,*)
2020-09-24 16:39:15 +02:00
call ACFDT(exchange_kernel,.false.,.true.,.false.,TDA,.false.,singlet,triplet,eta, &
2020-09-24 11:56:06 +02:00
nBas,nC,nO,nV,nR,nS,ERI,eHF,eHF,EcAC)
2020-03-13 09:18:18 +01:00
if(exchange_kernel) then
EcAC(1) = 0.5d0*EcAC(1)
2020-09-24 11:56:06 +02:00
EcAC(2) = 1.5d0*EcAC(2)
2020-03-13 09:18:18 +01:00
end if
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
write(*,'(2X,A50,F20.10)') 'AC@RPA correlation energy (singlet) =',EcAC(1)
write(*,'(2X,A50,F20.10)') 'AC@RPA correlation energy (triplet) =',EcAC(2)
write(*,'(2X,A50,F20.10)') 'AC@RPA correlation energy =',EcAC(1) + EcAC(2)
write(*,'(2X,A50,F20.10)') 'AC@RPA total energy =',ENuc + ERHF + EcAC(1) + EcAC(2)
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
end if
2020-01-13 23:08:03 +01:00
2020-10-07 22:51:30 +02:00
end subroutine RPA