Module Pattern_mod

module Pattern_mod

        ! Uses
    use tdc_mod
    use precision_mod
    use physicalconstants_mod
    use det_geom_mod

        ! Types
    public type window_type
    public type coord_type
    public type cluster_type
    public type lincl_type
    public type line_type
    public type clusterstat_type

        ! Variables
    integer (kind=I4), public, PARAMETER :: MaxWindows = 21
    integer (kind=I4), public, PARAMETER :: MaxHitsPl = 12
    integer (kind=I4), public, PARAMETER :: MaxClPerPl = 4
    integer (kind=I4), public, PARAMETER :: MaxClPerPr = 8
    integer (kind=I4), public, PARAMETER :: MaxCir = 5
    integer (kind=I4), public, PARAMETER :: MaxWinTracks = 10
    integer (kind=I4), public, PARAMETER :: MaxDeltas = 20
    integer (kind=I4), public, PARAMETER :: MaxDkWinCDA = 190
    real (kind=R4), public, PARAMETER :: MaxCDA = 500
    integer (kind=I4), public, DIMENSION(2, 3), TARGET :: PPlaneLim = RESHAPE ((/ 1, 12, 4, 9, 6, 7 /), (/ 2, 3 /))
    integer (kind=I4), public, DIMENSION(2, 3), TARGET :: PPairLim = RESHAPE ((/ 1, 6, 2, 5, 3, 4 /), (/ 2, 3 /))
    integer (kind=I4), public, DIMENSION(2, 3), TARGET :: DPlaneLim = RESHAPE ((/ 1, 44, 8, 37, 22, 23 /), (/ 2, 3 /))
    integer (kind=I4), public, DIMENSION(2, 3), TARGET :: DPairLim = RESHAPE ((/ 1, 22, 4, 19, 11, 12 /), (/ 2, 3 /))
    integer (kind=I4), public, DIMENSION(2) :: PatStep = (/ 1, -1 /)
    integer (kind=I4), public :: nWindows
    integer (kind=I4), public :: PrPl
    integer (kind=I4), public :: MuWin
    integer (kind=I4), public :: DecayWin
    integer (kind=I4), public :: TriggerWin
    integer (kind=I4), public :: EventType
    integer (kind=I4), public :: nDeltas
    integer (kind=I4), public :: nMuonDeltas
    integer (kind=I4), public :: nDecayDeltas
    integer (kind=I4), public :: nBeam_eDeltas
    integer (kind=I4), public, DIMENSION(MaxWindows) :: nDCCl
    real (kind=R4), public, DIMENSION(MaxWindows) :: DCClLenPerWin
    integer (kind=I4), public, PARAMETER :: MAX_BEAM_POSITRONS = MaxWindows
    integer (kind=I4), public :: nBeamPositrons
    integer (kind=I4), public :: nPions
    integer (kind=I4), public :: nNoiseCosmicGas
    integer (kind=i4), public :: nMuons
    integer (kind=i4), public :: nDecayPositrons
    integer (kind=i4), public :: nOverlaps
    integer (kind=i4), public :: nDecayNoMuon
    integer (kind=I4), public, dimension (MAX_BEAM_POSITRONS) :: BeamPosWin
    integer (kind=i4), public, dimension (MaxWindows) :: MuWindows
    integer (kind=i4), public, dimension (MaxWindows) :: DecayWindows
    integer (kind=i4), public, dimension (MaxWindows) :: DecayMuWin
    integer (kind=i4), public :: nSoftUncor
    integer (kind=i4), public :: nUnknown
    real (kind=R4), public, DIMENSION(MaxDkWinCDA) :: DkWincda
    real (kind=R4), public, DIMENSION(MaxDkWinCDA) :: dkwincdaz
    real (kind=R4), public, DIMENSION(MaxDkWinCDA) :: dkwincdadefl
    type (window_type), public, DIMENSION(MaxWindows), TARGET :: Window
    type (cluster_type), public, DIMENSION(MaxWindows, max_planes_p/2), TARGET :: PCCl
    type (cluster_type), public, DIMENSION(MaxWindows, max_planes_d/2), TARGET :: DCCl
    type (line_type), public, DIMENSION(MaxDeltas), TARGET :: Delta
    type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinAllCl
    type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinPCCl
    type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinBothCl
    type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinUpCl
    type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinDnCl

end module Pattern_mod
==============================================================================
Pattern_mod contains the global types and variables used in window,
 cluster, and tracking  calculations.
------------------------------------------------------------------------------

Description of Types

window_type

public type window_type
    integer (kind=I4) :: NumPCHits
             Number of PC hits in window 
    integer (kind=I4) :: NumDCHits
             Number of DC hits in window
    integer (kind=I4) :: WType
             Window type, defined and filled in evalwin and
    integer (kind=I4) :: CodeFlag
             windex
 This code flag specifies which part of the code 
    real (kind=R4) :: t0
             assigned the window type
 Earliest PC time associated with window
    real (kind=R4) :: t0sigma
    real (kind=R4) :: tStart
             Start time for window
    real (kind=R4) :: tEnd
             End time for window
    type (whits_type), DIMENSION(max_planes_p, max_wires_p) :: PCWhits
             Structure
    type (whits_type), DIMENSION(max_planes_d, max_wires_d) :: DCWhits
             holding PC hit information, indexed by plane and
 HITWIRE (as opposed to wire)
 Structure
    integer (kind=I4), DIMENSION(max_planes_p) :: PC_Nphits
             holding DC hit information, indexed by plane and
 HITWIRE (as opposed to wire)
 Number of wires hit in PC
    integer (kind=I4), DIMENSION(max_planes_d) :: DC_Nphits
             Number of wires hit in DC
    integer (kind=i4) :: pc_nwhits
             Total number of PC wires hit for all planes
    integer (kind=i4) :: dc_nwhits
             Total number of DC wirew hit for all planes
    real (kind=r4) :: uspcwidavg
             average of upstream pc widths for window
    real (kind=r4) :: uphitspp
    real (kind=r4) :: dnhitspp
    integer (kind=i4) :: startPlane
    integer (kind=i4) :: stopPlane
    integer (kind=i4) :: firstPC
    integer (kind=i4) :: lastPC
    integer (kind=i4) :: firstDC
    integer (kind=i4) :: lastDC
    integer (kind=i4) :: restrictplanesmin
    integer (kind=i4) :: restrictplanesmax
    logical :: analyze
             Historical, may not be used
    logical :: OverlapPrev
             Does window overlap with previous window
    logical :: OverlapNext
             Does window overlap with following window
    character :: Pid
             Particle ID, historical, may not be used
    integer (kind=i4) :: nDeltas
             Number of deltas found by linear_mod
end type window_type

coord_type

public type coord_type
    integer (kind=I4) :: uMin
             Minimum u wire in cluster
    integer (kind=I4) :: uMax
             Maximum u wire in cluster
    integer (kind=I4) :: vMin
             Minimum v wire in cluster
    integer (kind=I4) :: vMax
             Maximum v wire in cluster
    real (kind=R8) :: RuMin
             Minimum u in cluster
    real (kind=R8) :: RuMax
             Maximum u in cluster
    real (kind=R8) :: RvMin
             Minimum v in cluster
    real (kind=R8) :: RvMax
             Maximum v in cluster
    real (kind=R8) :: uBar
             u coordinate of cluster center
    real (kind=R8) :: vBar
             v coordinate of cluster center
    real (kind=R8) :: area
             Area covered by cluster
    real (kind=R8) :: Size
             "Invariant" size of cluster
    real (kind=R8) :: uz
             z coordinate of u plane
    real (kind=R8) :: vz
             z coordinate of v plane
    real (kind=R8) :: z
             z coordinate of two dimensional cluster
    integer (kind=I4) :: nuHits
             Number of u hits in the cluster
    integer (kind=I4) :: nvHits
             Number of v hits in the cluster
    integer (kind=I4), DIMENSION(MaxHitsPl) :: uHit
             indices into tdc structures
    integer (kind=I4), DIMENSION(MaxHitsPl) :: vHit
             indices into tdc structures
end type coord_type
 coord_type is for a structure within the structure cluster_type that
 holds the size and coordinate information for the cluster.

cluster_type

public type cluster_type
    integer (kind=I4) :: nuCl
             Number of clusters formed on u plane
    integer (kind=I4) :: nvCl
             Number of clusters formed on v plane
    integer (kind=I4) :: nCl
             Number of two dimensional clusters formed
    integer (kind=I4) :: uPlane
             u plane index
    integer (kind=I4) :: vPlane
             v plane index
    type (coord_type), DIMENSION(MaxClPerPr) :: Coord
             Cluster coordinates, hits
end type cluster_type
 cluster_type stores the number of clusters for a given window and pair.

lincl_type

public type lincl_type
    character :: DCorPC
             'D' for DCs, 'P' for PCs
    integer (kind=I4) :: iPr
             Pair index
    integer (kind=I4) :: iCl
             Cluster index
end type lincl_type
 lincl_type is used in line_type.  Indices are used to access cluster
 information from PCCl and DCCl structures.

line_type

public type line_type
    integer (kind=I4) :: Parent
             Track number of parent track (not yet implemented)
    integer (kind=I4) :: nCl
             Number of small clusters in line
    integer (kind=I4) :: nPairs
             Number of pairs in line
    integer (kind=I4) :: nSkipped
             Number of pairs skipped within line
    integer (kind=I4) :: iWin
             Window where line is found
    real (kind=R4) :: uMin
             minimum u of intersection of all clusters in line
    real (kind=R4) :: uMax
             maximum u of intersection of all clusters in line
    real (kind=R4) :: vMin
             minimum v of intersection of all clusters in line
    real (kind=R4) :: vMax
             maximum v of intersection of all clusters in line
    real (kind=R4) :: zMin
             minimum z of all PAIRS(average of 2 planes) in line
    real (kind=R4) :: zMax
             maximum z of all PAIRS(average of 2 planes) in line
    real (kind=R4) :: u
             u coordinate of line
    real (kind=R4) :: v
             v coordinate of line
    type (lincl_type), DIMENSION(2*(max_planes_p + max_planes_d)) :: LinCl
end type line_type

clusterstat_type

public type clusterstat_type
    real (kind=R4), dimension (3) :: sm_areanCl
             Number of clusters for pairs with smallest area sum  
    real (kind=R8), dimension (3) :: sm_areasum
             Area sum for pairs with smallest area sum            
    real (kind=R4), dimension (3) :: lg_areanCl
             Number of clusters for pairs with largest area sum   
    real (kind=R4), dimension (3) :: lg_areasum
             Area sum for pairs with largest area sum           
    integer (kind=i4) :: areanCl
             Number of clusters
    real (kind=R8) :: areasum
             Area Sum                                             
    real (kind=R4) :: areaavg
             Area average                                         
    real (kind=R4), dimension (6) :: Rareaavg
             Area averages, removing largest/smallest pairs       
    real (kind=R4), dimension (3) :: sm_sizenCl
              (-3lg,-2lg,-1lg,-3lg-3sm,-2lg-2sm,-1lg-1sm)         
 Number of clusters for pairs with smallest size sum  
    real (kind=R8), dimension (3) :: sm_sizesum
             Size sum for pairs with smallest size sum            
    real (kind=R4), dimension (3) :: lg_sizenCl
             Number of clusters for pairs with largest size sum   
    real (kind=R4), dimension (3) :: lg_sizesum
             Size sum for pairs with largest size sum             
    integer (kind=i4) :: sizenCl
             number of clusters
    real (kind=R8) :: sizesum
             Size Sum                                             
    real (kind=R4) :: sizeavg
             Size average                                         
    real (kind=R4), dimension (6) :: Rsizeavg
             Size averages, removing largest/smallest pairs       
end type clusterstat_type

Description of Variables

MaxWindows

integer (kind=I4), public, PARAMETER :: MaxWindows = 21

MaxHitsPl

integer (kind=I4), public, PARAMETER :: MaxHitsPl = 12

MaxClPerPl

integer (kind=I4), public, PARAMETER :: MaxClPerPl = 4

MaxClPerPr

integer (kind=I4), public, PARAMETER :: MaxClPerPr = 8

MaxCir

integer (kind=I4), public, PARAMETER :: MaxCir = 5

MaxWinTracks

integer (kind=I4), public, PARAMETER :: MaxWinTracks = 10

MaxDeltas

integer (kind=I4), public, PARAMETER :: MaxDeltas = 20

MaxDkWinCDA

integer (kind=I4), public, PARAMETER :: MaxDkWinCDA = 190
 INTEGER(I4), PUBLIC, PARAMETER::MaxDkWinCDA = 45 ! let's assume 10(maxcda=45) tracks max

MaxCDA

real (kind=R4), public, PARAMETER :: MaxCDA = 500

PPlaneLim

integer (kind=I4), public, DIMENSION(2, 3), TARGET :: PPlaneLim = RESHAPE ((/ 1, 12, 4, 9, 6, 7 /), (/ 2, 3 /))
 Each of the arrays below has the format of (istream, limit).
 These are used extensively throughout the pattern recognition modules.
 Limit = 1 is the outer pair/plane.
 Limit = 2 is the innermost pair/plane of the dense stack/outer PCs
 Limit = 3 is the inner pair/plane.

PPairLim

integer (kind=I4), public, DIMENSION(2, 3), TARGET :: PPairLim = RESHAPE ((/ 1, 6, 2, 5, 3, 4 /), (/ 2, 3 /))

DPlaneLim

integer (kind=I4), public, DIMENSION(2, 3), TARGET :: DPlaneLim = RESHAPE ((/ 1, 44, 8, 37, 22, 23 /), (/ 2, 3 /))

DPairLim

integer (kind=I4), public, DIMENSION(2, 3), TARGET :: DPairLim = RESHAPE ((/ 1, 22, 4, 19, 11, 12 /), (/ 2, 3 /))

PatStep

integer (kind=I4), public, DIMENSION(2) :: PatStep = (/ 1, -1 /)

nWindows

integer (kind=I4), public :: nWindows
 Number of windows in event

PrPl

integer (kind=I4), public :: PrPl
 1st or 2nd plane in pair, internal to

MuWin

integer (kind=I4), public :: MuWin
 pattern recognition
 Window id for muon window

DecayWin

integer (kind=I4), public :: DecayWin
 Window id for positron decay

TriggerWin

integer (kind=I4), public :: TriggerWin
 Window id for trigger particle

EventType

integer (kind=I4), public :: EventType
 Classification for event

nDeltas

integer (kind=I4), public :: nDeltas
 Number of deltas

nMuonDeltas

integer (kind=I4), public :: nMuonDeltas
 Number of deltas produced by muon

nDecayDeltas

integer (kind=I4), public :: nDecayDeltas
 Number of deltas by decay positron

nBeam_eDeltas

integer (kind=I4), public :: nBeam_eDeltas
 Number of deltas by beam positron

nDCCl

integer (kind=I4), public, DIMENSION(MaxWindows) :: nDCCl
 Test

DCClLenPerWin

real (kind=R4), public, DIMENSION(MaxWindows) :: DCClLenPerWin
 Test

MAX_BEAM_POSITRONS

integer (kind=I4), public, PARAMETER :: MAX_BEAM_POSITRONS = MaxWindows

nBeamPositrons

integer (kind=I4), public :: nBeamPositrons

nPions

integer (kind=I4), public :: nPions

nNoiseCosmicGas

integer (kind=I4), public :: nNoiseCosmicGas

nMuons

integer (kind=i4), public :: nMuons

nDecayPositrons

integer (kind=i4), public :: nDecayPositrons

nOverlaps

integer (kind=i4), public :: nOverlaps

nDecayNoMuon

integer (kind=i4), public :: nDecayNoMuon

BeamPosWin

integer (kind=I4), public, dimension (MAX_BEAM_POSITRONS) :: BeamPosWin

MuWindows

integer (kind=i4), public, dimension (MaxWindows) :: MuWindows

DecayWindows

integer (kind=i4), public, dimension (MaxWindows) :: DecayWindows

DecayMuWin

integer (kind=i4), public, dimension (MaxWindows) :: DecayMuWin

nSoftUncor

integer (kind=i4), public :: nSoftUncor

nUnknown

integer (kind=i4), public :: nUnknown

DkWincda

real (kind=R4), public, DIMENSION(MaxDkWinCDA) :: DkWincda
 CDA values for the

dkwincdaz

real (kind=R4), public, DIMENSION(MaxDkWinCDA) :: dkwincdaz
 CDA values for the

dkwincdadefl

real (kind=R4), public, DIMENSION(MaxDkWinCDA) :: dkwincdadefl
 CDA values for the

Window

type (window_type), public, DIMENSION(MaxWindows), TARGET :: Window

PCCl

type (cluster_type), public, DIMENSION(MaxWindows, max_planes_p/2), TARGET :: PCCl

DCCl

type (cluster_type), public, DIMENSION(MaxWindows, max_planes_d/2), TARGET :: DCCl

Delta

type (line_type), public, DIMENSION(MaxDeltas), TARGET :: Delta

WinAllCl

type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinAllCl

WinPCCl

type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinPCCl

WinBothCl

type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinBothCl

WinUpCl

type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinUpCl

WinDnCl

type (clusterstat_type), public, DIMENSION(MaxWindows), TARGET :: WinDnCl