4
1
mirror of https://github.com/pfloos/quack synced 2024-06-23 13:42:19 +02:00
quack/src/RPA/linear_response.f90

103 lines
2.7 KiB
Fortran
Raw Normal View History

2020-09-24 11:56:06 +02:00
subroutine linear_response(ispin,dRPA,TDA,BSE,eta,nBas,nC,nO,nV,nR,nS,lambda,e,ERI,Omega_RPA,rho_RPA,EcRPA,Omega,XpY,XmY)
2019-03-19 10:13:33 +01:00
! Compute linear response
implicit none
include 'parameters.h'
! Input variables
logical,intent(in) :: dRPA,TDA,BSE
2020-01-23 21:22:41 +01:00
double precision,intent(in) :: eta
2019-03-19 10:13:33 +01:00
integer,intent(in) :: ispin,nBas,nC,nO,nV,nR,nS
2020-01-08 10:17:19 +01:00
double precision,intent(in) :: lambda
double precision,intent(in) :: e(nBas)
double precision,intent(in) :: ERI(nBas,nBas,nBas,nBas)
2020-09-24 11:56:06 +02:00
double precision,intent(in) :: Omega_RPA(nS)
double precision,intent(in) :: rho_RPA(nBas,nBas,nS)
2019-03-19 10:13:33 +01:00
! Local variables
2020-01-15 09:52:37 +01:00
integer :: ia
2019-03-19 10:13:33 +01:00
double precision :: trace_matrix
2020-01-16 23:13:47 +01:00
double precision,allocatable :: A(:,:)
double precision,allocatable :: B(:,:)
double precision,allocatable :: ApB(:,:)
double precision,allocatable :: AmB(:,:)
double precision,allocatable :: AmBSq(:,:)
double precision,allocatable :: AmBIv(:,:)
double precision,allocatable :: Z(:,:)
2019-03-19 10:13:33 +01:00
! Output variables
double precision,intent(out) :: EcRPA
2020-01-14 14:44:01 +01:00
double precision,intent(out) :: Omega(nS)
double precision,intent(out) :: XpY(nS,nS)
double precision,intent(out) :: XmY(nS,nS)
2019-03-19 10:13:33 +01:00
! Memory allocation
2020-01-16 23:13:47 +01:00
allocate(A(nS,nS),B(nS,nS),ApB(nS,nS),AmB(nS,nS),AmBSq(nS,nS),AmBIv(nS,nS),Z(nS,nS))
2019-03-19 10:13:33 +01:00
! Build A and B matrices
2020-01-08 10:17:19 +01:00
call linear_response_A_matrix(ispin,dRPA,nBas,nC,nO,nV,nR,nS,lambda,e,ERI,A)
2020-04-22 00:39:52 +02:00
2020-09-24 11:56:06 +02:00
if(BSE) call Bethe_Salpeter_A_matrix(eta,nBas,nC,nO,nV,nR,nS,lambda,ERI,Omega_RPA,rho_RPA,A)
2019-03-19 10:13:33 +01:00
! Tamm-Dancoff approximation
B = 0d0
if(.not. TDA) then
2020-01-08 10:17:19 +01:00
call linear_response_B_matrix(ispin,dRPA,nBas,nC,nO,nV,nR,nS,lambda,ERI,B)
2020-04-22 00:39:52 +02:00
2020-09-24 11:56:06 +02:00
if(BSE) call Bethe_Salpeter_B_matrix(eta,nBas,nC,nO,nV,nR,nS,lambda,ERI,Omega_RPA,rho_RPA,B)
2019-03-19 10:13:33 +01:00
2020-04-22 00:39:52 +02:00
end if
2019-03-19 10:13:33 +01:00
! Build A + B and A - B matrices
ApB = A + B
2019-04-29 09:43:33 +02:00
AmB = A - B
2019-03-19 10:13:33 +01:00
2020-01-14 22:56:20 +01:00
! Diagonalize linear response matrix
2019-03-19 10:13:33 +01:00
call diagonalize_matrix(nS,AmB,Omega)
if(minval(Omega) < 0d0) &
2020-01-16 23:13:47 +01:00
call print_warning('You may have instabilities in linear response: A-B is not positive definite!!')
2019-03-19 10:13:33 +01:00
2020-01-15 22:29:43 +01:00
do ia=1,nS
if(Omega(ia) < 0d0) Omega(ia) = 0d0
end do
2020-01-16 23:13:47 +01:00
call ADAt(nS,AmB,1d0*sqrt(Omega),AmBSq)
call ADAt(nS,AmB,1d0/sqrt(Omega),AmBIv)
2019-03-19 10:13:33 +01:00
2020-01-14 22:56:20 +01:00
Z = matmul(AmBSq,matmul(ApB,AmBSq))
2019-04-29 09:43:33 +02:00
2019-03-19 10:13:33 +01:00
call diagonalize_matrix(nS,Z,Omega)
if(minval(Omega) < 0d0) &
2020-01-16 23:13:47 +01:00
call print_warning('You may have instabilities in linear response: negative excitations!!')
2019-03-19 10:13:33 +01:00
2020-01-15 09:52:37 +01:00
do ia=1,nS
if(Omega(ia) < 0d0) Omega(ia) = 0d0
end do
2019-03-19 10:13:33 +01:00
Omega = sqrt(Omega)
2020-01-16 23:13:47 +01:00
2019-03-19 10:13:33 +01:00
XpY = matmul(transpose(Z),AmBSq)
2020-01-15 22:29:43 +01:00
call DA(nS,1d0/sqrt(Omega),XpY)
2019-03-19 10:13:33 +01:00
2020-01-16 23:13:47 +01:00
XmY = matmul(transpose(Z),AmBIv)
call DA(nS,1d0*sqrt(Omega),XmY)
2020-01-14 14:44:01 +01:00
2019-03-19 10:13:33 +01:00
! Compute the RPA correlation energy
EcRPA = 0.5d0*(sum(Omega) - trace_matrix(nS,A))
end subroutine linear_response