mirror of
https://github.com/pfloos/quack
synced 2024-12-22 20:35:36 +01:00
UBSE
This commit is contained in:
parent
2a6f83dbf9
commit
8f5b1779de
151
src/QuAcK/unrestricted_Bethe_Salpeter.f90
Normal file
151
src/QuAcK/unrestricted_Bethe_Salpeter.f90
Normal file
@ -0,0 +1,151 @@
|
||||
subroutine unrestricted_Bethe_Salpeter(TDA_W,TDA,dBSE,dTDA,evDyn,spin_conserved,spin_flip,eta, &
|
||||
nBas,nC,nO,nV,nR,nSa,nSb,nSt,ERI_aaaa,ERI_aabb,ERI_bbbb, &
|
||||
eW,eGW,OmRPA,XpY_RPA,XmY_RPA,rho_RPA,EcRPA,EcBSE)
|
||||
|
||||
! Compute the Bethe-Salpeter excitation energies
|
||||
|
||||
implicit none
|
||||
include 'parameters.h'
|
||||
|
||||
! Input variables
|
||||
|
||||
logical,intent(in) :: TDA_W
|
||||
logical,intent(in) :: TDA
|
||||
logical,intent(in) :: dBSE
|
||||
logical,intent(in) :: dTDA
|
||||
logical,intent(in) :: evDyn
|
||||
logical,intent(in) :: spin_conserved
|
||||
logical,intent(in) :: spin_flip
|
||||
|
||||
double precision,intent(in) :: eta
|
||||
integer,intent(in) :: nBas
|
||||
integer,intent(in) :: nC(nspin)
|
||||
integer,intent(in) :: nO(nspin)
|
||||
integer,intent(in) :: nV(nspin)
|
||||
integer,intent(in) :: nR(nspin)
|
||||
integer,intent(in) :: nSa
|
||||
integer,intent(in) :: nSb
|
||||
integer,intent(in) :: nSt
|
||||
double precision,intent(in) :: eW(nBas,nspin)
|
||||
double precision,intent(in) :: eGW(nBas,nspin)
|
||||
double precision,intent(in) :: ERI_aaaa(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: ERI_aabb(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: ERI_bbbb(nBas,nBas,nBas,nBas)
|
||||
|
||||
double precision :: OmRPA(nSt)
|
||||
double precision :: XpY_RPA(nSt,nSt)
|
||||
double precision :: XmY_RPA(nSt,nSt)
|
||||
double precision :: rho_RPA(nBas,nBas,nSt,nspin)
|
||||
|
||||
! Local variables
|
||||
|
||||
integer :: ispin
|
||||
integer :: isp_W
|
||||
double precision,allocatable :: OmBSE(:)
|
||||
double precision,allocatable :: XpY_BSE(:,:)
|
||||
double precision,allocatable :: XmY_BSE(:,:)
|
||||
|
||||
! Output variables
|
||||
|
||||
double precision,intent(out) :: EcRPA
|
||||
double precision,intent(out) :: EcBSE
|
||||
|
||||
! Memory allocation
|
||||
|
||||
allocate(OmBSE(nSt),XpY_BSE(nSt,nSt),XmY_BSE(nSt,nSt))
|
||||
|
||||
!----------------------------!
|
||||
! Spin-conserved excitations !
|
||||
!----------------------------!
|
||||
|
||||
if(spin_conserved) then
|
||||
|
||||
ispin = 1
|
||||
isp_W = 1
|
||||
EcBSE = 0d0
|
||||
|
||||
! Compute spin-conserved RPA screening
|
||||
|
||||
call unrestricted_linear_response(isp_W,.true.,TDA_W,.false.,eta,nBas,nC,nO,nV,nR,nSa,nSb,nSt,1d0, &
|
||||
eW,ERI_aaaa,ERI_aabb,ERI_bbbb,rho_RPA,EcRPA,OmRPA,XpY_RPA,XmY_RPA)
|
||||
|
||||
call unrestricted_excitation_density(nBas,nC,nO,nR,nSa,nSb,nSt,ERI_aaaa,ERI_aabb,ERI_bbbb,XpY_RPA,rho_RPA)
|
||||
|
||||
! Compute BSE excitation energies
|
||||
|
||||
OmBSE(:) = OmRPA(:)
|
||||
|
||||
call unrestricted_linear_response(ispin,.true.,TDA,.true.,eta,nBas,nC,nO,nV,nR,nSa,nSb,nSt,1d0, &
|
||||
eGW,ERI_aaaa,ERI_aabb,ERI_bbbb,rho_RPA,EcBSE,OmBSE,XpY_BSE,XmY_BSE)
|
||||
|
||||
call print_excitation('BSE@UG0W0',5,nSt,OmBSE)
|
||||
|
||||
!-------------------------------------------------
|
||||
! 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
|
||||
!
|
||||
! call Bethe_Salpeter_dynamic_perturbation_iterative(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW(:),OmRPA(:,ispin),OmBSE(:,ispin), &
|
||||
! XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin),rho_RPA(:,:,:,ispin))
|
||||
! else
|
||||
!
|
||||
! call Bethe_Salpeter_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW(:),OmRPA(:,ispin),OmBSE(:,ispin), &
|
||||
! XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin),rho_RPA(:,:,:,ispin))
|
||||
! end if
|
||||
|
||||
! end if
|
||||
|
||||
end if
|
||||
|
||||
!-----------------------!
|
||||
! Spin-flip excitations !
|
||||
!-----------------------!
|
||||
|
||||
!if(spin_flip) then
|
||||
|
||||
! ispin = 2
|
||||
! isp_W = 1
|
||||
! EcBSE(ispin) = 0d0
|
||||
|
||||
! ! Compute (singlet) RPA screening
|
||||
|
||||
! call linear_response(isp_W,.true.,TDA_W,.false.,eta,nBas,nC,nO,nV,nR,nS,1d0,eW,ERI, &
|
||||
! rho_RPA(:,:,:,ispin),EcRPA(ispin),OmRPA(:,ispin),XpY_RPA(:,:,ispin),XmY_RPA(:,:,ispin))
|
||||
! call excitation_density(nBas,nC,nO,nR,nS,ERI,XpY_RPA(:,:,ispin),rho_RPA(:,:,:,ispin))
|
||||
|
||||
! ! Compute BSE excitation energies
|
||||
|
||||
! OmBSE(:,ispin) = OmRPA(:,ispin)
|
||||
|
||||
! call linear_response(ispin,.true.,TDA,.true.,eta,nBas,nC,nO,nV,nR,nS,1d0,eGW,ERI, &
|
||||
! rho_RPA(:,:,:,ispin),EcBSE(ispin),OmBSE(:,ispin),XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin))
|
||||
! call print_excitation('BSE ',ispin,nS,OmBSE(:,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
|
||||
!
|
||||
! call Bethe_Salpeter_dynamic_perturbation_iterative(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW,OmRPA(:,ispin),OmBSE(:,ispin), &
|
||||
! XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin),rho_RPA(:,:,:,ispin))
|
||||
! else
|
||||
!
|
||||
! call Bethe_Salpeter_dynamic_perturbation(dTDA,eta,nBas,nC,nO,nV,nR,nS,eGW,OmRPA(:,ispin),OmBSE(:,ispin), &
|
||||
! XpY_BSE(:,:,ispin),XmY_BSE(:,:,ispin),rho_RPA(:,:,:,ispin))
|
||||
! end if
|
||||
|
||||
! end if
|
||||
|
||||
! end if
|
||||
|
||||
end subroutine unrestricted_Bethe_Salpeter
|
140
src/QuAcK/unrestricted_Bethe_Salpeter_A_matrix.f90
Normal file
140
src/QuAcK/unrestricted_Bethe_Salpeter_A_matrix.f90
Normal file
@ -0,0 +1,140 @@
|
||||
subroutine unrestricted_Bethe_Salpeter_A_matrix(eta,nBas,nC,nO,nV,nR,nSa,nSb,nSt,lambda,ERI_aaaa,ERI_aabb,ERI_bbbb,Omega,rho,A_lr)
|
||||
|
||||
! Compute the extra term for Bethe-Salpeter equation for linear response in the unrestricted formalism
|
||||
|
||||
implicit none
|
||||
include 'parameters.h'
|
||||
|
||||
! Input variables
|
||||
|
||||
integer,intent(in) :: nBas
|
||||
integer,intent(in) :: nC(nspin)
|
||||
integer,intent(in) :: nO(nspin)
|
||||
integer,intent(in) :: nV(nspin)
|
||||
integer,intent(in) :: nR(nspin)
|
||||
integer,intent(in) :: nSa
|
||||
integer,intent(in) :: nSb
|
||||
integer,intent(in) :: nSt
|
||||
double precision,intent(in) :: eta
|
||||
double precision,intent(in) :: lambda
|
||||
double precision,intent(in) :: ERI_aaaa(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: ERI_aabb(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: ERI_bbbb(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: Omega(nSt)
|
||||
double precision,intent(in) :: rho(nBas,nBas,nSt,nspin)
|
||||
|
||||
! Local variables
|
||||
|
||||
double precision :: chi
|
||||
double precision :: eps
|
||||
integer :: i,j,a,b,ia,jb,kc
|
||||
|
||||
! Output variables
|
||||
|
||||
double precision,intent(out) :: A_lr(nSt,nSt)
|
||||
|
||||
!--------------------------------!
|
||||
! Build part A of the BSE matrix !
|
||||
!--------------------------------!
|
||||
|
||||
! alpha-alpha block
|
||||
|
||||
ia = 0
|
||||
do i=nC(1)+1,nO(1)
|
||||
do a=nO(1)+1,nBas-nR(1)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(1)+1,nO(1)
|
||||
do b=nO(1)+1,nBas-nR(1)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,j,kc,1)*rho(a,b,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,j,kc,2)*rho(a,b,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
A_lr(ia,jb) = A_lr(ia,jb) - lambda*ERI_aaaa(i,b,j,a) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! alpha-beta block
|
||||
|
||||
ia = 0
|
||||
do i=nC(1)+1,nO(1)
|
||||
do a=nO(1)+1,nBas-nR(1)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(2)+1,nO(2)
|
||||
do b=nO(2)+1,nBas-nR(2)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,j,kc,1)*rho(a,b,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,j,kc,2)*rho(a,b,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
A_lr(ia,nSa+jb) = A_lr(ia,nSa+jb) - lambda*ERI_aabb(i,b,j,a) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! beta-alpha block
|
||||
|
||||
ia = 0
|
||||
do i=nC(2)+1,nO(2)
|
||||
do a=nO(2)+1,nBas-nR(2)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(1)+1,nO(1)
|
||||
do b=nO(1)+1,nBas-nR(1)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,j,kc,1)*rho(a,b,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,j,kc,2)*rho(a,b,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
A_lr(nSa+ia,jb) = A_lr(nSa+ia,jb) - lambda*ERI_aabb(b,i,a,j) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! beta-beta block
|
||||
|
||||
ia = 0
|
||||
do i=nC(2)+1,nO(2)
|
||||
do a=nO(2)+1,nBas-nR(2)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(2)+1,nO(2)
|
||||
do b=nO(2)+1,nBas-nR(2)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,j,kc,1)*rho(a,b,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,j,kc,2)*rho(a,b,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
A_lr(nSa+ia,nSa+jb) = A_lr(nSa+ia,nSa+jb) - lambda*ERI_bbbb(i,b,j,a) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
end subroutine unrestricted_Bethe_Salpeter_A_matrix
|
136
src/QuAcK/unrestricted_Bethe_Salpeter_B_matrix.f90
Normal file
136
src/QuAcK/unrestricted_Bethe_Salpeter_B_matrix.f90
Normal file
@ -0,0 +1,136 @@
|
||||
subroutine unrestricted_Bethe_Salpeter_B_matrix(eta,nBas,nC,nO,nV,nR,nSa,nSb,nSt,lambda,ERI_aaaa,ERI_aabb,ERI_bbbb,Omega,rho,B_lr)
|
||||
|
||||
! Compute the extra term for Bethe-Salpeter equation for linear response
|
||||
|
||||
implicit none
|
||||
include 'parameters.h'
|
||||
|
||||
! Input variables
|
||||
|
||||
integer,intent(in) :: nBas
|
||||
integer,intent(in) :: nC(nspin)
|
||||
integer,intent(in) :: nO(nspin)
|
||||
integer,intent(in) :: nV(nspin)
|
||||
integer,intent(in) :: nR(nspin)
|
||||
integer,intent(in) :: nSa
|
||||
integer,intent(in) :: nSb
|
||||
integer,intent(in) :: nSt
|
||||
double precision,intent(in) :: eta
|
||||
double precision,intent(in) :: lambda
|
||||
double precision,intent(in) :: ERI_aaaa(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: ERI_aabb(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: ERI_bbbb(nBas,nBas,nBas,nBas)
|
||||
double precision,intent(in) :: Omega(nSt)
|
||||
double precision,intent(in) :: rho(nBas,nBas,nSt,nspin)
|
||||
|
||||
! Local variables
|
||||
|
||||
double precision :: chi
|
||||
double precision :: eps
|
||||
integer :: i,j,a,b,ia,jb,kc
|
||||
|
||||
! Output variables
|
||||
|
||||
double precision,intent(out) :: B_lr(nSt,nSt)
|
||||
|
||||
! alpha-alpha block
|
||||
|
||||
ia = 0
|
||||
do i=nC(1)+1,nO(1)
|
||||
do a=nO(1)+1,nBas-nR(1)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(1)+1,nO(1)
|
||||
do b=nO(1)+1,nBas-nR(1)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,b,kc,1)*rho(a,j,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,b,kc,2)*rho(a,j,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
B_lr(ia,jb) = B_lr(ia,jb) - lambda*ERI_aaaa(i,j,b,a) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! alpha-beta block
|
||||
|
||||
ia = 0
|
||||
do i=nC(1)+1,nO(1)
|
||||
do a=nO(1)+1,nBas-nR(1)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(2)+1,nO(2)
|
||||
do b=nO(2)+1,nBas-nR(2)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,b,kc,1)*rho(a,j,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,b,kc,2)*rho(a,j,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
B_lr(ia,nSa+jb) = B_lr(ia,nSa+jb) - lambda*ERI_aabb(i,j,b,a) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! beta-alpha block
|
||||
|
||||
ia = 0
|
||||
do i=nC(2)+1,nO(2)
|
||||
do a=nO(2)+1,nBas-nR(2)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(1)+1,nO(1)
|
||||
do b=nO(1)+1,nBas-nR(1)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,b,kc,1)*rho(a,j,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,b,kc,2)*rho(a,j,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
B_lr(nSa+ia,jb) = B_lr(nSa+ia,jb) - lambda*ERI_aabb(j,i,a,b) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! beta-beta block
|
||||
|
||||
ia = 0
|
||||
do i=nC(2)+1,nO(2)
|
||||
do a=nO(2)+1,nBas-nR(2)
|
||||
ia = ia + 1
|
||||
jb = 0
|
||||
do j=nC(2)+1,nO(2)
|
||||
do b=nO(2)+1,nBas-nR(2)
|
||||
jb = jb + 1
|
||||
|
||||
chi = 0d0
|
||||
do kc=1,nSt
|
||||
eps = Omega(kc)**2 + eta**2
|
||||
chi = chi + rho(i,b,kc,1)*rho(a,j,kc,1)*Omega(kc)/eps &
|
||||
+ rho(i,b,kc,2)*rho(a,j,kc,2)*Omega(kc)/eps
|
||||
enddo
|
||||
|
||||
B_lr(nSa+ia,nSa+jb) = B_lr(nSa+ia,nSa+jb) - lambda*ERI_bbbb(i,j,b,a) + 2d0*lambda*chi
|
||||
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
|
||||
end subroutine unrestricted_Bethe_Salpeter_B_matrix
|
Loading…
Reference in New Issue
Block a user