module unpmc_mod
        ! Uses
    use precision_mod
    use chambers_mod
    use det_geom_mod, ONLY: max_wires_d, max_wires_p
    use hitpos_struct_mod
    use namelist_mod
    use track_mod
    use hists_mod
    use calibrations_mod
        ! Types
    public type mctrack_type
    public type mcsp_type
    public type mctr_type
        ! Variables
    integer, public :: McVersion
    integer, private, PARAMETER :: kMaxMC_nDCHits = 1000
    integer, private, PARAMETER :: kMaxMC_nPCHits = 1000
    type (HitPos_type), public, TARGET, dimension (kMaxMC_nDCHits) :: MC_DCHitPos
    type (HitPos_type), public, TARGET, dimension (kMaxMC_nPCHits) :: MC_PCHitPos
    integer (kind=i4), public :: MC_nDCHits
    integer (kind=i4), public :: MC_nPCHits
    integer, public, PARAMETER :: kMaxMcTracks = 1000
    integer, public :: fNumMcTracks = 0
    type (mctrack_type), public, TARGET, dimension (kMaxMcTracks) :: fMcTracks
    integer, private, PARAMETER :: kMaxMCSP = 1000
    type (mcsp_type), public :: mcsp
    integer, public :: musrLength = 0
    real (kind=R4), public, dimension (300) :: musrData = 0
    real, public :: mcMuonSpin
    type (mctr_type), public :: mctrData
    integer, private, EXTERNAL :: BLOCAT
    integer, private, EXTERNAL :: BDLEN
    integer, private, EXTERNAL :: cdfuse
    integer (kind=I4), public :: iMCMuonStop
    integer (kind=I4), public :: iMCDecayStart
    real (kind=R8), public, DIMENSION(3) :: MCDecayP
    real (kind=R8), public :: MCDecayCos
    real (kind=R8), public :: MCDecayR
    real (kind=R8), public :: MCDecayZ
    real (kind=R8), public :: MCtanTheta
    logical, public :: mMCDecay
    real (kind=R8), public :: mMCtanTheta
    real (kind=R8), public :: mMCDecayR
    real (kind=R8), public :: mMCDecayP
        ! Subroutines and functions
    public function unpmc (print)
    public subroutine FillMCp_cos ()
    private function unpMCEV () result (success)
    private function unpMCTR () result (success)
    private function unpMCT2 () result (success)
    public subroutine UnpackMUSR ()
    public subroutine UnpMcBFLD ()
    public subroutine UnpMcCALF ()
    private subroutine CheckCalFileName (calfilename, inam, inewlen)
    public subroutine UnpGeantSP ()
    private function UnpMCSP () result (success)
    private function UnpMCS2 () result (success)
    private function UnpMCS3 () result (success)
    private subroutine SortHitPos (hits, nhits, order)
    public subroutine PrintMcTracks ()
    public subroutine PrintMcTrack (trk)
end module unpmc_mod
---------------------------------------------------------------------------
 Date 1 Dec 00
 Gets data from ybos banks and creates and fills  data structures for
 tdc's and mc histories. Adc's and scintillators coming soon!
--------------------------------------------------------------------------- 
Author: Art Olin
Version: Modified to unpack space point bank from Geant (14 May 2001) Blair Jamieson
public type mctrack_type
    integer :: itrack
             geant track number
    integer :: ipid
             geant pid
    real (kind=R8), dimension (3) :: V
             starting / stopping point  (cm)
    real (kind=R8), dimension (3) :: P
             momentum (MeV)
    integer :: Q
             charge
    real (kind=R8) :: t
             particle vertex time
    integer :: istop
             geant stop code - See Geant .../source/istop.par
end type mctrack_type
 Data structure to unpack the tracks generated by GEANT
public type mcsp_type
    integer :: nummcsp
    integer, dimension (kMaxMCSP) :: itrack
             track number
    integer, dimension (kMaxMCSP) :: iplane
             plane number
    integer, dimension (kMaxMCSP) :: iwire
             wire number
    integer, dimension (kMaxMCSP) :: iambig
             geant hit ambiguity
    real (kind=R8), dimension (kMaxMCSP) :: tof
             geant time-of-flight
    real (kind=R8), dimension (kMaxMCSP) :: time
             geant drift time
    real (kind=R8), dimension (kMaxMCSP) :: distance
             geant drift distance
    real (kind=R8), dimension (kMaxMCSP,3) :: pos
             geant hit coordinates
    real (kind=R8), dimension (kMaxMCSP,3) :: steppos
             geant step coordinates
    real (kind=R8), dimension (kMaxMCSP,3) :: stepmom
             geant step momentum
end type mcsp_type
public type mctr_type
    integer :: e614vrn
    integer :: idrun
    integer :: ievent
    integer, dimension (2) :: nrndm
    real (kind=R4) :: spin3
    integer, dimension (25) :: ranluxSeed
end type mctr_type
 MCTR header data
integer, public :: McVersion
integer, private, PARAMETER :: kMaxMC_nDCHits = 1000
integer, private, PARAMETER :: kMaxMC_nPCHits = 1000
type (HitPos_type), public, TARGET, dimension (kMaxMC_nDCHits) :: MC_DCHitPos
type (HitPos_type), public, TARGET, dimension (kMaxMC_nPCHits) :: MC_PCHitPos
integer (kind=i4), public :: MC_nDCHits
integer (kind=i4), public :: MC_nPCHits
integer, public, PARAMETER :: kMaxMcTracks = 1000 Array to store the tracks generated by GEANT
integer, public :: fNumMcTracks = 0
type (mctrack_type), public, TARGET, dimension (kMaxMcTracks) :: fMcTracks
integer, private, PARAMETER :: kMaxMCSP = 1000 Data structure to store geant space points
type (mcsp_type), public :: mcsp
integer, public :: musrLength = 0 Data structures for the MUSR bank
real (kind=R4), public, dimension (300) :: musrData = 0
real, public :: mcMuonSpin Muon spin
type (mctr_type), public :: mctrData
integer, private, EXTERNAL :: BLOCAT
integer, private, EXTERNAL :: BDLEN
integer, private, EXTERNAL :: cdfuse
integer (kind=I4), public :: iMCMuonStop
integer (kind=I4), public :: iMCDecayStart
real (kind=R8), public, DIMENSION(3) :: MCDecayP
real (kind=R8), public :: MCDecayCos
real (kind=R8), public :: MCDecayR
real (kind=R8), public :: MCDecayZ
real (kind=R8), public :: MCtanTheta
logical, public :: mMCDecay
real (kind=R8), public :: mMCtanTheta
real (kind=R8), public :: mMCDecayR
real (kind=R8), public :: mMCDecayP
public function unpmc (print)
    logical, INTENT(in) :: print
    integer :: unpmc
             return value: 0=success, 1=failure
end function unpmc
public subroutine FillMCp_cos ()
    ! Calls: HF1
end subroutine FillMCp_cos
----------------------------------------------------------------------------
 Date created:  June 26, 2003
 Routine fills global structure for MC p and cos(theta) if event has single
 muon with a decay positron.  Variables filled:
 iMCMuonStop   - index into fMCTracks for stopping vertex of muon
 iMCDecayStart - index into fMCTracks for starting vertex of decay positron
                 iMCDecayStart = -1 indicates that decay was not found
 MCDecayP      - initial momentum of decay positron (MeV/c)
                 if iMCDecayStart > 0
 MCDecayCos    - initial cos(theta) of decay positron (MeV/c)
                 if iMCDecayStart > 0
 MCDecayR      - initial R of decay positron (cm)
----------------------------------------------------------------------------
Author: Jim Musser
private function unpMCEV () result (success)
    logical :: success
             return value
    ! Calls: kerror, xyz2uvz3
end function unpMCEV
private function unpMCTR () result (success)
    logical :: success
             return value
    ! Calls: kerror, xyz2uvz3
end function unpMCTR
private function unpMCT2 () result (success)
    logical :: success
             return value
    ! Calls: kerror, xyz2uvz3
end function unpMCT2
public subroutine UnpackMUSR ()
    ! Calls: kerror
end subroutine UnpackMUSR
public subroutine UnpMcBFLD ()
    ! Calls: kerror
end subroutine UnpMcBFLD
 UnpMcBFLD ( Blair, Mina Apr1,2005)
-------------------------------
 Unpack BFLD bank in geant files, to see what field setting
 was used there, and use as default in mofia unless overridden
 somehow.
public subroutine UnpMcCALF ()
    ! Calls: CheckCalFileName, kerror
end subroutine UnpMcCALF
 UnpMcCALF (Blair Aug 2002)
----------
 Unpacks the calibration files used in generating the
 geant run being analyzed.  This automatically sets the
 calibration files to use in the analysis.  If you want
 to override these files, use a USE statement.
private subroutine CheckCalFileName (calfilename, inam, inewlen)
    character (len=*), intent(inout) :: calfilename
    integer (kind=i4), intent(in) :: inam
    integer (kind=i4), intent(out) :: inewlen
    ! Calls: getenv
end subroutine CheckCalFileName
public subroutine UnpGeantSP ()
    ! Calls: PrintMcTracks, SortHitPos
end subroutine UnpGeantSP
 UnpGeantSP (Blair Jamieson May2001)
 ----------
 Gets data from ybos banks and creates and fills data structures for
 geant histories of space points.
 
 Data is stored in the structures MC_DCHitPos and MC_PCHitPos which are
 instances of HitPos_type
 If there is no such data available, then 
   MC_nDCHits = 0
   MC_nPCHits = 0
private function UnpMCSP () result (success)
    logical :: success
             return value
    ! Calls: kerror, xyz2uvz3
end function UnpMCSP
 UnpMCSP (Blair Jamieson May2001)
 ----------
 Gets data from ybos banks and creates and fills data structures for
 geant histories of space points.
 
 Data is stored in the structures MC_DCHitPos and MC_PCHitPos which are
 instances of HitPos_type
 If there is no such data available, then 
   MC_nDCHits = 0
   MC_nPCHits = 0
private function UnpMCS2 () result (success)
    logical :: success
    ! Calls: kerror, xyz2uvz3
end function UnpMCS2
private function UnpMCS3 () result (success)
    logical :: success
    ! Calls: kerror, xyz2uvz3
end function UnpMCS3
private subroutine SortHitPos (hits, nhits, order)
    type (HitPos_TYPE), INTENT(INOUT), dimension (:) :: hits
    integer (kind=I4), INTENT(IN) :: nhits
    integer (kind=I4), INTENT(IN) :: order
end subroutine SortHitPos
public subroutine PrintMcTracks ()
    ! Calls: PrintMcTrack
end subroutine PrintMcTracks
public subroutine PrintMcTrack (trk)
    type (mctrack_type), INTENT(in) :: trk
end subroutine PrintMcTrack