Skip to content

Commit

Permalink
2PA bug corrected
Browse files Browse the repository at this point in the history
Corrected the sign of 2PA resp part
  • Loading branch information
mdewergi committed Sep 12, 2023
1 parent 0b95209 commit b1a3335
Showing 1 changed file with 10 additions and 10 deletions.
20 changes: 10 additions & 10 deletions linear_response.f
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ SUBROUTINE lresp(nci,apb,amb,iconf,maxconf,xl,yl,zl,moci,no,nv)
integer ::ix,iy,iz

real*4 ::start_time,end_time

character(len=14):: dummy

mu=0.0
Expand Down Expand Up @@ -4608,13 +4608,13 @@ SUBROUTINE lresp_2PA_SP(nci,apb,amb,iconf,maxconf,xl,yl,zl,moci,


real*4 ::start_time,end_time
real*4 ::alpha_xx,alpha_xy,alpha_xz

real*4 ::alpha_xx,alpha_xy,alpha_xz
real*4 ::alpha_yy,alpha_yz
real*4 ::alpha_zz

if(nroot<num_trans)stop 'number of 2PA excitations too large!'

open(unit=60,file='2PA-abs',status='replace')

mu=0.0
Expand Down Expand Up @@ -4656,9 +4656,9 @@ SUBROUTINE lresp_2PA_SP(nci,apb,amb,iconf,maxconf,xl,yl,zl,moci,
idum1=max(io,iv)
idum2=min(io,iv)
ij=idum2+idum1*(idum1-1)/2
mu_x(j)=-2.0*real(xl(ij),4)
mu_y(j)=-2.0*real(yl(ij),4)
mu_z(j)=-2.0*real(zl(ij),4)
mu_x(j)=-real(xl(ij),4)
mu_y(j)=-real(yl(ij),4)
mu_z(j)=-real(zl(ij),4)
enddo
!$omp end do
!$omp end parallel
Expand All @@ -4668,7 +4668,7 @@ SUBROUTINE lresp_2PA_SP(nci,apb,amb,iconf,maxconf,xl,yl,zl,moci,
XmY(:,:)=0.0
X(:,:)=0.0
Y(:,:)=0.0
omega=eci(ii)/2.0
omega=-eci(ii)/2.0
call cpu_time(start_time)
allocate(inv_resp(nci*(nci+1)/2))
inv_resp=apb-omega**2.0*inv_amb
Expand Down Expand Up @@ -4827,7 +4827,7 @@ SUBROUTINE lresp_2PA_SP(nci,apb,amb,iconf,maxconf,xl,yl,zl,moci,
call TPA_resp_fast_SP(ix,iy,X,Y,Xci,Yci,nroot,
. A_list,B_list,counter_A,counter_B,
. mu,maxconf,no,nv,nci,moci,ii,iconf,A,B)
sigma(ix,iy)=(-A+B)
sigma(ix,iy)=(-A+B)/2.0
if(ix/=iy)then
sigma(iy,ix)=sigma(ix,iy)
endif
Expand Down

0 comments on commit b1a3335

Please sign in to comment.