4
1
mirror of https://github.com/pfloos/quack synced 2024-06-22 21:22:20 +02:00
quack/src/GW/Bethe_Salpeter_dynamic_perturbation.f90

132 lines
4.8 KiB
Fortran
Raw Normal View History

2023-07-10 14:50:16 +02:00
subroutine Bethe_Salpeter_dynamic_perturbation(BSE2,dTDA,eta,nBas,nC,nO,nV,nR,nS,eW,eGW, &
dipole_int,OmRPA,rho_RPA,OmBSE,XpY,XmY,W,A_stat)
2020-04-22 00:39:52 +02:00
! Compute dynamical effects via perturbation theory for BSE
implicit none
include 'parameters.h'
! Input variables
2023-07-10 14:50:16 +02:00
logical,intent(in) :: BSE2
2020-06-14 13:04:16 +02:00
logical,intent(in) :: dTDA
2020-04-22 00:39:52 +02:00
double precision,intent(in) :: eta
2020-04-23 23:13:15 +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
2021-02-25 10:55:08 +01:00
double precision,intent(in) :: eW(nBas)
2020-04-23 23:13:15 +02:00
double precision,intent(in) :: eGW(nBas)
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
2020-04-23 23:13:15 +02:00
double precision,intent(in) :: OmRPA(nS)
2020-09-24 11:56:06 +02:00
double precision,intent(in) :: rho_RPA(nBas,nBas,nS)
2020-04-23 23:13:15 +02:00
double precision,intent(in) :: OmBSE(nS)
double precision,intent(in) :: XpY(nS,nS)
double precision,intent(in) :: XmY(nS,nS)
2023-07-10 14:50:16 +02:00
double precision,intent(in) :: W(nBas,nBas,nBas,nBas)
double precision,intent(in) :: A_stat(nS,nS)
2020-04-22 00:39:52 +02:00
! Local variables
integer :: ia
2020-06-03 12:06:16 +02:00
2022-01-11 15:23:43 +01:00
integer :: maxS = 10
2020-05-15 13:08:07 +02:00
double precision :: gapGW
2020-04-22 00:39:52 +02:00
double precision,allocatable :: OmDyn(:)
2020-04-23 23:13:15 +02:00
double precision,allocatable :: ZDyn(:)
2020-04-22 00:39:52 +02:00
double precision,allocatable :: X(:)
double precision,allocatable :: Y(:)
2020-06-01 11:35:17 +02:00
2020-06-11 15:36:16 +02:00
double precision,allocatable :: Ap_dyn(:,:)
double precision,allocatable :: ZAp_dyn(:,:)
2020-06-01 11:35:17 +02:00
2020-06-11 15:36:16 +02:00
double precision,allocatable :: Bp_dyn(:,:)
double precision,allocatable :: ZBp_dyn(:,:)
double precision,allocatable :: Am_dyn(:,:)
double precision,allocatable :: ZAm_dyn(:,:)
double precision,allocatable :: Bm_dyn(:,:)
double precision,allocatable :: ZBm_dyn(:,:)
2020-04-22 00:39:52 +02:00
! Memory allocation
2022-01-11 15:23:43 +01:00
maxS = min(nS,maxS)
allocate(OmDyn(maxS),ZDyn(maxS),X(nS),Y(nS),Ap_dyn(nS,nS),ZAp_dyn(nS,nS))
2020-05-20 16:49:16 +02:00
2020-06-11 15:36:16 +02:00
if(.not.dTDA) allocate(Am_dyn(nS,nS),ZAm_dyn(nS,nS),Bp_dyn(nS,nS),ZBp_dyn(nS,nS),Bm_dyn(nS,nS),ZBm_dyn(nS,nS))
2020-05-15 13:08:07 +02:00
2020-06-14 13:04:16 +02:00
if(dTDA) then
write(*,*)
write(*,*) '*** dynamical TDA activated ***'
write(*,*)
end if
2020-05-15 13:08:07 +02:00
gapGW = eGW(nO+1) - eGW(nO)
2020-04-22 00:39:52 +02:00
2020-04-23 23:13:15 +02:00
write(*,*) '---------------------------------------------------------------------------------------------------'
2020-06-14 13:18:56 +02:00
write(*,*) ' First-order dynamical correction to static Bethe-Salpeter excitation energies '
2020-04-23 23:13:15 +02:00
write(*,*) '---------------------------------------------------------------------------------------------------'
2020-06-03 12:06:16 +02:00
write(*,'(A57,F10.6,A3)') ' BSE neutral excitation must be lower than the GW gap = ',gapGW*HaToeV,' eV'
write(*,*) '---------------------------------------------------------------------------------------------------'
2020-04-23 23:13:15 +02:00
write(*,'(2X,A5,1X,A20,1X,A20,1X,A20,1X,A20)') '#','Static (eV)','Dynamic (eV)','Correction (eV)','Renorm. (eV)'
write(*,*) '---------------------------------------------------------------------------------------------------'
2020-05-15 13:08:07 +02:00
2022-01-11 15:23:43 +01:00
do ia=1,maxS
2020-04-22 00:39:52 +02:00
2020-04-22 09:55:58 +02:00
X(:) = 0.5d0*(XpY(ia,:) + XmY(ia,:))
Y(:) = 0.5d0*(XpY(ia,:) - XmY(ia,:))
2020-04-22 00:39:52 +02:00
2020-06-01 11:35:17 +02:00
! First-order correction
2020-05-20 16:46:07 +02:00
2020-06-01 11:35:17 +02:00
if(dTDA) then
2020-05-15 13:08:07 +02:00
2020-06-01 11:35:17 +02:00
! Resonant part of the BSE correction for dynamical TDA
2020-05-15 13:08:07 +02:00
2021-11-10 09:42:30 +01:00
call Bethe_Salpeter_A_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW,OmRPA,rho_RPA,OmBSE(ia),Ap_dyn,ZAp_dyn)
2020-04-23 23:13:15 +02:00
2023-07-10 14:50:16 +02:00
if(BSE2) call BSE2_GW_A_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,eGW,W,OmBSE(ia),Ap_dyn,ZAp_dyn,W)
2020-06-17 22:10:08 +02:00
ZDyn(ia) = dot_product(X,matmul(ZAp_dyn,X))
2023-07-10 14:50:16 +02:00
OmDyn(ia) = dot_product(X,matmul( Ap_dyn - A_stat,X))
2020-04-22 00:39:52 +02:00
2020-04-23 23:13:15 +02:00
else
2020-04-22 00:39:52 +02:00
2020-06-01 11:35:17 +02:00
! Resonant and anti-resonant part of the BSE correction
2020-05-20 16:46:07 +02:00
2020-09-24 11:56:06 +02:00
call Bethe_Salpeter_AB_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW,OmRPA,rho_RPA,OmBSE(ia), &
2020-06-17 22:10:08 +02:00
Ap_dyn,Am_dyn,Bp_dyn,Bm_dyn)
2020-04-22 00:39:52 +02:00
2020-06-01 11:35:17 +02:00
! Renormalization factor of the resonant and anti-resonant parts
2020-05-20 16:46:07 +02:00
2020-09-24 11:56:06 +02:00
call Bethe_Salpeter_ZAB_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW,OmRPA,rho_RPA,OmBSE(ia), &
2020-06-17 22:10:08 +02:00
ZAp_dyn,ZAm_dyn,ZBp_dyn,ZBm_dyn)
2020-05-20 16:46:07 +02:00
2020-06-17 22:10:08 +02:00
ZDyn(ia) = dot_product(X,matmul(ZAp_dyn,X)) &
- dot_product(Y,matmul(ZAm_dyn,Y)) &
+ dot_product(X,matmul(ZBp_dyn,Y)) &
- dot_product(Y,matmul(ZBm_dyn,X))
2020-05-20 16:46:07 +02:00
2020-06-17 22:10:08 +02:00
OmDyn(ia) = dot_product(X,matmul(Ap_dyn,X)) &
- dot_product(Y,matmul(Am_dyn,Y)) &
+ dot_product(X,matmul(Bp_dyn,Y)) &
- dot_product(Y,matmul(Bm_dyn,X))
2020-04-22 09:55:58 +02:00
2020-04-23 23:13:15 +02:00
end if
2020-04-22 09:55:58 +02:00
2020-06-17 22:10:08 +02:00
ZDyn(ia) = 1d0/(1d0 - ZDyn(ia))
2020-05-15 13:08:07 +02:00
OmDyn(ia) = ZDyn(ia)*OmDyn(ia)
2020-04-22 00:39:52 +02:00
2020-04-23 23:13:15 +02:00
write(*,'(2X,I5,5X,F15.6,5X,F15.6,5X,F15.6,5X,F15.6)') &
ia,OmBSE(ia)*HaToeV,(OmBSE(ia)+OmDyn(ia))*HaToeV,OmDyn(ia)*HaToeV,ZDyn(ia)
2020-04-22 00:39:52 +02:00
end do
2020-04-23 23:13:15 +02:00
write(*,*) '---------------------------------------------------------------------------------------------------'
2020-04-22 00:39:52 +02:00
write(*,*)
2020-04-22 09:55:58 +02:00
end subroutine Bethe_Salpeter_dynamic_perturbation