10
1
mirror of https://github.com/pfloos/quack synced 2025-01-08 04:15:56 +01:00
QuAcK/src/GW/ccRG0W0.f90

265 lines
6.3 KiB
Fortran
Raw Normal View History

2024-09-17 16:39:38 +02:00
subroutine ccRG0W0(maxSCF,thresh,max_diis,nBas,nOrb,nC,nO,nV,nR,ERI,ENuc,ERHF,eHF)
2024-09-16 22:30:23 +02:00
! CC-based GW module
implicit none
include 'parameters.h'
! Input variables
integer,intent(in) :: maxSCF
double precision,intent(in) :: thresh
2024-09-17 16:39:38 +02:00
integer,intent(in) :: max_diis
2024-09-16 22:30:23 +02:00
integer,intent(in) :: nBas
integer,intent(in) :: nOrb
integer,intent(in) :: nC
integer,intent(in) :: nO
integer,intent(in) :: nV
integer,intent(in) :: nR
double precision,intent(in) :: ENuc
double precision,intent(in) :: ERHF
double precision,intent(in) :: eHF(nOrb)
double precision,intent(in) :: ERI(nOrb,nOrb,nOrb,nOrb)
! Local variables
2024-09-17 16:39:38 +02:00
integer :: p,q,r,s
2024-09-16 22:30:23 +02:00
integer :: i,j,k,l
integer :: a,b,c,d
integer :: nSCF
double precision :: Conv
2024-09-17 19:12:45 +02:00
double precision :: x
2024-09-16 22:30:23 +02:00
double precision,allocatable :: eGW(:)
double precision,allocatable :: Z(:)
2024-09-17 16:39:38 +02:00
double precision,allocatable :: del(:,:,:)
2024-09-17 19:12:45 +02:00
double precision,allocatable :: vec(:,:,:)
2024-09-17 16:39:38 +02:00
double precision,allocatable :: res(:,:,:)
double precision,allocatable :: amp(:,:,:)
integer :: n_diis
double precision :: rcond
double precision,allocatable :: r_diis(:,:)
double precision,allocatable :: t_diis(:,:)
2024-09-16 22:30:23 +02:00
! Hello world
write(*,*)
write(*,*)'*****************************'
write(*,*)'* CC-based G0W0 Calculation *'
write(*,*)'*****************************'
write(*,*)
! Form energy denominator and guess amplitudes
2024-09-17 19:12:45 +02:00
allocate(del(nO,nV,nOrb))
allocate(vec(nO,nV,nOrb))
allocate(res(nO,nV,nOrb))
allocate(amp(nO,nV,nOrb))
2024-09-17 16:39:38 +02:00
2024-09-16 22:30:23 +02:00
allocate(eGW(nOrb),Z(nOrb))
2024-09-17 19:12:45 +02:00
allocate(r_diis(nO*nV*nOrb,max_diis))
allocate(t_diis(nO*nV*nOrb,max_diis))
2024-09-17 16:39:38 +02:00
2024-09-16 22:30:23 +02:00
! Initialization
eGW(:) = eHF(:)
2024-09-17 19:12:45 +02:00
Z(:) = 1d0
! Compute energy differences
do i=nC+1,nO
do j=nC+1,nO
do a=1,nV-nR
del(i,a,j) = eHF(i) + eHF(j) - eHF(nO+a)
end do
end do
end do
do i=nC+1,nO
do a=1,nV-nR
do b=1,nV-nR
del(i,a,nO+b) = eHF(nO+a) + eHF(nO+b) - eHF(i)
end do
end do
end do
2024-09-16 22:30:23 +02:00
!-------------------------!
! Main loop over orbitals !
!-------------------------!
2024-09-17 19:12:45 +02:00
do p=nC+1,nO+1
2024-09-16 22:30:23 +02:00
! Initialization
Conv = 1d0
nSCF = 0
2024-09-17 16:39:38 +02:00
n_diis = 0
t_diis(:,:) = 0d0
r_diis(:,:) = 0d0
rcond = 0d0
amp(:,:,:) = 0d0
res(:,:,:) = 0d0
2024-09-17 19:12:45 +02:00
! Compute energy differences
2024-09-17 09:10:16 +02:00
do i=nC+1,nO
2024-09-17 19:12:45 +02:00
do a=1,nV-nR
do j=nC+1,nO
vec(i,a,j) = sqrt(2d0)*ERI(p,nO+a,i,j)
2024-09-17 09:10:16 +02:00
end do
end do
end do
2024-09-17 19:12:45 +02:00
2024-09-17 09:10:16 +02:00
do i=nC+1,nO
2024-09-17 19:12:45 +02:00
do a=1,nV-nR
do b=1,nV-nR
vec(i,a,nO+b) = sqrt(2d0)*ERI(p,i,nO+b,nO+a)
2024-09-17 09:10:16 +02:00
end do
end do
end do
2024-09-16 22:30:23 +02:00
!----------------------!
! Loop over amplitudes !
!----------------------!
write(*,*)
2024-09-17 16:39:38 +02:00
write(*,*)'-------------------------------------------------------------'
write(*,*)'| CC-based G0W0 calculation |'
write(*,*)'-------------------------------------------------------------'
write(*,'(1X,A1,1X,A3,1X,A1,1X,A15,1X,A1,1X,A15,1X,A1,1X,A15,1X,A1,1X)') &
2024-09-16 22:30:23 +02:00
'|','#','|','HF','|','G0W0','|','Conv','|'
2024-09-17 16:39:38 +02:00
write(*,*)'-------------------------------------------------------------'
2024-09-16 22:30:23 +02:00
do while(Conv > thresh .and. nSCF < maxSCF)
! Increment
nSCF = nSCF + 1
! Compute residual for 2h1p sector
2024-09-17 19:12:45 +02:00
res(:,:,:) = vec(:,:,:) + (del(:,:,:) - eGW(p))*amp(:,:,:)
2024-09-16 22:30:23 +02:00
2024-09-17 19:12:45 +02:00
do i=nC+1,nO
do a=1,nV-nR
do j=nC+1,nO
2024-09-16 22:30:23 +02:00
do k=nC+1,nO
2024-09-17 19:12:45 +02:00
do c=1,nV-nR
2024-09-16 22:30:23 +02:00
2024-09-17 19:12:45 +02:00
res(i,a,j) = res(i,a,j) - 2d0*ERI(j,nO+c,nO+a,k)*amp(i,c,k)
2024-09-16 22:30:23 +02:00
end do
end do
end do
end do
end do
! Compute residual for 2p1h sector
do i=nC+1,nO
2024-09-17 19:12:45 +02:00
do a=1,nV-nR
do b=1,nV-nR
2024-09-16 22:30:23 +02:00
do k=nC+1,nO
2024-09-17 19:12:45 +02:00
do c=1,nV-nR
2024-09-16 22:30:23 +02:00
2024-09-17 19:12:45 +02:00
res(i,a,nO+b) = res(i,a,nO+b) + 2d0*ERI(nO+a,k,i,nO+c)*amp(k,c,nO+b)
2024-09-16 22:30:23 +02:00
end do
end do
end do
end do
end do
2024-09-17 19:12:45 +02:00
! Check convergence
2024-09-16 22:30:23 +02:00
2024-09-17 16:39:38 +02:00
Conv = maxval(abs(res))
2024-09-16 22:30:23 +02:00
! Update amplitudes
2024-09-17 16:39:38 +02:00
2024-09-17 19:12:45 +02:00
amp(:,:,:) = amp(:,:,:) - res(:,:,:)/(del(:,:,:) - eHF(p))
2024-09-16 22:30:23 +02:00
2024-09-17 16:39:38 +02:00
! DIIS extrapolation
if(max_diis > 1) then
n_diis = min(n_diis+1,max_diis)
2024-09-17 19:12:45 +02:00
call DIIS_extrapolation(rcond,nO*nV*nOrb,nO*nV*nOrb,n_diis,r_diis,t_diis,res,amp)
2024-09-17 16:39:38 +02:00
end if
! Compute quasiparticle energy
2024-09-16 22:30:23 +02:00
eGW(p) = eHF(p)
2024-09-17 16:39:38 +02:00
2024-09-17 19:12:45 +02:00
do i=nC+1,nO
do a=1,nV-nR
do q=nC+1,nOrb-nR
2024-09-16 22:30:23 +02:00
2024-09-17 19:12:45 +02:00
eGW(p) = eGW(p) + vec(i,a,q)*amp(i,a,q)
2024-09-16 22:30:23 +02:00
end do
end do
end do
2024-09-17 16:39:38 +02:00
2024-09-16 22:30:23 +02:00
! Dump results
2024-09-17 16:39:38 +02:00
write(*,'(1X,A1,1X,I3,1X,A1,1X,F15.10,1X,A1,1X,F15.10,1X,A1,1X,F15.10,1X,A1,1X)') &
2024-09-16 22:30:23 +02:00
'|',nSCF,'|',eHF(p)*HaToeV,'|',eGW(p)*HaToeV,'|',Conv,'|'
end do
2024-09-17 16:39:38 +02:00
write(*,*)'-------------------------------------------------------------'
2024-09-16 22:30:23 +02:00
!------------------------------------------------------------------------
! End of SCF loop
!------------------------------------------------------------------------
! Did it actually converge?
if(nSCF == maxSCF) then
write(*,*)
write(*,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
write(*,*)' Convergence failed '
write(*,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
write(*,*)
stop
end if
write(*,*)'-------------------------------------------------------------------------------'
write(*,*)' CC-G0W0 calculation '
write(*,*)'-------------------------------------------------------------------------------'
write(*,'(1X,A1,1X,A3,1X,A1,1X,A15,1X,A1,1X,A15,1X,A1,1X,A15,1X,A1,1X,A15,1X,A1,1X)') &
'|','#','|','e_HF (eV)','|','Sig_c (eV)','|','Z','|','e_QP (eV)','|'
write(*,*)'-------------------------------------------------------------------------------'
2024-09-17 16:39:38 +02:00
write(*,'(1X,A1,1X,I3,1X,A1,1X,F15.10,1X,A1,1X,F15.10,1X,A1,1X,F15.10,1X,A1,1X,F15.10,1X,A1,1X)') &
2024-09-16 22:30:23 +02:00
'|',p,'|',eHF(p)*HaToeV,'|',(eGW(p)-eHF(p))*HaToeV,'|',Z(p),'|',eGW(p)*HaToeV,'|'
write(*,*)'-------------------------------------------------------------------------------'
end do
end subroutine