4
1
mirror of https://github.com/pfloos/quack synced 2024-06-02 03:15:31 +02:00
quack/src/LR/unrestricted_linear_response_C_pp.f90
2021-12-16 12:28:28 +01:00

116 lines
2.8 KiB
Fortran

subroutine unrestricted_linear_response_C_pp(ispin,nBas,nC,nO,nV,nR,nPaa,nPab,nPbb,nPt,lambda,&
e,ERI_aaaa,ERI_aabb,ERI_bbbb,C_pp)
! Compute linear response
implicit none
include 'parameters.h'
! Input variables
integer,intent(in) :: ispin
integer,intent(in) :: nBas
integer,intent(in) :: nC(nspin)
integer,intent(in) :: nO(nspin)
integer,intent(in) :: nV(nspin)
integer,intent(in) :: nR(nspin)
integer,intent(in) :: nPaa
integer,intent(in) :: nPab
integer,intent(in) :: nPbb
integer,intent(in) :: nPt
double precision,intent(in) :: lambda
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
double precision :: eF
double precision,external :: Kronecker_delta
integer :: i,j,a,b,c,d,ab,cd
! Output variables
double precision,intent(out) :: C_pp(nPt,nPt)
eF = 0d0
!-----------------------------------------------
! Build C matrix for spin-conserving transitions
!-----------------------------------------------
if(ispin == 1) then
! aaaa block
ab = 0
do a=nO(1)+1,nBas-nR(1)
do b=a,nBas-nR(1)
ab = ab + 1
cd = 0
do c=nO(1)+1,nBas-nR(1)
do d=c,nBas-nR(1)
cd = cd + 1
C_pp(ab,cd) = (e(a,1) + e(b,1) - eF)*Kronecker_delta(a,c)*Kronecker_delta(b,d) &
+ lambda*(ERI_aaaa(a,b,c,d) - ERI_aaaa(a,b,d,c))
!write(*,*) C_pp(ab,cd)
end do
end do
end do
end do
! bbbb block
ab = 0
do a=nO(2)+1,nBas-nR(2)
do b=a,nBas-nR(2)
ab = ab + 1
cd = 0
do c=nO(2)+1,nBas-nR(2)
do d=c,nBas-nR(2)
cd = cd + 1
C_pp(nPaa+ab,nPaa+cd) = (e(a,2) + e(b,2) - eF)*Kronecker_delta(a,c) &
*Kronecker_delta(b,d) + lambda*(ERI_bbbb(a,b,c,d) - ERI_bbbb(a,b,d,c))
!write(*,*) 'nPaa+ab',nPaa+ab
end do
end do
end do
end do
end if
!
!-----------------------------------------------
! Build C matrix for spin-flip transitions
!-----------------------------------------------
if(ispin == 2) then
C_pp(:,:) = 0d0
! abab block
ab = 0
do a=nO(1)+1,nBas-nR(1)
do b=nO(2)+1,nBas-nR(2)
ab = ab + 1
cd = 0
do c=nO(1)+1,nBas-nR(1)
do d=nO(2)+1,nBas-nR(2)
cd = cd + 1
C_pp(ab,cd) = (e(a,1) + e(b,2))*Kronecker_delta(a,c) &
*Kronecker_delta(b,c) + lambda*ERI_aabb(a,b,c,d)
end do
end do
end do
end do
end if
end subroutine unrestricted_linear_response_C_pp