4
1
mirror of https://github.com/pfloos/quack synced 2024-06-02 11:25:28 +02:00
quack/src/RPA/ppURPA.f90

168 lines
5.4 KiB
Fortran
Raw Normal View History

2023-11-11 23:00:00 +01:00
subroutine ppURPA(dotest,TDA,doACFDT,spin_conserved,spin_flip,nBas,nC,nO,nV,nR,ENuc,EUHF,ERI_aaaa,ERI_aabb,ERI_bbbb,e)
2021-12-13 14:28:05 +01:00
! Perform unrestricted pp-RPA calculations
implicit none
include 'parameters.h'
! Input variables
2023-11-11 23:00:00 +01:00
logical,intent(in) :: dotest
2021-12-13 14:28:05 +01:00
logical,intent(in) :: TDA
logical,intent(in) :: doACFDT
logical,intent(in) :: spin_conserved
logical,intent(in) :: spin_flip
integer,intent(in) :: nBas
integer,intent(in) :: nC(nspin)
integer,intent(in) :: nO(nspin)
integer,intent(in) :: nV(nspin)
integer,intent(in) :: nR(nspin)
double precision,intent(in) :: ENuc
double precision,intent(in) :: EUHF
double precision,intent(in) :: e(nBas,nspin)
double precision,intent(in) :: ERI_aaaa(nBas,nBas,nBas,nBas)
double precision,intent(in) :: ERI_aabb(nBas,nBas,nBas,nBas)
double precision,intent(in) :: ERI_bbbb(nBas,nBas,nBas,nBas)
! Local variables
2022-01-29 13:51:06 +01:00
integer :: ispin,iblock
2021-12-16 12:28:28 +01:00
integer :: nPaa,nPbb,nPab,nP_sc,nP_sf
integer :: nHaa,nHbb,nHab,nH_sc,nH_sf
2023-07-21 13:04:29 +02:00
double precision,allocatable :: Om1sc(:),Om1sf(:)
2021-12-16 12:28:28 +01:00
double precision,allocatable :: X1sc(:,:),X1sf(:,:)
double precision,allocatable :: Y1sc(:,:),Y1sf(:,:)
2023-07-21 13:04:29 +02:00
double precision,allocatable :: Om2sc(:),Om2sf(:)
2021-12-16 12:28:28 +01:00
double precision,allocatable :: X2sc(:,:),X2sf(:,:)
double precision,allocatable :: Y2sc(:,:),Y2sf(:,:)
2023-11-11 23:00:00 +01:00
double precision :: EcRPA(nspin)
2021-12-13 14:28:05 +01:00
double precision :: EcAC(nspin)
! Hello world
write(*,*)
2023-11-11 23:00:00 +01:00
write(*,*)'***********************************'
write(*,*)'* Unrestricted pp-RPA Calculation *'
write(*,*)'***********************************'
2021-12-13 14:28:05 +01:00
write(*,*)
! Initialization
2023-11-11 23:00:00 +01:00
EcRPA(:) = 0d0
2021-12-13 14:28:05 +01:00
EcAC(:) = 0d0
2022-02-15 13:51:18 +01:00
!alpha-beta block
2021-12-16 12:28:28 +01:00
2022-02-15 13:51:18 +01:00
ispin = 1
iblock = 3
2021-12-16 12:28:28 +01:00
2022-02-15 13:51:18 +01:00
nPab = nV(1)*nV(2)
nHab = nO(1)*nO(2)
2021-12-16 12:28:28 +01:00
2022-02-15 13:51:18 +01:00
nP_sc = nPab
nH_sc = nHab
2021-12-13 14:28:05 +01:00
2021-12-31 12:49:13 +01:00
! Memory allocation
2021-12-13 14:28:05 +01:00
2023-07-21 13:04:29 +02:00
allocate(Om1sc(nP_sc),X1sc(nP_sc,nP_sc),Y1sc(nH_sc,nP_sc), &
Om2sc(nH_sc),X2sc(nP_sc,nH_sc),Y2sc(nH_sc,nH_sc))
2021-12-13 14:28:05 +01:00
2023-07-21 13:04:29 +02:00
call ppULR(iblock,TDA,nBas,nC,nO,nV,nR,nPaa,nPab,nPbb, &
nP_sc,nHaa,nHab,nHbb,nH_sc,1d0,e,ERI_aaaa, &
ERI_aabb,ERI_bbbb,Om1sc,X1sc,Y1sc, &
2023-11-11 23:00:00 +01:00
Om2sc,X2sc,Y2sc,EcRPA(ispin))
2022-01-29 13:51:06 +01:00
2023-11-22 10:07:23 +01:00
call print_excitation_energies('ppRPA@UHF','2p (alpha-beta)',nP_sc,Om1sc)
call print_excitation_energies('ppRPA@UHF','2h (alpha-beta)',nH_sc,Om2sc)
2021-12-13 14:28:05 +01:00
2022-02-15 13:51:18 +01:00
!alpha-alpha block
2021-12-13 14:28:05 +01:00
2022-02-15 13:51:18 +01:00
ispin = 2
iblock = 4
2021-12-13 14:28:05 +01:00
2022-02-15 13:51:18 +01:00
nPaa = nV(1)*(nV(1)-1)/2
nPbb = nV(2)*(nV(2)-1)/2
2021-12-13 14:28:05 +01:00
2022-02-15 13:51:18 +01:00
nP_sf = nPaa
2021-12-31 12:49:13 +01:00
2022-02-15 13:51:18 +01:00
nHaa = nO(1)*(nO(1)-1)/2
nHbb = nO(2)*(nO(2)-1)/2
2021-12-31 12:49:13 +01:00
2022-02-15 13:51:18 +01:00
nH_sf = nHaa
2021-12-31 12:49:13 +01:00
2023-07-21 13:04:29 +02:00
allocate(Om1sf(nP_sf),X1sf(nP_sf,nP_sf),Y1sf(nH_sf,nP_sf), &
Om2sf(nH_sf),X2sf(nP_sf,nH_sf),Y2sf(nH_sf,nH_sf))
2021-12-31 12:49:13 +01:00
2023-07-21 13:04:29 +02:00
call ppULR(iblock,TDA,nBas,nC,nO,nV,nR,nPaa,nPab,nPbb, &
nP_sf,nHaa,nHab,nHbb,nH_sf,1d0,e,ERI_aaaa, &
ERI_aabb,ERI_bbbb,Om1sf,X1sf,Y1sf, &
2023-11-11 23:00:00 +01:00
Om2sf,X2sf,Y2sf,EcRPA(ispin))
2021-12-31 12:49:13 +01:00
2023-11-22 10:07:23 +01:00
call print_excitation_energies('ppRPA@UHF','2h (alpha-alpha)',nP_sf,Om1sf)
call print_excitation_energies('ppRPA@UHF','2p (alpha-alpha)',nH_sf,Om2sf)
2021-12-31 12:49:13 +01:00
2023-07-21 13:04:29 +02:00
deallocate(Om1sf,X1sf,Y1sf,Om2sf,X2sf,Y2sf)
2021-12-31 12:49:13 +01:00
2022-02-15 13:51:18 +01:00
!beta-beta block
2022-01-29 13:51:06 +01:00
2022-02-15 13:51:18 +01:00
iblock = 7
2021-12-31 12:49:13 +01:00
2022-02-15 13:51:18 +01:00
nP_sf = nPbb
nH_sf = nHbb
2021-12-31 12:49:13 +01:00
2023-07-21 13:04:29 +02:00
allocate(Om1sf(nP_sf),X1sf(nP_sf,nP_sf),Y1sf(nH_sf,nP_sf), &
Om2sf(nH_sf),X2sf(nP_sf,nH_sf),Y2sf(nH_sf,nH_sf))
2021-12-31 12:49:13 +01:00
2023-07-21 13:04:29 +02:00
call ppULR(iblock,TDA,nBas,nC,nO,nV,nR,nPaa,nPab,nPbb,&
nP_sf,nHaa,nHab,nHbb,nH_sf,1d0,e,ERI_aaaa,&
ERI_aabb,ERI_bbbb,Om1sf,X1sf,Y1sf,&
2023-11-11 23:00:00 +01:00
Om2sf,X2sf,Y2sf,EcRPA(ispin))
2021-12-13 14:28:05 +01:00
2023-11-22 10:07:23 +01:00
call print_excitation_energies('ppRPA@UHF','2p (beta-beta)',nP_sf,Om1sf)
call print_excitation_energies('ppRPA@UHF','2h (beta-beta)',nH_sf,Om2sf)
2021-12-13 14:28:05 +01:00
2023-11-11 23:00:00 +01:00
EcRPA(2) = 3d0*EcRPA(2)
2021-12-13 14:28:05 +01:00
write(*,*)
write(*,*)'-------------------------------------------------------------------------------'
2023-11-11 23:00:00 +01:00
write(*,'(2X,A50,F20.10,A3)') 'Tr@ppURPA correlation energy (spin-conserved) = ',EcRPA(1),' au'
write(*,'(2X,A50,F20.10,A3)') 'Tr@ppURPA correlation energy (spin-flip) = ',EcRPA(2),' au'
write(*,'(2X,A50,F20.10,A3)') 'Tr@ppURPA correlation energy = ',sum(EcRPA),' au'
write(*,'(2X,A50,F20.10,A3)') 'Tr@ppURPA total energy = ',ENuc + EUHF + sum(EcRPA),' au'
2021-12-13 14:28:05 +01:00
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)
! 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_pp(TDA,singlet,triplet,nBas,nC,nO,nV,nR,nS,ERI,e,EcAC)
! 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
2023-11-14 14:31:27 +01:00
! Testing zone
2023-11-11 23:00:00 +01:00
if(dotest) then
2023-11-14 14:31:27 +01:00
call dump_test_value('U','ppRPA correlation energy',sum(EcRPA))
2023-11-11 23:00:00 +01:00
end if
2023-07-21 13:04:29 +02:00
end subroutine