4
1
mirror of https://github.com/pfloos/quack synced 2024-06-22 21:22:20 +02:00
quack/src/LR/oscillator_strength.f90

72 lines
1.9 KiB
Fortran
Raw Normal View History

2020-10-05 16:58:19 +02:00
subroutine oscillator_strength(nBas,nC,nO,nV,nR,nS,maxS,dipole_int,Omega,XpY,XmY,os)
2020-10-04 14:22:38 +02:00
! Compute linear response
implicit none
include 'parameters.h'
! Input variables
integer,intent(in) :: nBas
integer,intent(in) :: nC
integer,intent(in) :: nO
integer,intent(in) :: nV
integer,intent(in) :: nR
integer,intent(in) :: nS
2020-10-05 16:58:19 +02:00
integer,intent(in) :: maxS
2020-10-04 14:22:38 +02:00
double precision :: dipole_int(nBas,nBas,ncart)
double precision,intent(in) :: Omega(nS)
double precision,intent(in) :: XpY(nS,nS)
double precision,intent(in) :: XmY(nS,nS)
! Local variables
integer :: ia,jb,i,j,a,b
integer :: ixyz
double precision,allocatable :: f(:,:)
! Output variables
2022-09-09 21:48:50 +02:00
double precision,intent(out) :: os(nS)
2020-10-04 14:22:38 +02:00
! Memory allocation
2020-10-05 16:58:19 +02:00
allocate(f(maxS,ncart))
2020-10-04 14:22:38 +02:00
! Initialization
f(:,:) = 0d0
! Compute dipole moments and oscillator strengths
2020-10-05 16:58:19 +02:00
do ia=1,maxS
2020-10-04 14:22:38 +02:00
do ixyz=1,ncart
jb = 0
do j=nC+1,nO
do b=nO+1,nBas-nR
jb = jb + 1
f(ia,ixyz) = f(ia,ixyz) + dipole_int(j,b,ixyz)*XpY(ia,jb)
end do
end do
end do
end do
f(:,:) = sqrt(2d0)*f(:,:)
2020-10-05 16:58:19 +02:00
do ia=1,maxS
2020-10-04 14:22:38 +02:00
os(ia) = 2d0/3d0*Omega(ia)*sum(f(ia,:)**2)
end do
2020-10-05 16:58:19 +02:00
write(*,*) '---------------------------------------------------------------'
write(*,*) ' Transition dipole moment (au) '
write(*,*) '---------------------------------------------------------------'
write(*,'(A3,5A12)') '#','X','Y','Z','dip. str.','osc. str.'
write(*,*) '---------------------------------------------------------------'
do ia=1,maxS
write(*,'(I3,5F12.6)') ia,(f(ia,ixyz),ixyz=1,ncart),sum(f(ia,:)**2),os(ia)
end do
write(*,*) '---------------------------------------------------------------'
write(*,*)
2020-10-04 14:22:38 +02:00
end subroutine oscillator_strength