2020-09-24 11:56:06 +02:00
|
|
|
subroutine Bethe_Salpeter_ZA_matrix_dynamic(eta,nBas,nC,nO,nV,nR,nS,lambda,eGW,OmRPA,rho_RPA,OmBSE,ZA_dyn)
|
2020-04-23 23:13:44 +02:00
|
|
|
|
|
|
|
! Compute the dynamic part of the Bethe-Salpeter equation matrices
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
include 'parameters.h'
|
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
|
|
|
integer,intent(in) :: nBas,nC,nO,nV,nR,nS
|
|
|
|
double precision,intent(in) :: eta
|
|
|
|
double precision,intent(in) :: lambda
|
|
|
|
double precision,intent(in) :: eGW(nBas)
|
|
|
|
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:44 +02:00
|
|
|
double precision,intent(in) :: OmBSE
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
integer :: maxS
|
|
|
|
double precision :: chi
|
|
|
|
double precision :: eps
|
|
|
|
integer :: i,j,a,b,ia,jb,kc
|
|
|
|
|
|
|
|
! Output variables
|
|
|
|
|
2020-05-20 16:46:07 +02:00
|
|
|
double precision,intent(out) :: ZA_dyn(nS,nS)
|
2020-04-23 23:13:44 +02:00
|
|
|
|
|
|
|
! Initialization
|
|
|
|
|
2020-05-20 16:46:07 +02:00
|
|
|
ZA_dyn(:,:) = 0d0
|
2020-04-23 23:13:44 +02:00
|
|
|
|
|
|
|
! Number of poles taken into account
|
|
|
|
|
|
|
|
maxS = nS
|
|
|
|
|
|
|
|
! Build dynamic A matrix
|
|
|
|
|
|
|
|
ia = 0
|
|
|
|
do i=nC+1,nO
|
|
|
|
do a=nO+1,nBas-nR
|
|
|
|
ia = ia + 1
|
|
|
|
jb = 0
|
|
|
|
do j=nC+1,nO
|
|
|
|
do b=nO+1,nBas-nR
|
|
|
|
jb = jb + 1
|
|
|
|
|
|
|
|
chi = 0d0
|
|
|
|
do kc=1,maxS
|
|
|
|
|
2020-06-17 22:10:08 +02:00
|
|
|
eps = + OmBSE - OmRPA(kc) - (eGW(a) - eGW(j))
|
2020-09-24 11:56:06 +02:00
|
|
|
chi = chi + rho_RPA(i,j,kc)*rho_RPA(a,b,kc)*(eps**2 - eta**2)/(eps**2 + eta**2)**2
|
2020-04-23 23:13:44 +02:00
|
|
|
|
2020-06-17 22:10:08 +02:00
|
|
|
eps = + OmBSE - OmRPA(kc) - (eGW(b) - eGW(i))
|
2020-09-24 11:56:06 +02:00
|
|
|
chi = chi + rho_RPA(i,j,kc)*rho_RPA(a,b,kc)*(eps**2 - eta**2)/(eps**2 + eta**2)**2
|
2020-04-23 23:13:44 +02:00
|
|
|
|
|
|
|
enddo
|
|
|
|
|
2020-05-20 16:46:07 +02:00
|
|
|
ZA_dyn(ia,jb) = ZA_dyn(ia,jb) + 2d0*lambda*chi
|
2020-04-23 23:13:44 +02:00
|
|
|
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2020-05-20 16:46:07 +02:00
|
|
|
end subroutine Bethe_Salpeter_ZA_matrix_dynamic
|