SUBROUTINE get_sector( tterm, phi_ir, ndim_ir, sector_wf, ndim_sector, whichir, nchir ) !========================================================================================= ! Written by: Jeff Crawford ! ! This routine obtains the projection of the time-propagated wave function along a line of ! constant rho (rho_infty) in the asymptotic region of the potential. ! This is done after each time step. ! ! Variables: ! td_pwf_vals = (OUTPUT) = Delves' theta points of the projected wave function. These ! are the same as the APH chi points for the collinear case. ! sector_pwf_prod = (OUTPUT) = values of the projected wave function Use Numeric_Kinds_Module USE CommonInfo_Module USE APH_Module USE Jacobi_Module USE Delves_Module USE Print_Module USE SymGroup_Module IMPLICIT NONE !========================================================================================= ! I N P U T INTEGER,INTENT(IN) :: tterm, ndim_ir, ndim_sector, whichir, nchir COMPLEX(dp),INTENT(IN) :: phi_ir(ndim_ir) !========================================================================================= ! O U T P U T COMPLEX(dp) :: sector_wf(ndim_sector) !========================================================================================= ! I N T E R N A L S INTEGER :: itheta, ichi, ir_pt, sec_pt, fpt, lpt !========================================================================================= ! F U N C T I O N S INTEGER :: aphindex, aphindex_tc !========================================================================================= ! Pick off wave function at constant rho infinity surface. This is from fpt to ! lpt fpt=aphindex(ntheta,nchir,ind_rho_infty,1,1,.false.) lpt=aphindex(ntheta,nchir,ind_rho_infty,ntheta,nchir,.false.) sector_wf=phi_ir(fpt:lpt) ! DO itheta=1,ntheta ! DO ichi=1,nchir ! ir_pt=aphindex(ntheta,nchir,ind_rho_infty,itheta,ichi,.false.) ! sec_pt=aphindex_tc(nchir,itheta,ichi) ! sector_wf(sec_pt)=phi_ir(ir_pt) ! ENDDO ! ENDDO END SUBROUTINE get_sector