mirror of
https://github.com/pfloos/quack
synced 2024-11-03 20:53:53 +01:00
dynamic BSE@GT
This commit is contained in:
parent
978e8b6a2c
commit
fc0f9bb5f0
@ -13,9 +13,9 @@
|
|||||||
# G0F2* evGF2* qsGF2* G0F3 evGF3
|
# G0F2* evGF2* qsGF2* G0F3 evGF3
|
||||||
F F F F F
|
F F F F F
|
||||||
# G0W0* evGW* qsGW* ufG0W0 ufGW
|
# G0W0* evGW* qsGW* ufG0W0 ufGW
|
||||||
F F F F F
|
T F F F F
|
||||||
# G0T0 evGT qsGT
|
# G0T0 evGT qsGT
|
||||||
T F F
|
F F F
|
||||||
# MCMP2
|
# MCMP2
|
||||||
F
|
F
|
||||||
# * unrestricted version available
|
# * unrestricted version available
|
||||||
|
@ -15,6 +15,6 @@
|
|||||||
# ACFDT: AC Kx XBS
|
# ACFDT: AC Kx XBS
|
||||||
F F F
|
F F F
|
||||||
# BSE: BSE dBSE dTDA evDyn
|
# BSE: BSE dBSE dTDA evDyn
|
||||||
T F T F
|
T T T F
|
||||||
# MCMP2: nMC nEq nWalk dt nPrint iSeed doDrift
|
# MCMP2: nMC nEq nWalk dt nPrint iSeed doDrift
|
||||||
1000000 100000 10 0.3 10000 1234 T
|
1000000 100000 10 0.3 10000 1234 T
|
||||||
|
@ -73,9 +73,9 @@ subroutine Bethe_Salpeter_Tmatrix(TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,
|
|||||||
allocate(TAs(nS,nS),TBs(nS,nS),TAt(nS,nS),TBt(nS,nS), &
|
allocate(TAs(nS,nS),TBs(nS,nS),TAt(nS,nS),TBt(nS,nS), &
|
||||||
OmBSE(nS,nspin),XpY_BSE(nS,nS,nspin),XmY_BSE(nS,nS,nspin))
|
OmBSE(nS,nspin),XpY_BSE(nS,nS,nspin),XmY_BSE(nS,nS,nspin))
|
||||||
|
|
||||||
!----------------------------------------------
|
!---------------------------------------!
|
||||||
! Compute T-matrix for alpha-beta block
|
! Compute T-matrix for alpha-beta block !
|
||||||
!----------------------------------------------
|
!---------------------------------------!
|
||||||
|
|
||||||
ispin = 1
|
ispin = 1
|
||||||
iblock = 3
|
iblock = 3
|
||||||
@ -93,9 +93,9 @@ subroutine Bethe_Salpeter_Tmatrix(TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,
|
|||||||
! print*,'ab block of TB'
|
! print*,'ab block of TB'
|
||||||
! call matout(nS,nS,TBs)
|
! call matout(nS,nS,TBs)
|
||||||
|
|
||||||
!----------------------------------------------
|
!----------------------------------------!
|
||||||
! Compute T-matrix for alpha-alpha block
|
! Compute T-matrix for alpha-alpha block !
|
||||||
!----------------------------------------------
|
!----------------------------------------!
|
||||||
|
|
||||||
ispin = 2
|
ispin = 2
|
||||||
iblock = 4
|
iblock = 4
|
||||||
@ -113,9 +113,9 @@ subroutine Bethe_Salpeter_Tmatrix(TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,
|
|||||||
! print*,'aa block of TB'
|
! print*,'aa block of TB'
|
||||||
! call matout(nS,nS,TBt)
|
! call matout(nS,nS,TBt)
|
||||||
|
|
||||||
!-------------------
|
!------------------!
|
||||||
! Singlet manifold
|
! Singlet manifold !
|
||||||
!-------------------
|
!------------------!
|
||||||
|
|
||||||
if(singlet) then
|
if(singlet) then
|
||||||
|
|
||||||
@ -124,39 +124,18 @@ subroutine Bethe_Salpeter_Tmatrix(TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,
|
|||||||
|
|
||||||
! Compute BSE singlet excitation energies
|
! Compute BSE singlet excitation energies
|
||||||
|
|
||||||
call linear_response_Tmatrix(ispin,.false.,TDA,eta,nBas,nC,nO,nV,nR,nS,1d0,eGT,ERI,TAs+TAt,TBs+TBt, &
|
call linear_response_Tmatrix(ispin,.false.,TDA,eta,nBas,nC,nO,nV,nR,nS,1d0,eGT,ERI,TAt+TAs,TBt+TBs, &
|
||||||
EcBSE(ispin),OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
EcBSE(ispin),OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
||||||
|
|
||||||
call print_excitation('BSE@GT ',ispin,nS,OmBSE(:,ispin))
|
call print_excitation('BSE@GT ',ispin,nS,OmBSE(:,ispin))
|
||||||
call print_transition_vectors(.true.,nBas,nC,nO,nV,nR,nS,dipole_int, &
|
call print_transition_vectors(.true.,nBas,nC,nO,nV,nR,nS,dipole_int, &
|
||||||
OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
||||||
|
|
||||||
!-------------------------------------------------
|
|
||||||
! Compute the dynamical screening at the BSE level
|
|
||||||
!-------------------------------------------------
|
|
||||||
|
|
||||||
if(dBSE) then
|
|
||||||
|
|
||||||
! Compute dynamic correction for BSE via perturbation theory (iterative or renormalized)
|
|
||||||
|
|
||||||
if(evDyn) then
|
|
||||||
|
|
||||||
print*, ' Iterative dynamical correction for BSE@GT NYI'
|
|
||||||
! call Bethe_Salpeter_dynamic_perturbation_iterative(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW,dipole_int,OmRPA,rho_RPA, &
|
|
||||||
! OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
|
||||||
else
|
|
||||||
|
|
||||||
call Bethe_Salpeter_Tmatrix_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,nOOs,nVVs,Omega1s,Omega2s,rho1s,rho2s, &
|
|
||||||
eT,eGT,dipole_int,OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
|
||||||
end if
|
end if
|
||||||
|
|
||||||
end if
|
!------------------!
|
||||||
|
! Triplet manifold !
|
||||||
end if
|
!------------------!
|
||||||
|
|
||||||
!-------------------
|
|
||||||
! Triplet manifold
|
|
||||||
!-------------------
|
|
||||||
|
|
||||||
if(triplet) then
|
if(triplet) then
|
||||||
|
|
||||||
@ -171,9 +150,11 @@ subroutine Bethe_Salpeter_Tmatrix(TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,
|
|||||||
call print_transition_vectors(.false.,nBas,nC,nO,nV,nR,nS,dipole_int, &
|
call print_transition_vectors(.false.,nBas,nC,nO,nV,nR,nS,dipole_int, &
|
||||||
OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
||||||
|
|
||||||
!-------------------------------------------------
|
end if
|
||||||
! Compute the dynamical screening at the BSE level
|
|
||||||
!-------------------------------------------------
|
!--------------------------------------------------!
|
||||||
|
! Compute the dynamical screening at the BSE level !
|
||||||
|
!--------------------------------------------------!
|
||||||
|
|
||||||
if(dBSE) then
|
if(dBSE) then
|
||||||
|
|
||||||
@ -181,16 +162,14 @@ subroutine Bethe_Salpeter_Tmatrix(TDA_T,TDA,dBSE,dTDA,evDyn,singlet,triplet,eta,
|
|||||||
|
|
||||||
if(evDyn) then
|
if(evDyn) then
|
||||||
|
|
||||||
|
|
||||||
print*, ' Iterative dynamical correction for BSE@GT NYI'
|
print*, ' Iterative dynamical correction for BSE@GT NYI'
|
||||||
! call Bethe_Salpeter_dynamic_perturbation_iterative(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW,dipole_int,OmRPA,rho_RPA, &
|
! call Bethe_Salpeter_dynamic_perturbation_iterative(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW,dipole_int,OmRPA,rho_RPA, &
|
||||||
! OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
! OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
||||||
else
|
else
|
||||||
|
|
||||||
call Bethe_Salpeter_Tmatrix_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,nOOt,nVVt,Omega1t,Omega2t,rho1t,rho2t, &
|
call Bethe_Salpeter_Tmatrix_dynamic_perturbation(singlet,triplet,dTDA,eta,nBas,nC,nO,nV,nR,nS,nOOs,nVVs,nOOt,nVVt, &
|
||||||
eT,eGT,dipole_int,OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
Omega1s,Omega2s,Omega1t,Omega2t,rho1s,rho2s,rho1t,rho2t,eT,eGT, &
|
||||||
end if
|
dipole_int,OmBSE,XpY_BSE,XmY_BSE,TAs,TBs,TAt,TBt)
|
||||||
|
|
||||||
end if
|
end if
|
||||||
|
|
||||||
end if
|
end if
|
||||||
|
@ -1,5 +1,7 @@
|
|||||||
subroutine Bethe_Salpeter_Tmatrix_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,Omega1,Omega2,rho1,rho2, &
|
subroutine Bethe_Salpeter_Tmatrix_dynamic_perturbation(singlet,triplet,dTDA,eta,nBas,nC,nO,nV,nR,nS,nOOs,nVVs,nOOt,nVVt, &
|
||||||
eT,eGT,dipole_int,OmBSE,XpY,XmY)
|
Omega1s,Omega2s,Omega1t,Omega2t,rho1s,rho2s,rho1t,rho2t,eT,eGT, &
|
||||||
|
dipole_int,OmBSE,XpY,XmY,TAs,TBs,TAt,TBt)
|
||||||
|
|
||||||
! Compute dynamical effects via perturbation theory for BSE@GT
|
! Compute dynamical effects via perturbation theory for BSE@GT
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
@ -7,6 +9,8 @@ subroutine Bethe_Salpeter_Tmatrix_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR
|
|||||||
|
|
||||||
! Input variables
|
! Input variables
|
||||||
|
|
||||||
|
logical,intent(in) :: singlet
|
||||||
|
logical,intent(in) :: triplet
|
||||||
logical,intent(in) :: dTDA
|
logical,intent(in) :: dTDA
|
||||||
double precision,intent(in) :: eta
|
double precision,intent(in) :: eta
|
||||||
integer,intent(in) :: nBas
|
integer,intent(in) :: nBas
|
||||||
@ -16,116 +20,152 @@ subroutine Bethe_Salpeter_Tmatrix_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR
|
|||||||
integer,intent(in) :: nR
|
integer,intent(in) :: nR
|
||||||
integer,intent(in) :: nS
|
integer,intent(in) :: nS
|
||||||
|
|
||||||
integer,intent(in) :: nOO
|
integer,intent(in) :: nOOs
|
||||||
integer,intent(in) :: nVV
|
integer,intent(in) :: nVVs
|
||||||
|
integer,intent(in) :: nOOt
|
||||||
|
integer,intent(in) :: nVVt
|
||||||
|
|
||||||
double precision,intent(in) :: eT(nBas)
|
double precision,intent(in) :: eT(nBas)
|
||||||
double precision,intent(in) :: eGT(nBas)
|
double precision,intent(in) :: eGT(nBas)
|
||||||
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
|
double precision,intent(in) :: dipole_int(nBas,nBas,ncart)
|
||||||
double precision,intent(in) :: OmBSE(nS)
|
double precision,intent(in) :: OmBSE(nS,nspin)
|
||||||
double precision,intent(in) :: XpY(nS,nS)
|
double precision,intent(in) :: XpY(nS,nS,nspin)
|
||||||
double precision,intent(in) :: XmY(nS,nS)
|
double precision,intent(in) :: XmY(nS,nS,nspin)
|
||||||
|
|
||||||
double precision,intent(in) :: Omega1(nVV)
|
double precision,intent(in) :: Omega1s(nVVs)
|
||||||
double precision,intent(in) :: Omega2(nOO)
|
double precision,intent(in) :: Omega2s(nOOs)
|
||||||
double precision,intent(in) :: rho1(nBas,nBas,nVV)
|
double precision,intent(in) :: rho1s(nBas,nBas,nVVs)
|
||||||
double precision,intent(in) :: rho2(nBas,nBas,nOO)
|
double precision,intent(in) :: rho2s(nBas,nBas,nOOs)
|
||||||
|
double precision,intent(in) :: Omega1t(nVVt)
|
||||||
|
double precision,intent(in) :: Omega2t(nOOt)
|
||||||
|
double precision,intent(in) :: rho1t(nBas,nBas,nVVt)
|
||||||
|
double precision,intent(in) :: rho2t(nBas,nBas,nOOt)
|
||||||
|
|
||||||
|
double precision,intent(in) :: TAs(nS,nS)
|
||||||
|
double precision,intent(in) :: TBs(nS,nS)
|
||||||
|
double precision,intent(in) :: TAt(nS,nS)
|
||||||
|
double precision,intent(in) :: TBt(nS,nS)
|
||||||
|
|
||||||
! Local variables
|
! Local variables
|
||||||
|
|
||||||
integer :: ia
|
integer :: ia
|
||||||
|
integer :: ispin
|
||||||
|
|
||||||
integer,parameter :: maxS = 10
|
integer :: maxS = 10
|
||||||
double precision :: gapGT
|
double precision :: gapGT
|
||||||
|
|
||||||
double precision,allocatable :: OmDyn(:)
|
double precision,allocatable :: OmDyn(:,:)
|
||||||
double precision,allocatable :: ZDyn(:)
|
double precision,allocatable :: ZDyn(:,:)
|
||||||
double precision,allocatable :: X(:)
|
double precision,allocatable :: X(:)
|
||||||
double precision,allocatable :: Y(:)
|
double precision,allocatable :: Y(:)
|
||||||
|
|
||||||
double precision,allocatable :: Ap_dyn(:,:)
|
double precision,allocatable :: dTAs(:,:)
|
||||||
double precision,allocatable :: ZAp_dyn(:,:)
|
double precision,allocatable :: ZAs(:,:)
|
||||||
|
|
||||||
double precision,allocatable :: Bp_dyn(:,:)
|
double precision,allocatable :: dTAt(:,:)
|
||||||
double precision,allocatable :: ZBp_dyn(:,:)
|
double precision,allocatable :: ZAt(:,:)
|
||||||
|
|
||||||
double precision,allocatable :: Am_dyn(:,:)
|
|
||||||
double precision,allocatable :: ZAm_dyn(:,:)
|
|
||||||
|
|
||||||
double precision,allocatable :: Bm_dyn(:,:)
|
|
||||||
double precision,allocatable :: ZBm_dyn(:,:)
|
|
||||||
|
|
||||||
! Memory allocation
|
! Memory allocation
|
||||||
|
|
||||||
allocate(OmDyn(nS),ZDyn(nS),X(nS),Y(nS),Ap_dyn(nS,nS),ZAp_dyn(nS,nS))
|
maxS = min(nS,maxS)
|
||||||
|
allocate(OmDyn(maxS,nspin),ZDyn(maxS,nspin),X(nS),Y(nS),dTAs(nS,nS),ZAs(nS,nS),dTAt(nS,nS),ZAt(nS,nS))
|
||||||
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))
|
|
||||||
|
|
||||||
if(dTDA) then
|
if(dTDA) then
|
||||||
write(*,*)
|
write(*,*)
|
||||||
write(*,*) '*** dynamical TDA activated ***'
|
write(*,*) '*** dynamical TDA activated ***'
|
||||||
write(*,*)
|
write(*,*)
|
||||||
|
else
|
||||||
|
print*, ' Beyond-TDA dynamical correction for BSE@GT NYI'
|
||||||
|
return
|
||||||
end if
|
end if
|
||||||
|
|
||||||
|
OmDyn(:,:) = 0d0
|
||||||
|
ZDyn(:,:) = 0d0
|
||||||
|
|
||||||
|
do ia=1,maxS
|
||||||
|
|
||||||
|
! Compute dynamical T-matrix for alpha-beta block !
|
||||||
|
|
||||||
|
ispin = 1
|
||||||
|
call dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOOs,nVVs,1d0,eGT,Omega1s,Omega2s,rho1s,rho2s,OmBSE(ia,ispin),dTAs,ZAs)
|
||||||
|
|
||||||
|
! Compute dynamical T-matrix for alpha-beta block !
|
||||||
|
|
||||||
|
ispin = 2
|
||||||
|
call dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOOt,nVVt,1d0,eGT,Omega1t,Omega2t,rho1t,rho2t,OmBSE(ia,ispin),dTAt,ZAt)
|
||||||
|
|
||||||
|
do ispin=1,nspin
|
||||||
|
|
||||||
|
X(:) = 0.5d0*(XpY(ia,:,ispin) + XmY(ia,:,ispin))
|
||||||
|
Y(:) = 0.5d0*(XpY(ia,:,ispin) - XmY(ia,:,ispin))
|
||||||
|
|
||||||
|
! First-order correction
|
||||||
|
|
||||||
|
if(ispin == 1) then
|
||||||
|
ZDyn(ia,ispin) = dot_product(X,matmul(ZAt+ZAs,X))
|
||||||
|
OmDyn(ia,ispin) = dot_product(X,matmul(dTAt+dTAs,X)) - dot_product(X,matmul(TAt+TAs,X))
|
||||||
|
end if
|
||||||
|
|
||||||
|
if(ispin == 2) then
|
||||||
|
ZDyn(ia,ispin) = dot_product(X,matmul(ZAt-ZAs,X))
|
||||||
|
OmDyn(ia,ispin) = dot_product(X,matmul(dTAt-dTAs,X)) - dot_product(X,matmul(TAt-TAs,X))
|
||||||
|
end if
|
||||||
|
|
||||||
|
ZDyn(ia,ispin) = 1d0/(1d0 - ZDyn(ia,ispin))
|
||||||
|
OmDyn(ia,ispin) = ZDyn(ia,ispin)*OmDyn(ia,ispin)
|
||||||
|
|
||||||
|
end do
|
||||||
|
|
||||||
|
end do
|
||||||
|
|
||||||
|
!--------------!
|
||||||
|
! Dump results !
|
||||||
|
!--------------!
|
||||||
|
|
||||||
gapGT = eGT(nO+1) - eGT(nO)
|
gapGT = eGT(nO+1) - eGT(nO)
|
||||||
|
|
||||||
|
if(singlet) then
|
||||||
|
|
||||||
|
ispin = 1
|
||||||
|
|
||||||
write(*,*) '---------------------------------------------------------------------------------------------------'
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
write(*,*) ' First-order dynamical correction to static Bethe-Salpeter excitation energies '
|
write(*,*) ' First-order dynamical correction to static singlet Bethe-Salpeter excitation energies '
|
||||||
write(*,*) '---------------------------------------------------------------------------------------------------'
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
write(*,'(A57,F10.6,A3)') ' BSE neutral excitation must be lower than the GT gap = ',gapGT*HaToeV,' eV'
|
write(*,'(A57,F10.6,A3)') ' BSE neutral excitation must be lower than the GT gap = ',gapGT*HaToeV,' eV'
|
||||||
write(*,*) '---------------------------------------------------------------------------------------------------'
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
write(*,'(2X,A5,1X,A20,1X,A20,1X,A20,1X,A20)') '#','Static (eV)','Dynamic (eV)','Correction (eV)','Renorm. (eV)'
|
write(*,'(2X,A5,1X,A20,1X,A20,1X,A20,1X,A20)') '#','Static (eV)','Dynamic (eV)','Correction (eV)','Renorm. (eV)'
|
||||||
write(*,*) '---------------------------------------------------------------------------------------------------'
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
|
||||||
do ia=1,min(nS,maxS)
|
do ia=1,maxS
|
||||||
|
|
||||||
X(:) = 0.5d0*(XpY(ia,:) + XmY(ia,:))
|
|
||||||
Y(:) = 0.5d0*(XpY(ia,:) - XmY(ia,:))
|
|
||||||
|
|
||||||
! First-order correction
|
|
||||||
|
|
||||||
if(dTDA) then
|
|
||||||
|
|
||||||
! Resonant part of the BSE correction for dynamical TDA
|
|
||||||
|
|
||||||
call dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,1d0,eGT,Omega1,Omega2,rho1,rho2,OmBSE(ia),Ap_dyn,Zap_dyn)
|
|
||||||
|
|
||||||
ZDyn(ia) = dot_product(X,matmul(ZAp_dyn,X))
|
|
||||||
OmDyn(ia) = dot_product(X,matmul( Ap_dyn,X))
|
|
||||||
|
|
||||||
else
|
|
||||||
|
|
||||||
print*, ' Beyond-TDA dynamical correction for BSE@GT NYI'
|
|
||||||
! Resonant and anti-resonant part of the BSE correction
|
|
||||||
|
|
||||||
! call dynamic_Tmatrix_TAB(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,1d0,eGT,Omega1,Omega2,rho1,rho2,OmBSE(ia), &
|
|
||||||
! Ap_dyn,Am_dyn,Bp_dyn,Bm_dyn)
|
|
||||||
|
|
||||||
! Renormalization factor of the resonant and anti-resonant parts
|
|
||||||
|
|
||||||
! call dynamic_Tmatrix_ZAB(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,1d0,eGT,Omega1,Omega2,rho1,rho2,OmBSE(ia), &
|
|
||||||
! ZAp_dyn,ZAm_dyn,ZBp_dyn,ZBm_dyn)
|
|
||||||
|
|
||||||
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))
|
|
||||||
|
|
||||||
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))
|
|
||||||
|
|
||||||
end if
|
|
||||||
|
|
||||||
ZDyn(ia) = 1d0/(1d0 - ZDyn(ia))
|
|
||||||
OmDyn(ia) = ZDyn(ia)*OmDyn(ia)
|
|
||||||
|
|
||||||
write(*,'(2X,I5,5X,F15.6,5X,F15.6,5X,F15.6,5X,F15.6)') &
|
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)
|
ia,OmBSE(ia,ispin)*HaToeV,(OmBSE(ia,ispin)+OmDyn(ia,ispin))*HaToeV,OmDyn(ia,ispin)*HaToeV,ZDyn(ia,ispin)
|
||||||
|
|
||||||
end do
|
end do
|
||||||
|
|
||||||
write(*,*) '---------------------------------------------------------------------------------------------------'
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
write(*,*)
|
write(*,*)
|
||||||
|
|
||||||
|
end if
|
||||||
|
|
||||||
|
if(triplet) then
|
||||||
|
|
||||||
|
ispin = 2
|
||||||
|
|
||||||
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
write(*,*) ' First-order dynamical correction to static triplet Bethe-Salpeter excitation energies '
|
||||||
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
write(*,'(A57,F10.6,A3)') ' BSE neutral excitation must be lower than the GT gap = ',gapGT*HaToeV,' eV'
|
||||||
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
write(*,'(2X,A5,1X,A20,1X,A20,1X,A20,1X,A20)') '#','Static (eV)','Dynamic (eV)','Correction (eV)','Renorm. (eV)'
|
||||||
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
|
||||||
|
do ia=1,maxS
|
||||||
|
write(*,'(2X,I5,5X,F15.6,5X,F15.6,5X,F15.6,5X,F15.6)') &
|
||||||
|
ia,OmBSE(ia,ispin)*HaToeV,(OmBSE(ia,ispin)+OmDyn(ia,ispin))*HaToeV,OmDyn(ia,ispin)*HaToeV,ZDyn(ia,ispin)
|
||||||
|
end do
|
||||||
|
|
||||||
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
write(*,*)
|
||||||
|
|
||||||
|
end if
|
||||||
|
|
||||||
end subroutine Bethe_Salpeter_Tmatrix_dynamic_perturbation
|
end subroutine Bethe_Salpeter_Tmatrix_dynamic_perturbation
|
||||||
|
@ -61,11 +61,6 @@ subroutine G0T0(doACFDT,exchange_kernel,doXBS,BSE,TDA_T,TDA,dBSE,dTDA,evDyn,sing
|
|||||||
double precision,allocatable :: SigT(:)
|
double precision,allocatable :: SigT(:)
|
||||||
double precision,allocatable :: Z(:)
|
double precision,allocatable :: Z(:)
|
||||||
|
|
||||||
double precision,allocatable :: Omega(:,:)
|
|
||||||
double precision,allocatable :: XpY(:,:,:)
|
|
||||||
double precision,allocatable :: XmY(:,:,:)
|
|
||||||
double precision,allocatable :: rho(:,:,:,:)
|
|
||||||
|
|
||||||
! Output variables
|
! Output variables
|
||||||
|
|
||||||
double precision,intent(out) :: eG0T0(nBas)
|
double precision,intent(out) :: eG0T0(nBas)
|
||||||
@ -147,20 +142,35 @@ subroutine G0T0(doACFDT,exchange_kernel,doXBS,BSE,TDA_T,TDA,dBSE,dTDA,evDyn,sing
|
|||||||
|
|
||||||
call excitation_density_Tmatrix(iblock,nBas,nC,nO,nV,nR,nOOs,nVVs,ERI_MO,X1s,Y1s,rho1s,X2s,Y2s,rho2s)
|
call excitation_density_Tmatrix(iblock,nBas,nC,nO,nV,nR,nOOs,nVVs,ERI_MO,X1s,Y1s,rho1s,X2s,Y2s,rho2s)
|
||||||
|
|
||||||
call self_energy_Tmatrix_diag(eta,nBas,nC,nO,nV,nR,nOOs,nVVs,eHF,sqrt(1d0)*Omega1s,rho1s,sqrt(1d0)*Omega2s,rho2s,EcGM,SigT)
|
if(regularize) then
|
||||||
|
|
||||||
|
call regularized_self_energy_Tmatrix_diag(eta,nBas,nC,nO,nV,nR,nOOs,nVVs,eHF,Omega1s,rho1s,Omega2s,rho2s,EcGM,SigT)
|
||||||
|
call regularized_renormalization_factor_Tmatrix(eta,nBas,nC,nO,nV,nR,nOOs,nVVs,eHF,Omega1s,rho1s,Omega2s,rho2s,Z)
|
||||||
|
|
||||||
|
else
|
||||||
|
|
||||||
|
call self_energy_Tmatrix_diag(eta,nBas,nC,nO,nV,nR,nOOs,nVVs,eHF,Omega1s,rho1s,Omega2s,rho2s,EcGM,SigT)
|
||||||
call renormalization_factor_Tmatrix(eta,nBas,nC,nO,nV,nR,nOOs,nVVs,eHF,Omega1s,rho1s,Omega2s,rho2s,Z)
|
call renormalization_factor_Tmatrix(eta,nBas,nC,nO,nV,nR,nOOs,nVVs,eHF,Omega1s,rho1s,Omega2s,rho2s,Z)
|
||||||
|
|
||||||
|
end if
|
||||||
|
|
||||||
iblock = 4
|
iblock = 4
|
||||||
|
|
||||||
call excitation_density_Tmatrix(iblock,nBas,nC,nO,nV,nR,nOOt,nVVt,ERI_MO,X1t,Y1t,rho1t,X2t,Y2t,rho2t)
|
call excitation_density_Tmatrix(iblock,nBas,nC,nO,nV,nR,nOOt,nVVt,ERI_MO,X1t,Y1t,rho1t,X2t,Y2t,rho2t)
|
||||||
|
|
||||||
call self_energy_Tmatrix_diag(eta,nBas,nC,nO,nV,nR,nOOt,nVVt,eHF,Omega1t,sqrt(1.5d0)*rho1t,Omega2t,sqrt(1.5d0)*rho2t,EcGM,SigT)
|
if(regularize) then
|
||||||
|
|
||||||
|
call regularized_self_energy_Tmatrix_diag(eta,nBas,nC,nO,nV,nR,nOOt,nVVt,eHF,Omega1t,rho1t,Omega2t,rho2t,EcGM,SigT)
|
||||||
|
call regularized_renormalization_factor_Tmatrix(eta,nBas,nC,nO,nV,nR,nOOt,nVVt,eHF,Omega1t,rho1t,Omega2t,rho2t,Z)
|
||||||
|
|
||||||
|
else
|
||||||
|
|
||||||
|
call self_energy_Tmatrix_diag(eta,nBas,nC,nO,nV,nR,nOOt,nVVt,eHF,Omega1t,rho1t,Omega2t,rho2t,EcGM,SigT)
|
||||||
call renormalization_factor_Tmatrix(eta,nBas,nC,nO,nV,nR,nOOt,nVVt,eHF,Omega1t,rho1t,Omega2t,rho2t,Z)
|
call renormalization_factor_Tmatrix(eta,nBas,nC,nO,nV,nR,nOOt,nVVt,eHF,Omega1t,rho1t,Omega2t,rho2t,Z)
|
||||||
|
|
||||||
Z(:) = 1d0/(1d0 - Z(:))
|
end if
|
||||||
|
|
||||||
|
Z(:) = 1d0/(1d0 - Z(:))
|
||||||
|
|
||||||
!----------------------------------------------
|
!----------------------------------------------
|
||||||
! Compute the exchange part of the self-energy
|
! Compute the exchange part of the self-energy
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
subroutine dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,lambda,eGT,Omega1,Omega2,rho1,rho2,OmBSE,A_dyn,ZA_dyn)
|
subroutine dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,lambda,eGT,Omega1,Omega2,rho1,rho2,OmBSE,TA,ZA)
|
||||||
|
|
||||||
! Compute the dynamic part of the Bethe-Salpeter equation matrices for GT
|
! Compute the dynamic part of the Bethe-Salpeter equation matrices for GT
|
||||||
|
|
||||||
@ -36,13 +36,13 @@ subroutine dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,lambda,eGT,Omega1,O
|
|||||||
|
|
||||||
! Output variables
|
! Output variables
|
||||||
|
|
||||||
double precision,intent(out) :: A_dyn(nS,nS)
|
double precision,intent(out) :: TA(nS,nS)
|
||||||
double precision,intent(out) :: ZA_dyn(nS,nS)
|
double precision,intent(out) :: ZA(nS,nS)
|
||||||
|
|
||||||
! Initialization
|
! Initialization
|
||||||
|
|
||||||
A_dyn(:,:) = 0d0
|
TA(:,:) = 0d0
|
||||||
ZA_dyn(:,:) = 0d0
|
ZA(:,:) = 0d0
|
||||||
|
|
||||||
! Build dynamic A matrix
|
! Build dynamic A matrix
|
||||||
|
|
||||||
@ -57,31 +57,17 @@ subroutine dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,lambda,eGT,Omega1,O
|
|||||||
|
|
||||||
chi = 0d0
|
chi = 0d0
|
||||||
|
|
||||||
do cd=1,nVV
|
|
||||||
eps = - Omega1(cd)
|
|
||||||
chi = chi + rho1(i,b,cd)*rho1(j,a,cd)*eps/(eps**2 + eta**2)
|
|
||||||
end do
|
|
||||||
|
|
||||||
do kl=1,nOO
|
|
||||||
eps = + Omega2(kl)
|
|
||||||
chi = chi + rho2(i,b,kl)*rho2(j,a,kl)*eps/(eps**2 + eta**2)
|
|
||||||
end do
|
|
||||||
|
|
||||||
A_dyn(ia,jb) = A_dyn(ia,jb) - lambda*chi
|
|
||||||
|
|
||||||
chi = 0d0
|
|
||||||
|
|
||||||
do cd=1,nVV
|
do cd=1,nVV
|
||||||
eps = + OmBSE - Omega1(cd) + (eGT(i) + eGT(j))
|
eps = + OmBSE - Omega1(cd) + (eGT(i) + eGT(j))
|
||||||
chi = chi + rho1(i,b,cd)*rho1(j,a,cd)*eps/(eps**2 + eta**2)
|
chi = chi + rho1(i,b,cd)*rho1(j,a,cd)*eps/(eps**2 + eta**2)
|
||||||
end do
|
end do
|
||||||
|
|
||||||
do kl=1,nOO
|
! do kl=1,nOO
|
||||||
eps = + OmBSE + Omega2(kl) - (eGT(a) + eGT(b))
|
! eps = + OmBSE + Omega2(kl) - (eGT(a) + eGT(b))
|
||||||
chi = chi + rho2(i,b,kl)*rho2(j,a,kl)*eps/(eps**2 + eta**2)
|
! chi = chi + rho2(i,b,kl)*rho2(j,a,kl)*eps/(eps**2 + eta**2)
|
||||||
end do
|
! end do
|
||||||
|
|
||||||
A_dyn(ia,jb) = A_dyn(ia,jb) + 1d0*lambda*chi
|
TA(ia,jb) = TA(ia,jb) + 1d0*lambda*chi
|
||||||
|
|
||||||
chi = 0d0
|
chi = 0d0
|
||||||
|
|
||||||
@ -90,12 +76,12 @@ subroutine dynamic_Tmatrix_A(eta,nBas,nC,nO,nV,nR,nS,nOO,nVV,lambda,eGT,Omega1,O
|
|||||||
chi = chi + rho1(i,b,cd)*rho1(j,a,cd)*(eps**2 - eta**2)/(eps**2 + eta**2)**2
|
chi = chi + rho1(i,b,cd)*rho1(j,a,cd)*(eps**2 - eta**2)/(eps**2 + eta**2)**2
|
||||||
end do
|
end do
|
||||||
|
|
||||||
do kl=1,nOO
|
! do kl=1,nOO
|
||||||
eps = + OmBSE + Omega2(kl) - (eGT(a) + eGT(b))
|
! eps = + OmBSE + Omega2(kl) - (eGT(a) + eGT(b))
|
||||||
chi = chi + rho2(i,b,kl)*rho2(j,a,kl)*(eps**2 - eta**2)/(eps**2 + eta**2)**2
|
! chi = chi + rho2(i,b,kl)*rho2(j,a,kl)*(eps**2 - eta**2)/(eps**2 + eta**2)**2
|
||||||
end do
|
! end do
|
||||||
|
|
||||||
ZA_dyn(ia,jb) = ZA_dyn(ia,jb) - 1d0*lambda*chi
|
ZA(ia,jb) = ZA(ia,jb) - 1d0*lambda*chi
|
||||||
|
|
||||||
end do
|
end do
|
||||||
end do
|
end do
|
||||||
|
@ -29,7 +29,7 @@ subroutine Bethe_Salpeter_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,eW,e
|
|||||||
|
|
||||||
integer :: ia
|
integer :: ia
|
||||||
|
|
||||||
integer,parameter :: maxS = 10
|
integer :: maxS = 10
|
||||||
double precision :: gapGW
|
double precision :: gapGW
|
||||||
|
|
||||||
double precision,allocatable :: OmDyn(:)
|
double precision,allocatable :: OmDyn(:)
|
||||||
@ -51,7 +51,8 @@ subroutine Bethe_Salpeter_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,eW,e
|
|||||||
|
|
||||||
! Memory allocation
|
! Memory allocation
|
||||||
|
|
||||||
allocate(OmDyn(nS),ZDyn(nS),X(nS),Y(nS),Ap_dyn(nS,nS),ZAp_dyn(nS,nS))
|
maxS = min(nS,maxS)
|
||||||
|
allocate(OmDyn(maxS),ZDyn(maxS),X(nS),Y(nS),Ap_dyn(nS,nS),ZAp_dyn(nS,nS))
|
||||||
|
|
||||||
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))
|
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))
|
||||||
|
|
||||||
@ -71,7 +72,7 @@ subroutine Bethe_Salpeter_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,eW,e
|
|||||||
write(*,'(2X,A5,1X,A20,1X,A20,1X,A20,1X,A20)') '#','Static (eV)','Dynamic (eV)','Correction (eV)','Renorm. (eV)'
|
write(*,'(2X,A5,1X,A20,1X,A20,1X,A20,1X,A20)') '#','Static (eV)','Dynamic (eV)','Correction (eV)','Renorm. (eV)'
|
||||||
write(*,*) '---------------------------------------------------------------------------------------------------'
|
write(*,*) '---------------------------------------------------------------------------------------------------'
|
||||||
|
|
||||||
do ia=1,min(nS,maxS)
|
do ia=1,maxS
|
||||||
|
|
||||||
X(:) = 0.5d0*(XpY(ia,:) + XmY(ia,:))
|
X(:) = 0.5d0*(XpY(ia,:) + XmY(ia,:))
|
||||||
Y(:) = 0.5d0*(XpY(ia,:) - XmY(ia,:))
|
Y(:) = 0.5d0*(XpY(ia,:) - XmY(ia,:))
|
||||||
|
Loading…
Reference in New Issue
Block a user