Module Cluster_mod
module Cluster_mod
! Uses
use Precision_mod
use Chambers_mod
use Det_Geom_mod
use Tdc_mod
use Unp_mod
use Namelist_mod
use Hists_mod
use Pattern_mod
! Types
private type pnt_arr
! Variables
type (coord_type), private, DIMENSION(MaxClPerPl), SAVE, TARGET :: UCrd
type (coord_type), private, DIMENSION(MaxClPerPl), SAVE, TARGET :: VCrd
integer (kind=I4), private, DIMENSION(:), POINTER :: x_minP
integer (kind=I4), private, DIMENSION(:), POINTER :: x_maxP
integer (kind=I4), private, DIMENSION(MaxClPerPr), TARGET :: nuHits
integer (kind=I4), private, DIMENSION(MaxClPerPr), TARGET :: nvHits
integer (kind=I4), private, DIMENSION(MaxClPerPr, MaxHitsPl), TARGET :: uHit
integer (kind=I4), private, DIMENSION(MaxClPerPr, MaxHitsPl), TARGET :: vHit
type (pnt_arr), private, DIMENSION(MaxClPerPl) :: xHit
integer (kind=I4), private, DIMENSION(:), POINTER :: nxHitsP
integer (kind=I4), private, DIMENSION(:), POINTER :: nuHitsP
integer (kind=I4), private, DIMENSION(:), POINTER :: nvHitsP
real (kind=R8), private, DIMENSION(:), POINTER :: zP
integer (kind=I4), private, POINTER :: nClP
integer (kind=I4), private :: PrevWire
integer (kind=I4), private :: PrevHitWire
integer (kind=I4), private :: nPhits
type (cluster_type), private, POINTER :: ClP
type (whits_type), private, DIMENSION(:), POINTER :: WhitsP
type (plane_type), private, POINTER :: PlaneP
type (wire_type), private, DIMENSION(:,:), POINTER :: WireP
real (kind=R8), private :: uz
real (kind=R8), private :: vz
! Subroutines and functions
public subroutine Clustering (PCorDC, iWindow, iPlane)
public subroutine ClusteringGeneric (PCorDC, Cl, Win, iWindow, iPlane, n_DCCl, LenPerWin)
private subroutine CombineUVCluster (iuCl, jvCl, kCl)
private subroutine InsertClWire (jHitWire)
private subroutine uvBar (iuCl, jvCl, uBar, vBar)
private subroutine NewCluster (jHitWire, iStat)
private subroutine Initialize (PCorDC, Cl, Win, iPlane, iPair, Plane, Wire)
private function InBounds (uBar, vBar, iStat)
public subroutine ClearCluster (iStream, iWindow)
public subroutine ClearClusterGeneric (iStream, Cl)
public subroutine ClusterStat (iWindow)
private subroutine CalcAvgAreaSize (clstat, clust, clust2, pairmin, pairmax, pairmin2, pairmax2)
end module Cluster_mod
Cluster_mod
==============================================================================
Author: Jim Musser
Major Revision Jan. 31, 2002
Last Updated: Feb. 6, 2002
------------------------------------------------------------------------------
Routines for creating, clearing, and filling cluster structures. Clusters
are intersections of hit u wires and hit v wires within a pair of adjacent
planes. Data is stored in PCCl for PC hits and DCCl for DC hits. Cluster
routines are called from within window_mod. Clusters are used extensively
by the firstguess code.
==============================================================================!! Added dead wire code for dc p43w42 and p4w26 AO
Description of Types
pnt_arr
private type pnt_arr
integer (kind=I4), DIMENSION(:), POINTER :: P
end type pnt_arr
Description of Variables
UCrd
type (coord_type), private, DIMENSION(MaxClPerPl), SAVE, TARGET :: UCrd
VCrd
type (coord_type), private, DIMENSION(MaxClPerPl), SAVE, TARGET :: VCrd
x_minP
integer (kind=I4), private, DIMENSION(:), POINTER :: x_minP
x_maxP
integer (kind=I4), private, DIMENSION(:), POINTER :: x_maxP
nuHits
integer (kind=I4), private, DIMENSION(MaxClPerPr), TARGET :: nuHits
nvHits
integer (kind=I4), private, DIMENSION(MaxClPerPr), TARGET :: nvHits
uHit
integer (kind=I4), private, DIMENSION(MaxClPerPr, MaxHitsPl), TARGET :: uHit
vHit
integer (kind=I4), private, DIMENSION(MaxClPerPr, MaxHitsPl), TARGET :: vHit
xHit
type (pnt_arr), private, DIMENSION(MaxClPerPl) :: xHit
nxHitsP
integer (kind=I4), private, DIMENSION(:), POINTER :: nxHitsP
nuHitsP
integer (kind=I4), private, DIMENSION(:), POINTER :: nuHitsP
nvHitsP
integer (kind=I4), private, DIMENSION(:), POINTER :: nvHitsP
zP
real (kind=R8), private, DIMENSION(:), POINTER :: zP
nClP
integer (kind=I4), private, POINTER :: nClP
PrevWire
integer (kind=I4), private :: PrevWire
PrevHitWire
integer (kind=I4), private :: PrevHitWire
nPhits
integer (kind=I4), private :: nPhits
ClP
type (cluster_type), private, POINTER :: ClP
WhitsP
type (whits_type), private, DIMENSION(:), POINTER :: WhitsP
PlaneP
type (plane_type), private, POINTER :: PlaneP
WireP
type (wire_type), private, DIMENSION(:,:), POINTER :: WireP
uz
real (kind=R8), private :: uz
vz
real (kind=R8), private :: vz
Description of Subroutines and Functions
Clustering
public subroutine Clustering (PCorDC, iWindow, iPlane)
character, INTENT(in) :: PCorDC
integer (kind=I4), INTENT(in) :: iWindow
integer (kind=I4), INTENT(in) :: iPlane
! Calls: ClusteringGeneric
end subroutine Clustering
------------------------------------------------------------------------------
Clustering creates clusters of hits from the intersections of hit u wires and
hit v wires.
------------------------------------------------------------------------------
ClusteringGeneric
public subroutine ClusteringGeneric (PCorDC, Cl, Win, iWindow, iPlane, n_DCCl, LenPerWin)
character, INTENT(in) :: PCorDC
type (cluster_type), INTENT(inout) :: Cl
type (window_type), INTENT(in) :: Win
integer (kind=I4), INTENT(in) :: iWindow
integer (kind=I4), INTENT(in) :: iPlane
integer (kind=I4), INTENT(inout) :: n_DCCl
real (kind=I4), INTENT(inout) :: LenPerWin
! Calls: CombineUVCluster, HF2, Initialize, InsertClWire, NewCluster, kerror, uvBar
end subroutine ClusteringGeneric
----------------------------------------------------------------------------
----------------------------------------------------------------------------
CombineUVCluster
private subroutine CombineUVCluster (iuCl, jvCl, kCl)
integer (kind=I4), INTENT(in) :: iuCl
integer (kind=I4), INTENT(in) :: jvCl
integer (kind=I4), INTENT(in) :: kCl
end subroutine CombineUVCluster
----------------------------------------------------------------------------
CombineUVCluster creates combined uv clusters out of u clusters and v
clusters. If there is a dead plane, then the remaining plane is used
by itself.
----------------------------------------------------------------------------
InsertClWire
private subroutine InsertClWire (jHitWire)
integer (kind=I4), INTENT(in) :: jHitWire
end subroutine InsertClWire
----------------------------------------------------------------------------
Jan. 31, 2002
InsertClWire inserts the hits on jHitWire into a cluster
----------------------------------------------------------------------------
uvBar
private subroutine uvBar (iuCl, jvCl, uBar, vBar)
integer (kind=I4), INTENT(in) :: iuCl
integer (kind=I4), INTENT(in) :: jvCl
real (kind=R4), INTENT(out) :: uBar
real (kind=R4), INTENT(out) :: vBar
end subroutine uvBar
----------------------------------------------------------------------------
Feb. 1, 2002
----------------------------------------------------------------------------
NewCluster
private subroutine NewCluster (jHitWire, iStat)
integer (kind=I4), INTENT(in) :: jHitWire
integer (kind=I4), INTENT(inout) :: iStat
! Calls: InsertClWire
end subroutine NewCluster
----------------------------------------------------------------------------
Jan. 31, 2002
NewCluster creates a new cluster using the hits on jHitWire
----------------------------------------------------------------------------
Initialize
private subroutine Initialize (PCorDC, Cl, Win, iPlane, iPair, Plane, Wire)
character, INTENT(in) :: PCorDC
type (cluster_type), INTENT(inout), TARGET :: Cl
type (window_type), INTENT(in), TARGET :: Win
integer (kind=I4), INTENT(in) :: iPlane
integer (kind=I4), INTENT(in) :: iPair
type (plane_type), INTENT(in), TARGET :: Plane
type (wire_type), DIMENSION(:,:), INTENT(in), TARGET :: Wire
end subroutine Initialize
----------------------------------------------------------------------------
InBounds
private function InBounds (uBar, vBar, iStat)
real (kind=R4), INTENT(in) :: uBar
real (kind=R4), INTENT(in) :: vBar
integer (kind=I4), INTENT(out) :: iStat
logical :: InBounds
end function InBounds
------------------------------------------------------------------------------
Feb. 1, 2002
Variation of previous FUNCTION RediusCut
InBounds determines whether a cluster center is within the detector volume.
------------------------------------------------------------------------------
ClearCluster
public subroutine ClearCluster (iStream, iWindow)
integer (kind=I4), INTENT(in) :: iStream
integer (kind=I4), INTENT(in) :: iWindow
! Calls: ClearClusterGeneric
end subroutine ClearCluster
------------------------------------------------------------------------------
Added Jan. 30, 2002 by Jim. ClearCluster clears the cluster structure for a
single window. Now it is written as a wrapper that calls a generic
Clearing routine that can clear any cluster_type structure.
------------------------------------------------------------------------------
ClearClusterGeneric
public subroutine ClearClusterGeneric (iStream, Cl)
integer (kind=I4), INTENT(in) :: iStream
type (cluster_type), DIMENSION(:), INTENT(inout) :: Cl
end subroutine ClearClusterGeneric
----------------------------------------------------------------------------
ClearClusterGeneric is a routine that clears any cluster_type structure
ClusterStat
public subroutine ClusterStat (iWindow)
integer (kind=i4), INTENT(in) :: iWindow
! Calls: CalcAvgAreaSize
end subroutine ClusterStat
SUBROUTINE ClusterStat( iWindow )
---------------------------------------------------------------------------
This subroutine calculates average cluster area and sizes, by window and
by stream.
CalcAvgAreaSize
private subroutine CalcAvgAreaSize (clstat, clust, clust2, pairmin, pairmax, pairmin2, pairmax2)
type (clusterstat_type), INTENT(out) :: clstat
type (cluster_type), POINTER, dimension (:) :: clust
type (cluster_type), POINTER, dimension (:) :: clust2
integer (kind=i4), INTENT(in) :: pairmin
integer (kind=i4), INTENT(in) :: pairmax
integer (kind=i4), INTENT(in) :: pairmin2
integer (kind=i4), INTENT(in) :: pairmax2
end subroutine CalcAvgAreaSize
SUBROUTINE CalcAvgAreaSize( clstat, clustP, clust2P, pairmin,
pairmax, pairmin2, pairmax2 )
-------------------------------------------------------------
This subroutine does the calculation of average cluster area
and average cluster size for PC and/or DC clusters from a minimum
plane pair to maximum plane pair. For calculation for just PC or just
DC, pass a dummy cluster structure array for clust2, and set parimin2
to 0.
Inputs:
type(cluster_type) clust(MaxPairs)
type(cluster_type) clust2(MaxPairs)
integer pairmin, pairmax, pairmin2,pairmax2
Output:
type(clusterstat_type) clstat