4
1
mirror of https://github.com/pfloos/quack synced 2024-07-17 16:33:43 +02:00
quack/src/QuAcK/QuAcK.f90

493 lines
18 KiB
Fortran
Raw Normal View History

2019-03-19 10:13:33 +01:00
program QuAcK
implicit none
include 'parameters.h'
2020-09-22 15:32:26 +02:00
logical :: unrestricted = .false.
2023-09-05 17:23:40 +02:00
logical :: doHF,doRHF,doUHF,doROHF,doRMOM,doUMOM
2021-03-03 11:37:46 +01:00
logical :: dostab
2020-10-13 13:44:24 +02:00
logical :: doKS
2023-07-17 14:21:39 +02:00
logical :: doMP,doMP2,doMP3
2023-07-22 22:19:46 +02:00
logical :: doCC,doCCD,dopCCD,doDCD,doCCSD,doCCSDT
2023-07-23 11:16:42 +02:00
logical :: dodrCCD,dorCCD,docrCCD,dolCCD
2023-07-23 10:29:24 +02:00
logical :: doCI,doCIS,doCIS_D,doCID,doCISD,doFCI
2023-07-23 11:16:42 +02:00
logical :: doRPA,dophRPA,dophRPAx,docrRPA,doppRPA
2023-07-23 11:58:18 +02:00
logical :: doGF,doG0F2,doevGF2,doqsGF2,doG0F3,doevGF3
2023-07-23 17:41:44 +02:00
logical :: doGW,doG0W0,doevGW,doqsGW,doufG0W0,doufGW,doSRGqsGW
logical :: doGT,doG0T0pp,doevGTpp,doqsGTpp
2023-07-03 23:15:07 +02:00
logical :: doG0T0eh,doevGTeh,doqsGTeh
2019-07-09 23:09:32 +02:00
2023-07-17 13:51:52 +02:00
integer :: nNuc,nBas
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)
2023-07-17 13:51:52 +02:00
double precision :: ENuc,EHF
2019-03-19 10:13:33 +01:00
double precision,allocatable :: ZNuc(:),rNuc(:,:)
2023-07-17 13:51:52 +02:00
double precision,allocatable :: cHF(:,:,:),epsHF(:,:),PHF(:,:,:)
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
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(:,:,:)
2023-10-24 14:39:02 +02: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(:,:,:,:)
integer :: ixyz
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(:,:,:,:)
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-23 17:41:44 +02:00
double precision :: start_MP ,end_MP ,t_MP
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
2019-03-19 10:13:33 +01:00
2023-07-23 11:58:18 +02:00
integer :: maxSCF_HF,max_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
logical :: reg_MP
2023-07-23 11:58:18 +02:00
integer :: maxSCF_CC,max_diis_CC
2019-03-19 10:13:33 +01:00
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
integer :: maxSCF_GF,max_diis_GF,renorm_GF
2019-03-19 10:13:33 +01:00
double precision :: thresh_GF
logical :: DIIS_GF,lin_GF,reg_GF
2020-06-03 12:06:16 +02:00
double precision :: eta_GF
2019-03-19 10:13:33 +01:00
2023-07-23 11:58:18 +02:00
integer :: maxSCF_GW,max_diis_GW
2019-03-19 10:13:33 +01:00
double precision :: thresh_GW
logical :: DIIS_GW,TDA_W,lin_GW,reg_GW
2020-06-03 12:06:16 +02:00
double precision :: eta_GW
2019-03-19 10:13:33 +01:00
2023-07-23 11:58:18 +02:00
integer :: maxSCF_GT,max_diis_GT
2021-12-17 11:41:40 +01:00
double precision :: thresh_GT
logical :: DIIS_GT,TDA_T,lin_GT,reg_GT
2021-12-17 11:41:40 +01:00
double precision :: eta_GT
2023-07-21 10:21:54 +02:00
logical :: dophBSE,dophBSE2,doppBSE,dBSE,dTDA
2023-07-12 23:16:37 +02:00
2020-06-14 21:20:01 +02:00
2023-07-29 09:24:55 +02:00
!-------------!
! Hello World !
!-------------!
2019-03-19 10:13:33 +01:00
write(*,*)
write(*,*) '******************************************************************************************'
write(*,*) '* QuAcK QuAcK QuAcK *'
write(*,*) '* __ __ __ __ __ __ __ __ __ *'
write(*,*) '* <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ <(o )___ *'
write(*,*) '* ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / ( ._> / *'
write(*,*) '*|--------------------------------------------------------------------------------------|*'
write(*,*) '******************************************************************************************'
write(*,*)
2023-07-29 09:24:55 +02:00
!-----------------------!
! Starting QuAcK timing !
!-----------------------!
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
2023-07-29 09:24:55 +02:00
!------------------!
! Method selection !
!------------------!
2019-03-19 10:13:33 +01:00
2023-09-05 17:23:40 +02:00
call read_methods(doRHF,doUHF,doROHF,doRMOM,doUMOM,doKS, &
doMP2,doMP3, &
doCCD,dopCCD,doDCD,doCCSD,doCCSDT, &
dodrCCD,dorCCD,docrCCD,dolCCD, &
doCIS,doCIS_D,doCID,doCISD,doFCI, &
dophRPA,dophRPAx,docrRPA,doppRPA, &
doG0F2,doevGF2,doqsGF2, &
doG0F3,doevGF3, &
doG0W0,doevGW,doqsGW,doSRGqsGW, &
doufG0W0,doufGW, &
doG0T0pp,doevGTpp,doqsGTpp, &
2023-07-03 23:15:07 +02:00
doG0T0eh,doevGTeh,doqsGTeh)
2019-03-19 10:13:33 +01:00
2023-07-29 09:24:55 +02:00
!--------------------------!
! Read options for methods !
!--------------------------!
2019-03-19 10:13:33 +01:00
2023-07-23 11:58:18 +02:00
call read_options(maxSCF_HF,thresh_HF,DIIS_HF,max_diis_HF,guess_type,ortho_type,mix,level_shift,dostab, &
reg_MP, &
2023-07-23 11:58:18 +02:00
maxSCF_CC,thresh_CC,DIIS_CC,max_diis_CC, &
TDA,singlet,triplet,spin_conserved,spin_flip, &
maxSCF_GF,thresh_GF,DIIS_GF,max_diis_GF,lin_GF,eta_GF,renorm_GF,reg_GF, &
maxSCF_GW,thresh_GW,DIIS_GW,max_diis_GW,lin_GW,eta_GW,reg_GW,TDA_W, &
maxSCF_GT,thresh_GT,DIIS_GT,max_diis_GT,lin_GT,eta_GT,reg_GT,TDA_T, &
doACFDT,exchange_kernel,doXBS, &
2023-07-21 10:45:10 +02:00
dophBSE,dophBSE2,doppBSE,dBSE,dTDA)
2019-03-19 10:13:33 +01:00
2023-07-29 09:24:55 +02:00
!------------------------------------------------!
! Read input information !
!------------------------------------------------!
! 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 10:13:33 +01:00
2023-07-17 13:35:24 +02: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-29 09:24:55 +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)
2020-01-22 09:20:18 +01:00
nS(:) = (nO(:) - nC(:))*(nV(:) - nR(:))
2019-03-19 10:13:33 +01:00
2023-07-29 09:24:55 +02:00
!--------------------------------------!
! Read one- and two-electron integrals !
!--------------------------------------!
2019-03-19 10:13:33 +01:00
! Memory allocation for one- and two-electron integrals
2023-07-23 11:16:42 +02:00
allocate(cHF(nBas,nBas,nspin),epsHF(nBas,nspin),PHF(nBas,nBas,nspin),S(nBas,nBas),T(nBas,nBas), &
2023-07-17 13:35:24 +02:00
V(nBas,nBas),Hc(nBas,nBas),X(nBas,nBas),ERI_AO(nBas,nBas,nBas,nBas),dipole_int_AO(nBas,nBas,ncart), &
2023-10-24 14:39:02 +02:00
dipole_int_MO(nBas,nBas,ncart),F_AO(nBas,nBas,nspin))
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
2023-07-17 13:35:24 +02:00
call read_integrals(nBas,S,T,V,Hc,ERI_AO)
call read_dipole_integrals(nBas,dipole_int_AO)
2019-05-07 22:55:36 +02:00
2023-03-14 14:11:01 +01:00
call wall_time(end_int)
2019-05-07 22:55:36 +02:00
2023-07-23 11:16:42 +02:00
t_int = end_int - start_int
write(*,*)
2023-10-24 17:03:41 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for reading integrals = ',t_int,' seconds'
2023-07-23 11:16:42 +02:00
write(*,*)
2019-03-19 10:13:33 +01:00
! Compute orthogonalization matrix
call orthogonalization_matrix(ortho_type,nBas,S,X)
2023-07-29 09:24:55 +02:00
!---------------------!
! Hartree-Fock module !
!---------------------!
2019-03-19 10:13:33 +01:00
2023-09-05 17:23:40 +02:00
doHF = doRHF .or. doUHF .or. doROHF .or. doRMOM .or. doUMOM
2019-03-19 10:13:33 +01:00
2023-07-17 13:35:24 +02:00
if(doHF) then
2020-10-08 17:19:48 +02:00
2023-03-14 14:11:01 +01:00
call wall_time(start_HF)
2023-09-05 17:23:40 +02:00
call HF(doRHF,doUHF,doROHF,doRMOM,doUMOM,unrestricted,maxSCF_HF,thresh_HF,max_diis_HF, &
2023-10-24 14:39:02 +02:00
guess_type,mix,level_shift,nNuc,ZNuc,rNuc,ENuc,nBas,nO,S,T,V,Hc,F_AO,ERI_AO, &
dipole_int_AO,X,EHF,epsHF,cHF,PHF)
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-10-24 17:03:41 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for HF = ',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
2023-07-29 09:24:55 +02:00
!------------------!
! Kohn-Sham module !
!------------------!
2020-10-13 13:44:24 +02:00
if(doKS) then
2021-02-15 17:27:06 +01:00
! Switch on the unrestricted flag
unrestricted = .true.
2023-07-29 09:24:55 +02:00
call wall_time(start_KS)
2023-07-23 10:29:24 +02:00
write(*,*)
write(*,*) 'KS module has been disabled for now! Sorry.'
write(*,*)
2023-07-23 11:58:18 +02:00
! call eDFT(maxSCF_HF,thresh_HF,max_diis_HF,guess_type,mix,level_shift,nNuc,ZNuc,rNuc,ENuc,nBas,nEl,nC, &
2023-07-03 14:33:48 +02:00
! nO,nV,nR,nShell,TotAngMomShell,CenterShell,KShell,DShell,ExpShell, &
2023-07-17 13:51:52 +02:00
! max_ang_mom,min_exponent,max_exponent,S,T,V,Hc,X,ERI_AO,dipole_int_AO,EHF,epsHF,cHF,PHF,Vxc)
2023-07-29 09:24:55 +02:00
call wall_time(end_KS)
2020-10-13 13:44:24 +02:00
t_KS = end_KS - start_KS
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for KS = ',t_KS,' seconds'
write(*,*)
end if
2023-07-29 09:24:55 +02:00
!----------------------------------!
! AO to MO integral transformation !
!----------------------------------!
2019-03-19 10:13:33 +01:00
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(*,*)
2023-07-17 13:35:24 +02:00
if(unrestricted) then
2019-05-07 22:55:36 +02:00
2023-07-17 13:35:24 +02:00
! Read and transform dipole-related integrals
allocate(dipole_int_aa(nBas,nBas,ncart),dipole_int_bb(nBas,nBas,ncart))
dipole_int_aa(:,:,:) = dipole_int_AO(:,:,:)
dipole_int_bb(:,:,:) = dipole_int_AO(:,:,:)
do ixyz=1,ncart
call AOtoMO_transform(nBas,cHF(:,:,1),dipole_int_aa(:,:,ixyz))
call AOtoMO_transform(nBas,cHF(:,:,2),dipole_int_bb(:,:,ixyz))
end do
! Memory allocation
allocate(ERI_MO_aaaa(nBas,nBas,nBas,nBas),ERI_MO_aabb(nBas,nBas,nBas,nBas),ERI_MO_bbbb(nBas,nBas,nBas,nBas))
! 4-index transform for (aa|aa) block
2023-07-29 09:24:55 +02:00
call AOtoMO_integral_transform(1,1,1,1,nBas,cHF,ERI_AO,ERI_MO_aaaa)
2023-07-17 13:35:24 +02:00
! 4-index transform for (aa|bb) block
2023-07-29 09:24:55 +02:00
call AOtoMO_integral_transform(1,1,2,2,nBas,cHF,ERI_AO,ERI_MO_aabb)
2023-07-17 13:35:24 +02:00
! 4-index transform for (bb|bb) block
2023-07-29 09:24:55 +02:00
call AOtoMO_integral_transform(2,2,2,2,nBas,cHF,ERI_AO,ERI_MO_bbbb)
2020-09-22 23:08:47 +02:00
2023-07-17 13:35:24 +02:00
else
2020-09-18 13:52:35 +02:00
2023-07-17 13:35:24 +02:00
! Memory allocation
2023-10-24 14:39:02 +02:00
allocate(ERI_MO(nBas,nBas,nBas,nBas),F_MO(nBas,nBas,nspin))
2022-01-07 09:56:30 +01:00
2023-07-17 13:35:24 +02:00
! Read and transform dipole-related integrals
dipole_int_MO(:,:,:) = dipole_int_AO(:,:,:)
do ixyz=1,ncart
call AOtoMO_transform(nBas,cHF,dipole_int_MO(:,:,ixyz))
end do
! 4-index transform
2023-07-29 09:24:55 +02:00
call AOtoMO_integral_transform(1,1,1,1,nBas,cHF,ERI_AO,ERI_MO)
2023-07-17 13:35:24 +02:00
2023-10-24 14:39:02 +02:00
F_MO(:,:,1) = F_AO(:,:,1)
2023-07-17 13:35:24 +02:00
call AOtoMO_transform(nBas,cHF,F_MO)
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-10-24 17:03:41 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU 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
2023-07-29 09:24:55 +02:00
!-----------------------------------!
! Stability analysis of HF solution !
!-----------------------------------!
2021-03-03 11:37:46 +01:00
if(dostab) then
2023-07-29 09:24:55 +02:00
call wall_time(start_stab)
2021-03-03 11:37:46 +01:00
if(unrestricted) then
2023-07-17 13:51:52 +02:00
call UHF_stability(nBas,nC,nO,nV,nR,nS,epsHF,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb)
2021-03-03 11:37:46 +01:00
else
2023-07-17 13:51:52 +02:00
call RHF_stability(nBas,nC,nO,nV,nR,nS,epsHF,ERI_MO)
2021-03-03 11:37:46 +01:00
end if
2023-07-29 09:24:55 +02:00
call wall_time(end_stab)
2021-03-03 11:37:46 +01:00
t_stab = end_stab - start_stab
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for stability analysis = ',t_stab,' seconds'
write(*,*)
end if
2023-07-29 09:24:55 +02:00
!-----------------------!
! Moller-Plesset module !
!-----------------------!
2019-03-19 10:13:33 +01:00
2023-07-17 14:21:39 +02:00
doMP = doMP2 .or. doMP3
2019-03-19 10:13:33 +01:00
2023-07-17 14:21:39 +02:00
if(doMP) then
2019-03-19 10:13:33 +01:00
2023-07-29 09:24:55 +02:00
call wall_time(start_MP)
call MP(doMP2,doMP3,unrestricted,reg_MP,nBas,nC,nO,nV,nR,ERI_MO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,ENuc,EHF,epsHF)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-22 22:19:46 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for MP = ',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
2023-07-29 09:24:55 +02:00
!------------------------!
! Coupled-cluster module !
!------------------------!
2019-03-19 10:13:33 +01:00
2023-07-23 11:16:42 +02:00
doCC = doCCD .or. dopCCD .or. doDCD .or. doCCSD .or. doCCSDT .or. &
dodrCCD .or. dorCCD .or. docrCCD .or. dolCCD
2019-03-19 10:13:33 +01:00
2023-07-22 22:19:46 +02:00
if(doCC) then
2020-03-21 22:50:43 +01:00
2023-07-29 09:24:55 +02:00
call wall_time(start_CC)
2023-07-23 11:16:42 +02:00
call CC(doCCD,dopCCD,doDCD,doCCSD,doCCSDT,dodrCCD,dorCCD,docrCCD,dolCCD, &
2023-07-23 11:58:18 +02:00
maxSCF_CC,thresh_CC,max_diis_CC,nBas,nC,nO,nV,nR,ERI_MO,ENuc,EHF,epsHF)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-22 22:19:46 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CC = ',t_CC,' seconds'
2020-01-14 14:44:01 +01:00
write(*,*)
end if
2023-07-29 09:24:55 +02:00
!----------------------------------!
! Configuration interaction module !
!----------------------------------!
2019-03-19 10:13:33 +01:00
2023-07-23 10:29:24 +02:00
doCI = doCIS .or. doCID .or. doCISD .or. doFCI
2020-09-24 16:39:15 +02:00
2023-07-23 10:29:24 +02:00
if(doCI) then
2020-04-20 12:28:19 +02:00
2023-07-29 09:24:55 +02:00
call wall_time(start_CI)
2023-07-23 11:16:42 +02:00
call CI(doCIS,doCIS_D,doCID,doCISD,doFCI,unrestricted,singlet,triplet,spin_conserved,spin_flip, &
2023-07-23 10:40:39 +02:00
nBas,nC,nO,nV,nR,nS,ERI_MO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_MO,dipole_int_aa,dipole_int_bb, &
epsHF,EHF,cHF,S,F_MO)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-23 10:29:24 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for CI = ',t_CI,' seconds'
2020-04-20 12:28:19 +02:00
write(*,*)
end if
2023-07-29 09:24:55 +02:00
!-----------------------------------!
! Random-phase approximation module !
!-----------------------------------!
2020-01-13 23:08:03 +01:00
2023-07-23 11:16:42 +02:00
doRPA = dophRPA .or. dophRPAx .or. docrRPA .or. doppRPA
2020-09-23 09:46:44 +02:00
2023-07-23 11:16:42 +02:00
if(doRPA) then
2019-03-19 10:13:33 +01:00
2023-07-29 09:24:55 +02:00
call wall_time(start_RPA)
2023-07-23 11:16:42 +02:00
call RPA(dophRPA,dophRPAx,docrRPA,doppRPA,unrestricted, &
TDA,doACFDT,exchange_kernel,singlet,triplet,spin_conserved,spin_flip, &
nBas,nC,nO,nV,nR,nS,ENuc,EHF,ERI_MO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb, &
dipole_int_MO,dipole_int_aa,dipole_int_bb,epsHF,cHF,S)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-23 11:16:42 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for RPA = ',t_RPA,' seconds'
2019-10-05 23:09:20 +02:00
write(*,*)
end if
2023-07-29 09:24:55 +02:00
!-------------------------!
! Green's function module !
!-------------------------!
2019-03-19 10:13:33 +01:00
2023-07-23 11:58:18 +02:00
doGF = doG0F2 .or. doevGF2 .or. doqsGF2 .or. doG0F3 .or. doevGF3
2019-03-19 10:13:33 +01:00
2023-07-23 11:58:18 +02:00
if(doGF) then
2020-03-19 10:21:18 +01:00
2023-07-29 09:24:55 +02:00
call wall_time(start_GF)
call GF(doG0F2,doevGF2,doqsGF2,doG0F3,doevGF3,unrestricted,renorm_GF,maxSCF_GF,thresh_GF,max_diis_GF, &
dophBSE,doppBSE,TDA,dBSE,dTDA,singlet,triplet,spin_conserved,spin_flip,lin_GF,eta_GF,reg_GF, &
2023-07-23 11:58:18 +02:00
nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO,nV,nR,nS,EHF,S,X,T,V,Hc,ERI_AO,ERI_MO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb, &
dipole_int_AO,dipole_int_MO,dipole_int_aa,dipole_int_bb,PHF,cHF,epsHF)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-29 09:24:55 +02:00
!-----------!
! GW module !
!-----------!
2019-03-19 10:13:33 +01:00
2023-07-23 17:41:44 +02:00
doGW = doG0W0 .or. doevGW .or. doqsGW .or. doufG0W0 .or. doufGW .or. doSRGqsGW
2020-10-21 12:09:18 +02:00
2023-07-23 17:41:44 +02:00
if(doGW) then
2021-10-18 21:11:01 +02:00
2023-07-29 09:24:55 +02:00
call wall_time(start_GW)
2023-07-23 18:03:15 +02:00
call GW(doG0W0,doevGW,doqsGW,doufG0W0,doufGW,doSRGqsGW,unrestricted,maxSCF_GW,thresh_GW,max_diis_GW,doACFDT, &
2023-07-23 17:41:44 +02:00
exchange_kernel,doXBS,dophBSE,dophBSE2,doppBSE,TDA_W,TDA,dBSE,dTDA,singlet,triplet,spin_conserved,spin_flip, &
lin_GW,eta_GW,reg_GW,nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO,nV,nR,nS,EHF,S,X,T,V,Hc, &
2023-07-23 18:03:15 +02:00
ERI_AO,ERI_MO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_AO,dipole_int_MO,dipole_int_aa,dipole_int_bb, &
2023-07-23 17:41:44 +02:00
PHF,cHF,epsHF)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-23 17:41:44 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for GW = ',t_GW,' seconds'
2021-10-18 21:11:01 +02:00
write(*,*)
end if
2023-07-29 09:24:55 +02:00
!-----------------!
! T-matrix module !
!-----------------!
2021-10-18 14:14:46 +02:00
2023-07-23 17:41:44 +02:00
doGT = doG0T0pp .or. doevGTpp .or. doqsGTpp .or. doG0T0eh .or. doevGTeh .or. doqsGTeh
2019-03-19 10:13:33 +01:00
2023-07-23 17:41:44 +02:00
if(doGT) then
2019-10-16 18:14:47 +02:00
2023-07-29 09:24:55 +02:00
call wall_time(start_GT)
2023-07-23 18:03:15 +02:00
call GT(doG0T0pp,doevGTpp,doqsGTpp,doG0T0eh,doevGTeh,doqsGTeh,unrestricted,maxSCF_GT,thresh_GT,max_diis_GT,doACFDT, &
2023-07-23 22:03:42 +02:00
exchange_kernel,doXBS,dophBSE,dophBSE2,doppBSE,TDA_T,TDA,dBSE,dTDA,singlet,triplet,spin_conserved,spin_flip, &
lin_GT,eta_GT,reg_GT,nNuc,ZNuc,rNuc,ENuc,nBas,nC,nO,nV,nR,nS,EHF,S,X,T,V,Hc, &
2023-07-23 18:03:15 +02:00
ERI_AO,ERI_MO,ERI_MO_aaaa,ERI_MO_aabb,ERI_MO_bbbb,dipole_int_AO,dipole_int_MO,dipole_int_aa,dipole_int_bb, &
2023-07-23 17:41:44 +02:00
PHF,cHF,epsHF)
2023-07-29 09:24:55 +02:00
call wall_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
2023-07-23 17:41:44 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for GT = ',t_GT,' seconds'
2023-07-03 23:15:07 +02:00
write(*,*)
end if
2023-07-29 09:24:55 +02: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-10-24 17:03:41 +02:00
write(*,'(A65,1X,F9.3,A8)') 'Total CPU time for QuAcK = ',t_QuAcK,' seconds'
2019-04-24 18:00:54 +02:00
write(*,*)
2023-07-20 12:37:54 +02:00
end program