4
1
mirror of https://github.com/pfloos/quack synced 2024-06-22 13:12:19 +02:00
quack/src/GF/evGF2.f90

151 lines
4.1 KiB
Fortran
Raw Normal View History

2021-03-05 22:34:48 +01:00
subroutine evGF2(BSE,TDA,dBSE,dTDA,evDyn,maxSCF,thresh,max_diis,singlet,triplet, &
2021-12-17 11:41:40 +01:00
linearize,eta,regularize,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,dipole_int,eHF)
2019-03-19 10:13:33 +01:00
2020-03-19 10:21:18 +01:00
! Perform eigenvalue self-consistent second-order Green function calculation
2019-03-19 10:13:33 +01:00
implicit none
include 'parameters.h'
! Input variables
2020-06-01 17:14:42 +02:00
logical,intent(in) :: BSE
logical,intent(in) :: TDA
2020-06-15 23:04:07 +02:00
logical,intent(in) :: dBSE
logical,intent(in) :: dTDA
2020-06-16 14:02:14 +02:00
logical,intent(in) :: evDyn
2019-03-19 10:13:33 +01:00
integer,intent(in) :: maxSCF
double precision,intent(in) :: thresh
integer,intent(in) :: max_diis
2021-03-05 22:34:48 +01:00
logical,intent(in) :: singlet
logical,intent(in) :: triplet
2019-10-18 23:16:37 +02:00
logical,intent(in) :: linearize
2020-06-01 17:14:42 +02:00
double precision,intent(in) :: eta
2021-12-17 11:41:40 +01:00
logical,intent(in) :: regularize
2019-04-29 09:52:21 +02:00
integer,intent(in) :: nBas
integer,intent(in) :: nO
integer,intent(in) :: nC
integer,intent(in) :: nV
integer,intent(in) :: nR
2020-06-01 17:14:42 +02:00
integer,intent(in) :: nS
double precision,intent(in) :: ENuc
double precision,intent(in) :: ERHF
2020-06-03 12:06:16 +02:00
double precision,intent(in) :: eHF(nBas)
2020-06-03 12:24:38 +02:00
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
2019-03-19 10:13:33 +01:00
! Local variables
2019-04-24 15:33:04 +02:00
integer :: nSCF
integer :: n_diis
2021-03-06 23:08:43 +01:00
double precision :: Ec
2020-06-03 12:24:38 +02:00
double precision :: EcBSE(nspin)
2019-04-24 15:33:04 +02:00
double precision :: Conv
double precision :: rcond
2019-04-29 09:52:21 +02:00
double precision,allocatable :: eGF2(:)
double precision,allocatable :: eOld(:)
2021-03-06 15:27:35 +01:00
double precision,allocatable :: SigC(:)
2019-10-18 23:16:37 +02:00
double precision,allocatable :: Z(:)
2019-04-29 09:52:21 +02:00
double precision,allocatable :: error_diis(:,:)
double precision,allocatable :: e_diis(:,:)
2019-03-19 10:13:33 +01:00
! Hello world
write(*,*)
write(*,*)'************************************************'
write(*,*)'| Second-order Green function calculation |'
write(*,*)'************************************************'
write(*,*)
! Memory allocation
2021-03-06 15:27:35 +01:00
allocate(SigC(nBas),Z(nBas),eGF2(nBas),eOld(nBas),error_diis(nBas,max_diis),e_diis(nBas,max_diis))
2019-03-19 10:13:33 +01:00
! Initialization
Conv = 1d0
nSCF = 0
n_diis = 0
e_diis(:,:) = 0d0
error_diis(:,:) = 0d0
2020-06-03 12:06:16 +02:00
eGF2(:) = eHF(:)
eOld(:) = eHF(:)
2022-01-06 22:36:30 +01:00
rcond = 0d0
2019-03-19 10:13:33 +01:00
!------------------------------------------------------------------------
! Main SCF loop
!------------------------------------------------------------------------
do while(Conv > thresh .and. nSCF < maxSCF)
! Frequency-dependent second-order contribution
2021-12-17 13:36:26 +01:00
if(regularize) then
call regularized_self_energy_GF2_diag(eta,nBas,nC,nO,nV,nR,nS,eHF,eGF2,ERI,SigC,Z)
else
2023-07-04 11:56:00 +02:00
call GF2_self_energy_diag(eta,nBas,nC,nO,nV,nR,nS,eHF,eGF2,ERI,SigC,Z)
2021-12-17 13:36:26 +01:00
end if
2019-10-18 23:16:37 +02:00
if(linearize) then
2021-03-06 15:27:35 +01:00
eGF2(:) = eHF(:) + Z(:)*SigC(:)
2019-10-18 23:16:37 +02:00
else
2021-03-06 15:27:35 +01:00
eGF2(:) = eHF(:) + SigC(:)
2019-10-18 23:16:37 +02:00
end if
2019-03-19 10:13:33 +01:00
Conv = maxval(abs(eGF2 - eOld))
2019-04-29 09:52:21 +02:00
! Print results
2023-01-12 10:20:12 +01:00
call MP2(regularize,nBas,nC,nO,nV,nR,ERI,ENuc,EHF,eGF2,Ec)
2021-03-06 23:08:43 +01:00
call print_evGF2(nBas,nO,nSCF,Conv,eHF,SigC,Z,eGF2,ENuc,ERHF,Ec)
2019-04-29 09:52:21 +02:00
2019-03-19 10:13:33 +01:00
! DIIS extrapolation
n_diis = min(n_diis+1,max_diis)
2019-04-24 15:33:04 +02:00
call DIIS_extrapolation(rcond,nBas,nBas,n_diis,error_diis,e_diis,eGF2-eOld,eGF2)
if(abs(rcond) < 1d-15) n_diis = 0
2019-03-19 10:13:33 +01:00
2019-04-29 09:52:21 +02:00
eOld(:) = eGF2(:)
2019-03-19 10:13:33 +01:00
! Increment
nSCF = nSCF + 1
2019-04-29 09:52:21 +02:00
end do
2019-03-19 10:13:33 +01:00
!------------------------------------------------------------------------
! End main SCF loop
!------------------------------------------------------------------------
! Did it actually converge?
if(nSCF == maxSCF+1) then
write(*,*)
write(*,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
write(*,*)' Convergence failed '
write(*,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
write(*,*)
2020-06-03 12:46:26 +02:00
stop
2019-04-29 09:52:21 +02:00
end if
2019-03-19 10:13:33 +01:00
2020-06-03 12:24:38 +02:00
! Perform BSE2 calculation
if(BSE) then
2023-07-04 11:56:00 +02:00
call GF2_phBSE2(TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,nBas,nC,nO,nV,nR,nS,ERI,dipole_int,eHF,eGF2,EcBSE)
2020-06-03 12:24:38 +02:00
end if
2023-07-04 11:56:00 +02:00
end subroutine