SUBROUTINE overlap_aph(sector_wf, sfunc, ndim_sec, overlap_element, whichir, nchir) !========================================================================================= ! This routine otains the overlap of the Delves' "vibrational" functions with the ! propagated wave function at each time step. ! These will make up the F matrix elements at each energy after they have been Fourier ! transformed ! ! NOTE 2: These will be channel dependent when NOT dealing with an AAA system ! ! Variables: ! Input ! isf = the final state "vibrational" quantum number for the Delves' functions ! ! Output ! overlap_element = the overlap of a Delves' "vibrational" wave function of state f with ! the propagated wave function at a particular time ! !========================================================================================= USE Numeric_Kinds_Module USE CommonInfo_Module USE APH_Module USE Jacobi_Module USE Delves_Module USE Print_Module !USE Overlap_Module USE SymGroup_Module USE SurfaceAPH_Module IMPLICIT NONE !========================================================================================= ! I N P U T INTEGER,INTENT(IN) :: ndim_sec, whichir,nchir REAL(dp),INTENT(IN) :: sfunc(ndim_sec) COMPLEX(dp),INTENT(INOUT) :: sector_wf(ndim_sec) !========================================================================================= ! O U T P U T COMPLEX(dp),INTENT(OUT) :: overlap_element !======================================================================================== ! I N T E R N A L S INTEGER :: itheta, ichi, sec_pt!, chishift COMPLEX(dp) :: chi_sum, theta_sum !========================================================================================= ! A L L O C A T A B L E !========================================================================================= ! F U N C T I O N S INTEGER :: aphindex_tc !temp !REAL(dp) theta_sum_real,theta_sum_imag,sec_real(ndim_sec),sec_imag(ndim_sec) !========================================================================================= ! N A M E L I S T S !======================================================================================== ! Integrate overlap_element=Cmplx(0.d0,0.d0,dp) DO itheta=1,ndim_sec overlap_element=overlap_element+sector_wf(itheta)*sfunc(itheta)*deltachi ENDDO ! sector_wf=sector_wf*sfunc*deltachi ! overlap_element=SUM(sector_wf) !========================== ! original method ! theta_sum=0.d0 ! DO itheta=1,ntheta ! chi_sum=0.d0 ! DO ichi=1,nchir ! sec_pt=aphindex_tc(nchir,itheta,ichi) ! chi_sum=chi_sum+sector_wf(sec_pt)*sfunc(sec_pt)*deltachi ! ENDDO ! theta_sum=theta_sum+chi_sum!*Sqrt(weights(itheta)) ! ENDDO ! overlap_element=theta_sum END SUBROUTINE overlap_aph