2024-08-29 00:00:41 +02:00
|
|
|
|
|
|
|
! ---
|
|
|
|
|
|
|
|
subroutine RGW(dotest, doG0W0, doevGW, doqsGW, doufG0W0, doufGW, doSRGqsGW, maxSCF, thresh, max_diis, doACFDT, &
|
|
|
|
exchange_kernel, doXBS, dophBSE, dophBSE2, doppBSE, TDA_W, TDA, dBSE, dTDA, singlet, triplet, &
|
|
|
|
linearize, eta, regularize, nNuc, ZNuc, rNuc, ENuc, nBas_AOs, nBas_MOs, nC, nO, nV, nR, nS, ERHF, &
|
|
|
|
S, X, T, V, Hc, ERI_AO, ERI_MO, dipole_int_AO, dipole_int_MO, PHF, cHF, eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
|
2023-11-28 10:40:15 +01:00
|
|
|
! Restricted GW module
|
2023-07-23 17:41:44 +02:00
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
2023-11-13 17:39:30 +01:00
|
|
|
logical,intent(in) :: dotest
|
|
|
|
|
|
|
|
logical,intent(in) :: doG0W0
|
|
|
|
logical,intent(in) :: doevGW
|
|
|
|
logical,intent(in) :: doqsGW
|
|
|
|
logical,intent(in) :: doufG0W0
|
|
|
|
logical,intent(in) :: doufGW
|
|
|
|
logical,intent(in) :: doSRGqsGW
|
2023-07-23 17:41:44 +02:00
|
|
|
|
|
|
|
integer,intent(in) :: maxSCF
|
|
|
|
integer,intent(in) :: max_diis
|
|
|
|
double precision,intent(in) :: thresh
|
|
|
|
logical,intent(in) :: doACFDT
|
|
|
|
logical,intent(in) :: exchange_kernel
|
|
|
|
logical,intent(in) :: doXBS
|
|
|
|
logical,intent(in) :: dophBSE
|
|
|
|
logical,intent(in) :: dophBSE2
|
|
|
|
logical,intent(in) :: TDA_W
|
|
|
|
logical,intent(in) :: TDA
|
|
|
|
logical,intent(in) :: dBSE
|
|
|
|
logical,intent(in) :: dTDA
|
|
|
|
logical,intent(in) :: doppBSE
|
|
|
|
logical,intent(in) :: singlet
|
|
|
|
logical,intent(in) :: triplet
|
|
|
|
logical,intent(in) :: linearize
|
|
|
|
double precision,intent(in) :: eta
|
|
|
|
logical,intent(in) :: regularize
|
|
|
|
|
|
|
|
integer,intent(in) :: nNuc
|
|
|
|
double precision,intent(in) :: ZNuc(nNuc)
|
|
|
|
double precision,intent(in) :: rNuc(nNuc,ncart)
|
|
|
|
double precision,intent(in) :: ENuc
|
|
|
|
|
2024-08-29 00:00:41 +02:00
|
|
|
integer,intent(in) :: nBas_AOs, nBas_MOs
|
2023-11-29 16:20:53 +01:00
|
|
|
integer,intent(in) :: nC
|
|
|
|
integer,intent(in) :: nO
|
|
|
|
integer,intent(in) :: nV
|
|
|
|
integer,intent(in) :: nR
|
|
|
|
integer,intent(in) :: nS
|
2023-07-23 17:41:44 +02:00
|
|
|
|
2023-11-24 15:31:29 +01:00
|
|
|
double precision,intent(in) :: ERHF
|
2024-08-29 00:00:41 +02:00
|
|
|
double precision,intent(in) :: eHF(nBas_MOs)
|
|
|
|
double precision,intent(in) :: cHF(nBas_AOs,nBas_MOs)
|
|
|
|
double precision,intent(in) :: PHF(nBas_AOs,nBas_AOs)
|
|
|
|
double precision,intent(in) :: S(nBas_AOs,nBas_AOs)
|
|
|
|
double precision,intent(in) :: T(nBas_AOs,nBas_AOs)
|
|
|
|
double precision,intent(in) :: V(nBas_AOs,nBas_AOs)
|
|
|
|
double precision,intent(in) :: Hc(nBas_AOs,nBas_AOs)
|
|
|
|
double precision,intent(in) :: X(nBas_AOs,nBas_MOs)
|
|
|
|
double precision,intent(in) :: ERI_AO(nBas_AOs,nBas_AOs,nBas_AOs,nBas_AOs)
|
|
|
|
double precision,intent(in) :: ERI_MO(nBas_MOs,nBas_MOs,nBas_MOs,nBas_MOs)
|
|
|
|
double precision,intent(in) :: dipole_int_AO(nBas_AOs,nBas_AOs,ncart)
|
|
|
|
double precision,intent(in) :: dipole_int_MO(nBas_MOs,nBas_MOs,ncart)
|
2023-07-23 17:41:44 +02:00
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
double precision :: start_GW ,end_GW ,t_GW
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform G0W0 calculatiom
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doG0W0) then
|
|
|
|
|
|
|
|
call wall_time(start_GW)
|
2023-11-13 17:39:30 +01:00
|
|
|
call RG0W0(dotest,doACFDT,exchange_kernel,doXBS,dophBSE,dophBSE2,TDA_W,TDA,dBSE,dTDA,doppBSE,singlet,triplet, &
|
2024-08-29 00:00:41 +02:00
|
|
|
linearize,eta,regularize,nBas_MOs,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
call wall_time(end_GW)
|
|
|
|
|
|
|
|
t_GW = end_GW - start_GW
|
2024-08-29 00:00:41 +02:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for G0W0 = ',t_GW,' seconds'
|
2023-07-23 17:41:44 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform evGW calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doevGW) then
|
|
|
|
|
|
|
|
call wall_time(start_GW)
|
2023-11-13 17:39:30 +01:00
|
|
|
call evRGW(dotest,maxSCF,thresh,max_diis,doACFDT,exchange_kernel,doXBS,dophBSE,dophBSE2,TDA_W,TDA,dBSE,dTDA,doppBSE, &
|
2024-08-29 00:00:41 +02:00
|
|
|
singlet,triplet,linearize,eta,regularize,nBas_AOs,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
call wall_time(end_GW)
|
|
|
|
|
|
|
|
t_GW = end_GW - start_GW
|
2024-08-29 00:00:41 +02:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for evGW = ',t_GW,' seconds'
|
2023-07-23 17:41:44 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform qsGW calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doqsGW) then
|
|
|
|
|
|
|
|
call wall_time(start_GW)
|
2024-08-29 00:00:41 +02:00
|
|
|
call qsRGW(dotest, maxSCF, thresh, max_diis, doACFDT, exchange_kernel, doXBS, dophBSE, dophBSE2, &
|
|
|
|
TDA_W, TDA, dBSE, dTDA, doppBSE, singlet, triplet, eta, regularize, nNuc, ZNuc, rNuc, &
|
|
|
|
ENuc, nBas_AOs, nBas_MOs, nC, nO, nV, nR, nS, ERHF, S, X, T, V, Hc, ERI_AO, ERI_MO, &
|
|
|
|
dipole_int_AO, dipole_int_MO, PHF, cHF, eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
call wall_time(end_GW)
|
|
|
|
|
|
|
|
t_GW = end_GW - start_GW
|
2024-08-29 00:00:41 +02:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for qsGW = ',t_GW,' seconds'
|
2023-07-23 17:41:44 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform SRG-qsGW calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doSRGqsGW) then
|
|
|
|
|
|
|
|
call wall_time(start_GW)
|
2024-08-29 00:00:41 +02:00
|
|
|
call SRG_qsGW(dotest, maxSCF, thresh, max_diis, doACFDT, exchange_kernel, doXBS, &
|
|
|
|
dophBSE, dophBSE2, TDA_W, TDA, dBSE, dTDA, singlet, triplet, eta, &
|
|
|
|
nNuc, ZNuc, rNuc, ENuc, nBas_AOs, nBas_MOs, nC, nO, nV, nR, nS, &
|
|
|
|
ERHF, S, X, T, V, Hc, ERI_AO, ERI_MO, dipole_int_AO, dipole_int_MO, &
|
|
|
|
PHF, cHF, eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
call wall_time(end_GW)
|
|
|
|
|
|
|
|
t_GW = end_GW - start_GW
|
2024-08-29 00:00:41 +02:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for qsGW = ',t_GW,' seconds'
|
2023-07-23 17:41:44 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform ufG0W0 calculatiom
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doufG0W0) then
|
|
|
|
|
|
|
|
call wall_time(start_GW)
|
2024-08-29 00:00:41 +02:00
|
|
|
! TODO
|
|
|
|
call ufG0W0(dotest,TDA_W,nBas_AOs,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
call wall_time(end_GW)
|
|
|
|
|
|
|
|
t_GW = end_GW - start_GW
|
2024-08-29 00:00:41 +02:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for ufG0W0 = ',t_GW,' seconds'
|
2023-07-23 17:41:44 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform ufGW calculatiom
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doufGW) then
|
|
|
|
|
|
|
|
call wall_time(start_GW)
|
2024-08-29 00:00:41 +02:00
|
|
|
! TODO
|
|
|
|
call ufGW(dotest,TDA_W,nBas_AOs,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,eHF)
|
2023-07-23 17:41:44 +02:00
|
|
|
call wall_time(end_GW)
|
|
|
|
|
|
|
|
t_GW = end_GW - start_GW
|
2024-08-29 00:00:41 +02:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for ufGW = ',t_GW,' seconds'
|
2023-07-23 17:41:44 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
end subroutine
|