module xtalk_mod ! Uses use precision_mod use det_geom_mod use chambers_mod use filters_mod use tdc_mod use unp_mod use namelist_mod use hists_mod ! Variables logical, public, dimension (dc_mngw) :: DC_IsXtalk logical, public, dimension (pc_mngw) :: PC_IsXtalk integer (kind=i4), public, PARAMETER :: max_nAway = 79 integer (kind=i4), public, PARAMETER :: nWidthBins = 7 integer (kind=i4), private, PARAMETER, dimension (nWidthBins-1) :: WidthBins = (/ 70, 100, 200, 300, 500, 1000 /) integer (kind=i4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D,max_nAway) :: DC_nAdjHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D,max_nAway) :: DC_nXtalkHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D, nWidthBins) :: DC_nWideHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D, nWidthBins) :: DC_nCausedXtalk = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D) :: DC_nAllHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_PlaneMultSum = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_EventSum = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_WireSingleHit = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_WireMultHit = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P,MAX_WIRES_P,max_nAway) :: PC_nAdjHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P,MAX_WIRES_P,max_nAway) :: PC_nXtalkHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P, nWidthBins) :: PC_nWideHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P, nWidthBins) :: PC_nCausedXtalk = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P,MAX_WIRES_P) :: PC_nAllHits = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_PlaneMultSum = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_EventSum = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_WireSingleHit = 0 integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_WireMultHit = 0 ! Subroutines and functions public subroutine XtalkInit () public subroutine XTalk () private subroutine XTalk_Main (FirstPlane, LastPlane, Plane, Wire, nPhits, Whits, nWhits, tdc, WidthCut, WidthDiffCut, TDCuts, H, nAdjHits, nXtalkHits, nWideHits, nCausedXtalk, nAllHits, nAway, PlaneMultSum, EventSum, WireSingleHit, WireMultHit, IsXtalk) public subroutine XtalkPrint () private subroutine XtalkFillHists () private subroutine XtalkAfterFillHists () private subroutine XtalkPCHists (FirstPlane, LastPlane, nPhits, Whits, tdc, H) private subroutine CrossTalkFillHists (FirstPlane, LastPlane, nPhits, Whits, tdc, H, WidthCut, TimeDiffCuts) end module xtalk_mod ======================================================== version 2.1 September 1999 -------------------------------------------------------- Cross talk analysis ========================================================Author: Maher Quraan, Art Olin, Marc Lalancette
Version: 2.2qod
logical, public, dimension (dc_mngw) :: DC_IsXtalk
logical, public, dimension (pc_mngw) :: PC_IsXtalk
integer (kind=i4), public, PARAMETER :: max_nAway = 79
integer (kind=i4), public, PARAMETER :: nWidthBins = 7
integer (kind=i4), private, PARAMETER, dimension (nWidthBins-1) :: WidthBins = (/ 70, 100, 200, 300, 500, 1000 /)
integer (kind=i4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D,max_nAway) :: DC_nAdjHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D,max_nAway) :: DC_nXtalkHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D, nWidthBins) :: DC_nWideHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D, nWidthBins) :: DC_nCausedXtalk = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D) :: DC_nAllHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_PlaneMultSum = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_EventSum = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_WireSingleHit = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_D) :: DC_WireMultHit = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P,MAX_WIRES_P,max_nAway) :: PC_nAdjHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P,MAX_WIRES_P,max_nAway) :: PC_nXtalkHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P, nWidthBins) :: PC_nWideHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P, nWidthBins) :: PC_nCausedXtalk = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P,MAX_WIRES_P) :: PC_nAllHits = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_PlaneMultSum = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_EventSum = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_WireSingleHit = 0
integer (kind=i4), private, DIMENSION(MAX_PLANES_P) :: PC_WireMultHit = 0
public subroutine XtalkInit () end subroutine XtalkInit
public subroutine XTalk () ! Calls: XTalkFillHists, XTalk_Main, XtalkAfterFillHists end subroutine XTalk ======================================================== September 1999 -------------------------------------------------------- Crosstalk counters Art Olin added call to remove xtalk hits from the whits structures. Marc Lalancette June 2002, added layer to call generic subroutine for PCs and DCs and fixed errors in the algorithm. (introduced new ones and fixed those too :) Marc Lalancette August 2002, trimmed down, fast version of xtalk. ========================================================Author: Maher Quraan
Version: 2.1
private subroutine XTalk_Main (FirstPlane, LastPlane, Plane, Wire, nPhits, Whits, nWhits, tdc, WidthCut, WidthDiffCut, TDCuts, H, nAdjHits, nXtalkHits, nWideHits, nCausedXtalk, nAllHits, nAway, PlaneMultSum, EventSum, WireSingleHit, WireMultHit, IsXtalk) integer (kind=i4), INTENT(IN) :: FirstPlane integer (kind=i4), INTENT(IN) :: LastPlane type (plane_type), INTENT(IN), dimension (:) :: Plane type (wire_type), INTENT(IN), dimension (:,:) :: Wire integer (kind=i4), INTENT(INOUT), dimension (:) :: nPhits type (whits_type), INTENT(INOUT), TARGET, dimension (:,:) :: Whits integer (kind=i4), INTENT(INOUT) :: nWhits type (tdc_type), INTENT(INOUT), TARGET, dimension (:) :: tdc real (kind=r4), INTENT(IN) :: WidthCut real (kind=r4), INTENT(IN) :: WidthDiffCut real (kind=r4), INTENT(IN), dimension (:) :: TDCuts integer (kind=i4), INTENT(IN), dimension (2) :: H integer (kind=i4), INTENT(INOUT), dimension (:,:,:) :: nAdjHits integer (kind=i4), INTENT(INOUT), dimension (:,:,:) :: nXtalkHits integer (kind=i4), INTENT(INOUT), dimension (:,:) :: nWideHits integer (kind=i4), INTENT(INOUT), dimension (:,:) :: nCausedXtalk integer (kind=i4), INTENT(INOUT), dimension (:,:) :: nAllHits integer (kind=i4), INTENT(IN) :: nAway integer (kind=i4), INTENT(INOUT), dimension (:) :: PlaneMultSum integer (kind=i4), INTENT(INOUT), dimension (:) :: EventSum integer (kind=i4), INTENT(INOUT), dimension (:) :: WireSingleHit integer (kind=i4), INTENT(INOUT), dimension (:) :: WireMultHit logical, INTENT(INOUT), dimension (:) :: IsXtalk ! Calls: Xtalk_FindMisses, Xtalk_IsDouble, hf2, kerror end subroutine XTalk_Main
public subroutine XtalkPrint () ! Calls: CrossTalkPrint, kerror end subroutine XtalkPrint
private subroutine XtalkFillHists () ! Calls: CrossTalkFillHists, XtalkPCHists end subroutine XtalkFillHists
private subroutine XtalkAfterFillHists () ! Calls: CrossTalkFillHists, XtalkPCHists end subroutine XtalkAfterFillHists
private subroutine XtalkPCHists (FirstPlane, LastPlane, nPhits, Whits, tdc, H) integer (kind=i4), INTENT(IN) :: FirstPlane integer (kind=i4), INTENT(IN) :: LastPlane integer (kind=i4), INTENT(IN), dimension (:) :: nPhits type (whits_type), INTENT(IN), TARGET, dimension (:,:) :: Whits type (tdc_type), INTENT(IN), TARGET, dimension (:) :: tdc integer (kind=i4), INTENT(IN), dimension (:) :: H ! Calls: hf2 end subroutine XtalkPCHists
private subroutine CrossTalkFillHists (FirstPlane, LastPlane, nPhits, Whits, tdc, H, WidthCut, TimeDiffCuts) integer (kind=i4), INTENT(IN) :: FirstPlane integer (kind=i4), INTENT(IN) :: LastPlane integer (kind=i4), INTENT(IN), dimension (:) :: nPhits type (whits_type), INTENT(IN), TARGET, dimension (:,:) :: Whits type (tdc_type), INTENT(IN), TARGET, dimension (:) :: tdc integer (kind=i4), INTENT(IN), dimension (2) :: H real (kind=r4), INTENT(IN) :: WidthCut real (kind=r4), INTENT(IN), dimension (:) :: TimeDiffCuts ! Calls: hf1, hf2 end subroutine CrossTalkFillHists