2023-11-13 16:15:15 +01:00
|
|
|
subroutine GG0F2(dotest,dophBSE,doppBSE,TDA,dBSE,dTDA,linearize,eta,regularize, &
|
2023-10-27 13:35:10 +02:00
|
|
|
nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,dipole_int,eHF)
|
|
|
|
|
|
|
|
! Perform a one-shot second-order Green function calculation
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
2023-11-13 16:15:15 +01:00
|
|
|
logical,intent(in) :: dotest
|
|
|
|
|
2023-10-27 13:35:10 +02:00
|
|
|
logical,intent(in) :: dophBSE
|
|
|
|
logical,intent(in) :: doppBSE
|
|
|
|
logical,intent(in) :: TDA
|
|
|
|
logical,intent(in) :: dBSE
|
|
|
|
logical,intent(in) :: dTDA
|
|
|
|
logical,intent(in) :: linearize
|
|
|
|
double precision,intent(in) :: eta
|
|
|
|
logical,intent(in) :: regularize
|
|
|
|
integer,intent(in) :: nBas
|
|
|
|
integer,intent(in) :: nO
|
|
|
|
integer,intent(in) :: nC
|
|
|
|
integer,intent(in) :: nV
|
|
|
|
integer,intent(in) :: nR
|
|
|
|
integer,intent(in) :: nS
|
|
|
|
double precision,intent(in) :: ENuc
|
|
|
|
double precision,intent(in) :: ERHF
|
|
|
|
double precision,intent(in) :: eHF(nBas)
|
|
|
|
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
|
|
|
|
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
double precision :: Ec
|
2023-10-27 13:56:53 +02:00
|
|
|
double precision :: EcBSE
|
2023-10-27 13:35:10 +02:00
|
|
|
double precision,allocatable :: eGFlin(:)
|
|
|
|
double precision,allocatable :: eGF(:)
|
|
|
|
double precision,allocatable :: SigC(:)
|
|
|
|
double precision,allocatable :: Z(:)
|
|
|
|
|
|
|
|
! Hello world
|
|
|
|
|
2023-11-13 16:15:15 +01:00
|
|
|
|
2023-10-27 13:35:10 +02:00
|
|
|
write(*,*)
|
2023-11-13 16:15:15 +01:00
|
|
|
write(*,*)'********************************'
|
|
|
|
write(*,*)'* Generalized G0F2 Calculation *'
|
|
|
|
write(*,*)'********************************'
|
2023-10-27 13:35:10 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
! Memory allocation
|
|
|
|
|
|
|
|
allocate(SigC(nBas),Z(nBas),eGFlin(nBas),eGF(nBas))
|
|
|
|
|
|
|
|
! Frequency-dependent second-order contribution
|
|
|
|
|
|
|
|
if(regularize) then
|
|
|
|
|
|
|
|
! call GF2_reg_self_energy_diag(eta,nBas,nC,nO,nV,nR,eHF,ERI,SigC,Z)
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call GGF2_self_energy_diag(eta,nBas,nC,nO,nV,nR,eHF,ERI,SigC,Z)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
eGFlin(:) = eHF(:) + Z(:)*SigC(:)
|
|
|
|
|
|
|
|
if(linearize) then
|
|
|
|
|
|
|
|
write(*,*) '*** Quasiparticle energies obtained by linearization ***'
|
|
|
|
|
|
|
|
eGF(:) = eGFlin(:)
|
|
|
|
|
|
|
|
else
|
|
|
|
|
2023-11-27 09:56:32 +01:00
|
|
|
write(*,*) ' *** Quasiparticle energies obtained by root search *** '
|
2023-10-27 13:35:10 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
call GGF2_QP_graph(eta,nBas,nC,nO,nV,nR,eHF,ERI,eGFlin,eHF,eGF,Z)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
! Print results
|
|
|
|
|
2023-11-13 16:15:15 +01:00
|
|
|
call GMP2(.false.,regularize,nBas,nC,nO,nV,nR,ERI,ENuc,EHF,eGF,Ec)
|
2023-11-15 10:17:58 +01:00
|
|
|
call print_RG0F2(nBas,nO,eHF,SigC,eGF,Z,ENuc,ERHF,Ec)
|
2023-10-27 13:35:10 +02:00
|
|
|
|
|
|
|
! Perform BSE2 calculation
|
|
|
|
|
2023-10-27 13:56:53 +02:00
|
|
|
if(dophBSE) then
|
|
|
|
|
|
|
|
call GGF2_phBSE2(TDA,dBSE,dTDA,eta,nBas,nC,nO,nV,nR,nS,ERI,dipole_int,eGF,EcBSE)
|
2023-10-27 13:35:10 +02:00
|
|
|
|
2023-10-27 13:56:53 +02:00
|
|
|
write(*,*)
|
|
|
|
write(*,*)'-------------------------------------------------------------------------------'
|
|
|
|
write(*,'(2X,A50,F20.10,A3)') 'Tr@phBSE@GG0F2 correlation energy =',EcBSE,' au'
|
|
|
|
write(*,'(2X,A50,F20.10,A3)') 'Tr@phBSE@GG0F2 total energy =',ENuc + EHF + EcBSE,' au'
|
|
|
|
write(*,*)'-------------------------------------------------------------------------------'
|
|
|
|
write(*,*)
|
2023-10-27 13:35:10 +02:00
|
|
|
|
2023-10-27 13:56:53 +02:00
|
|
|
end if
|
2023-10-27 13:35:10 +02:00
|
|
|
|
|
|
|
! Perform ppBSE2 calculation
|
|
|
|
|
|
|
|
! if(doppBSE) then
|
|
|
|
!
|
2023-10-27 13:56:53 +02:00
|
|
|
! call GGF2_ppBSE2(TDA,dBSE,dTDA,eta,nBas,nC,nO,nV,nR,ERI,dipole_int,eGF,EcBSE)
|
2023-10-27 13:35:10 +02:00
|
|
|
|
|
|
|
! write(*,*)
|
|
|
|
! write(*,*)'-------------------------------------------------------------------------------'
|
2023-10-27 13:56:53 +02:00
|
|
|
! write(*,'(2X,A50,F20.10,A3)') 'Tr@ppBSE@GG0F2 correlation energy =',EcBSE,' au'
|
|
|
|
! write(*,'(2X,A50,F20.10,A3)') 'Tr@ppBSE@GG0F2 total energy =',ENuc + ERHF + EcBSE,' au'
|
2023-10-27 13:35:10 +02:00
|
|
|
! write(*,*)'-------------------------------------------------------------------------------'
|
|
|
|
! write(*,*)
|
|
|
|
|
|
|
|
! end if
|
|
|
|
|
2023-11-13 16:15:15 +01:00
|
|
|
! Testing zone
|
|
|
|
|
|
|
|
if(dotest) then
|
|
|
|
|
2023-11-14 14:31:27 +01:00
|
|
|
call dump_test_value('G','G0F2 correlation energy',Ec)
|
|
|
|
call dump_test_value('G','G0F2 HOMO energy',eGF(nO))
|
|
|
|
call dump_test_value('G','G0F2 LUMO energy',eGF(nO+1))
|
2023-11-13 16:15:15 +01:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-10-27 13:35:10 +02:00
|
|
|
end subroutine
|