2019-03-19 10:13:33 +01:00
|
|
|
program QuAcK
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
|
2019-05-07 22:55:36 +02:00
|
|
|
logical :: doSph
|
2020-09-22 15:32:26 +02:00
|
|
|
logical :: unrestricted = .false.
|
2019-03-19 10:13:33 +01:00
|
|
|
logical :: doRHF,doUHF,doMOM
|
2021-03-03 11:37:46 +01:00
|
|
|
logical :: dostab
|
2020-10-13 13:44:24 +02:00
|
|
|
logical :: doKS
|
2022-12-01 09:42:23 +01:00
|
|
|
logical :: doMP2,doMP3
|
2021-11-10 14:47:26 +01:00
|
|
|
logical :: doCCD,dopCCD,doDCD,doCCSD,doCCSDT
|
|
|
|
logical :: do_drCCD,do_rCCD,do_crCCD,do_lCCD
|
2021-03-08 17:00:05 +01:00
|
|
|
logical :: doCIS,doCIS_D,doCID,doCISD,doFCI
|
2021-11-10 14:47:26 +01:00
|
|
|
logical :: doRPA,doRPAx,docrRPA,doppRPA
|
2020-04-20 12:28:19 +02:00
|
|
|
logical :: doADC
|
2021-03-05 22:34:48 +01:00
|
|
|
logical :: doG0F2,doevGF2,doqsGF2,doG0F3,doevGF3
|
2022-11-29 12:11:09 +01:00
|
|
|
logical :: doG0W0,doevGW,doqsGW,doufG0W0,doufGW,doSRGqsGW
|
2023-07-03 23:15:07 +02:00
|
|
|
logical :: doG0T0pp,doevGTpp,doqsGTpp
|
|
|
|
logical :: doG0T0eh,doevGTeh,doqsGTeh
|
2019-07-09 23:09:32 +02:00
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
integer :: nNuc,nBas,nBasCABS
|
2020-09-21 16:54:38 +02:00
|
|
|
integer :: nEl(nspin)
|
|
|
|
integer :: nC(nspin)
|
|
|
|
integer :: nO(nspin)
|
|
|
|
integer :: nV(nspin)
|
|
|
|
integer :: nR(nspin)
|
2019-10-18 23:16:37 +02:00
|
|
|
integer :: nS(nspin)
|
2019-03-19 10:13:33 +01:00
|
|
|
double precision :: ENuc,ERHF,EUHF,Norm
|
2022-12-01 09:42:23 +01:00
|
|
|
double precision :: EcMP2(3),EcMP3
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
double precision,allocatable :: ZNuc(:),rNuc(:,:)
|
|
|
|
double precision,allocatable :: cHF(:,:,:),eHF(:,:),PHF(:,:,:)
|
2021-02-15 21:44:24 +01:00
|
|
|
double precision,allocatable :: Vxc(:,:)
|
2020-01-14 21:27:34 +01:00
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
double precision,allocatable :: eG0W0(:,:)
|
|
|
|
double precision,allocatable :: eG0T0(:,:)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-01-14 21:27:34 +01:00
|
|
|
logical :: doACFDT
|
2020-01-16 21:39:00 +01:00
|
|
|
logical :: exchange_kernel
|
2020-01-14 21:27:34 +01:00
|
|
|
logical :: doXBS
|
|
|
|
|
2020-09-28 21:25:25 +02:00
|
|
|
double precision,allocatable :: S(:,:)
|
|
|
|
double precision,allocatable :: T(:,:)
|
|
|
|
double precision,allocatable :: V(:,:)
|
|
|
|
double precision,allocatable :: Hc(:,:)
|
|
|
|
double precision,allocatable :: X(:,:)
|
2020-10-21 12:58:37 +02:00
|
|
|
double precision,allocatable :: dipole_int_AO(:,:,:)
|
|
|
|
double precision,allocatable :: dipole_int_MO(:,:,:)
|
2020-09-28 22:58:58 +02:00
|
|
|
double precision,allocatable :: dipole_int_aa(:,:,:)
|
|
|
|
double precision,allocatable :: dipole_int_bb(:,:,:)
|
2022-01-04 11:39:33 +01:00
|
|
|
double precision,allocatable :: F_AO(:,:)
|
|
|
|
double precision,allocatable :: F_MO(:,:)
|
2020-04-16 17:02:01 +02:00
|
|
|
double precision,allocatable :: ERI_AO(:,:,:,:)
|
|
|
|
double precision,allocatable :: ERI_MO(:,:,:,:)
|
2020-09-28 21:25:25 +02:00
|
|
|
integer :: ixyz
|
2020-09-22 23:08:47 +02:00
|
|
|
integer :: bra1,bra2
|
|
|
|
integer :: ket1,ket2
|
2020-09-22 22:13:51 +02:00
|
|
|
double precision,allocatable :: ERI_MO_aaaa(:,:,:,:)
|
|
|
|
double precision,allocatable :: ERI_MO_aabb(:,:,:,:)
|
|
|
|
double precision,allocatable :: ERI_MO_bbbb(:,:,:,:)
|
2020-04-16 17:02:01 +02:00
|
|
|
double precision,allocatable :: ERI_ERF_AO(:,:,:,:)
|
|
|
|
double precision,allocatable :: ERI_ERF_MO(:,:,:,:)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2019-04-24 18:00:54 +02:00
|
|
|
double precision :: start_QuAcK ,end_QuAcK ,t_QuAcK
|
2019-05-07 22:55:36 +02:00
|
|
|
double precision :: start_int ,end_int ,t_int
|
2019-03-19 10:13:33 +01:00
|
|
|
double precision :: start_HF ,end_HF ,t_HF
|
2021-03-03 11:37:46 +01:00
|
|
|
double precision :: start_stab ,end_stab ,t_stab
|
2020-10-13 13:44:24 +02:00
|
|
|
double precision :: start_KS ,end_KS ,t_KS
|
2019-05-07 22:55:36 +02:00
|
|
|
double precision :: start_AOtoMO ,end_AOtoMO ,t_AOtoMO
|
2023-07-04 09:27:35 +02:00
|
|
|
double precision :: start_CC ,end_CC ,t_CC
|
|
|
|
double precision :: start_CI ,end_CI ,t_CI
|
2020-01-13 23:08:03 +01:00
|
|
|
double precision :: start_RPA ,end_RPA ,t_RPA
|
2023-07-04 09:27:35 +02:00
|
|
|
double precision :: start_GF ,end_GF ,t_GF
|
|
|
|
double precision :: start_GW ,end_GW ,t_GW
|
|
|
|
double precision :: start_GT ,end_GT ,t_GT
|
|
|
|
double precision :: start_MP ,end_MP ,t_MP
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
integer :: maxSCF_HF,n_diis_HF
|
2022-02-03 10:05:58 +01:00
|
|
|
double precision :: thresh_HF,level_shift
|
|
|
|
logical :: DIIS_HF,guess_type,ortho_type,mix
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2022-11-30 17:18:51 +01:00
|
|
|
logical :: regMP
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
integer :: maxSCF_CC,n_diis_CC
|
|
|
|
double precision :: thresh_CC
|
|
|
|
logical :: DIIS_CC
|
|
|
|
|
2020-09-22 23:08:47 +02:00
|
|
|
logical :: singlet
|
|
|
|
logical :: triplet
|
|
|
|
logical :: spin_conserved
|
|
|
|
logical :: spin_flip
|
2020-06-15 23:04:07 +02:00
|
|
|
logical :: TDA
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-03-19 10:33:56 +01:00
|
|
|
integer :: maxSCF_GF,n_diis_GF,renormGF
|
2019-03-19 10:13:33 +01:00
|
|
|
double precision :: thresh_GF
|
2021-12-17 11:41:40 +01:00
|
|
|
logical :: DIIS_GF,linGF,regGF
|
2020-06-03 12:06:16 +02:00
|
|
|
double precision :: eta_GF
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
integer :: maxSCF_GW,n_diis_GW
|
|
|
|
double precision :: thresh_GW
|
2023-07-04 10:37:54 +02:00
|
|
|
logical :: DIIS_GW,COHSEX,TDA_W,linGW,regGW
|
2020-06-03 12:06:16 +02:00
|
|
|
double precision :: eta_GW
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2021-12-17 11:41:40 +01:00
|
|
|
integer :: maxSCF_GT,n_diis_GT
|
|
|
|
double precision :: thresh_GT
|
|
|
|
logical :: DIIS_GT,TDA_T,linGT,regGT
|
|
|
|
double precision :: eta_GT
|
|
|
|
|
2022-11-28 10:52:06 +01:00
|
|
|
logical :: BSE,dBSE,dTDA,evDyn,ppBSE,BSE2
|
2020-06-14 21:20:01 +02:00
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
! Hello World
|
|
|
|
|
|
|
|
write(*,*)
|
|
|
|
write(*,*) '******************************************************************************************'
|
|
|
|
write(*,*) '* QuAcK QuAcK QuAcK *'
|
|
|
|
write(*,*) '* __ __ __ __ __ __ __ __ __ *'
|
|
|
|
write(*,*) '* <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ *'
|
|
|
|
write(*,*) '* ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / *'
|
|
|
|
write(*,*) '*|--------------------------------------------------------------------------------------|*'
|
|
|
|
write(*,*) '******************************************************************************************'
|
|
|
|
write(*,*)
|
|
|
|
|
2019-05-07 22:55:36 +02:00
|
|
|
! Spherium calculation?
|
|
|
|
|
2019-05-23 09:53:23 +02:00
|
|
|
doSph = .false.
|
2019-05-07 22:55:36 +02:00
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(start_QuAcK)
|
2019-04-24 18:00:54 +02:00
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
! Which calculations do you want to do?
|
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
call read_methods(doRHF,doUHF,doKS,doMOM, &
|
2022-12-01 09:42:23 +01:00
|
|
|
doMP2,doMP3, &
|
2021-11-10 14:47:26 +01:00
|
|
|
doCCD,dopCCD,doDCD,doCCSD,doCCSDT, &
|
|
|
|
do_drCCD,do_rCCD,do_crCCD,do_lCCD, &
|
|
|
|
doCIS,doCIS_D,doCID,doCISD,doFCI, &
|
|
|
|
doRPA,doRPAx,docrRPA,doppRPA, &
|
|
|
|
doG0F2,doevGF2,doqsGF2, &
|
|
|
|
doG0F3,doevGF3, &
|
2022-11-29 12:11:09 +01:00
|
|
|
doG0W0,doevGW,doqsGW,doSRGqsGW, &
|
2021-11-10 14:47:26 +01:00
|
|
|
doufG0W0,doufGW, &
|
2023-07-03 23:15:07 +02:00
|
|
|
doG0T0pp,doevGTpp,doqsGTpp, &
|
|
|
|
doG0T0eh,doevGTeh,doqsGTeh)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
! Read options for methods
|
|
|
|
|
2022-02-02 15:06:51 +01:00
|
|
|
call read_options(maxSCF_HF,thresh_HF,DIIS_HF,n_diis_HF,guess_type,ortho_type,mix,level_shift,dostab, &
|
2022-11-30 17:18:51 +01:00
|
|
|
regMP, &
|
2022-02-02 15:06:51 +01:00
|
|
|
maxSCF_CC,thresh_CC,DIIS_CC,n_diis_CC, &
|
|
|
|
TDA,singlet,triplet,spin_conserved,spin_flip, &
|
|
|
|
maxSCF_GF,thresh_GF,DIIS_GF,n_diis_GF,linGF,eta_GF,renormGF,regGF, &
|
2023-07-04 10:37:54 +02:00
|
|
|
maxSCF_GW,thresh_GW,DIIS_GW,n_diis_GW,linGW,eta_GW,regGW,COHSEX,TDA_W, &
|
2022-02-02 15:06:51 +01:00
|
|
|
maxSCF_GT,thresh_GT,DIIS_GT,n_diis_GT,linGT,eta_GT,regGT,TDA_T, &
|
|
|
|
doACFDT,exchange_kernel,doXBS, &
|
2022-11-29 09:54:18 +01:00
|
|
|
BSE,dBSE,dTDA,evDyn,ppBSE,BSE2)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Read input information
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
! Read number of atoms, number of electrons of the system
|
|
|
|
! nC = number of core orbitals
|
|
|
|
! nO = number of occupied orbitals
|
|
|
|
! nV = number of virtual orbitals (see below)
|
|
|
|
! nR = number of Rydberg orbitals
|
|
|
|
! nBas = number of basis functions (see below)
|
|
|
|
! = nO + nV
|
|
|
|
! nS = number of single excitation
|
|
|
|
! = nO*nV
|
|
|
|
|
2019-03-19 11:21:34 +01:00
|
|
|
call read_molecule(nNuc,nEl(:),nO(:),nC(:),nR(:))
|
2020-03-14 23:00:44 +01:00
|
|
|
allocate(ZNuc(nNuc),rNuc(nNuc,ncart))
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
! Read geometry
|
|
|
|
|
|
|
|
call read_geometry(nNuc,ZNuc,rNuc,ENuc)
|
|
|
|
|
2023-07-03 14:33:48 +02:00
|
|
|
! allocate(CenterShell(maxShell,ncart),TotAngMomShell(maxShell),KShell(maxShell),DShell(maxShell,maxK), &
|
|
|
|
! ExpShell(maxShell,maxK),max_ang_mom(nNuc),min_exponent(nNuc,maxL+1),max_exponent(nNuc))
|
2020-03-25 09:48:58 +01:00
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
2023-07-03 14:33:48 +02:00
|
|
|
! Read basis set information from PySCF
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2023-07-03 14:33:48 +02:00
|
|
|
call read_basis_pyscf (nBas,nO,nV)
|
|
|
|
! call read_basis(nNuc,rNuc,nBas,nO,nV,nShell,TotAngMomShell,CenterShell,KShell,DShell,ExpShell, &
|
|
|
|
! max_ang_mom,min_exponent,max_exponent)
|
2020-01-22 09:20:18 +01:00
|
|
|
nS(:) = (nO(:) - nC(:))*(nV(:) - nR(:))
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Read one- and two-electron integrals
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
! Memory allocation for one- and two-electron integrals
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
allocate(cHF(nBas,nBas,nspin),eHF(nBas,nspin),eG0W0(nBas,nspin),eG0T0(nBas,nspin),PHF(nBas,nBas,nspin), &
|
2020-10-06 14:24:54 +02:00
|
|
|
S(nBas,nBas),T(nBas,nBas),V(nBas,nBas),Hc(nBas,nBas),X(nBas,nBas),ERI_AO(nBas,nBas,nBas,nBas), &
|
2022-01-04 11:39:33 +01:00
|
|
|
dipole_int_AO(nBas,nBas,ncart),dipole_int_MO(nBas,nBas,ncart),Vxc(nBas,nspin),F_AO(nBas,nBas))
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
! Read integrals
|
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(start_int)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
if(doSph) then
|
|
|
|
|
2020-09-15 10:40:51 +02:00
|
|
|
call read_integrals_sph(nBas,S,T,V,Hc,ERI_AO)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2020-09-15 10:40:51 +02:00
|
|
|
call read_integrals(nBas,S,T,V,Hc,ERI_AO)
|
2020-10-21 12:58:37 +02:00
|
|
|
call read_dipole_integrals(nBas,dipole_int_AO)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(end_int)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
t_int = end_int - start_int
|
|
|
|
write(*,*)
|
2023-03-14 14:11:01 +01:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for reading integrals = ',t_int,' seconds'
|
2019-05-07 22:55:36 +02:00
|
|
|
write(*,*)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
! Compute orthogonalization matrix
|
|
|
|
|
|
|
|
call orthogonalization_matrix(ortho_type,nBas,S,X)
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute RHF energy
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doRHF) then
|
|
|
|
|
2020-10-08 17:19:48 +02:00
|
|
|
! Check that RHF calculation is worth doing...
|
|
|
|
|
|
|
|
if(nO(1) /= nO(2)) then
|
|
|
|
write(*,*) ' !!! The system does not appear to be closed shell !!!'
|
|
|
|
write(*,*)
|
|
|
|
stop
|
|
|
|
end if
|
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(start_HF)
|
2022-02-02 15:06:51 +01:00
|
|
|
call RHF(maxSCF_HF,thresh_HF,n_diis_HF,guess_type,level_shift,nNuc,ZNuc,rNuc,ENuc, &
|
2022-01-04 11:39:33 +01:00
|
|
|
nBas,nO,S,T,V,Hc,F_AO,ERI_AO,dipole_int_AO,X,ERHF,eHF,cHF,PHF,Vxc)
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(end_HF)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
t_HF = end_HF - start_HF
|
2023-03-14 14:11:01 +01:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for RHF = ',t_HF,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2020-10-13 13:44:24 +02:00
|
|
|
! Compute UHF energy
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doUHF) then
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
! Switch on the unrestricted flag
|
|
|
|
unrestricted = .true.
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
call cpu_time(start_HF)
|
2022-02-02 15:06:51 +01:00
|
|
|
call UHF(maxSCF_HF,thresh_HF,n_diis_HF,guess_type,mix,level_shift,nNuc,ZNuc,rNuc,ENuc, &
|
2021-02-15 17:27:06 +01:00
|
|
|
nBas,nO,S,T,V,Hc,ERI_AO,dipole_int_AO,X,EUHF,eHF,cHF,PHF,Vxc)
|
2019-03-19 10:13:33 +01:00
|
|
|
call cpu_time(end_HF)
|
|
|
|
|
|
|
|
t_HF = end_HF - start_HF
|
2019-03-19 11:33:49 +01:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for UHF = ',t_HF,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-10-13 13:44:24 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute KS energy
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doKS) then
|
|
|
|
|
2021-02-15 17:27:06 +01:00
|
|
|
! Switch on the unrestricted flag
|
|
|
|
unrestricted = .true.
|
|
|
|
|
2020-10-13 13:44:24 +02:00
|
|
|
call cpu_time(start_KS)
|
2023-07-03 14:33:48 +02:00
|
|
|
! call eDFT(maxSCF_HF,thresh_HF,n_diis_HF,guess_type,mix,level_shift,nNuc,ZNuc,rNuc,ENuc,nBas,nEl,nC, &
|
|
|
|
! nO,nV,nR,nShell,TotAngMomShell,CenterShell,KShell,DShell,ExpShell, &
|
|
|
|
! max_ang_mom,min_exponent,max_exponent,S,T,V,Hc,X,ERI_AO,dipole_int_AO,EUHF,eHF,cHF,PHF,Vxc)
|
2020-10-14 09:27:42 +02:00
|
|
|
|
2020-10-13 13:44:24 +02:00
|
|
|
call cpu_time(end_KS)
|
|
|
|
|
|
|
|
t_KS = end_KS - start_KS
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for KS = ',t_KS,' seconds'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Maximum overlap method
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doMOM) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_HF)
|
2021-05-19 15:11:44 +02:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
! call UMOM()
|
|
|
|
|
|
|
|
else
|
|
|
|
|
2023-06-30 16:47:26 +02:00
|
|
|
call MOM(maxSCF_HF,thresh_HF,n_diis_HF,guess_type,nNuc,ZNuc,rNuc,ENuc, &
|
2021-05-19 15:11:44 +02:00
|
|
|
nBas,nO,S,T,V,Hc,ERI_AO,dipole_int_AO,X,ERHF,eHF,cHF,PHF,Vxc)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_HF)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_HF = end_HF - start_HF
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for MOM = ',t_HF,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! AO to MO integral transform for post-HF methods
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(start_AOtoMO)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
2020-03-12 15:04:16 +01:00
|
|
|
write(*,*)
|
|
|
|
write(*,*) 'AO to MO transformation... Please be patient'
|
|
|
|
write(*,*)
|
|
|
|
|
2019-05-07 22:55:36 +02:00
|
|
|
if(doSph) then
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
allocate(ERI_MO(nBas,nBas,nBas,nBas))
|
2020-04-16 17:02:01 +02:00
|
|
|
ERI_MO(:,:,:,:) = ERI_AO(:,:,:,:)
|
2019-05-07 22:55:36 +02:00
|
|
|
print*,'!!! MO = AO !!!'
|
2020-04-16 17:02:01 +02:00
|
|
|
deallocate(ERI_AO)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-09-28 21:25:25 +02:00
|
|
|
! Read and transform dipole-related integrals
|
|
|
|
|
2020-09-28 22:58:58 +02:00
|
|
|
allocate(dipole_int_aa(nBas,nBas,ncart),dipole_int_bb(nBas,nBas,ncart))
|
2020-10-21 12:58:37 +02:00
|
|
|
dipole_int_aa(:,:,:) = dipole_int_AO(:,:,:)
|
|
|
|
dipole_int_bb(:,:,:) = dipole_int_AO(:,:,:)
|
2020-09-28 21:25:25 +02:00
|
|
|
do ixyz=1,ncart
|
2020-09-28 22:58:58 +02:00
|
|
|
call AOtoMO_transform(nBas,cHF(:,:,1),dipole_int_aa(:,:,ixyz))
|
|
|
|
call AOtoMO_transform(nBas,cHF(:,:,2),dipole_int_bb(:,:,ixyz))
|
2020-09-28 21:25:25 +02:00
|
|
|
end do
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
! Memory allocation
|
|
|
|
|
2020-10-05 23:00:56 +02:00
|
|
|
allocate(ERI_MO_aaaa(nBas,nBas,nBas,nBas),ERI_MO_aabb(nBas,nBas,nBas,nBas),ERI_MO_bbbb(nBas,nBas,nBas,nBas))
|
2020-09-18 13:52:35 +02:00
|
|
|
|
|
|
|
! 4-index transform for (aa|aa) block
|
|
|
|
|
2020-09-22 23:08:47 +02:00
|
|
|
bra1 = 1
|
|
|
|
bra2 = 1
|
|
|
|
ket1 = 1
|
|
|
|
ket2 = 1
|
|
|
|
call AOtoMO_integral_transform(bra1,bra2,ket1,ket2,nBas,cHF,ERI_AO,ERI_MO_aaaa)
|
2020-09-18 13:52:35 +02:00
|
|
|
|
2020-09-22 22:13:51 +02:00
|
|
|
! 4-index transform for (aa|bb) block
|
2020-09-18 13:52:35 +02:00
|
|
|
|
2020-09-22 23:08:47 +02:00
|
|
|
bra1 = 1
|
|
|
|
bra2 = 1
|
|
|
|
ket1 = 2
|
|
|
|
ket2 = 2
|
|
|
|
call AOtoMO_integral_transform(bra1,bra2,ket1,ket2,nBas,cHF,ERI_AO,ERI_MO_aabb)
|
2020-09-18 13:52:35 +02:00
|
|
|
|
2020-09-22 22:13:51 +02:00
|
|
|
! 4-index transform for (bb|bb) block
|
2020-09-18 13:52:35 +02:00
|
|
|
|
2020-09-22 23:08:47 +02:00
|
|
|
bra1 = 2
|
|
|
|
bra2 = 2
|
|
|
|
ket1 = 2
|
|
|
|
ket2 = 2
|
|
|
|
call AOtoMO_integral_transform(bra1,bra2,ket1,ket2,nBas,cHF,ERI_AO,ERI_MO_bbbb)
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
else
|
|
|
|
|
|
|
|
! Memory allocation
|
|
|
|
|
|
|
|
allocate(ERI_MO(nBas,nBas,nBas,nBas))
|
2022-01-04 11:39:33 +01:00
|
|
|
allocate(F_MO(nBas,nBas))
|
2020-09-28 21:25:25 +02:00
|
|
|
|
|
|
|
! Read and transform dipole-related integrals
|
|
|
|
|
2020-10-21 12:58:37 +02:00
|
|
|
dipole_int_MO(:,:,:) = dipole_int_AO(:,:,:)
|
2020-09-28 21:25:25 +02:00
|
|
|
do ixyz=1,ncart
|
2020-10-21 12:58:37 +02:00
|
|
|
call AOtoMO_transform(nBas,cHF,dipole_int_MO(:,:,ixyz))
|
2020-09-28 21:25:25 +02:00
|
|
|
end do
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
! 4-index transform
|
|
|
|
|
2020-09-22 23:08:47 +02:00
|
|
|
bra1 = 1
|
|
|
|
bra2 = 1
|
|
|
|
ket1 = 1
|
|
|
|
ket2 = 1
|
|
|
|
call AOtoMO_integral_transform(bra1,bra2,ket1,ket2,nBas,cHF,ERI_AO,ERI_MO)
|
2022-01-07 09:56:30 +01:00
|
|
|
|
2022-01-04 11:39:33 +01:00
|
|
|
F_MO(:,:) = F_AO(:,:)
|
|
|
|
call AOtoMO_transform(nBas,cHF,F_MO)
|
2022-01-07 09:56:30 +01:00
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
end if
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(end_AOtoMO)
|
2019-05-07 22:55:36 +02:00
|
|
|
|
|
|
|
t_AOtoMO = end_AOtoMO - start_AOtoMO
|
2023-03-14 14:11:01 +01:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for AO to MO transformation = ',t_AOtoMO,' seconds'
|
2019-05-07 22:55:36 +02:00
|
|
|
write(*,*)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2021-03-03 11:37:46 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Stability analysis of HF solution
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(dostab) then
|
|
|
|
|
|
|
|
call cpu_time(start_stab)
|
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
call UHF_stability(nBas,nC,nO,nV,nR,nS,eHF,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb)
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call RHF_stability(nBas,nC,nO,nV,nR,nS,eHF,ERI_MO)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
call cpu_time(end_stab)
|
|
|
|
|
|
|
|
t_stab = end_stab - start_stab
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for stability analysis = ',t_stab,' seconds'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute MP2 energy
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doMP2) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_MP)
|
2020-09-18 13:52:35 +02:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-09-22 22:13:51 +02:00
|
|
|
call UMP2(nBas,nC,nO,nV,nR,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,ENuc,EUHF,eHF,EcMP2)
|
2020-09-18 13:52:35 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2022-11-30 17:18:51 +01:00
|
|
|
call MP2(regMP,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF,EcMP2)
|
2020-09-18 13:52:35 +02:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_MP)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_MP = end_MP - start_MP
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for MP2 = ',t_MP,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute MP3 energy
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doMP3) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_MP)
|
2020-09-21 16:54:38 +02:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
write(*,*) 'MP3 NYI for UHF reference'
|
|
|
|
stop
|
|
|
|
|
|
|
|
else
|
|
|
|
|
2020-10-19 13:57:56 +02:00
|
|
|
call MP3(nBas,nC,nO,nV,nR,ERI_MO,eHF,ENuc,ERHF)
|
2020-09-21 16:54:38 +02:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_MP)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_MP = end_MP - start_MP
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for MP3 = ',t_MP,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform CCD calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doCCD) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2022-09-09 21:48:50 +02:00
|
|
|
call CCD(.false.,maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CCD = ',t_CC,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2020-12-04 13:26:08 +01:00
|
|
|
! Perform DCD calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doDCD) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2020-12-04 13:26:08 +01:00
|
|
|
call DCD(maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR, &
|
|
|
|
ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2020-12-04 13:26:08 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for DCD = ',t_CC,' seconds'
|
2020-12-04 13:26:08 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2019-03-19 10:13:33 +01:00
|
|
|
! Perform CCSD or CCSD(T) calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-01-13 23:08:03 +01:00
|
|
|
if(doCCSDT) doCCSD = .true.
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
if(doCCSD) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2022-09-09 21:48:50 +02:00
|
|
|
call CCSD(.false.,maxSCF_CC,thresh_CC,n_diis_CC,doCCSDT,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2022-09-09 21:48:50 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CCSD or CCSD(T)= ',t_CC,' seconds'
|
2022-09-09 21:48:50 +02:00
|
|
|
write(*,*)
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
end if
|
|
|
|
|
2020-03-21 22:50:43 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform direct ring CCD calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(do_drCCD) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2022-09-27 14:07:31 +02:00
|
|
|
call drCCD(maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2020-03-21 22:50:43 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for direct ring CCD = ',t_CC,' seconds'
|
2020-03-21 22:50:43 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2020-01-14 14:44:01 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform ring CCD calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-03-21 22:50:43 +01:00
|
|
|
if(do_rCCD) then
|
2020-01-14 14:44:01 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2022-11-08 15:38:46 +01:00
|
|
|
call rCCD(.false.,maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2020-01-14 14:44:01 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for rCCD = ',t_CC,' seconds'
|
2020-01-14 14:44:01 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2021-11-10 14:47:26 +01:00
|
|
|
! Perform crossed-ring CCD calculation
|
2020-01-14 14:44:01 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
if(do_crCCD) then
|
2020-01-14 14:44:01 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2022-09-27 14:07:31 +02:00
|
|
|
call crCCD(maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2021-11-10 14:47:26 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for crossed-ring CCD = ',t_CC,' seconds'
|
2020-03-21 22:50:43 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2021-11-10 14:47:26 +01:00
|
|
|
! Perform ladder CCD calculation
|
2021-11-10 09:42:30 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
if(do_lCCD) then
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2021-11-10 14:47:26 +01:00
|
|
|
call lCCD(maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR, &
|
2021-11-10 09:42:30 +01:00
|
|
|
ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2021-11-10 09:42:30 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for ladder CCD = ',t_CC,' seconds'
|
2021-11-10 09:42:30 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2020-03-21 22:50:43 +01:00
|
|
|
! Perform pair CCD calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
if(dopCCD) then
|
2020-03-21 22:50:43 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CC)
|
2020-11-05 15:51:33 +01:00
|
|
|
call pCCD(maxSCF_CC,thresh_CC,n_diis_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CC)
|
2020-03-21 22:50:43 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CC = end_CC - start_CC
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for pair CCD = ',t_CC,' seconds'
|
2020-01-14 14:44:01 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute CIS excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doCIS) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CI)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
2020-09-24 16:39:15 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-09-28 21:25:25 +02:00
|
|
|
call UCIS(spin_conserved,spin_flip,nBas,nC,nO,nV,nR,nS,ERI_MO_aaaa,ERI_MO_aabb, &
|
2020-10-05 23:00:56 +02:00
|
|
|
ERI_MO_bbbb,dipole_int_aa,dipole_int_bb,eHF,cHF,S)
|
2020-09-24 16:39:15 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2020-10-21 12:58:37 +02:00
|
|
|
call CIS(singlet,triplet,doCIS_D,nBas,nC,nO,nV,nR,nS,ERI_MO,dipole_int_MO,eHF)
|
2020-09-24 16:39:15 +02:00
|
|
|
|
|
|
|
end if
|
2022-01-02 17:14:10 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CI)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CI = end_CI - start_CI
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CIS = ',t_CI,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-04-20 12:28:19 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute CID excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doCID) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CI)
|
2022-01-04 11:39:33 +01:00
|
|
|
call CID(singlet,triplet,nBas,nC,nO,nV,nR,ERI_MO,F_MO,ERHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CI)
|
2020-04-20 12:28:19 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CI = end_CI - start_CI
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CID = ',t_CI,' seconds'
|
2020-04-20 12:28:19 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute CISD excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doCISD) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CI)
|
2022-01-04 11:39:33 +01:00
|
|
|
call CISD(singlet,triplet,nBas,nC,nO,nV,nR,ERI_MO,F_MO,ERHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CI)
|
2020-04-20 12:28:19 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CI = end_CI - start_CI
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CISD = ',t_CI,' seconds'
|
2020-04-20 12:28:19 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2020-01-13 23:08:03 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute (direct) RPA excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doRPA) then
|
|
|
|
|
|
|
|
call cpu_time(start_RPA)
|
2020-09-23 09:46:44 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-10-07 22:51:30 +02:00
|
|
|
call URPA(TDA,doACFDT,exchange_kernel,spin_conserved,spin_flip,0d0,nBas,nC,nO,nV,nR,nS,ENuc,EUHF, &
|
2020-10-05 23:00:56 +02:00
|
|
|
ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_aa,dipole_int_bb,eHF,cHF,S)
|
2020-09-23 09:46:44 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2020-10-21 12:58:37 +02:00
|
|
|
call RPA(TDA,doACFDT,exchange_kernel,singlet,triplet,0d0,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
2020-09-23 09:46:44 +02:00
|
|
|
|
|
|
|
end if
|
2020-01-13 23:08:03 +01:00
|
|
|
call cpu_time(end_RPA)
|
|
|
|
|
|
|
|
t_RPA = end_RPA - start_RPA
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for RPA = ',t_RPA,' seconds'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
2020-01-16 21:39:00 +01:00
|
|
|
! Compute RPAx (RPA with exchange) excitations
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-01-14 19:53:52 +01:00
|
|
|
if(doRPAx) then
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
call cpu_time(start_RPA)
|
2020-09-23 09:46:44 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-09-24 16:39:15 +02:00
|
|
|
call URPAx(TDA,doACFDT,exchange_kernel,spin_conserved,spin_flip,0d0,nBas,nC,nO,nV,nR,nS,ENuc,EUHF, &
|
2020-10-05 23:00:56 +02:00
|
|
|
ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_aa,dipole_int_bb,eHF,cHF,S)
|
2020-09-23 09:46:44 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2022-09-28 16:09:09 +02:00
|
|
|
call RPAx(TDA,doACFDT,exchange_kernel,singlet,triplet,0d0,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
2020-09-23 09:46:44 +02:00
|
|
|
|
|
|
|
end if
|
2021-11-10 14:47:26 +01:00
|
|
|
call cpu_time(end_RPA)
|
|
|
|
|
|
|
|
t_RPA = end_RPA - start_RPA
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for RPAx = ',t_RPA,' seconds'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute cr-RPA excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(docrRPA) then
|
|
|
|
|
|
|
|
call cpu_time(start_RPA)
|
|
|
|
call crRPA(TDA,doACFDT,exchange_kernel,singlet,triplet,0d0,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
|
|
|
call cpu_time(end_RPA)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
t_RPA = end_RPA - start_RPA
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for pp-RPA = ',t_RPA,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2019-10-05 23:09:20 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute pp-RPA excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doppRPA) then
|
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
call cpu_time(start_RPA)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
2021-12-13 14:30:49 +01:00
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
call ppURPA(TDA,doACFDT,spin_conserved,spin_flip,nBas,nC,nO,nV,nR,ENuc,EUHF,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,eHF)
|
|
|
|
|
|
|
|
else
|
|
|
|
|
2022-08-17 15:52:13 +02:00
|
|
|
call ppRPA(TDA,doACFDT,singlet,triplet,nBas,nC,nO,nV,nR,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
2021-12-13 14:30:49 +01:00
|
|
|
|
|
|
|
end if
|
2022-01-02 17:14:10 +01:00
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
call cpu_time(end_RPA)
|
2019-10-05 23:09:20 +02:00
|
|
|
|
2021-11-10 14:47:26 +01:00
|
|
|
t_RPA = end_RPA - start_RPA
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for pp-RPA = ',t_RPA,' seconds'
|
2019-10-05 23:09:20 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute ADC excitations
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-04-20 12:28:19 +02:00
|
|
|
! if(doADC) then
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-04-20 12:28:19 +02:00
|
|
|
! call cpu_time(start_ADC)
|
2020-09-22 23:08:47 +02:00
|
|
|
! call ADC(singlet,triplet,maxSCF_GF,thresh_GF,n_diis_GF, &
|
2020-06-05 22:34:32 +02:00
|
|
|
! nBas,nC,nO,nV,nR,eHF,ERI_MO)
|
2020-04-20 12:28:19 +02:00
|
|
|
! call cpu_time(end_ADC)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-04-20 12:28:19 +02:00
|
|
|
! t_ADC = end_ADC - start_ADC
|
|
|
|
! write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for ADC = ',t_ADC,' seconds'
|
|
|
|
! write(*,*)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-04-20 12:28:19 +02:00
|
|
|
! end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2020-03-19 10:21:18 +01:00
|
|
|
! Compute G0F2 electronic binding energies
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-03-19 10:21:18 +01:00
|
|
|
if(doG0F2) then
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GF)
|
2021-03-08 17:00:05 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
2021-12-17 11:41:40 +01:00
|
|
|
call UG0F2(BSE,TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip,linGF,eta_GF,regGF, &
|
|
|
|
nBas,nC,nO,nV,nR,nS,ENuc,EUHF,S,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb, &
|
|
|
|
dipole_int_aa,dipole_int_bb,eHF)
|
2021-03-08 17:00:05 +01:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2021-12-17 11:41:40 +01:00
|
|
|
call G0F2(BSE,TDA,dBSE,dTDA,evDyn,singlet,triplet,linGF,eta_GF,regGF, &
|
|
|
|
nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,dipole_int_MO,eHF)
|
2021-03-08 17:00:05 +01:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GF)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GF = end_GF - start_GF
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for GF2 = ',t_GF,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2020-03-19 10:21:18 +01:00
|
|
|
! Compute evGF2 electronic binding energies
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-03-19 10:21:18 +01:00
|
|
|
if(doevGF2) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GF)
|
2021-03-08 20:09:54 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
call evUGF2(maxSCF_GF,thresh_GF,n_diis_GF,BSE,TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip, &
|
2021-12-17 11:41:40 +01:00
|
|
|
eta_GF,regGF,nBas,nC,nO,nV,nR,nS,ENuc,EUHF,S,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb, &
|
2021-03-08 20:09:54 +01:00
|
|
|
dipole_int_aa,dipole_int_bb,cHF,eHF)
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call evGF2(BSE,TDA,dBSE,dTDA,evDyn,maxSCF_GF,thresh_GF,n_diis_GF, &
|
2021-12-17 11:41:40 +01:00
|
|
|
singlet,triplet,linGF,eta_GF,regGF,nBas,nC,nO,nV,nR,nS,ENuc,ERHF, &
|
2021-03-08 20:09:54 +01:00
|
|
|
ERI_MO,dipole_int_MO,eHF)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GF)
|
2020-03-19 10:21:18 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GF = end_GF - start_GF
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for GF2 = ',t_GF,' seconds'
|
2020-03-19 10:21:18 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2021-03-05 22:34:48 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform qsGF2 calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doqsGF2) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GF)
|
2021-03-05 22:34:48 +01:00
|
|
|
|
2021-03-07 23:04:47 +01:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2021-12-17 11:41:40 +01:00
|
|
|
call qsUGF2(maxSCF_GF,thresh_GF,n_diis_GF,BSE,TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip,eta_GF,regGF, &
|
2021-03-07 23:04:47 +01:00
|
|
|
nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO,nV,nR,nS,EUHF,S,X,T,V,Hc,ERI_AO, &
|
|
|
|
ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_AO,dipole_int_aa,dipole_int_bb,PHF,cHF,eHF)
|
|
|
|
|
|
|
|
else
|
|
|
|
|
2021-12-17 11:41:40 +01:00
|
|
|
call qsGF2(maxSCF_GF,thresh_GF,n_diis_GF,BSE,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta_GF,regGF,nNuc,ZNuc,rNuc,ENuc, &
|
2021-03-07 23:04:47 +01:00
|
|
|
nBas,nC,nO,nV,nR,nS,ERHF,S,X,T,V,Hc,ERI_AO,ERI_MO,dipole_int_AO,dipole_int_MO,PHF,cHF,eHF)
|
|
|
|
|
|
|
|
end if
|
2021-03-05 22:34:48 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GF)
|
2021-03-05 22:34:48 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GF = end_GF - start_GF
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for qsGF2 = ',t_GF,' seconds'
|
2021-03-05 22:34:48 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2020-03-19 10:21:18 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute G0F3 electronic binding energies
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doG0F3) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GF)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
print*,'!!! G0F3 NYI at the unrestricted level !!!'
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call G0F3(renormGF,nBas,nC,nO,nV,nR,ERI_MO,eHF)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GF)
|
2020-03-19 10:21:18 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GF = end_GF - start_GF
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for GF3 = ',t_GF,' seconds'
|
2020-03-19 10:21:18 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute evGF3 electronic binding energies
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doevGF3) then
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GF)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
print*,'!!! evGF3 NYI at the unrestricted level !!!'
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call evGF3(maxSCF_GF,thresh_GF,n_diis_GF,renormGF,nBas,nC,nO,nV,nR,ERI_MO,eHF)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GF)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GF = end_GF - start_GF
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for GF3 = ',t_GF,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform G0W0 calculatiom
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
eG0W0(:,:) = eHF(:,:)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
if(doG0W0) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GW)
|
2020-09-18 13:52:35 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-09-28 22:58:58 +02:00
|
|
|
call UG0W0(doACFDT,exchange_kernel,doXBS,COHSEX,BSE,TDA_W,TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip, &
|
2021-12-17 11:41:40 +01:00
|
|
|
linGW,eta_GW,regGW,nBas,nC,nO,nV,nR,nS,ENuc,EUHF,S,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb, &
|
2021-02-15 17:27:06 +01:00
|
|
|
dipole_int_aa,dipole_int_bb,PHF,cHF,eHF,Vxc,eG0W0)
|
2020-09-18 13:52:35 +02:00
|
|
|
else
|
|
|
|
|
2023-07-04 10:37:54 +02:00
|
|
|
call G0W0(doACFDT,exchange_kernel,doXBS,COHSEX,BSE,BSE2,TDA_W,TDA,dBSE,dTDA,evDyn,ppBSE,singlet,triplet, &
|
|
|
|
linGW,eta_GW,regGW,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_AO,ERI_MO,dipole_int_MO,PHF,cHF,eHF,Vxc,eG0W0)
|
2020-09-18 13:52:35 +02:00
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GW)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GW = end_GW - start_GW
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for G0W0 = ',t_GW,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform evGW calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doevGW) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GW)
|
2020-09-24 22:50:56 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2020-09-28 22:58:58 +02:00
|
|
|
call evUGW(maxSCF_GW,thresh_GW,n_diis_GW,doACFDT,exchange_kernel,doXBS,COHSEX,BSE,TDA_W,TDA, &
|
2022-11-30 16:41:19 +01:00
|
|
|
dBSE,dTDA,evDyn,spin_conserved,spin_flip,eta_GW,regGW,nBas,nC,nO,nV,nR,nS,ENuc, &
|
2021-02-15 17:27:06 +01:00
|
|
|
EUHF,S,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_aa,dipole_int_bb, &
|
|
|
|
PHF,cHF,eHF,Vxc,eG0W0)
|
2020-09-24 22:50:56 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2022-09-09 21:48:50 +02:00
|
|
|
call evGW(maxSCF_GW,thresh_GW,n_diis_GW,doACFDT,exchange_kernel,doXBS,COHSEX, &
|
2023-06-30 16:47:26 +02:00
|
|
|
BSE,BSE2,TDA_W,TDA,dBSE,dTDA,evDyn,ppBSE,singlet,triplet,linGW,eta_GW,regGW, &
|
2021-02-15 17:27:06 +01:00
|
|
|
nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_AO,ERI_MO,dipole_int_MO,PHF,cHF,eHF,Vxc,eG0W0)
|
2020-09-24 22:50:56 +02:00
|
|
|
end if
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GW)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GW = end_GW - start_GW
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for evGW = ',t_GW,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform qsGW calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doqsGW) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call wall_time(start_GW)
|
2020-10-21 12:09:18 +02:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
2021-10-22 21:10:31 +02:00
|
|
|
call qsUGW(maxSCF_GW,thresh_GW,n_diis_GW,doACFDT,exchange_kernel,doXBS,COHSEX,BSE,TDA_W,TDA, &
|
2022-11-30 16:41:19 +01:00
|
|
|
dBSE,dTDA,evDyn,spin_conserved,spin_flip,eta_GW,regGW,nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO, &
|
2020-10-21 12:58:37 +02:00
|
|
|
nV,nR,nS,EUHF,S,X,T,V,Hc,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_AO, &
|
|
|
|
dipole_int_aa,dipole_int_bb,PHF,cHF,eHF)
|
2020-10-21 12:09:18 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2021-10-22 21:10:31 +02:00
|
|
|
call qsGW(maxSCF_GW,thresh_GW,n_diis_GW,doACFDT,exchange_kernel,doXBS,COHSEX, &
|
2022-11-30 16:41:19 +01:00
|
|
|
BSE,BSE2,TDA_W,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta_GW,regGW,nNuc,ZNuc,rNuc,ENuc, &
|
2020-10-21 12:58:37 +02:00
|
|
|
nBas,nC,nO,nV,nR,nS,ERHF,S,X,T,V,Hc,ERI_AO,ERI_MO,dipole_int_AO,dipole_int_MO,PHF,cHF,eHF)
|
2020-10-21 12:09:18 +02:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call wall_time(end_GW)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GW = end_GW - start_GW
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for qsGW = ',t_GW,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2021-10-18 14:14:46 +02:00
|
|
|
!------------------------------------------------------------------------
|
2022-11-29 12:11:09 +01:00
|
|
|
! Perform SRG-qsGW calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doSRGqsGW) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call wall_time(start_GW)
|
2022-11-29 12:11:09 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
print*,'Unrestricted version of SRG-qsGW NYI'
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call SRG_qsGW(maxSCF_GW,thresh_GW,n_diis_GW,doACFDT,exchange_kernel,doXBS,BSE,BSE2,TDA_W,TDA,dBSE,dTDA,evDyn, &
|
|
|
|
singlet,triplet,eta_GW,nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO,nV,nR,nS,ERHF,S,X,T,V,Hc,ERI_AO,ERI_MO, &
|
|
|
|
dipole_int_AO,dipole_int_MO,PHF,cHF,eHF)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call wall_time(end_GW)
|
2022-11-29 12:11:09 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GW = end_GW - start_GW
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for qsGW = ',t_GW,' seconds'
|
2022-11-29 12:11:09 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
2021-10-18 21:11:01 +02:00
|
|
|
! Perform ufG0W0 calculatiom
|
2021-10-18 14:14:46 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2021-10-18 21:11:01 +02:00
|
|
|
if(doufG0W0) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GW)
|
2023-06-30 16:47:26 +02:00
|
|
|
call ufG0W0(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,eHF,TDA_W)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GW)
|
2021-10-18 21:11:01 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GW = end_GW - start_GW
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for ufG0W0 = ',t_GW,' seconds'
|
2021-10-18 21:11:01 +02:00
|
|
|
write(*,*)
|
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
if(BSE) call ufBSE(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,eHF,eG0W0)
|
|
|
|
|
2021-10-18 21:11:01 +02:00
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform ufGW calculatiom
|
|
|
|
!------------------------------------------------------------------------
|
2021-10-18 14:14:46 +02:00
|
|
|
|
|
|
|
if(doufGW) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GW)
|
2021-12-17 11:41:40 +01:00
|
|
|
call ufGW(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,eHF)
|
2023-06-29 18:54:00 +02:00
|
|
|
! call CCGW(maxSCF_CC,thresh_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,ERHF,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GW)
|
2021-10-18 14:14:46 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GW = end_GW - start_GW
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for ufGW = ',t_GW,' seconds'
|
2021-10-18 14:14:46 +02:00
|
|
|
write(*,*)
|
|
|
|
|
2022-11-08 15:38:46 +01:00
|
|
|
if(BSE) call ufBSE(nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_MO,eHF,eG0W0)
|
2021-10-26 18:45:49 +02:00
|
|
|
|
2021-10-18 14:14:46 +02:00
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
2023-07-04 10:32:47 +02:00
|
|
|
! Perform G0T0pp calculatiom
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2020-09-18 13:52:35 +02:00
|
|
|
eG0T0(:,:) = eHF(:,:)
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
if(doG0T0pp) then
|
2019-10-16 18:14:47 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GT)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
2022-02-07 10:46:43 +01:00
|
|
|
!print*,'!!! G0T0 NYI at the unrestricted level !!!'
|
|
|
|
call UG0T0(doACFDT,exchange_kernel,doXBS,BSE,TDA_T,TDA,dBSE,dTDA,evDyn, &
|
|
|
|
spin_conserved,spin_flip,linGT,eta_GT,regGT,nBas,nC,nO,nV, &
|
|
|
|
nR,nS,ENuc,EUHF,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb, &
|
|
|
|
dipole_int_aa,dipole_int_bb,PHF,cHF,eHF,Vxc,eG0T0)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2022-01-26 13:05:16 +01:00
|
|
|
! call soG0T0(eta_GT,nBas,nC,nO,nV,nR,ENuc,ERHF,ERI_MO,eHF)
|
2023-07-04 10:32:47 +02:00
|
|
|
call G0T0pp(doACFDT,exchange_kernel,doXBS,BSE,TDA_T,TDA,dBSE,dTDA,evDyn,ppBSE,singlet,triplet, &
|
|
|
|
linGT,eta_GT,regGT,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_AO,ERI_MO,dipole_int_MO, &
|
|
|
|
PHF,cHF,eHF,Vxc,eG0T0)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GT)
|
2019-10-16 18:14:47 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GT = end_GT - start_GT
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for G0T0 = ',t_GT,' seconds'
|
2019-03-19 10:13:33 +01:00
|
|
|
write(*,*)
|
|
|
|
|
2019-07-09 23:09:32 +02:00
|
|
|
end if
|
2019-03-19 10:13:33 +01:00
|
|
|
|
2020-04-13 14:19:14 +02:00
|
|
|
!------------------------------------------------------------------------
|
2023-07-04 10:32:47 +02:00
|
|
|
! Perform evGTpp calculatiom
|
2020-04-13 14:19:14 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
if(doevGTpp) then
|
2020-04-13 14:19:14 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GT)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
2022-02-16 13:29:22 +01:00
|
|
|
call evUGT(maxSCF_GT,thresh_GT,n_diis_GT,doACFDT,exchange_kernel,doXBS, &
|
|
|
|
BSE,TDA_T,TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip,&
|
|
|
|
eta_GT,regGT,nBas,nC,nO,nV,nR,nS,ENuc,EUHF,ERI_AO, &
|
|
|
|
ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_aa, &
|
|
|
|
dipole_int_bb,PHF,cHF,eHF,Vxc,eG0T0)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2023-07-04 10:32:47 +02:00
|
|
|
call evGTpp(maxSCF_GT,thresh_GT,n_diis_GT,doACFDT,exchange_kernel,doXBS, &
|
|
|
|
BSE,TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta_GT,regGT, &
|
|
|
|
nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_AO,ERI_MO,dipole_int_MO, &
|
|
|
|
PHF,cHF,eHF,Vxc,eG0T0)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GT)
|
2020-04-13 14:19:14 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GT = end_GT - start_GT
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for evGT = ',t_GT,' seconds'
|
2020-04-13 14:19:14 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2021-10-17 23:04:22 +02:00
|
|
|
!------------------------------------------------------------------------
|
2023-07-04 10:32:47 +02:00
|
|
|
! Perform qsGTpp calculation
|
2021-10-17 23:04:22 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
if(doqsGTpp) then
|
2021-10-17 23:04:22 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GT)
|
2021-10-17 23:04:22 +02:00
|
|
|
|
2022-01-02 17:14:10 +01:00
|
|
|
if(unrestricted) then
|
|
|
|
|
2022-02-25 09:40:39 +01:00
|
|
|
call qsUGT(maxSCF_GT,thresh_GT,n_diis_GT,doACFDT,exchange_kernel,doXBS,BSE,TDA_T, &
|
|
|
|
TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip,eta_GT,regGT,nBas,nC,nO,nV,&
|
|
|
|
nR,nS,nNuc,ZNuc,rNuc,ENuc,EUHF,S,X,T,V,Hc,ERI_AO,ERI_MO_aaaa,ERI_MO_aabb,&
|
|
|
|
ERI_MO_bbbb,dipole_int_AO,dipole_int_aa,dipole_int_bb,PHF,cHF,eHF)
|
2022-01-02 17:14:10 +01:00
|
|
|
else
|
|
|
|
|
2023-07-04 10:32:47 +02:00
|
|
|
call qsGTpp(maxSCF_GT,thresh_GT,n_diis_GT,doACFDT,exchange_kernel,doXBS, &
|
|
|
|
BSE,TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta_GT,regGT, &
|
|
|
|
nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO,nV,nR,nS,ERHF,S,X,T,V,Hc, &
|
|
|
|
ERI_AO,ERI_MO,dipole_int_AO,dipole_int_MO,PHF,cHF,eHF)
|
2022-01-02 17:14:10 +01:00
|
|
|
|
|
|
|
end if
|
2021-10-17 23:04:22 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GT)
|
2021-10-17 23:04:22 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GT = end_GT - start_GT
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for qsGT = ',t_GT,' seconds'
|
2021-10-17 23:04:22 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-06-29 18:54:00 +02:00
|
|
|
!------------------------------------------------------------------------
|
2023-07-03 23:15:07 +02:00
|
|
|
! Perform G0T0eh calculatiom
|
2023-06-29 18:54:00 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
eG0T0(:,:) = eHF(:,:)
|
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
if(doG0T0eh) then
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GT)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
print*,'!!! eh G0T0 NYI at the unrestricted level !!!'
|
2023-06-29 18:54:00 +02:00
|
|
|
|
|
|
|
else
|
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
call G0T0eh(doACFDT,exchange_kernel,doXBS,BSE,BSE2,TDA_W,TDA,dBSE,dTDA,evDyn,ppBSE,singlet,triplet, &
|
2023-06-29 18:54:00 +02:00
|
|
|
linGW,eta_GW,regGW,nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_AO,ERI_MO,dipole_int_MO,PHF,cHF,eHF,Vxc,eG0T0)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GT)
|
2023-06-29 18:54:00 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GT = end_GT - start_GT
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for G0T0 = ',t_GT,' seconds'
|
2023-06-29 18:54:00 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2023-07-03 23:15:07 +02:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform evGTeh calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doevGTeh) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_GT)
|
2023-07-03 23:15:07 +02:00
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call evGTeh(maxSCF_GT,thresh_GT,n_diis_GT,doACFDT,exchange_kernel,doXBS, &
|
2023-07-04 08:29:16 +02:00
|
|
|
BSE,BSE2,TDA_T,TDA,dBSE,dTDA,evDyn,ppBSE,singlet,triplet,linGT,eta_GT,regGT, &
|
2023-07-03 23:15:07 +02:00
|
|
|
nBas,nC,nO,nV,nR,nS,ENuc,ERHF,ERI_AO,ERI_MO,dipole_int_MO,PHF,cHF,eHF,Vxc,eG0T0)
|
|
|
|
end if
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_GT)
|
|
|
|
|
|
|
|
t_GT = end_GT - start_GT
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for evGT = ',t_GT,' seconds'
|
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Perform qsGTeh calculation
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doqsGTeh) then
|
|
|
|
|
|
|
|
call wall_time(start_GT)
|
|
|
|
|
|
|
|
if(unrestricted) then
|
|
|
|
|
|
|
|
else
|
|
|
|
|
|
|
|
call qsGTeh(maxSCF_GT,thresh_GT,n_diis_GT,doACFDT,exchange_kernel,doXBS, &
|
|
|
|
BSE,BSE2,TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta_GT,regGT,nNuc,ZNuc,rNuc,ENuc, &
|
|
|
|
nBas,nC,nO,nV,nR,nS,ERHF,S,X,T,V,Hc,ERI_AO,ERI_MO,dipole_int_AO,dipole_int_MO,PHF,cHF,eHF)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
call wall_time(end_GT)
|
2023-07-03 23:15:07 +02:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_GT = end_GT - start_GT
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for qsGW = ',t_GT,' seconds'
|
2023-07-03 23:15:07 +02:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2021-03-08 17:00:05 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! Compute FCI
|
|
|
|
!------------------------------------------------------------------------
|
|
|
|
|
|
|
|
if(doFCI) then
|
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(start_CI)
|
2022-12-01 09:45:30 +01:00
|
|
|
write(*,*) ' FCI is not yet implemented! Sorry.'
|
|
|
|
! call FCI(nBas,nC,nO,nV,nR,ERI_MO,eHF)
|
2023-07-04 09:27:35 +02:00
|
|
|
call cpu_time(end_CI)
|
2021-03-08 17:00:05 +01:00
|
|
|
|
2023-07-04 09:27:35 +02:00
|
|
|
t_CI = end_CI - start_CI
|
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for FCI = ',t_CI,' seconds'
|
2021-03-08 17:00:05 +01:00
|
|
|
write(*,*)
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
!------------------------------------------------------------------------
|
|
|
|
! End of QuAcK
|
|
|
|
!------------------------------------------------------------------------
|
2019-04-24 18:00:54 +02:00
|
|
|
|
2023-03-14 14:11:01 +01:00
|
|
|
call wall_time(end_QuAcK)
|
2019-04-24 18:00:54 +02:00
|
|
|
|
|
|
|
t_QuAcK = end_QuAcK - start_QuAcK
|
2023-03-14 14:11:01 +01:00
|
|
|
write(*,'(A65,1X,F9.3,A8)') 'Total wall time for QuAcK = ',t_QuAcK,' seconds'
|
2019-04-24 18:00:54 +02:00
|
|
|
write(*,*)
|
|
|
|
|
2019-03-19 10:13:33 +01:00
|
|
|
end program QuAcK
|