4
1
mirror of https://github.com/pfloos/quack synced 2024-08-08 05:20:29 +02:00

fix ufG0W0

This commit is contained in:
Pierre-Francois Loos 2023-11-06 11:07:20 +01:00
parent 849bb698f1
commit 2b5a08fd87
3 changed files with 56 additions and 36 deletions

View File

@ -1,5 +1,5 @@
# RHF UHF GHF ROHF # RHF UHF GHF ROHF
F F T F T F F F
# MP2 MP3 # MP2 MP3
F F F F
# CCD pCCD DCD CCSD CCSD(T) # CCD pCCD DCD CCSD CCSD(T)
@ -13,6 +13,6 @@
# G0F2 evGF2 qsGF2 G0F3 evGF3 # G0F2 evGF2 qsGF2 G0F3 evGF3
F F F F F F F F F F
# G0W0 evGW qsGW SRG-qsGW ufG0W0 ufGW # G0W0 evGW qsGW SRG-qsGW ufG0W0 ufGW
F F F F F F T F F F T F
# G0T0pp evGTpp qsGTpp G0T0eh evGTeh qsGTeh # G0T0pp evGTpp qsGTpp G0T0eh evGTeh qsGTeh
F F F F F F F F F F F F

View File

@ -1,5 +1,5 @@
# HF: maxSCF thresh DIIS guess mix shift stab search # HF: maxSCF thresh DIIS guess mix shift stab search
1000 0.00001 5 3 0.0 0.0 F T 1000 0.0000001 5 1 0.0 0.0 F F
# MP: reg # MP: reg
F F
# CC: maxSCF thresh DIIS # CC: maxSCF thresh DIIS
@ -7,11 +7,11 @@
# spin: TDA spin_conserved spin_flip # spin: TDA spin_conserved spin_flip
F T T F T T
# GF: maxSCF thresh DIIS lin eta renorm reg # GF: maxSCF thresh DIIS lin eta renorm reg
256 0.00001 5 F 0.0 0 F 256 0.00001 5 F 0.0 0 F
# GW: maxSCF thresh DIIS lin eta TDA_W reg # GW: maxSCF thresh DIIS lin eta TDA_W reg
256 0.00001 5 F 0.0 F F 256 0.00001 5 F 0.0 F F
# GT: maxSCF thresh DIIS lin eta TDA_T reg # GT: maxSCF thresh DIIS lin eta TDA_T reg
256 0.00001 5 F 0.0 F F 256 0.00001 5 F 0.0 F F
# ACFDT: AC Kx XBS # ACFDT: AC Kx XBS
F F T F F T
# BSE: phBSE phBSE2 ppBSE dBSE dTDA # BSE: phBSE phBSE2 ppBSE dBSE dTDA

View File

@ -28,6 +28,7 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
integer :: jb,kc,ia,ja integer :: jb,kc,ia,ja
integer :: klc,kcd,ija,ijb,iab,jab integer :: klc,kcd,ija,ijb,iab,jab
logical :: dRPA
integer :: ispin integer :: ispin
double precision :: EcRPA double precision :: EcRPA
integer :: n2h1p,n2p1h,nH integer :: n2h1p,n2p1h,nH
@ -36,13 +37,15 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
double precision,allocatable :: cGW(:,:) double precision,allocatable :: cGW(:,:)
double precision,allocatable :: eGW(:) double precision,allocatable :: eGW(:)
double precision,allocatable :: Z(:) double precision,allocatable :: Z(:)
double precision,allocatable :: OmRPA(:) double precision,allocatable :: Aph(:,:)
double precision,allocatable :: XpY_RPA(:,:) double precision,allocatable :: Bph(:,:)
double precision,allocatable :: XmY_RPA(:,:) double precision,allocatable :: Om(:)
double precision,allocatable :: rho_RPA(:,:,:) double precision,allocatable :: XpY(:,:)
double precision,allocatable :: XmY(:,:)
double precision,allocatable :: rho(:,:,:)
logical :: verbose = .true. logical :: verbose = .true.
double precision,parameter :: cutoff1 = 0.0d0 double precision,parameter :: cutoff1 = 0.01d0
double precision,parameter :: cutoff2 = 0.01d0 double precision,parameter :: cutoff2 = 0.01d0
! Output variables ! Output variables
@ -55,33 +58,33 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
write(*,*)'**********************************************' write(*,*)'**********************************************'
write(*,*) write(*,*)
! Dimension of the supermatrix
write(*,*) 'Tamm-Dancoff approximation for dynamic screening by default!'
write(*,*)
! Dimension of the supermatrix ! Dimension of the supermatrix
n2h1p = nO*nO*nV n2h1p = nO*nO*nV
n2p1h = nV*nV*nO n2p1h = nV*nV*nO
nH = 1 + n2h1p + n2p1h nH = 1 + n2h1p + n2p1h
! Memory allocation ! Memory allocation
allocate(H(nH,nH),cGW(nH,nH),eGW(nH),Z(nH)) allocate(H(nH,nH),cGW(nH,nH),eGW(nH),Z(nH))
! Initialization ! Initialization
dRPA = .true.
EcRPA = 0d0
H(:,:) = 0d0 H(:,:) = 0d0
p=nO !Compute only the HOMO!
!!! Compute only the HOMO !!!
p=nO
if (TDA_W) then if (TDA_W) then
! TDA for W ! TDA for W
write(*,*) 'Tamm-Dancoff approximation' write(*,*) 'Tamm-Dancoff approximation actived!'
write(*,*) 'No need to compute RPA quantities first'
write(*,*) write(*,*)
!---------------------------! !---------------------------!
@ -95,6 +98,7 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
! | V2p1h 0 C2p1h | ! ! | V2p1h 0 C2p1h | !
! ! ! !
!---------------------------! !---------------------------!
!-------------! !-------------!
! Block C2h1p ! ! Block C2h1p !
!-------------! !-------------!
@ -160,6 +164,7 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
!-------------! !-------------!
! Block V2h1p ! ! Block V2h1p !
!-------------! !-------------!
klc = 0 klc = 0
do k=nC+1,nO do k=nC+1,nO
do l=nC+1,nO do l=nC+1,nO
@ -176,6 +181,7 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
!-------------! !-------------!
! Block V2p1h ! ! Block V2p1h !
!-------------! !-------------!
kcd = 0 kcd = 0
do k=nC+1,nO do k=nC+1,nO
do c=nO+1,nBas-nR do c=nO+1,nBas-nR
@ -191,10 +197,9 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
else else
! No TDA for W ! RPA for W
write(*,*) 'NO Tamm-Dancoff approximation' write(*,*) 'Tamm-Dancoff approximation deactivated!'
write(*,*) 'A prior RPA calculation will be done'
write(*,*) write(*,*)
!---------------------------! !---------------------------!
@ -210,50 +215,62 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
!---------------------------! !---------------------------!
! Memory allocation ! ! Memory allocation !
allocate(OmRPA(nS),XpY_RPA(nS,nS),XmY_RPA(nS,nS),rho_RPA(nBas,nBas,nS)) allocate(Om(nS),Aph(nS,nS),Bph(nS,nS),XpY(nS,nS),XmY(nS,nS),rho(nBas,nBas,nS))
! Spin manifold ! Spin manifold
ispin = 1 ispin = 1
!-------------------! !-------------------!
! Compute screening ! ! Compute screening !
!-------------------! !-------------------!
call phLR(ispin,.true.,TDA_W,0d0,nBas,nC,nO,nV,nR,nS,1d0,eHF,ERI,EcRPA,OmRPA,XpY_RPA,XmY_RPA)
call phLR_A(ispin,dRPA,nBas,nC,nO,nV,nR,nS,1d0,eHF,ERI,Aph)
if(.not.TDA_W) call phLR_B(ispin,dRPA,nBas,nC,nO,nV,nR,nS,1d0,ERI,Bph)
call phLR(TDA_W,nS,Aph,Bph,EcRPA,Om,XpY,XmY)
!--------------------------! !--------------------------!
! Compute spectral weights ! ! Compute spectral weights !
!--------------------------! !--------------------------!
call GW_excitation_density(nBas,nC,nO,nR,nS,ERI,XpY_RPA,rho_RPA)
call GW_excitation_density(nBas,nC,nO,nR,nS,ERI,XpY,rho)
!---------! !---------!
! Block F ! ! Block F !
!---------! !---------!
H(1,1) = eHF(p) H(1,1) = eHF(p)
!-------------! !-------------!
! Block D2h1p ! ! Block D2h1p !
!-------------! !-------------!
ija = 0 ija = 0
do i=nC+1,nO do i=nC+1,nO
do ja=1,nS do ja=1,nS
ija = ija + 1 ija = ija + 1
H(1+ija,1+ija) = eHF(i) - OmRPA(ja) H(1+ija,1+ija) = eHF(i) - Om(ja)
end do end do
end do end do
!-------------! !-------------!
! Block W2h1p ! ! Block W2h1p !
!-------------! !-------------!
ija = 0 ija = 0
do i=nC+1,nO do i=nC+1,nO
do ja=1,nS do ja=1,nS
ija = ija + 1 ija = ija + 1
H(1 ,1+ija) = sqrt(2d0)*rho_RPA(p,i,ja) H(1 ,1+ija) = sqrt(2d0)*rho(p,i,ja)
H(1+ija,1 ) = sqrt(2d0)*rho_RPA(p,i,ja) H(1+ija,1 ) = sqrt(2d0)*rho(p,i,ja)
end do end do
end do end do
!-------------! !-------------!
! Block D2h1p ! ! Block D2h1p !
!-------------! !-------------!
iab = 0 iab = 0
do b=nO+1,nBas-nR do b=nO+1,nBas-nR
ia = 0 ia = 0
@ -261,7 +278,7 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
do a=nO+1,nBas-nR do a=nO+1,nBas-nR
ia = ia + 1 ia = ia + 1
iab = iab + 1 iab = iab + 1
H(1+n2h1p+iab,1+n2h1p+iab) = eHF(b) + OmRPA(ia) H(1+n2h1p+iab,1+n2h1p+iab) = eHF(b) + Om(ia)
end do end do
end do end do
end do end do
@ -269,6 +286,7 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
!-------------! !-------------!
! Block W2p1h ! ! Block W2p1h !
!-------------! !-------------!
iab = 0 iab = 0
do b=nO+1,nBas-nR do b=nO+1,nBas-nR
ia = 0 ia = 0
@ -276,8 +294,8 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
do a=nO+1,nBas-nR do a=nO+1,nBas-nR
ia = ia + 1 ia = ia + 1
iab = iab + 1 iab = iab + 1
H(1 ,1+n2h1p+iab) = sqrt(2d0)*rho_RPA(p,b,ia) H(1 ,1+n2h1p+iab) = sqrt(2d0)*rho(p,b,ia)
H(1+n2h1p+iab,1 ) = sqrt(2d0)*rho_RPA(p,b,ia) H(1+n2h1p+iab,1 ) = sqrt(2d0)*rho(p,b,ia)
end do end do
end do end do
end do end do
@ -311,9 +329,11 @@ subroutine ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI,eHF,TDA_W)
write(*,*)'-------------------------------------------' write(*,*)'-------------------------------------------'
do s=1,nH do s=1,nH
write(*,'(1X,A1,1X,I3,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X)') & if(Z(s) > cutoff1) then
'|',s,'|',eGW(s)*HaToeV,'|',Z(s),'|' write(*,'(1X,A1,1X,I3,1X,A1,1X,F15.6,1X,A1,1X,F15.6,1X,A1,1X)') &
enddo '|',s,'|',eGW(s)*HaToeV,'|',Z(s),'|'
end if
end do
write(*,*)'-------------------------------------------' write(*,*)'-------------------------------------------'
write(*,*) write(*,*)