Module WindowBJ_mod

module WindowBJ_mod

        ! Uses
    use Precision_mod
    use Namelist_mod
    use Chambers_mod
    use Det_Geom_mod
    use Tdc_mod
    use Unp_mod
    use Hists_mod
    use Pattern_mod
    use Cluster_mod
    use Pattern_Log_mod
    use Xtalk_mod, ONLY: DC_IsXtalk, PC_IsXtalk
    use windowstat_mod
    use evalwin_mod
    use windex_mod
    use windowcalc_mod
    use pattern_log_mod
    use assigntowindow_mod
    use track_mod

        ! Subroutines and functions
    public subroutine WindowingBJ ()
    private subroutine ZeroTimeBinArrays ()
    private subroutine CalcPCTimeBinStat ()
    private subroutine CalcDCTimeBinStat ()
    private subroutine FillTimeBin (tbin, tdc, PorD)
    private function CalculateSigma (minx, maxx, sumx2, avgx, sumx, hitcount)
    private subroutine CalcTimeBinAvgSig (tbin)
    private subroutine PrintTimeBinStat ()
    private subroutine CalcPCpidTimes ()
    private subroutine PrintPCpidTimes ()
    private subroutine LookForLargeRadiusNoise ()
    private subroutine CalcWinPCStat ()
    private subroutine CalcWinDCStat ()
    private subroutine FillWinPC (pcstat, tdc, ip)
    private subroutine FillWinCH (chstat, tdc, PorD)
    private subroutine FillWinUpDn (Up, Dn, tdc, PorD)
    private subroutine FillWinUpDnRadius (Up, Dn, tdc, PorD)
    private subroutine FillWinSlide (slide, plane, tdc, PorD)
    private subroutine CalcWinPCSig (pcstat)
    private subroutine CalcWinCHSig (chstat)
    private subroutine ZeroWinArray (ipcwin)
    public subroutine GetGlobalPlane (iplane, igplane, PorD)
    public subroutine ClearWindowingBJ ()
    private function HitOnTrack (PCorDC, iTDC, FTrack, LTrack)
    private subroutine MoveToWindow (PCorDC, iWindow, Offset, iPlane, iHitWire)
    private subroutine WriteDebugFiles (BorA, iStream, iWindow, FTrack, LTrack)
    private subroutine HalfWindowClear (iStream, iWindow)
    public subroutine SplitOverlap (iStream, iWindow, Offset, FTrack, LTrack)

end module WindowBJ_mod

Description of Subroutines and Functions

WindowingBJ

public subroutine WindowingBJ ()
    ! Calls: AssignToWindows, CalcDCTimeBinStat, CalcPCTimeBinStat, CalcPCpidTimes, CalcWinDCStat, CalcWinPCStat, CalcWinSlideAvgSig, CalcWinStartStop, CalcWinUpDownStat, DoClustering, FillWindowBJhistos, GetScintHits, GetTriggerInfo, LookForLargeRadiusNoise, PrintPCpidTimes, PrintTimeBinStat, PrintUpDnPCStat, PrintWinCHStat, PrintWinSlideStat, WindowClearBJ, ZeroTimeBinArrays, hf1, logcl
end subroutine WindowingBJ
 SUBROUTINE WindowingBJ
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This is the main public call to windowing.  It is where all of 
 the calls to make windowing work are made.

ZeroTimeBinArrays

private subroutine ZeroTimeBinArrays ()
end subroutine ZeroTimeBinArrays
 SUBROUTINE ZeroTimeBinArrays
------------------------------------------------------------------
 Author: Blair
 Date: Jan.2003
 Description: 
 This subroutine clears all the counters in the per time bin
 structures.

CalcPCTimeBinStat

private subroutine CalcPCTimeBinStat ()
    ! Calls: CalcTimeBinAvgSig, FillTimeBin
end subroutine CalcPCTimeBinStat
 SUBROUTINE CalcPCTimeBinStat
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine is the steering routine for filling the PC
 array of per time bin information (PCt).

CalcDCTimeBinStat

private subroutine CalcDCTimeBinStat ()
    ! Calls: CalcTimeBinAvgSig, FillTimeBin
end subroutine CalcDCTimeBinStat
 SUBROUTINE CalcDCTimeBinStat
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine is the steering routine for filling the DC
 array of per time bin information (DCt).

FillTimeBin

private subroutine FillTimeBin (tbin, tdc, PorD)
    type (tbin_TYPE), INTENT(inout) :: tbin
    type (tdc_TYPE), INTENT(in) :: tdc
    character, INTENT(in) :: PorD
end subroutine FillTimeBin
 SUBROUTINE FillTimeBin
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Output: tbin = An element of tbin_TYPE (per time bin structure)
 Inputs: tdc = An element of a TDC structure (PC, or DC)
         PorD = 'P' for a PC tdc or 'D' for a DC tdc
 Description:
 This subroutine fills info about a particular tdc hit into the
 time bin that was passed.

CalculateSigma

private function CalculateSigma (minx, maxx, sumx2, avgx, sumx, hitcount)
    real (kind=r4), INTENT(in) :: minx
    real (kind=r4), INTENT(in) :: maxx
    real (kind=r8), INTENT(in) :: sumx2
    real (kind=r4), INTENT(in) :: avgx
    real (kind=r8), INTENT(in) :: sumx
    integer (kind=i4), INTENT(in) :: hitcount
    real :: CalculateSigma
end function CalculateSigma

CalcTimeBinAvgSig

private subroutine CalcTimeBinAvgSig (tbin)
    type (tbin_TYPE), INTENT(inout) :: tbin
end subroutine CalcTimeBinAvgSig
 SUBROUTINE CalcTimeBinAvgSig
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine uses the hitcounts and hit sums in the tbin_TYPE
 structure to calculate averages and sigmas of the hits.

PrintTimeBinStat

private subroutine PrintTimeBinStat ()
end subroutine PrintTimeBinStat
 SUBROUTINE PrintTimeBinStat
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine prints information about the per time bin
 arrays (both PCt, and DCt), to the screen.

CalcPCpidTimes

private subroutine CalcPCpidTimes ()
    ! Calls: ZeroWinArray
end subroutine CalcPCpidTimes
 SUBROUTINE CalcPCpidTimes
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine uses the PCt per time bin arrays to determine
 start and stop times for track time "windows".  It tries to see
 if there is an overlap within (100ns) of two tracks.  If there
 is then it calls the track an overlap.  The window time information
 is stored in the PCpid array.
 Modifications:
 Feb 25, 2003 -- Add some checks of DCt to see if DC's should make
                 a new particle window, in case no PC's were hit
 Mar.12, 2003 -- Don't make a new window if there is only one PC 
                 plane hit with narrow avg width, and fewer than 
                 10 DC hits.)
              -- Also don't make new window if there are fewer than 
                 4 PC hits with width avg less than 25, and less 
                 than 400 ns (8 tbins) after previous track, and 
                 with fewer than 10 dC htis.
 May 02, 2003 -- Bug found while running GEANT -- should check
                 for the case when have high angle decay which
                 doesn't start in tgt.  Get lots of DC hits before
                 any PC hits!
 May 20, 2003 -- Another bug fixed.  Needed to be careful looking
                 at time since last PC window that was created,
                 when previous window was created by DC.  Cant use
                 PCt array if previous window was created by DCs.

PrintPCpidTimes

private subroutine PrintPCpidTimes ()
end subroutine PrintPCpidTimes
 SUBROUTINE PrintPCpidTimes
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine prints information from (PCpid) the track times 
 as determined from the per time bin information.

LookForLargeRadiusNoise

private subroutine LookForLargeRadiusNoise ()
    ! Calls: FillWinUpDnRadius
end subroutine LookForLargeRadiusNoise
 SUBROUTINE LookForLargeRadiusNoise
------------------------------------------------------------------
 Author: Blair
 Date: Mar. 2003
 Description:
 This subroutine looks for outlier hits that could confuse calculations
 of average radius of hits, or spread of hits.

CalcWinPCStat

private subroutine CalcWinPCStat ()
    ! Calls: CalcWinCHSig, CalcWinPCSig, FillWinCH, FillWinPC, FillWinSlide, FillWinUpDn
end subroutine CalcWinPCStat
 SUBROUTINE CalcWinPCStat
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This is the main driving subroutine for calculating the per
 particle track plane statistics.  It loops through the PC hits
 and calls to add to the chamber, Up vs Down, and slide
 statistics.

CalcWinDCStat

private subroutine CalcWinDCStat ()
    ! Calls: CalcWinCHSig, FillWinCH, FillWinSlide, FillWinUpDn
end subroutine CalcWinDCStat
 SUBROUTINE CalcWinDCStat
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This is the main driving subroutine for calculating the per
 particle track plane statistics.  It loops through the DC hits
 and calls to add to the chamber, Up vs Down, and slide
 statistics.

FillWinPC

private subroutine FillWinPC (pcstat, tdc, ip)
    type (UpPC_TYPE), INTENT(inout) :: pcstat
    type (tdc_TYPE), INTENT(in) :: tdc
    integer (kind=i4), INTENT(in) :: ip
end subroutine FillWinPC
 SUBROUTINE FillWinPC( pcstat, tdc, ip )
------------------------------------------------------------------
 Author: Blair
 Date: Apr. 2003
 Outputs: pcstat - UpPC,TgtPC, or DnPC UpPC_TYPE 
 Inputs:  tdc - PC tdc_TYPE (tdc hit structure)
          ip - plane number in this stack (1-4)
 Description:
 This subroutine fills information about a tdc hit into the
 pc statistics for Upstream PC's, Target PC's or Downstream
 PC's

FillWinCH

private subroutine FillWinCH (chstat, tdc, PorD)
    type (CHstat_TYPE), INTENT(inout) :: chstat
    type (tdc_TYPE), INTENT(in) :: tdc
    character, INTENT(in) :: PorD
end subroutine FillWinCH
 SUBROUTINE FillWinCH( chstat, tdc, PorD )
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Outputs: chstat - PC or DC CHstat_TYPE (plane statistics per track)
 Inputs:  tdc - PC or DC tdc_TYPE (tdc hit structure)
          PorD - 'P' for PC or 'D' for DC
 Description:
 This subroutine fills information about a tdc hit into the
 plane statistics for a track stucture.

FillWinUpDn

private subroutine FillWinUpDn (Up, Dn, tdc, PorD)
    type (updnstream_type), intent(inout) :: Up
    type (updnstream_type), intent(inout) :: Dn
    type (tdc_TYPE), intent(in) :: tdc
    character :: PorD
end subroutine FillWinUpDn
 SUBROUTINE FillWinUpDn( Up, Dn, tdc, PorD )
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Outputs: Up - updnstream_type 
               (Statistics about upstream hits per window)
          Dn - updnstream_type
               (Statistics about downstream hits per window)
 Inputs:  tdc - PC or DC tdc_TYPE (tdc hit structure)
          PorD - 'P' for PC or 'D' for DC
 Description:
 This subroutine fills information about a tdc hit into the
 plane statistics for upstream of target or downstream of
 target.  Ignore target PC's for this.

FillWinUpDnRadius

private subroutine FillWinUpDnRadius (Up, Dn, tdc, PorD)
    type (updnstream_type), intent(inout) :: Up
    type (updnstream_type), intent(inout) :: Dn
    type (tdc_TYPE), intent(in) :: tdc
    character :: PorD
end subroutine FillWinUpDnRadius
 SUBROUTINE FillWinUpDnRadius( Up, Dn, tdc, PorD )
------------------------------------------------------------------
 Author: Blair
 Date: Mar. 2003
 Outputs: Up - updnstream_type 
               (Statistics about upstream hits per window)
          Dn - updnstream_type
               (Statistics about downstream hits per window)
 Inputs:  tdc - PC or DC tdc_TYPE (tdc hit structure)
          PorD - 'P' for PC or 'D' for DC
 Description:
 This subroutine fills radius (wire#) tdc hit into the
 plane statistics for upstream of target or downstream of
 target.

FillWinSlide

private subroutine FillWinSlide (slide, plane, tdc, PorD)
    type (Hitslide_TYPE), DIMENSION(:), INTENT( out ) :: slide
    type (stop_TYPE), INTENT( out ) :: plane
    type (tdc_TYPE), INTENT(in) :: tdc
    character :: PorD
end subroutine FillWinSlide
 SUBROUTINE FillWinSlide( slide, tdc, PorD )
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Outputs: slide - (hitslide_type array) statistics on hits in
                   eight plane slides 
 Inputs:  tdc - PC or DC tdc_TYPE (tdc hit structure)
          PorD - 'P' for PC or 'D' for DC
 Description:
 This subroutine fills information about a tdc hit into the
 plane statistics for eight plane slides.

CalcWinPCSig

private subroutine CalcWinPCSig (pcstat)
    type (UpPC_TYPE), INTENT(inout) :: pcstat
end subroutine CalcWinPCSig
 SUBROUTINE CalcWinPCSig( pcstat )
------------------------------------------------------------------
 Author: Blair
 Date: Apr. 2003
 Input/Output:  pcstat - (UpPC_TYPE) for UpPC, DnPC, or TgtPC
 Description:
 This subroutine calculates averages and sigmas for the different
 PC modules: Upstream (UpPC), target (TgtPC), and Downstream (DnPC)

CalcWinCHSig

private subroutine CalcWinCHSig (chstat)
    type (CHstat_TYPE), INTENT(inout) :: chstat
end subroutine CalcWinCHSig
 SUBROUTINE CalcWinCHSig( chstat )
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Input/Output:  chstat - (chstat_TYPE) plane statistics type per track
 Description:
 This subroutine calculates averages and sigmas for the chamber
 statistics type (once all of the sums have been completed).

ZeroWinArray

private subroutine ZeroWinArray (ipcwin)
    integer (kind=i4), INTENT(in) :: ipcwin
end subroutine ZeroWinArray
 SUBROUTINE ZeroWinArray( ipcwin ) 
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This subroutine initializes the Track structures 
 (win, and PCpid) counters for a track number (ipcwin).

GetGlobalPlane

public subroutine GetGlobalPlane (iplane, igplane, PorD)
    integer (kind=i4), INTENT(in) :: iplane
    integer (kind=i4), INTENT(out) :: igplane
    character, INTENT(in) :: PorD
end subroutine GetGlobalPlane

ClearWindowingBJ

public subroutine ClearWindowingBJ ()
end subroutine ClearWindowingBJ
 SUBROUTINE ClearWindowingBJ
------------------------------------------------------------------
 Author: Blair
 Date: Jan. 2003
 Description:
 This is the routine called before events are analyzed to
 reset the main global counters.
  

HitOnTrack

private function HitOnTrack (PCorDC, iTDC, FTrack, LTrack)
    character, INTENT(in) :: PCorDC
    integer (kind=I4), INTENT(in) :: iTDC
    integer (kind=I4), INTENT(in) :: FTrack
    integer (kind=I4), INTENT(in) :: LTrack
    logical :: HitOnTrack
end function HitOnTrack
----------------------------------------------------------------------------

MoveToWindow

private subroutine MoveToWindow (PCorDC, iWindow, Offset, iPlane, iHitWire)
    character, INTENT(in) :: PCorDC
    integer (kind=I4), INTENT(in) :: iWindow
    integer (kind=I4), INTENT(in) :: Offset
    integer (kind=I4), INTENT(in) :: iPlane
    integer (kind=I4), INTENT(in) :: iHitWire
end subroutine MoveToWindow
----------------------------------------------------------------------------

WriteDebugFiles

private subroutine WriteDebugFiles (BorA, iStream, iWindow, FTrack, LTrack)
    character, INTENT(in) :: BorA
    integer (kind=I4), INTENT(in) :: iStream
    integer (kind=I4), INTENT(in) :: iWindow
    integer (kind=I4), INTENT(in) :: FTrack
    integer (kind=I4), INTENT(in) :: LTrack
end subroutine WriteDebugFiles
----------------------------------------------------------------------------

HalfWindowClear

private subroutine HalfWindowClear (iStream, iWindow)
    integer (kind=I4), INTENT(in) :: iStream
    integer (kind=I4), INTENT(in) :: iWindow
end subroutine HalfWindowClear
----------------------------------------------------------------------------

SplitOverlap

public subroutine SplitOverlap (iStream, iWindow, Offset, FTrack, LTrack)
    integer (kind=I4), INTENT(in) :: iStream
    integer (kind=I4), INTENT(in) :: iWindow
    integer (kind=I4), INTENT(in) :: Offset
    integer (kind=I4), INTENT(in) :: FTrack
    integer (kind=I4), INTENT(in) :: LTrack
    ! Calls: ClearCluster, Clustering, HalfWindowClear, MoveToWindow, WriteDebugFiles
end subroutine SplitOverlap