2019-09-11 14:47:18 +02:00
|
|
|
subroutine CCSD_Ec_nc(nO,nV,t1,t2,Fov,OOVV,EcCCSD)
|
|
|
|
|
|
|
|
! Compute the CCSD correlatio energy in non-conanical form
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
|
|
|
integer,intent(in) :: nO,nV
|
|
|
|
|
|
|
|
double precision,intent(in) :: t1(nO,nV)
|
|
|
|
double precision,intent(in) :: t2(nO,nO,nV,nV)
|
|
|
|
|
|
|
|
double precision,intent(in) :: Fov(nO,nV)
|
|
|
|
|
|
|
|
double precision,intent(in) :: OOVV(nO,nO,nV,nV)
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
integer :: i,j,a,b
|
|
|
|
|
|
|
|
! Output variables
|
|
|
|
|
|
|
|
double precision,intent(out) :: EcCCSD
|
|
|
|
|
|
|
|
! Compute CCSD correlation energy
|
|
|
|
|
|
|
|
EcCCSD = 0d0
|
|
|
|
|
|
|
|
! Singles contribution
|
|
|
|
|
|
|
|
do i=1,nO
|
2019-09-11 20:56:36 +02:00
|
|
|
do a=1,nV
|
2019-09-11 14:47:18 +02:00
|
|
|
|
|
|
|
EcCCSD = EcCCSD + Fov(i,a)*t1(i,a)
|
|
|
|
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
! Doubles contribution
|
|
|
|
|
|
|
|
do i=1,nO
|
|
|
|
do j=1,nO
|
2019-09-11 20:56:36 +02:00
|
|
|
do a=1,nV
|
|
|
|
do b=1,nV
|
2019-09-11 14:47:18 +02:00
|
|
|
|
|
|
|
EcCCSD = EcCCSD &
|
|
|
|
+ 0.5d0*OOVV(i,j,a,b)*t1(i,a)*t1(j,b) &
|
|
|
|
+ 0.25d0*OOVV(i,j,a,b)*t2(i,j,a,b)
|
|
|
|
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
end subroutine CCSD_Ec_nc
|