Module Linear_mod

module Linear_mod

        ! Uses
    use precision_mod
    use tdc_mod
    use unp_mod
    use Pattern_mod
    use Hists_mod
    use namelist_mod
    use det_geom_mod
    use mc_delta_mod

        ! Variables
    integer (kind=I4), private, PARAMETER :: MaxLines = 10
    integer (kind=I4), private, PARAMETER :: MaxLineCls = 2 * (max_planes_p + max_planes_d)
    integer (kind=I4), private, PARAMETER :: MinLineCl = 3
    integer (kind=I4), private, PARAMETER :: SmallLim = 2
    integer (kind=I4), private :: OuterPair
    character, private :: OutDCorPC
    integer (kind=I4), private :: InnerPair
    character, private :: InDCorPC
    logical, private :: Begun
    logical, private :: Finished
    integer (kind=I4), private :: nLines
    logical, private :: ClUsed
    logical, private, DIMENSION(MaxLines) :: PairUsed
    type (line_type), private, DIMENSION(MaxLines), TARGET :: Line

        ! Subroutines and functions
    public subroutine Linear (iStream, iWindow, DeltaFound)
    private subroutine FindSubStack (iStream, iWindow)
    private subroutine FindDelta (DCorPC, iWindow, iPair)
    private subroutine NewLine (iWindow)
    private subroutine TestOnline (DCorPC, Crd, iLine, Online)
    private subroutine AddToLine (DCorPC, iWindow, iPair, iCl, iLine, Small)
    private function SmallCl (Crd)
    private subroutine RecordDelta (Recorded)
    private subroutine RemoveDeltaClusters ()
    public subroutine FillDeltaHists (DeltaSearch, DecaySuccess)
    public subroutine LogDeltas (iStream, iWindow, nPrevDeltas)
    private subroutine LogLines (iStream, iWindow)

end module Linear_mod
==============================================================================
 Author: Jim Musser
 Created: January 28, 2003
 Rewritten: February 19, 2003
------------------------------------------------------------------------------
 Linear_mod looks for hits that are linear parallel to the z-axis.  The code
 is primarily designed to look for deltas.  The entry point for the module is
 the subroutine linear, which is called from tracking_mod.

 Results are stored in Delta structure of type line_type, defined in
 pattern_mod.  Components are:
   INTEGER(I4)::Parent   ! Track number of parent track (not yet implemented)
   INTEGER(I4)::nCl      ! Number of small clusters in line
   INTEGER(I4)::nPairs   ! Number of pairs in line
   INTEGER(I4)::nSkipped ! Number of pairs skipped within line
   INTEGER(I4)::iWin     ! Window where line is found
   REAL(R4)::uMin        ! minimum u of intersection of all clusters in line
   REAL(R4)::uMax        ! maximum u of intersection of all clusters in line
   REAL(R4)::vMin        ! minimum v of intersection of all clusters in line
   REAL(R4)::vMax        ! maximum v of intersection of all clusters in line
   REAL(R4)::zMin        ! minimum z of all PAIRS(average of 2 planes) in line
   REAL(R4)::zMax        ! maximum z of all PAIRS(average of 2 planes) in line
   REAL(R4)::u           ! u coordinate of line
   REAL(R4)::v           ! v coordinate of line
   TYPE(lincl_type), DIMENSION(max_planes_p + max_planes_d)::LinCl ! Indices
==============================================================================

Description of Variables

MaxLines

integer (kind=I4), private, PARAMETER :: MaxLines = 10

MaxLineCls

integer (kind=I4), private, PARAMETER :: MaxLineCls = 2 * (max_planes_p + max_planes_d)

MinLineCl

integer (kind=I4), private, PARAMETER :: MinLineCl = 3

SmallLim

integer (kind=I4), private, PARAMETER :: SmallLim = 2

OuterPair

integer (kind=I4), private :: OuterPair

OutDCorPC

character, private :: OutDCorPC

InnerPair

integer (kind=I4), private :: InnerPair

InDCorPC

character, private :: InDCorPC

Begun

logical, private :: Begun

Finished

logical, private :: Finished

nLines

integer (kind=I4), private :: nLines

ClUsed

logical, private :: ClUsed

PairUsed

logical, private, DIMENSION(MaxLines) :: PairUsed

Line

type (line_type), private, DIMENSION(MaxLines), TARGET :: Line

Description of Subroutines and Functions

Linear

public subroutine Linear (iStream, iWindow, DeltaFound)
    integer (kind=I4), INTENT(in) :: iStream
    integer (kind=I4), INTENT(in) :: iWindow
    logical, INTENT(out) :: DeltaFound
    ! Calls: FindDelta, FindSubStack, RecordDelta, RemoveDeltaClusters
end subroutine Linear
------------------------------------------------------------------------------
 Linear is the steering routine for linear_mod.

FindSubStack

private subroutine FindSubStack (iStream, iWindow)
    integer (kind=I4), INTENT(in) :: iStream
    integer (kind=I4), INTENT(in) :: iWindow
    ! Calls: TestInsertSubStk
end subroutine FindSubStack
------------------------------------------------------------------------------
 FindSubStack finds the subset of pairs that have multiple clusters per pair
 and fills via TestInsertSubStk:
     OuterPair - the outermost pair
     OutDCorPC - the type of the outermost pair
     InnerPair - the innermost pair
     InDCorPC  - the type of the innermost pair

FindDelta

private subroutine FindDelta (DCorPC, iWindow, iPair)
    character, INTENT(in) :: DCorPC
    integer (kind=I4), INTENT(in) :: iWindow
    integer (kind=I4), INTENT(in) :: iPair
    ! Calls: AddToLine, NewLine, TestOnline
end subroutine FindDelta
------------------------------------------------------------------------------
 FindDelta

NewLine

private subroutine NewLine (iWindow)
    integer (kind=I4), INTENT(in) :: iWindow
end subroutine NewLine
------------------------------------------------------------------------------
 NewLine creates a new line and initializes appropriate variables

TestOnline

private subroutine TestOnline (DCorPC, Crd, iLine, Online)
    character, INTENT(in) :: DCorPC
    type (coord_type), INTENT(in) :: Crd
    integer (kind=I4), INTENT(in) :: iLine
    logical, INTENT(out) :: Online
    ! Calls: HFF1, HFF2
end subroutine TestOnline
------------------------------------------------------------------------------
 OnLine checks to see if a cluster is on a line.  Function requires average u
  of line and average u of the cluster to be within LineRes.  LineRes is a
 parameter measured in cm, defined at the top of this module.

AddToLine

private subroutine AddToLine (DCorPC, iWindow, iPair, iCl, iLine, Small)
    character, INTENT(in) :: DCorPC
    integer (kind=I4), INTENT(in) :: iWindow
    integer (kind=I4), INTENT(in) :: iPair
    integer (kind=I4), INTENT(in) :: iCl
    integer (kind=I4), INTENT(in) :: iLine
    logical, INTENT(in) :: Small
end subroutine AddToLine
------------------------------------------------------------------------------
 AddToLine adds a cluster to a line, recalculating the average u and v
 coordinates using the previous average and the new value according to the
 given formula.  xBar(n) is the average using the first n values.  x(n) is the
 nth value.
 xBar(n) =  (1/n)[(n-1)xBar(n-1) + x(n)]

SmallCl

private function SmallCl (Crd)
    type (coord_type), INTENT(in) :: Crd
    logical :: SmallCl
end function SmallCl
------------------------------------------------------------------------------
 SmallCl is called in FindDelta and is used to determine whether a cluster is
 of the size to be associated with only a delta. 

RecordDelta

private subroutine RecordDelta (Recorded)
    logical, INTENT(out) :: Recorded
end subroutine RecordDelta
------------------------------------------------------------------------------
 Save significant lines for plotting and fill delta histograms.

RemoveDeltaClusters

private subroutine RemoveDeltaClusters ()
    ! Calls: RemoveCls
end subroutine RemoveDeltaClusters
------------------------------------------------------------------------------
 RemoveLines removes clusters associated with deltas and "ghost" clusters that
 were a product of multiple possible combinations of u and v wire clusters.

FillDeltaHists

public subroutine FillDeltaHists (DeltaSearch, DecaySuccess)
    logical, INTENT(in) :: DeltaSearch
    logical, INTENT(in) :: DecaySuccess
    ! Calls: HFF1, HFF2, MCvsMOFIADeltaHists
end subroutine FillDeltaHists
------------------------------------------------------------------------------
 FillDeltaHists is called from tracking_mod after all windows for both halves
 of the detector have been through FirstGuess and HelixFit.

LogDeltas

public subroutine LogDeltas (iStream, iWindow, nPrevDeltas)
    integer (kind=I4), INTENT(in) :: iStream
    integer (kind=I4), INTENT(in) :: iWindow
    integer (kind=I4), INTENT(in) :: nPrevDeltas
end subroutine LogDeltas
------------------------------------------------------------------------------
 LogDeltas is called from tracking_mod after all deltas have been found in a
 window and detector half.

LogLines

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