4
1
mirror of https://github.com/pfloos/quack synced 2024-06-02 11:25:28 +02:00
quack/src/GW/GW_phBSE.f90

172 lines
5.3 KiB
Fortran
Raw Normal View History

2023-07-21 10:45:10 +02:00
subroutine GW_phBSE(dophBSE2,TDA_W,TDA,dBSE,dTDA,singlet,triplet,eta,nBas,nC,nO,nV,nR,nS,ERI,dipole_int,eW,eGW,EcBSE)
2020-01-14 21:27:34 +01:00
! Compute the Bethe-Salpeter excitation energies
implicit none
include 'parameters.h'
! Input variables
2023-07-21 10:45:10 +02:00
logical,intent(in) :: dophBSE2
2020-06-09 21:24:37 +02:00
logical,intent(in) :: TDA_W
2020-01-14 21:27:34 +01:00
logical,intent(in) :: TDA
2020-06-14 21:20:01 +02:00
logical,intent(in) :: dBSE
2020-06-14 13:04:16 +02:00
logical,intent(in) :: dTDA
2020-09-24 11:56:06 +02:00
logical,intent(in) :: singlet
logical,intent(in) :: triplet
2020-01-14 21:27:34 +01:00
2020-01-23 21:22:41 +01:00
double precision,intent(in) :: eta
2021-10-15 13:51:04 +02:00
integer,intent(in) :: nBas
integer,intent(in) :: nC
integer,intent(in) :: nO
integer,intent(in) :: nV
integer,intent(in) :: nR
integer,intent(in) :: nS
2020-01-14 21:27:34 +01:00
double precision,intent(in) :: eW(nBas)
double precision,intent(in) :: eGW(nBas)
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
2020-01-14 21:27:34 +01:00
! Local variables
2023-07-19 11:03:55 +02:00
logical :: dRPA = .false.
logical :: dRPA_W = .true.
2020-01-14 21:27:34 +01:00
integer :: ispin
2020-06-14 13:04:16 +02:00
integer :: isp_W
2020-09-24 11:56:06 +02:00
double precision :: EcRPA
double precision,allocatable :: OmRPA(:)
double precision,allocatable :: XpY_RPA(:,:)
double precision,allocatable :: XmY_RPA(:,:)
double precision,allocatable :: rho_RPA(:,:,:)
2023-07-12 22:56:20 +02:00
double precision,allocatable :: OmBSE(:)
double precision,allocatable :: XpY_BSE(:,:)
double precision,allocatable :: XmY_BSE(:,:)
2020-01-14 21:27:34 +01:00
2023-07-21 12:00:08 +02:00
double precision,allocatable :: Aph(:,:)
double precision,allocatable :: Bph(:,:)
2023-07-19 11:03:55 +02:00
2022-11-28 10:52:06 +01:00
double precision,allocatable :: KA_sta(:,:)
double precision,allocatable :: KB_sta(:,:)
2022-11-28 15:05:29 +01:00
double precision,allocatable :: W(:,:,:,:)
2020-01-14 21:27:34 +01:00
! Output variables
double precision,intent(out) :: EcBSE(nspin)
2020-04-22 00:39:52 +02:00
! Memory allocation
allocate(OmRPA(nS),XpY_RPA(nS,nS),XmY_RPA(nS,nS),rho_RPA(nBas,nBas,nS), &
2023-07-21 12:00:08 +02:00
Aph(nS,nS),Bph(nS,nS),KA_sta(nS,nS),KB_sta(nS,nS), &
2023-07-21 10:21:54 +02:00
OmBSE(nS),XpY_BSE(nS,nS),XmY_BSE(nS,nS))
2020-04-22 00:39:52 +02:00
2020-09-24 11:56:06 +02:00
!---------------------------------
! Compute (singlet) RPA screening
!---------------------------------
isp_W = 1
EcRPA = 0d0
2023-07-21 12:00:08 +02:00
call phLR_A(isp_W,dRPA_W,nBas,nC,nO,nV,nR,nS,1d0,eW,ERI,Aph)
if(.not.TDA_W) call phLR_B(isp_W,dRPA_W,nBas,nC,nO,nV,nR,nS,1d0,ERI,Bph)
2023-07-19 11:03:55 +02:00
2023-07-21 12:00:08 +02:00
call phLR(TDA_W,nS,Aph,Bph,EcRPA,OmRPA,XpY_RPA,XmY_RPA)
2023-07-04 10:51:03 +02:00
call GW_excitation_density(nBas,nC,nO,nR,nS,ERI,XpY_RPA,rho_RPA)
2020-09-24 11:56:06 +02:00
2023-07-19 11:03:55 +02:00
call GW_phBSE_static_kernel_A(eta,nBas,nC,nO,nV,nR,nS,1d0,ERI,OmRPA,rho_RPA,KA_sta)
call GW_phBSE_static_kernel_B(eta,nBas,nC,nO,nV,nR,nS,1d0,ERI,OmRPA,rho_RPA,KB_sta)
2020-04-22 00:39:52 +02:00
!-------------------
2020-01-14 21:27:34 +01:00
! Singlet manifold
2020-04-22 00:39:52 +02:00
!-------------------
2020-01-14 21:27:34 +01:00
2020-09-24 11:56:06 +02:00
if(singlet) then
2020-01-14 21:27:34 +01:00
ispin = 1
EcBSE(ispin) = 0d0
2023-07-19 11:03:55 +02:00
! Compute BSE excitation energies
2023-07-21 12:00:08 +02:00
call phLR_A(ispin,dRPA,nBas,nC,nO,nV,nR,nS,1d0,eGW,ERI,Aph)
if(.not.TDA) call phLR_B(ispin,dRPA,nBas,nC,nO,nV,nR,nS,1d0,ERI,Bph)
2023-07-19 11:03:55 +02:00
2022-11-28 15:05:29 +01:00
! Second-order BSE static kernel
2022-11-28 10:52:06 +01:00
2023-07-21 10:45:10 +02:00
if(dophBSE2) then
2022-11-28 15:05:29 +01:00
2023-07-19 11:03:55 +02:00
allocate(W(nBas,nBas,nBas,nBas))
write(*,*)
2022-11-28 15:05:29 +01:00
write(*,*) '*** Second-order BSE static kernel activated! ***'
2023-07-19 11:03:55 +02:00
write(*,*)
2023-07-28 15:00:17 +02:00
call GW_phBSE_static_kernel(eta,nBas,nC,nO,nV,nR,nS,1d0,ERI,OmRPA,rho_RPA,W)
2023-07-21 10:21:54 +02:00
call GW_phBSE2_static_kernel_A(eta,nBas,nC,nO,nV,nR,nS,1d0,eW,W,KA_sta)
2023-07-19 11:03:55 +02:00
2023-07-21 10:21:54 +02:00
if(.not.TDA) call GW_phBSE2_static_kernel_B(eta,nBas,nC,nO,nV,nR,nS,1d0,eW,W,KB_sta)
2023-07-19 11:03:55 +02:00
deallocate(W)
2022-11-28 15:05:29 +01:00
end if
2023-07-21 12:00:08 +02:00
Aph(:,:) = Aph(:,:) + KA_sta(:,:)
if(.not.TDA) Bph(:,:) = Bph(:,:) + KB_sta(:,:)
2023-07-21 10:21:54 +02:00
2023-07-21 12:00:08 +02:00
call phLR(TDA,nS,Aph,Bph,EcBSE(ispin),OmBSE,XpY_BSE,XmY_BSE)
2020-01-14 21:27:34 +01:00
2023-11-27 23:25:10 +01:00
call print_excitation_energies('phBSE@GW@RHF','singlet',nS,OmBSE)
2023-07-28 14:14:35 +02:00
call phLR_transition_vectors(.true.,nBas,nC,nO,nV,nR,nS,dipole_int,OmBSE,XpY_BSE,XmY_BSE)
2020-06-01 11:35:17 +02:00
2024-01-29 15:19:30 +01:00
!--------------------!
! Cumulant expansion !
!--------------------!
call RGWC(.false.,nBas,nC,nO,nR,nS,OmBSE,rho_RPA,eGW)
2023-07-24 22:34:52 +02:00
!----------------------------------------------------!
! Compute the dynamical screening at the phBSE level !
!----------------------------------------------------!
2020-06-01 11:35:17 +02:00
2023-07-21 10:21:54 +02:00
if(dBSE) &
2023-07-21 10:45:10 +02:00
call GW_phBSE_dynamic_perturbation(dophBSE2,dTDA,eta,nBas,nC,nO,nV,nR,nS,eW,eGW,ERI,dipole_int,OmRPA,rho_RPA, &
2023-07-21 10:21:54 +02:00
OmBSE,XpY_BSE,XmY_BSE,KA_sta,KB_sta)
2020-04-22 00:39:52 +02:00
2020-01-14 21:27:34 +01:00
end if
2020-04-22 00:39:52 +02:00
!-------------------
2020-01-14 21:27:34 +01:00
! Triplet manifold
2020-04-22 00:39:52 +02:00
!-------------------
2020-01-14 21:27:34 +01:00
2020-09-24 11:56:06 +02:00
if(triplet) then
2020-01-14 21:27:34 +01:00
ispin = 2
EcBSE(ispin) = 0d0
2020-04-23 23:13:15 +02:00
! Compute BSE excitation energies
2020-01-14 21:27:34 +01:00
2023-07-21 12:00:08 +02:00
call phLR_A(ispin,dRPA,nBas,nC,nO,nV,nR,nS,1d0,eGW,ERI,Aph)
if(.not.TDA) call phLR_B(ispin,dRPA,nBas,nC,nO,nV,nR,nS,1d0,ERI,Bph)
2023-07-19 11:03:55 +02:00
2023-07-21 12:00:08 +02:00
Aph(:,:) = Aph(:,:) + KA_sta(:,:)
if(.not.TDA) Bph(:,:) = Bph(:,:) + KB_sta(:,:)
2023-07-19 11:03:55 +02:00
2023-07-21 12:00:08 +02:00
call phLR(TDA,nS,Aph,Bph,EcBSE(ispin),OmBSE,XpY_BSE,XmY_BSE)
2023-07-19 11:03:55 +02:00
2023-11-27 23:25:10 +01:00
call print_excitation_energies('phBSE@GW@RHF','triplet',nS,OmBSE)
2023-07-28 14:14:35 +02:00
call phLR_transition_vectors(.false.,nBas,nC,nO,nV,nR,nS,dipole_int,OmBSE,XpY_BSE,XmY_BSE)
2020-06-01 11:35:17 +02:00
2020-06-14 21:20:01 +02:00
!-------------------------------------------------
2020-06-01 11:35:17 +02:00
! Compute the dynamical screening at the BSE level
2020-06-14 21:20:01 +02:00
!-------------------------------------------------
2020-06-01 11:35:17 +02:00
2023-07-21 10:21:54 +02:00
if(dBSE) &
2023-07-21 10:45:10 +02:00
call GW_phBSE_dynamic_perturbation(dophBSE2,dTDA,eta,nBas,nC,nO,nV,nR,nS,eW,eGW,ERI,dipole_int,OmRPA,rho_RPA, &
2023-07-21 10:21:54 +02:00
OmBSE,XpY_BSE,XmY_BSE,KA_sta,KB_sta)
2020-01-14 21:27:34 +01:00
end if
2023-07-04 10:51:03 +02:00
end subroutine