2020-04-23 23:13:15 +02:00
|
|
|
subroutine Bethe_Salpeter_dynamic_perturbation(TDA,eta,nBas,nC,nO,nV,nR,nS,eGW,OmRPA,OmBSE,XpY,XmY,rho)
|
2020-04-22 00:39:52 +02:00
|
|
|
|
|
|
|
! Compute dynamical effects via perturbation theory for BSE
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
|
|
|
logical,intent(in) :: TDA
|
|
|
|
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
|
|
|
|
|
|
|
|
double precision,intent(in) :: eGW(nBas)
|
|
|
|
double precision,intent(in) :: OmRPA(nS)
|
|
|
|
double precision,intent(in) :: OmBSE(nS)
|
|
|
|
double precision,intent(in) :: XpY(nS,nS)
|
|
|
|
double precision,intent(in) :: XmY(nS,nS)
|
|
|
|
double precision,intent(in) :: rho(nBas,nBas,nS)
|
2020-04-22 00:39:52 +02:00
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
integer :: ia
|
2020-06-03 12:06:16 +02:00
|
|
|
|
2020-06-07 09:59:36 +02:00
|
|
|
logical :: dTDA = .true.
|
2020-04-22 00:39:52 +02:00
|
|
|
integer,parameter :: 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-01 17:26:52 +02:00
|
|
|
double precision,allocatable :: A_dyn(:,:)
|
|
|
|
double precision,allocatable :: ZA_dyn(:,:)
|
2020-06-01 11:35:17 +02:00
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
double precision,allocatable :: B_dyn(:,:)
|
|
|
|
double precision,allocatable :: ZB_dyn(:,:)
|
2020-04-22 00:39:52 +02:00
|
|
|
|
|
|
|
! Memory allocation
|
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
allocate(OmDyn(nS),ZDyn(nS),X(nS),Y(nS),A_dyn(nS,nS),ZA_dyn(nS,nS))
|
2020-05-20 16:49:16 +02:00
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
if(.not.dTDA) allocate(B_dyn(nS,nS),ZB_dyn(nS,nS))
|
2020-05-15 13:08:07 +02:00
|
|
|
|
2020-06-03 12:06:16 +02:00
|
|
|
! Print main components of transition vectors
|
|
|
|
|
|
|
|
call print_transition_vectors(nBas,nC,nO,nV,nR,nS,OmBSE,XpY,XmY)
|
|
|
|
|
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(*,*) '---------------------------------------------------------------------------------------------------'
|
|
|
|
write(*,*) ' First-order dynamical correction to static Bethe-Salpeter excitation energies '
|
|
|
|
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
|
|
|
|
2020-04-22 09:55:58 +02:00
|
|
|
do ia=1,min(nS,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
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
call Bethe_Salpeter_A_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW(:),OmRPA(:),OmBSE(ia),rho(:,:,:), &
|
|
|
|
A_dyn(:,:))
|
2020-04-23 23:13:15 +02:00
|
|
|
|
2020-06-01 11:35:17 +02:00
|
|
|
! Renormalization factor of the resonant parts for dynamical TDA
|
2020-04-23 23:13:15 +02:00
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
call Bethe_Salpeter_ZA_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW(:),OmRPA(:),OmBSE(ia),rho(:,:,:), &
|
|
|
|
ZA_dyn(:,:))
|
2020-04-23 23:13:15 +02:00
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
ZDyn(ia) = dot_product(X(:),matmul(ZA_dyn(:,:),X(:)))
|
|
|
|
OmDyn(ia) = dot_product(X(:),matmul(A_dyn(:,:),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-06-01 11:35:17 +02:00
|
|
|
call Bethe_Salpeter_AB_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW(:),OmRPA(:),OmBSE(ia),rho(:,:,:), &
|
2020-06-01 17:26:52 +02:00
|
|
|
A_dyn(:,:),B_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-06-01 11:35:17 +02:00
|
|
|
call Bethe_Salpeter_ZAB_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,1d0,eGW(:),OmRPA(:),OmBSE(ia),rho(:,:,:), &
|
2020-06-01 17:26:52 +02:00
|
|
|
ZA_dyn(:,:),ZB_dyn(:,:))
|
2020-05-20 16:46:07 +02:00
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
ZDyn(ia) = dot_product(X(:),matmul(ZA_dyn(:,:),X(:))) &
|
|
|
|
- dot_product(Y(:),matmul(ZA_dyn(:,:),Y(:))) &
|
|
|
|
+ dot_product(X(:),matmul(ZB_dyn(:,:),Y(:))) &
|
|
|
|
- dot_product(Y(:),matmul(ZB_dyn(:,:),X(:)))
|
2020-05-20 16:46:07 +02:00
|
|
|
|
2020-06-01 17:26:52 +02:00
|
|
|
OmDyn(ia) = dot_product(X(:),matmul(A_dyn(:,:),X(:))) &
|
|
|
|
- dot_product(Y(:),matmul(A_dyn(:,:),Y(:))) &
|
|
|
|
+ dot_product(X(:),matmul(B_dyn(:,:),Y(:))) &
|
|
|
|
- dot_product(Y(:),matmul(B_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-05-20 16:46:07 +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
|