mirror of
https://github.com/pfloos/quack
synced 2024-12-22 04:14:26 +01:00
working in CCGW
This commit is contained in:
parent
37d312c789
commit
4d66fbc20d
353
src/GW/CCG0W0.f90
Normal file
353
src/GW/CCG0W0.f90
Normal file
@ -0,0 +1,353 @@
|
||||
subroutine CCG0W0(maxSCF,thresh,nBas,nOrb,nC,nO,nV,nR,ERI,ENuc,ERHF,eHF)
|
||||
|
||||
! CC-based GW module
|
||||
|
||||
implicit none
|
||||
include 'parameters.h'
|
||||
|
||||
! Input variables
|
||||
|
||||
integer,intent(in) :: maxSCF
|
||||
double precision,intent(in) :: thresh
|
||||
|
||||
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
|
||||
|
||||
integer :: p,q
|
||||
integer :: i,j,k,l
|
||||
integer :: a,b,c,d
|
||||
|
||||
integer :: nSCF
|
||||
double precision :: Conv
|
||||
|
||||
double precision,allocatable :: OVVO(:,:,:,:)
|
||||
double precision,allocatable :: VOOV(:,:,:,:)
|
||||
|
||||
double precision,allocatable :: delta_2h1p(:,:,:,:)
|
||||
double precision,allocatable :: delta_2p1h(:,:,:,:)
|
||||
|
||||
double precision,allocatable :: V_2h1p(:,:,:,:)
|
||||
double precision,allocatable :: V_2p1h(:,:,:,:)
|
||||
|
||||
double precision,allocatable :: r_2h1p(:,:,:,:)
|
||||
double precision,allocatable :: r_2p1h(:,:,:,:)
|
||||
|
||||
double precision,allocatable :: t_2h1p(:,:,:,:)
|
||||
double precision,allocatable :: t_2p1h(:,:,:,:)
|
||||
|
||||
double precision,allocatable :: x_2h1p(:,:)
|
||||
double precision,allocatable :: x_2p1h(:,:)
|
||||
|
||||
double precision,allocatable :: eGW(:)
|
||||
double precision,allocatable :: SigGW(:,:)
|
||||
double precision,allocatable :: cGW(:,:)
|
||||
double precision,allocatable :: Z(:)
|
||||
|
||||
integer,allocatable :: order(:)
|
||||
|
||||
! Hello world
|
||||
|
||||
write(*,*)
|
||||
write(*,*)'*****************************'
|
||||
write(*,*)'* CC-based G0W0 Calculation *'
|
||||
write(*,*)'*****************************'
|
||||
write(*,*)
|
||||
|
||||
! Create integral batches
|
||||
|
||||
allocate(OVVO(nO,nV,nV,nO),VOOV(nV,nO,nO,nV))
|
||||
|
||||
OVVO(:,:,:,:) = ERI( 1:nO ,nO+1:nOrb,nO+1:nOrb, 1:nO )
|
||||
VOOV(:,:,:,:) = ERI(nO+1:nOrb , 1:nO , 1:nO ,nO+1:nOrb)
|
||||
|
||||
! Form energy denominator and guess amplitudes
|
||||
|
||||
allocate(delta_2h1p(nO,nO,nV,nOrb),delta_2p1h(nO,nV,nV,nOrb))
|
||||
allocate(V_2h1p(nOrb,nO,nO,nV),V_2p1h(nOrb,nO,nV,nV))
|
||||
allocate(t_2h1p(nO,nO,nV,nOrb),t_2p1h(nO,nV,nV,nOrb))
|
||||
allocate(x_2h1p(nOrb,nOrb),x_2p1h(nOrb,nOrb))
|
||||
|
||||
do k=nC+1,nO
|
||||
do l=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
V_2h1p(p,k,l,c) = sqrt(2d0)*ERI(p,nO+c,k,l)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
do k=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
do d=1,nV-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
V_2p1h(p,k,c,d) = sqrt(2d0)*ERI(p,k,nO+d,nO+c)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
! Initialization
|
||||
|
||||
allocate(r_2h1p(nO,nO,nV,nOrb),r_2p1h(nO,nV,nV,nOrb))
|
||||
allocate(eGW(nOrb),SigGW(nOrb,nOrb),cGW(nOrb,nOrb),Z(nOrb))
|
||||
allocate(order(nOrb))
|
||||
|
||||
Conv = 1d0
|
||||
nSCF = 0
|
||||
eGW(:) = eHF(:)
|
||||
|
||||
t_2h1p(:,:,:,:) = 0d0
|
||||
t_2p1h(:,:,:,:) = 0d0
|
||||
|
||||
!------------------------------------------------------------------------
|
||||
! Main SCF loop
|
||||
!------------------------------------------------------------------------
|
||||
write(*,*)
|
||||
write(*,*)'----------------------------------------------'
|
||||
write(*,*)'| CCGW calculation |'
|
||||
write(*,*)'----------------------------------------------'
|
||||
write(*,'(1X,A1,1X,A3,1X,A1,1X,A10,1X,A1,1X,A10,1X,A1,1X,A10,1X,A1,1X)') &
|
||||
'|','#','|','HOMO','|','LUMO','|','Conv','|'
|
||||
write(*,*)'----------------------------------------------'
|
||||
|
||||
do while(Conv > thresh .and. nSCF < maxSCF)
|
||||
|
||||
! Increment
|
||||
|
||||
nSCF = nSCF + 1
|
||||
|
||||
! Compute energy differences
|
||||
|
||||
do i=nC+1,nO
|
||||
do j=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
delta_2h1p(i,j,a,p) = eGW(i) + eGW(j) - eGW(nO+a) - eHF(p)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
do i=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do b=1,nV-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
delta_2p1h(i,a,b,p) = eGW(nO+a) + eGW(nO+b) - eGW(i) - eHF(p)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
! Compute intermediates
|
||||
|
||||
x_2h1p(:,:) = 0d0
|
||||
|
||||
do p=nC+1,nOrb-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
do k=nC+1,nO
|
||||
do l=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
|
||||
x_2h1p(p,q) = x_2h1p(p,q) + V_2h1p(q,k,l,c)*t_2h1p(k,l,c,p)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
end do
|
||||
end do
|
||||
|
||||
x_2p1h(:,:) = 0d0
|
||||
|
||||
do p=nC+1,nOrb-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
do k=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
do d=1,nV-nR
|
||||
|
||||
x_2p1h(p,q) = x_2p1h(p,q) + V_2p1h(q,k,c,d)*t_2p1h(k,c,d,p)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
end do
|
||||
end do
|
||||
|
||||
! Compute residual for 2h1p sector
|
||||
|
||||
do i=nC+1,nO
|
||||
do j=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
r_2h1p(i,j,a,p) = V_2h1p(p,i,j,a) + delta_2h1p(i,j,a,p)*t_2h1p(i,j,a,p)
|
||||
|
||||
do k=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
|
||||
r_2h1p(i,j,a,p) = r_2h1p(i,j,a,p) - 2d0*OVVO(j,c,a,k)*t_2h1p(i,k,c,p)
|
||||
|
||||
end do
|
||||
end do
|
||||
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
r_2h1p(i,j,a,p) = r_2h1p(i,j,a,p) - t_2h1p(i,j,a,q)*x_2h1p(p,q) - t_2h1p(i,j,a,q)*x_2p1h(p,q)
|
||||
|
||||
end do
|
||||
|
||||
end do
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
! Compute residual for 2p1h sector
|
||||
|
||||
do i=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do b=1,nV-nR
|
||||
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
r_2p1h(i,a,b,p) = V_2p1h(p,i,a,b) + delta_2p1h(i,a,b,p)*t_2p1h(i,a,b,p)
|
||||
|
||||
do k=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
|
||||
r_2p1h(i,a,b,p) = r_2p1h(i,a,b,p) + 2d0*VOOV(a,k,i,c)*t_2p1h(k,c,b,p)
|
||||
|
||||
end do
|
||||
end do
|
||||
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
r_2p1h(i,a,b,p) = r_2p1h(i,a,b,p) - t_2p1h(i,a,b,q)*x_2h1p(p,q) - t_2p1h(i,a,b,q)*x_2p1h(p,q)
|
||||
|
||||
end do
|
||||
|
||||
end do
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
! Check convergence
|
||||
|
||||
Conv = max(maxval(abs(r_2h1p)),maxval(abs(r_2p1h)))
|
||||
|
||||
! Update amplitudes
|
||||
|
||||
t_2h1p(:,:,:,:) = t_2h1p(:,:,:,:) - r_2h1p(:,:,:,:)/delta_2h1p(:,:,:,:)
|
||||
t_2p1h(:,:,:,:) = t_2p1h(:,:,:,:) - r_2p1h(:,:,:,:)/delta_2p1h(:,:,:,:)
|
||||
|
||||
! Compute self-energy
|
||||
|
||||
SigGW(:,:) = 0d0
|
||||
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
SigGW(p,p) = SigGW(p,p) + eHF(p)
|
||||
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
do i=nC+1,nO
|
||||
do j=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
|
||||
SigGW(p,q) = SigGW(p,q) + V_2h1p(p,i,j,a)*t_2h1p(i,j,a,q)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
do i=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do b=1,nV-nR
|
||||
|
||||
SigGW(p,q) = SigGW(p,q) + V_2p1h(p,i,a,b)*t_2p1h(i,a,b,q)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
end do
|
||||
end do
|
||||
|
||||
! Diagonalize non-Hermitian matrix
|
||||
|
||||
call diagonalize_general_matrix(nOrb,SigGW,eGW,cGW)
|
||||
|
||||
do p=1,nOrb
|
||||
order(p) = p
|
||||
end do
|
||||
|
||||
call quick_sort(eGW,order,nOrb)
|
||||
call set_order(cGW,order,nOrb,nOrb)
|
||||
|
||||
! Renormalization factor
|
||||
|
||||
Z(:) = 1d0
|
||||
|
||||
! Dump results
|
||||
|
||||
write(*,'(1X,A1,1X,I3,1X,A1,1X,F10.6,1X,A1,1X,F10.6,1X,A1,1X,F10.6,1X,A1,1X)') &
|
||||
'|',nSCF,'|',eGW(nO)*HaToeV,'|',eGW(nO+1)*HaToeV,'|',Conv,'|'
|
||||
|
||||
end do
|
||||
write(*,*)'----------------------------------------------'
|
||||
!------------------------------------------------------------------------
|
||||
! End of SCF loop
|
||||
!------------------------------------------------------------------------
|
||||
|
||||
! Did it actually converge?
|
||||
|
||||
if(nSCF == maxSCF) then
|
||||
|
||||
write(*,*)
|
||||
write(*,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
|
||||
write(*,*)' Convergence failed '
|
||||
write(*,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
|
||||
write(*,*)
|
||||
|
||||
stop
|
||||
|
||||
end if
|
||||
|
||||
write(*,*)'-------------------------------------------------------------------------------'
|
||||
write(*,*)' CCGW 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(*,*)'-------------------------------------------------------------------------------'
|
||||
|
||||
do p=1,nOrb
|
||||
write(*,'(1X,A1,1X,I3,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X)') &
|
||||
'|',p,'|',eHF(p)*HaToeV,'|',(eGW(p)-eHF(p))*HaToeV,'|',Z(p),'|',eGW(p)*HaToeV,'|'
|
||||
end do
|
||||
write(*,*)'-------------------------------------------------------------------------------'
|
||||
|
||||
end subroutine
|
@ -1,4 +1,4 @@
|
||||
subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
subroutine CCGW(maxSCF,thresh,nBas,nOrb,nC,nO,nV,nR,ERI,ENuc,ERHF,eHF)
|
||||
|
||||
! CC-based GW module
|
||||
|
||||
@ -11,14 +11,15 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
double precision,intent(in) :: thresh
|
||||
|
||||
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) :: e(nBas)
|
||||
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: eHF(nOrb)
|
||||
double precision,intent(in) :: ERI(nOrb,nOrb,nOrb,nOrb)
|
||||
|
||||
! Local variables
|
||||
|
||||
@ -57,43 +58,43 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
! Hello world
|
||||
|
||||
write(*,*)
|
||||
write(*,*)'*****************************'
|
||||
write(*,*)'| CCGW calculation |'
|
||||
write(*,*)'*****************************'
|
||||
write(*,*)'***************************'
|
||||
write(*,*)'* CC-based GW Calculation *'
|
||||
write(*,*)'***************************'
|
||||
write(*,*)
|
||||
|
||||
! Create integral batches
|
||||
|
||||
allocate(OVVO(nO,nV,nV,nO),VOOV(nV,nO,nO,nV))
|
||||
|
||||
OVVO(:,:,:,:) = ERI( 1:nO ,nO+1:nBas,nO+1:nBas, 1:nO )
|
||||
VOOV(:,:,:,:) = ERI(nO+1:nBas , 1:nO , 1:nO ,nO+1:nBas)
|
||||
OVVO(:,:,:,:) = ERI( 1:nO ,nO+1:nOrb,nO+1:nOrb, 1:nO )
|
||||
VOOV(:,:,:,:) = ERI(nO+1:nOrb , 1:nO , 1:nO ,nO+1:nOrb)
|
||||
|
||||
! Form energy denominator and guess amplitudes
|
||||
|
||||
allocate(delta_2h1p(nO,nO,nV,nBas),delta_2p1h(nO,nV,nV,nBas))
|
||||
allocate(V_2h1p(nBas,nO,nO,nV),V_2p1h(nBas,nO,nV,nV))
|
||||
allocate(t_2h1p(nO,nO,nV,nBas),t_2p1h(nO,nV,nV,nBas))
|
||||
allocate(x_2h1p(nBas,nBas),x_2p1h(nBas,nBas))
|
||||
allocate(delta_2h1p(nO,nO,nV,nOrb),delta_2p1h(nO,nV,nV,nOrb))
|
||||
allocate(V_2h1p(nOrb,nO,nO,nV),V_2p1h(nOrb,nO,nV,nV))
|
||||
allocate(t_2h1p(nO,nO,nV,nOrb),t_2p1h(nO,nV,nV,nOrb))
|
||||
allocate(x_2h1p(nOrb,nOrb),x_2p1h(nOrb,nOrb))
|
||||
|
||||
do i=nC+1,nO
|
||||
do j=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do p=nC+1,nBas-nR
|
||||
do k=nC+1,nO
|
||||
do l=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
V_2h1p(p,i,j,a) = sqrt(2d0)*ERI(p,nO+a,i,j)
|
||||
V_2h1p(p,k,l,c) = sqrt(2d0)*ERI(p,nO+c,k,l)
|
||||
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
do i=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do b=1,nV-nR
|
||||
do p=nC+1,nBas-nR
|
||||
do k=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
do d=1,nV-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
V_2p1h(p,i,a,b) = sqrt(2d0)*ERI(p,i,nO+b,nO+a)
|
||||
V_2p1h(p,k,c,d) = sqrt(2d0)*ERI(p,k,nO+d,nO+c)
|
||||
|
||||
end do
|
||||
end do
|
||||
@ -102,13 +103,13 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
|
||||
! Initialization
|
||||
|
||||
allocate(r_2h1p(nO,nO,nV,nBas),r_2p1h(nO,nV,nV,nBas))
|
||||
allocate(eGW(nBas),SigGW(nBas,nBas),cGW(nBas,nBas),Z(nBas))
|
||||
allocate(order(nBas))
|
||||
allocate(r_2h1p(nO,nO,nV,nOrb),r_2p1h(nO,nV,nV,nOrb))
|
||||
allocate(eGW(nOrb),SigGW(nOrb,nOrb),cGW(nOrb,nOrb),Z(nOrb))
|
||||
allocate(order(nOrb))
|
||||
|
||||
Conv = 1d0
|
||||
nSCF = 0
|
||||
eGW(:) = e(:)
|
||||
Conv = 1d0
|
||||
nSCF = 0
|
||||
eGW(:) = eHF(:)
|
||||
|
||||
t_2h1p(:,:,:,:) = 0d0
|
||||
t_2p1h(:,:,:,:) = 0d0
|
||||
@ -135,9 +136,9 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
do i=nC+1,nO
|
||||
do j=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do p=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
delta_2h1p(i,j,a,p) = eGW(i) + eGW(j) - eGW(nO+a) - e(p)
|
||||
delta_2h1p(i,j,a,p) = eGW(i) + eGW(j) - eGW(nO+a) - eHF(p)
|
||||
|
||||
end do
|
||||
end do
|
||||
@ -147,9 +148,9 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
do i=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
do b=1,nV-nR
|
||||
do p=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
delta_2p1h(i,a,b,p) = eGW(nO+a) + eGW(nO+b) - eGW(i) - e(p)
|
||||
delta_2p1h(i,a,b,p) = eGW(nO+a) + eGW(nO+b) - eGW(i) - eHF(p)
|
||||
|
||||
end do
|
||||
end do
|
||||
@ -160,8 +161,8 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
|
||||
x_2h1p(:,:) = 0d0
|
||||
|
||||
do p=nC+1,nBas-nR
|
||||
do q=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
do k=nC+1,nO
|
||||
do l=nC+1,nO
|
||||
@ -178,8 +179,8 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
|
||||
x_2p1h(:,:) = 0d0
|
||||
|
||||
do p=nC+1,nBas-nR
|
||||
do q=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
do k=nC+1,nO
|
||||
do c=1,nV-nR
|
||||
@ -200,7 +201,7 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
do j=nC+1,nO
|
||||
do a=1,nV-nR
|
||||
|
||||
do p=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
r_2h1p(i,j,a,p) = V_2h1p(p,i,j,a) + delta_2h1p(i,j,a,p)*t_2h1p(i,j,a,p)
|
||||
|
||||
@ -212,7 +213,7 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
end do
|
||||
end do
|
||||
|
||||
do q=nC+1,nBas-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
r_2h1p(i,j,a,p) = r_2h1p(i,j,a,p) - t_2h1p(i,j,a,q)*x_2h1p(p,q) - t_2h1p(i,j,a,q)*x_2p1h(p,q)
|
||||
|
||||
@ -230,7 +231,7 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
do a=1,nV-nR
|
||||
do b=1,nV-nR
|
||||
|
||||
do p=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
r_2p1h(i,a,b,p) = V_2p1h(p,i,a,b) + delta_2p1h(i,a,b,p)*t_2p1h(i,a,b,p)
|
||||
|
||||
@ -242,7 +243,7 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
end do
|
||||
end do
|
||||
|
||||
do q=nC+1,nBas-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
r_2p1h(i,a,b,p) = r_2p1h(i,a,b,p) - t_2p1h(i,a,b,q)*x_2h1p(p,q) - t_2p1h(i,a,b,q)*x_2p1h(p,q)
|
||||
|
||||
@ -267,11 +268,11 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
|
||||
SigGW(:,:) = 0d0
|
||||
|
||||
do p=nC+1,nBas-nR
|
||||
do p=nC+1,nOrb-nR
|
||||
|
||||
SigGW(p,p) = SigGW(p,p) + e(p)
|
||||
SigGW(p,p) = SigGW(p,p) + eHF(p)
|
||||
|
||||
do q=nC+1,nBas-nR
|
||||
do q=nC+1,nOrb-nR
|
||||
|
||||
do i=nC+1,nO
|
||||
do j=nC+1,nO
|
||||
@ -298,14 +299,14 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
|
||||
! Diagonalize non-Hermitian matrix
|
||||
|
||||
call diagonalize_general_matrix(nBas,SigGW,eGW,cGW)
|
||||
call diagonalize_general_matrix(nOrb,SigGW,eGW,cGW)
|
||||
|
||||
do p=1,nBas
|
||||
do p=1,nOrb
|
||||
order(p) = p
|
||||
end do
|
||||
|
||||
call quick_sort(eGW,order,nBas)
|
||||
call set_order(cGW,order,nBas,nBas)
|
||||
call quick_sort(eGW,order,nOrb)
|
||||
call set_order(cGW,order,nOrb,nOrb)
|
||||
|
||||
! Renormalization factor
|
||||
|
||||
@ -343,9 +344,9 @@ subroutine CCGW(maxSCF,thresh,nBas,nC,nO,nV,nR,ERI,ENuc,ERHF,e)
|
||||
'|','#','|','e_HF (eV)','|','Sig_c (eV)','|','Z','|','e_QP (eV)','|'
|
||||
write(*,*)'-------------------------------------------------------------------------------'
|
||||
|
||||
do p=1,nBas
|
||||
do p=1,nOrb
|
||||
write(*,'(1X,A1,1X,I3,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X)') &
|
||||
'|',p,'|',e(p)*HaToeV,'|',(eGW(p)-e(p))*HaToeV,'|',Z(p),'|',eGW(p)*HaToeV,'|'
|
||||
'|',p,'|',eHF(p)*HaToeV,'|',(eGW(p)-eHF(p))*HaToeV,'|',Z(p),'|',eGW(p)*HaToeV,'|'
|
||||
end do
|
||||
write(*,*)'-------------------------------------------------------------------------------'
|
||||
|
@ -68,8 +68,10 @@ subroutine RGW(dotest,doG0W0,doevGW,doqsGW,doufG0W0,doufGW,maxSCF,thresh,max_dii
|
||||
|
||||
double precision :: start_GW ,end_GW ,t_GW
|
||||
|
||||
logical :: doCCGW
|
||||
|
||||
!------------------------------------------------------------------------
|
||||
! Perform G0W0 calculatiom
|
||||
! Perform G0W0 calculation
|
||||
!------------------------------------------------------------------------
|
||||
|
||||
if(doG0W0) then
|
||||
@ -122,7 +124,7 @@ subroutine RGW(dotest,doG0W0,doevGW,doqsGW,doufG0W0,doufGW,maxSCF,thresh,max_dii
|
||||
end if
|
||||
|
||||
!------------------------------------------------------------------------
|
||||
! Perform ufG0W0 calculatiom
|
||||
! Perform ufG0W0 calculation
|
||||
!------------------------------------------------------------------------
|
||||
|
||||
if(doufG0W0) then
|
||||
@ -139,7 +141,7 @@ subroutine RGW(dotest,doG0W0,doevGW,doqsGW,doufG0W0,doufGW,maxSCF,thresh,max_dii
|
||||
end if
|
||||
|
||||
!------------------------------------------------------------------------
|
||||
! Perform ufGW calculatiom
|
||||
! Perform ufGW calculation
|
||||
!------------------------------------------------------------------------
|
||||
|
||||
if(doufGW) then
|
||||
@ -155,4 +157,41 @@ subroutine RGW(dotest,doG0W0,doevGW,doqsGW,doufG0W0,doufGW,maxSCF,thresh,max_dii
|
||||
|
||||
end if
|
||||
|
||||
!------------------------------------------------------------------------
|
||||
! Perform CC-based G0W0 calculation
|
||||
!------------------------------------------------------------------------
|
||||
|
||||
doCCGW = .false.
|
||||
|
||||
if(doCCGW) then
|
||||
|
||||
call wall_time(start_GW)
|
||||
call CCG0W0(maxSCF,thresh,nBas,nOrb,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
||||
call wall_time(end_GW)
|
||||
|
||||
t_GW = end_GW - start_GW
|
||||
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for ufGW = ',t_GW,' seconds'
|
||||
write(*,*)
|
||||
|
||||
end if
|
||||
|
||||
|
||||
!------------------------------------------------------------------------
|
||||
! Perform CC-based GW calculation
|
||||
!------------------------------------------------------------------------
|
||||
|
||||
doCCGW = .false.
|
||||
|
||||
if(doCCGW) then
|
||||
|
||||
call wall_time(start_GW)
|
||||
call CCGW(maxSCF,thresh,nBas,nOrb,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
||||
call wall_time(end_GW)
|
||||
|
||||
t_GW = end_GW - start_GW
|
||||
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for ufGW = ',t_GW,' seconds'
|
||||
write(*,*)
|
||||
|
||||
end if
|
||||
|
||||
end subroutine
|
||||
|
@ -47,7 +47,7 @@ subroutine ufRGW(dotest,TDA_W,nBas,nOrb,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF)
|
||||
double precision,allocatable :: XmY(:,:)
|
||||
double precision,allocatable :: rho(:,:,:)
|
||||
|
||||
logical :: verbose = .true.
|
||||
logical :: verbose = .false.
|
||||
double precision,parameter :: cutoff1 = 0.01d0
|
||||
double precision,parameter :: cutoff2 = 0.01d0
|
||||
double precision :: eF
|
Loading…
Reference in New Issue
Block a user