2023-07-04 10:32:47 +02:00
|
|
|
subroutine GTpp_self_energy_diag(eta,nBas,nC,nO,nV,nR,nOO,nVV,e,Omega1,rho1,Omega2,rho2,EcGM,SigT)
|
2019-10-06 22:35:36 +02:00
|
|
|
|
|
|
|
! Compute diagonal of the correlation part of the T-matrix self-energy
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
|
|
|
double precision,intent(in) :: eta
|
|
|
|
integer,intent(in) :: nBas
|
|
|
|
integer,intent(in) :: nC
|
|
|
|
integer,intent(in) :: nO
|
|
|
|
integer,intent(in) :: nV
|
|
|
|
integer,intent(in) :: nR
|
2020-04-09 14:31:50 +02:00
|
|
|
integer,intent(in) :: nOO
|
|
|
|
integer,intent(in) :: nVV
|
2019-10-06 22:35:36 +02:00
|
|
|
double precision,intent(in) :: e(nBas)
|
2020-04-09 14:31:50 +02:00
|
|
|
double precision,intent(in) :: Omega1(nVV)
|
2021-10-16 15:34:34 +02:00
|
|
|
double precision,intent(in) :: rho1(nBas,nBas,nVV)
|
2020-04-09 14:31:50 +02:00
|
|
|
double precision,intent(in) :: Omega2(nOO)
|
2021-10-16 15:34:34 +02:00
|
|
|
double precision,intent(in) :: rho2(nBas,nBas,nOO)
|
2019-10-06 22:35:36 +02:00
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
2022-01-06 13:48:15 +01:00
|
|
|
integer :: i,j,a,b,p,cd,kl
|
2019-10-06 22:35:36 +02:00
|
|
|
double precision :: eps
|
|
|
|
|
|
|
|
! Output variables
|
|
|
|
|
2022-01-06 13:48:15 +01:00
|
|
|
double precision,intent(inout) :: EcGM
|
2021-10-17 23:04:22 +02:00
|
|
|
double precision,intent(inout) :: SigT(nBas)
|
2019-10-06 22:35:36 +02:00
|
|
|
|
2019-10-20 08:18:58 +02:00
|
|
|
!----------------------------------------------
|
|
|
|
! Occupied part of the T-matrix self-energy
|
2021-10-16 18:51:53 +02:00
|
|
|
!----------------------------------------------
|
2019-10-06 22:35:36 +02:00
|
|
|
|
|
|
|
do p=nC+1,nBas-nR
|
|
|
|
do i=nC+1,nO
|
2020-04-09 14:31:50 +02:00
|
|
|
do cd=1,nVV
|
2022-01-02 10:24:30 +01:00
|
|
|
eps = e(p) + e(i) - Omega1(cd)
|
2021-10-16 18:51:53 +02:00
|
|
|
SigT(p) = SigT(p) + rho1(p,i,cd)**2*eps/(eps**2 + eta**2)
|
2019-10-06 22:35:36 +02:00
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2021-10-16 18:51:53 +02:00
|
|
|
!----------------------------------------------
|
|
|
|
! Virtual part of the T-matrix self-energy
|
|
|
|
!----------------------------------------------
|
2019-10-06 22:35:36 +02:00
|
|
|
|
|
|
|
do p=nC+1,nBas-nR
|
2021-10-17 23:04:22 +02:00
|
|
|
do a=nO+1,nBas-nR
|
2020-04-09 14:31:50 +02:00
|
|
|
do kl=1,nOO
|
2022-01-02 10:24:30 +01:00
|
|
|
eps = e(p) + e(a) - Omega2(kl)
|
2021-10-17 23:04:22 +02:00
|
|
|
SigT(p) = SigT(p) + rho2(p,a,kl)**2*eps/(eps**2 + eta**2)
|
2019-10-06 22:35:36 +02:00
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2022-01-06 13:48:15 +01:00
|
|
|
!----------------------------------------------
|
|
|
|
! Galitskii-Migdal correlation energy
|
|
|
|
!----------------------------------------------
|
|
|
|
|
|
|
|
do i=nC+1,nO
|
|
|
|
do j=nC+1,nO
|
|
|
|
do cd=1,nVV
|
2022-01-07 09:37:11 +01:00
|
|
|
eps = e(i) + e(j) - Omega1(cd)
|
2022-01-07 15:14:00 +01:00
|
|
|
EcGM = EcGM + rho1(i,j,cd)*rho1(i,j,cd)*eps/(eps**2 + eta**2)
|
2022-01-06 13:48:15 +01:00
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
|
|
|
do a=nO+1,nBas-nR
|
|
|
|
do b=nO+1,nBas-nR
|
|
|
|
do kl=1,nOO
|
|
|
|
eps = e(a) + e(b) - Omega2(kl)
|
2022-01-07 15:14:00 +01:00
|
|
|
EcGM = EcGM - rho2(a,b,kl)*rho2(a,b,kl)*eps/(eps**2 + eta**2)
|
2022-01-06 13:48:15 +01:00
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2023-07-04 10:32:47 +02:00
|
|
|
end subroutine
|