From 391288e3f0933efecfcbabb2efa33a01e524490a Mon Sep 17 00:00:00 2001
From: Cdaq Account <cdaq@cdaql1.jlab.org>
Date: Mon, 6 Mar 2017 08:50:37 -0500
Subject: [PATCH] Files for hodo calibration, updated HMS and SHMS hodo
 parameters  and new scripts for output reports Add scripts for hms and shms
 which output report files Updated cuts files to produce the test needs for
 the reports. Created TEMPLATE directory with templates for the reports
 Created CALIBRATION/hodo_calib directory for hodoscope calibration

---
 CALIBRATION/hodo_calib/.gitignore            |  10 +
 CALIBRATION/hodo_calib/Maketof               |   1 +
 CALIBRATION/hodo_calib/hmstofcal.inp         |   8 +
 CALIBRATION/hodo_calib/shmstofcal.inp        |   8 +
 CALIBRATION/hodo_calib/tofcal.f              | 475 +++++++++++++++++++
 CALIBRATION/hodo_calib/tofcal.inp            |   8 +
 DEF-files/HMS/GEN/hstackana_report_cuts.def  |  51 +-
 DEF-files/SHMS/GEN/pstackana_report.def      | 183 +++++++
 DEF-files/SHMS/GEN/pstackana_report_cuts.def | 189 ++++++++
 PARAM/HMS/GEN/htracking.param                |   9 +-
 PARAM/HMS/HODO/hhodo.param                   | 286 ++++++++---
 PARAM/HMS/HODO/htofcal.param                 |   2 +
 PARAM/SHMS/GEN/ptracking.param               |   7 +-
 PARAM/SHMS/HODO/phodo.param                  | 194 ++++++--
 PARAM/SHMS/HODO/phodo.pos                    |  40 +-
 PARAM/SHMS/HODO/ptofcal.param                |   2 +
 SCRIPTS/HMS/replay_hms_report.C              |   6 +-
 SCRIPTS/SHMS/replay_shms_report.C            | 124 +++++
 TEMPLATES/hstackana.template                 |  26 +-
 TEMPLATES/pstackana.template                 |  64 +++
 20 files changed, 1531 insertions(+), 162 deletions(-)
 create mode 100644 CALIBRATION/hodo_calib/.gitignore
 create mode 100755 CALIBRATION/hodo_calib/Maketof
 create mode 100644 CALIBRATION/hodo_calib/hmstofcal.inp
 create mode 100644 CALIBRATION/hodo_calib/shmstofcal.inp
 create mode 100644 CALIBRATION/hodo_calib/tofcal.f
 create mode 100644 CALIBRATION/hodo_calib/tofcal.inp
 create mode 100644 DEF-files/SHMS/GEN/pstackana_report.def
 create mode 100644 DEF-files/SHMS/GEN/pstackana_report_cuts.def
 create mode 100644 PARAM/HMS/HODO/htofcal.param
 create mode 100644 PARAM/SHMS/HODO/ptofcal.param
 create mode 100644 SCRIPTS/SHMS/replay_shms_report.C
 create mode 100644 TEMPLATES/pstackana.template

diff --git a/CALIBRATION/hodo_calib/.gitignore b/CALIBRATION/hodo_calib/.gitignore
new file mode 100644
index 00000000..40514c5f
--- /dev/null
+++ b/CALIBRATION/hodo_calib/.gitignore
@@ -0,0 +1,10 @@
+fort.15
+hmsfort.37
+hmstofcal.179
+shmsfort.37
+tofcal.adchist
+tofcal.out
+tofcal.param
+tofcal.parampass1
+tofcal.tdchist
+tofcal
diff --git a/CALIBRATION/hodo_calib/Maketof b/CALIBRATION/hodo_calib/Maketof
new file mode 100755
index 00000000..41260f4b
--- /dev/null
+++ b/CALIBRATION/hodo_calib/Maketof
@@ -0,0 +1 @@
+gfortran -W -ff2c -fbounds-check -fno-automatic  -fdefault-real-8  tofcal.f -L$CERN_ROOT/lib -lmathlib -lpacklib -lkernlib  -o tofcal
diff --git a/CALIBRATION/hodo_calib/hmstofcal.inp b/CALIBRATION/hodo_calib/hmstofcal.inp
new file mode 100644
index 00000000..325dbd14
--- /dev/null
+++ b/CALIBRATION/hodo_calib/hmstofcal.inp
@@ -0,0 +1,8 @@
+hmsfort.37
+hmstofcal.53411
+sostofcal.46765
+htmp
+hmstofcal
+
+
+
diff --git a/CALIBRATION/hodo_calib/shmstofcal.inp b/CALIBRATION/hodo_calib/shmstofcal.inp
new file mode 100644
index 00000000..bfb05b84
--- /dev/null
+++ b/CALIBRATION/hodo_calib/shmstofcal.inp
@@ -0,0 +1,8 @@
+shmsfort.37
+hmstofcal.53411
+sostofcal.46765
+htmp
+shmstofcal
+
+
+
diff --git a/CALIBRATION/hodo_calib/tofcal.f b/CALIBRATION/hodo_calib/tofcal.f
new file mode 100644
index 00000000..5fe197d5
--- /dev/null
+++ b/CALIBRATION/hodo_calib/tofcal.f
@@ -0,0 +1,475 @@
+      program tofcal
+! Fit TOF for Hall C HMS or SOS with the form for each PMT:
+! tcorr = time - offset - path * velocity - adccor / sqrt(ADC)
+! where offset, velocity, and adccor are parameters
+! April 10, 2005 P. Bosted
+! Input file: tofcal.inp should contain name of data file to be fit
+!             First xter of file name should be "h" for HMS data
+!             and "s" for SOS. 
+! To generate an input file, set xdumptof = 1 in xdebug.param in
+! the PARAM directory, where x=h for HMS, x=s for SOS
+! The HMS output will be in fort.37, and the SOS in fort.38
+! The output parameters will be in tofcal.param. Insert these
+! into the xhodo.param file that you are using. Make sure to 
+! erase the old values of sigma, or put the new ones after the
+! old ones, so that they get used properly
+! Normal values of invadc_offset are between -50 and 50,
+! normal values of invadc_velocity are between 12 and 17 (50 is
+! default if not enough data for the fit), and normal values of
+! shodo_pos_invadc_adc are 20 to 50. Normal values of the sigmas
+! are 0.3 to 0.8 nsec. 
+
+      implicit none
+      integer i,j,k,n,nparam,ipn,ipl,idt,idet(1000),nhit(200)
+      integer ip1(200),ip2(200),ip3(200),ifail,nhit0(200)
+      integer ipdet(600),iptyp(600),iwork(1000),k1,k2,k3,k4,k5,k6
+      real*8 tr(1000),p(1000),zc(1000),tc1(1000),p2(1000),hival,dtc
+      real*8 ax(1000,1000),bx(1000),sum1(200),sum2(200),sum3(200)
+      real*8 mean0(200),sig0(200),mean(200),sig(200),dt,adc(1000)
+      real*8 toff(200),vel(200),quad(200),chisq,df,ttol,adcmin(200)
+      real*8 avtime,ntime
+      integer thist(200,10),iloop,adchist(200,18),phist(200,18)
+      integer thistf(200,50),adchistf(200,50)
+      integer adchistpm(200,20,2)
+
+      character*80 string
+      character*40 filename
+
+      open(unit=7,file='tofcal.inp')
+      read(7,'(a)') filename
+      open(unit=8,file='tofcal.out')
+      open(unit=11,file='tofcal.parampass1')
+      open(unit=12,file='tofcal.param')
+      open(unit=13,file='tofcal.adchist')
+      write(13,'(1x,'' xv'',50f5.0)') (20.*(j-0.5),j=1,50)
+      open(unit=14,file='tofcal.tdchist')
+      write(14,'(1x,'' xv'',50f5.1)') (-5.0+0.2*(j-0.5),j=1,50)
+
+! first see how many hits per PMT: need at least 100 for fitting
+! also make ADC histograms
+      open(unit=9,file=filename,err=998)
+       if(filename(1:1).ne.'h'.and.filename(1:1).ne.'s') then
+        write(6,'(1x,''error, input file name '',
+     >   '' sould start with h or s'')')
+        goto 999
+       endif
+       write(*,*) ' filling adc histograms'
+       do i=1,10000000
+        n=0
+        do j=1,1000
+          read(9,'(a)',end=10) string
+          read(string,'(1x,i1)') k
+          if(k.eq.0) goto 9
+          n=n+1
+          read(string,'(1x,i1,2i3,5f10.3)') ipn,ipl,idt, 
+     >      tr(n),p(n),zc(n),tc1(n),adc(n)
+          k = min(18, max(1, int((adc(n)/20.)+1)))
+          idet(n) = 100*(ipn-1) + 20*(ipl-1) + idt
+          adchist(idet(n), k) = adchist(idet(n), k) + 1 
+          k = min(50, max(1, int((adc(n)/20.)+1)))
+          adchistf(idet(n), k) = adchistf(idet(n), k) + 1 
+          nhit0(idet(n)) = nhit0(idet(n)) + 1.
+        enddo
+ 9      continue
+      enddo
+
+! find more or less where threshold is
+ 10   do i=1,200
+        adcmin(i)=50.
+        if(nhit0(i).gt.0.) then
+          write(13,'(i3,50i4)') i,(min(999,adchistf(i,j)),j=1,50)
+          hival=0.
+          k=0
+          do j=1,17
+            if(adchist(i,j).gt.hival) then
+              hival = adchist(i,j)
+              k = j
+            endif
+          enddo
+c for test
+c         do n=1,max(1,k)
+c           if(adchist(i,n).lt.hival/20.) adcmin(i)=20.*(n-0.5)
+c         enddo
+c         write(13,'(1x,''adcmin='',f6.1)') adcmin(i) 
+        endif
+      enddo
+      close(unit=9)
+      do i=1,200
+        sum1(i)=0.
+        sum2(i)=0.
+        sum3(i)=0.
+      enddo
+
+! Do everything twice, 2nd time with tighter tolerance (ttol) on
+! time differences, based on first pass
+      ttol=20.0
+      do iloop=1,2
+         write(*,*) ' loop = ',iloop
+! Initialize the fitting arrays
+        do i=1,1000
+          if(i.le.200) nhit(i)=0
+          bx(i)=0.
+          do j=1,1000
+            ax(i,j)=0.
+          enddo
+        enddo
+
+! read in data
+      open(unit=9,file=filename)
+      nparam=0
+      chisq=0.
+      df=0.
+      do i=1,10000000
+        n=0
+        do j=1,1000
+          read(9,'(a)',end=12) string
+          read(string,'(1x,i1)') k
+          if(k.eq.0) goto 11
+          n=n+1
+          read(string,'(1x,i1,2i3,5f10.3)') ipn,ipl,idt, 
+     >      tr(n),p(n),zc(n),tc1(n),adc(n)
+! linearize the detector numbers
+          idet(n) = 100*(ipn-1) + 20*(ipl-1) + idt
+          if(idet(n).lt.1.or.idet(n).gt.200) write(6,'(1x,
+     >      ''error! '',4i4)') ipn,ipl,idt,idet(n)
+
+! correct raw times for zpos using betap
+          tr(n) = tr(n)- zc(n)
+
+! remember path**2 or sqrt(p) or adc
+          p(n) = min(200., max(0., p(n)))
+c          adc(n) = min(500, max(0., adc(n)))
+          p2(n) = 1./sqrt(max(20., adc(n)))
+          k = min(18, max(1, int(p(n)/7.)+1))
+          phist(idet(n), k) = phist(idet(n), k) + 1 
+! ignore hits from paddles that are rarely hit
+          if(nhit0(idet(n)).lt.100) n=n-1
+        enddo
+
+! Loop over all pairs, if at least 6
+ 11     if(n.ge.6) then
+! see if this is first time a detector is used
+          do j=1,n
+            nhit(idet(j))=nhit(idet(j))+1
+
+! If first time detector used, assign corresponding parameters
+! Note that detector had has a fixed time offset (ip1) of zero
+! since all times are relative)
+            if(nhit(idet(j)).eq.1) then
+              if(idet(j).eq.10) then
+                ip1(idet(j))=0
+              else
+
+! fixed time offsets
+                nparam=nparam+1
+                ip1(idet(j))=nparam
+                ipdet(nparam)=idet(j)
+                iptyp(nparam)=1
+              endif
+
+! linear term in path 
+              nparam=nparam+1
+              ip2(idet(j))=nparam
+              ipdet(nparam)=idet(j)
+              iptyp(nparam)=2
+
+! quadratic term for path**2
+              nparam=nparam+1
+              ip3(idet(j))=nparam
+              ipdet(nparam)=idet(j)
+              iptyp(nparam)=3
+              k=idet(j)
+              write(8,'(1x,i3,4i5)') k,nhit(k),ip1(k),ip2(k),ip3(k)
+            endif
+          enddo ! loop over n
+
+! now loop over all pairs in fill in the matrix
+! also accumulate sums to get means and sigmas for each detector
+! of original corrected times as read in from the file
+          do j=1,n-1
+            do k=j+1,n
+              dt = tc1(j)-tc1(k)
+              dtc = dt
+              if(iloop.eq.1.or.abs(dt).lt.ttol) then
+               idt = min(10,max(1,int((dt+5.))+1))
+               thist(idet(j),idt) = thist(idet(j),idt) + 1
+               chisq = chisq + dt**2
+               df = df + 1
+               sum1(idet(j)) = sum1(idet(j)) + 1.
+               sum2(idet(j)) = sum2(idet(j)) + dt
+               sum3(idet(j)) = sum3(idet(j)) + dt**2
+               dt = tc1(k)-tc1(j)
+               idt = min(10,max(1,int((dt+5.))+1))
+               thist(idet(k),idt) = thist(idet(k),idt) + 1
+               sum1(idet(k)) = sum1(idet(k)) + 1.
+               sum2(idet(k)) = sum2(idet(k)) + dt
+               sum3(idet(k)) = sum3(idet(k)) + dt**2
+              endif
+              k1 = idet(j)
+              k2 = idet(k)
+              dt = (tr(j) + toff(k1) + vel(k1)*p(j) + quad(k1)*p2(j))-
+     >             (tr(k) + toff(k2) + vel(k2)*p(k) + quad(k2)*p2(k))
+              if(iloop.eq.1.or.abs(dt).lt.ttol) then
+               k1=ip1(idet(j))
+               k2=ip1(idet(k))
+               k3=ip2(idet(j))
+               k4=ip2(idet(k))
+               k5=ip3(idet(j))
+               k6=ip3(idet(k))
+               if(k1.gt.0) then
+                bx(k1) = bx(k1) - (tr(j)-tr(k))
+                ax(k1,k1) = ax(k1,k1) + 1.
+                ax(k1,k3) = ax(k1,k3) + p(j)
+                ax(k1,k4) = ax(k1,k4) - p(k)
+                ax(k1,k5) = ax(k1,k5) + p2(j)
+                ax(k1,k6) = ax(k1,k6) - p2(k)
+                ax(k3,k1) = ax(k3,k1) + p(j)
+                ax(k4,k1) = ax(k4,k1) - p(k)
+                ax(k5,k1) = ax(k5,k1) + p2(j)
+                ax(k6,k1) = ax(k6,k1) - p2(k)
+               endif
+               if(k1.gt.0.and.k2.gt.0) then
+                ax(k1,k2) = ax(k1,k2) - 1.
+                ax(k2,k1) = ax(k2,k1) - 1.
+               endif
+               if(k2.gt.0) then
+                bx(k2) = bx(k2) + (tr(j)-tr(k))
+                ax(k2,k2) = ax(k2,k2) + 1.
+                ax(k2,k3) = ax(k2,k3) - p(j)
+                ax(k2,k4) = ax(k2,k4) + p(k)
+                ax(k2,k5) = ax(k2,k5) - p2(j)
+                ax(k2,k6) = ax(k2,k6) + p2(k)
+                ax(k3,k2) = ax(k3,k2) - p(j)    
+                ax(k4,k2) = ax(k4,k2) + p(k)    
+                ax(k5,k2) = ax(k5,k2) - p2(j)    
+                ax(k6,k2) = ax(k6,k2) + p2(k)    
+               endif
+               bx(k3) = bx(k3) - (tr(j)-tr(k)) * p(j)
+               bx(k4) = bx(k4) + (tr(j)-tr(k)) * p(k)
+               bx(k5) = bx(k5) - (tr(j)-tr(k)) * p2(j)
+               bx(k6) = bx(k6) + (tr(j)-tr(k)) * p2(k)
+               ax(k3,k3) = ax(k3,k3) + p(j)*p(j)
+               ax(k3,k4) = ax(k3,k4) - p(k)*p(j)
+               ax(k3,k5) = ax(k3,k5) + p2(j)*p(j)
+               ax(k3,k6) = ax(k3,k6) - p2(k)*p(j)
+               ax(k4,k3) = ax(k4,k3) - p(j)*p(k)
+               ax(k4,k4) = ax(k4,k4) + p(k)*p(k)
+               ax(k4,k5) = ax(k4,k5) - p2(j)*p(k)
+               ax(k4,k6) = ax(k4,k6) + p2(k)*p(k)
+               ax(k5,k3) = ax(k5,k3) + p(j)*p2(j)
+               ax(k5,k4) = ax(k5,k4) - p(k)*p2(j)
+               ax(k5,k5) = ax(k5,k5) + p2(j)*p2(j)
+               ax(k5,k6) = ax(k5,k6) - p2(k)*p2(j)
+               ax(k6,k3) = ax(k6,k3) - p(j)*p2(k)
+               ax(k6,k4) = ax(k6,k4) + p(k)*p2(k)
+               ax(k6,k5) = ax(k6,k5) - p2(j)*p2(k)
+               ax(k6,k6) = ax(k6,k6) + p2(k)*p2(k)
+              endif
+            enddo
+          enddo
+        endif ! if n>1
+      enddo ! loop over reading in data 
+ 12   close(unit=9)
+
+! Histograms
+      if(iloop.eq.1) then
+       do i=1,200
+        if(sum1(i).gt.0.) then
+          write(13,'(i3,18i4)') i,(phist(i,j),j=1,18)
+        endif
+       enddo
+      endif
+! see how many hits per detector and get mean, sigma of original corr. times
+      do i=1,200
+        if(sum1(i).gt.0.) then
+          mean0(i)=sum2(i)/sum1(i)
+          sig0(i)=sqrt(sum3(i)/sum1(i) - mean0(i)**2)
+        endif
+        write(8,'(1x,i3,i5,2f6.2,10i5)') i,nhit(i),
+     >    mean0(i),sig0(i),(min(9999,thist(i,j)),j=1,10)
+        sum1(i)=0.
+        sum2(i)=0.
+        sum3(i)=0.
+        do j=1,10
+          thist(i,j)=0
+        enddo
+      enddo
+      df = max(1., df - nparam)
+      write(6,'(1x,''initial chi2/d.f.='',f8.3,'' for '',f7.0,
+     >   '' deg. freedom'')') chisq/df,df
+      write(8,'(1x,''initial chi2/d.f.='',f8.3,'' for '',f7.0,
+     >   '' deg. freedom'')') chisq/df,df
+
+! find the solutions
+      call deqn (nparam,ax,1000,iwork,ifail,1,bx)
+      write(8,'(1x,''ifail='',i10)') ifail
+
+! association of parameters with detectors
+      do i=1,nparam
+        if(iptyp(i).eq.1) toff(ipdet(i))=bx(i)
+        if(iptyp(i).eq.2)  vel(ipdet(i))=bx(i)
+        if(iptyp(i).eq.3) quad(ipdet(i))=bx(i)
+      enddo
+
+! write solutions
+      write(10 + iloop,'(/''; use '',a,
+     >  ''tofusinginvadc=1 if want invadc_offset''/
+     >  '';  invadc_linear, and invadc_adc to be used''/
+     >            a,''tofusinginvadc=1'')') 
+     >  filename(1:1),filename(1:1)
+      write(10+iloop,'(/a,''hodo_pos_invadc_offset ='',3(f8.2,'',''),
+     >  f8.2)') filename(1:1),(-1.0*toff(i),i=1,80,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                        '',3(f8.2,'',''),
+     >  f8.2)')(-1.0*toff(i),i=j,79+j,20)
+      enddo
+
+      write(10+iloop,'(/a,''hodo_neg_invadc_offset ='',3(f8.2,'',''),
+     >  f8.2)')filename(1:1),(-1.0*toff(i),i=101,180,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                        '',3(f8.2,'',''),
+     >  f8.2)')(-1.0*toff(i),i=100+j,179+j,20)
+      enddo
+
+      write(10+iloop,'(/a,''hodo_pos_invadc_linear ='',3(f8.2,'',''),
+     >  f8.2)')filename(1:1),( -1./min(-1./15.,vel(i)),i=1,80,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                        '',3(f8.2,'',''),
+     >  f8.2)')(-1./min(-1./15.,vel(i)),i=j,79+j,20)
+      enddo
+
+      write(10+iloop,'(/a,''hodo_neg_invadc_linear ='',3(f8.2,'',''),
+     >  f8.2)')filename(1:1),( -1./min(-1./15.,vel(i)),i=101,180,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                        '',3(f8.2,'',''),
+     >  f8.2)')(-1./min(-1./15.,vel(i)),i=100+j,179+j,20)
+      enddo
+
+      write(10+iloop,'(/a,''hodo_pos_invadc_adc='',3(f9.2,'',''),
+     >  f9.2)')filename(1:1),(-1.*quad(i),i=1,80,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                   '',3(f9.2,'',''),
+     >  f9.2)')(-1.*quad(i),i=j,79+j,20)
+      enddo
+
+      write(10+iloop,'(/a,''hodo_neg_invadc_adc='',3(f9.2,'',''),
+     >  f9.2)')filename(1:1),(-1.0*quad(i),i=101,180,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                   '',3(f9.2,'',''),
+     >  f9.2)')(-1.*quad(i),i=100+j,179+j,20)
+      enddo
+
+
+! read in data again and look at sigmas relative to average fp time
+      chisq = 0.
+      df = 0.
+      open(unit=9,file=filename)
+      do i=1,10000000
+        n=0
+        do j=1,1000
+          read(9,'(a)',end=14) string
+          read(string,'(1x,i1)') k
+          if(k.eq.0) goto 13
+          n=n+1
+          read(string,'(1x,i1,2i3,5f10.3)') ipn,ipl,idt, 
+     >      tr(n),p(n),zc(n),tc1(n),adc(n)
+          idet(n) = 100*(ipn-1) + 20*(ipl-1) + idt
+          tr(n) = tr(n)- zc(n)
+          p(n) = min(200., max(0., p(n)))
+c          adc(n) = min(500, max(0., adc(n)))
+          p2(n) = 1./sqrt(max(20., adc(n)))
+! ignore hits from paddles that are rarely hit
+          k1 = idet(n)
+          dt = (tr(n) + toff(k1) + vel(k1)*p(n) + quad(k1)*p2(n))  
+          if(nhit0(idet(n)).lt.100) n=n-1
+        enddo
+! Loop over all pairs, if at least 6 hits
+ 13     if(n.ge.6) then
+          do j=1,n
+            avtime=0.
+            ntime=0.
+            do k=1,n
+             if(k.ne.j) then
+              k1 = idet(j)
+              k2 = idet(k)
+              dt = (tr(k) + toff(k2) + vel(k2)*p(k) + quad(k2)*p2(k))
+              avtime = avtime + dt
+              ntime = ntime + 1.
+             endif
+            enddo
+            avtime = avtime / ntime
+            dt = (tr(j) + toff(k1) + vel(k1)*p(j) + quad(k1)*p2(j))-
+     >             avtime
+            if(iloop.eq.2) then
+              idt = min(50,max(1,int((dt+ 5.)/0.2)+1))
+              thistf(idet(j),idt) = thistf(idet(j),idt) + 1
+              idt = max(1,min(20, int(adc(j)/50.)+1))
+              if(dt.gt.0.) adchistpm(idet(j),idt,1)=
+     >          adchistpm(idet(j),idt,1)+1
+              if(dt.le.0.) adchistpm(idet(j),idt,2)=
+     >          adchistpm(idet(j),idt,2)+1
+            endif
+            if(iloop.eq.1.or.abs(dt).lt.ttol) then
+              idt = min(10,max(1,int((dt+ 5.))+1))
+              thist(idet(j),idt) = thist(idet(j),idt) + 1
+              chisq = chisq + dt**2
+              df = df + 1
+              sum1(idet(j)) = sum1(idet(j)) + 1.
+              sum2(idet(j)) = sum2(idet(j)) + dt
+              sum3(idet(j)) = sum3(idet(j)) + dt**2
+            endif
+          enddo
+        endif ! if n>5
+      enddo ! loop over reading in data 
+ 14   close(unit=9)
+! see how many hits per detector and get mean, sigma of original corr. times
+      do i=1,200
+        sig(i)=100.
+        if(sum1(i).gt.0.) then
+          mean(i)=sum2(i)/sum1(i)
+          sig(i)=sqrt(sum3(i)/sum1(i) - mean(i)**2)
+        endif
+        write(8,'(1x,i3,i5,2f6.2,10i5)') i,nhit(i),
+     >    mean(i),sig(i),(min(9999,thist(i,j)),j=1,10)
+        if(iloop.eq.2)
+     >    write(14,'(1x,i3,50i5)') i,(min(9999,thistf(i,j)),j=1,50)
+        sum1(i)=0.
+        sum2(i)=0.
+        sum3(i)=0.
+        do j=1,10
+          thist(i,j)=0
+        enddo
+      enddo
+      df = max(1., df - nparam)
+      write(6,'(1x,''  final chi2/d.f.='',f8.3,'' for '',f7.0,
+     >   '' deg. freedom'')') chisq/df,df
+      write(8,'(1x,''  final chi2/d.f.='',f8.3,'' for '',f7.0,
+     >   '' deg. freedom'')') chisq/df,df
+
+      write(10+iloop,'(/a,''hodo_pos_sigma ='',3(f8.2,'',''),
+     >  f8.2)')filename(1:1),(sig(i),i=  1, 80,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                '',3(f8.2,'',''),
+     >  f8.2)')(sig(i),i=    j, 79+j,20)
+      enddo
+      write(10+iloop,'(/a,''hodo_neg_sigma ='',3(f8.2,'',''),
+     >  f8.2)')filename(1:1),(sig(i),i=101,180,20)
+      do j=2,16
+       write(10+iloop,'(1x,''                '',3(f8.2,'',''),
+     >  f8.2)')(sig(i),i=100+j,179+j,20)
+      enddo
+
+      enddo ! loop over time tolerance
+
+      do i=1,200
+        write(15,'(1x,i3,20i4)') i,(adchistpm(i,j,1),j=1,20)
+        write(15,'(1x,i3,20i4)') i,(adchistpm(i,j,2),j=1,20)
+      enddo
+
+      goto 999
+
+ 998  write(6,'(1x,''error, cant find file '',a)') filename
+
+ 999  stop
+      end
+
diff --git a/CALIBRATION/hodo_calib/tofcal.inp b/CALIBRATION/hodo_calib/tofcal.inp
new file mode 100644
index 00000000..bfb05b84
--- /dev/null
+++ b/CALIBRATION/hodo_calib/tofcal.inp
@@ -0,0 +1,8 @@
+shmsfort.37
+hmstofcal.53411
+sostofcal.46765
+htmp
+shmstofcal
+
+
+
diff --git a/DEF-files/HMS/GEN/hstackana_report_cuts.def b/DEF-files/HMS/GEN/hstackana_report_cuts.def
index 504305c2..dd003ff5 100644
--- a/DEF-files/HMS/GEN/hstackana_report_cuts.def
+++ b/DEF-files/HMS/GEN/hstackana_report_cuts.def
@@ -42,25 +42,6 @@ hmsDC2_1hit_v1                H.dc.2v1.nhit == 1
 hmsDC2_1hit_y2                H.dc.2y2.nhit == 1
 hmsDC2_1hit_x2                H.dc.2x2.nhit == 1
 
-hmsDC1Planes6hits   (H.dc.1x1.nhit+H.dc.1y1.nhit+H.dc.1u1.nhit+H.dc.1v1.nhit+H.dc.1x2.nhit+H.dc.1y2.nhit) ==6
-hmsDC2Planes6hits   (H.dc.2x1.nhit+H.dc.2y1.nhit+H.dc.2u1.nhit+H.dc.2v1.nhit+H.dc.2x2.nhit+H.dc.2y2.nhit )==6
-hmsDC1_5hits_x1     (H.dc.1y1.nhit+H.dc.1u1.nhit+H.dc.1v1.nhit+H.dc.1x2.nhit+H.dc.1y2.nhit)==5
-hmsDC1_5hits_y1     (H.dc.1x1.nhit+H.dc.1u1.nhit+H.dc.1v1.nhit+H.dc.1x2.nhit+H.dc.1y2.nhit)==5
-hmsDC1_5hits_u1     (H.dc.1x1.nhit+H.dc.1y1.nhit+H.dc.1v1.nhit+H.dc.1x2.nhit+H.dc.1y2.nhit)==5
-hmsDC1_5hits_v1     (H.dc.1x1.nhit+H.dc.1y1.nhit+H.dc.1u1.nhit+H.dc.1x2.nhit+H.dc.1y2.nhit)==5 
-hmsDC1_5hits_x2     (H.dc.1x1.nhit+H.dc.1y1.nhit+H.dc.1u1.nhit+H.dc.1v1.nhit+H.dc.1y2.nhit)==5
-hmsDC1_5hits_y2     (H.dc.1x1.nhit+H.dc.1y1.nhit+H.dc.1u1.nhit+H.dc.1v1.nhit+H.dc.1x2.nhit)==5
-
-hmsDC2_5hits_x1     (H.dc.2y1.nhit+H.dc.2u1.nhit+H.dc.2v1.nhit+H.dc.2x2.nhit+H.dc.2y2.nhit)==5
-hmsDC2_5hits_y1     (H.dc.2x1.nhit+H.dc.2u1.nhit+H.dc.2v1.nhit+H.dc.2x2.nhit+H.dc.2y2.nhit)==5
-hmsDC2_5hits_u1     (H.dc.2x1.nhit+H.dc.2y1.nhit+H.dc.2v1.nhit+H.dc.2x2.nhit+H.dc.2y2.nhit)==5
-hmsDC2_5hits_v1     (H.dc.2x1.nhit+H.dc.2y1.nhit+H.dc.2u1.nhit+H.dc.2x2.nhit+H.dc.2y2.nhit)==5 
-hmsDC2_5hits_x2     (H.dc.2x1.nhit+H.dc.2y1.nhit+H.dc.2u1.nhit+H.dc.2v1.nhit+H.dc.2y2.nhit)==5
-hmsDC2_5hits_y2     (H.dc.2x1.nhit+H.dc.2y1.nhit+H.dc.2u1.nhit+H.dc.2v1.nhit+H.dc.2x2.nhit)==5
-
-
-
-
 h1hit1                H.dc.1x1.nhit >= 1
 h1hit2                H.dc.1y1.nhit >= 1
 h1hit3                H.dc.1u1.nhit >= 1
@@ -74,6 +55,38 @@ h2hit3                H.dc.2u1.nhit >= 1
 h2hit4                H.dc.2v1.nhit >= 1
 h2hit5                H.dc.2y2.nhit >= 1
 h2hit6                H.dc.2x2.nhit >= 1
+
+hmsDC1Planes6hits   (H.dc.1x1.nhit+H.dc.1y1.nhit+H.dc.1u1.nhit+H.dc.1v1.nhit+H.dc.1x2.nhit+H.dc.1y2.nhit) ==6
+hmsDC2Planes6hits   (H.dc.2x1.nhit+H.dc.2y1.nhit+H.dc.2u1.nhit+H.dc.2v1.nhit+H.dc.2x2.nhit+H.dc.2y2.nhit )==6
+hmsDC1_5hits_x1     hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_6hits_x1     h1hit1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_5hits_y1     hmsDC1_1hit_x1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_6hits_y1     h1hit2&&hmsDC1_1hit_x1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_5hits_u1     hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_6hits_u1     h1hit3&&hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_5hits_v1     hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2 
+hmsDC1_6hits_v1     h1hit4&&hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_x2&&hmsDC1_1hit_y2
+hmsDC1_5hits_x2     hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_y2
+hmsDC1_6hits_x2     h1hit6&&hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_y2
+hmsDC1_5hits_y2     hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2
+hmsDC1_6hits_y2     h1hit5&&hmsDC1_1hit_x1&&hmsDC1_1hit_y1&&hmsDC1_1hit_u1&&hmsDC1_1hit_v1&&hmsDC1_1hit_x2
+
+hmsDC2_5hits_x1     hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_6hits_x1     h2hit1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_5hits_y1     hmsDC2_1hit_x1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_6hits_y1     h2hit2&&hmsDC2_1hit_x1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_5hits_u1     hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_6hits_u1     h2hit3&&hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_5hits_v1     hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2 
+hmsDC2_6hits_v1     h2hit4&&hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_x2&&hmsDC2_1hit_y2
+hmsDC2_5hits_x2     hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_y2
+hmsDC2_6hits_x2     h2hit6&&hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_y2
+hmsDC2_5hits_y2     hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2
+hmsDC2_6hits_y2     h2hit5&&hmsDC2_1hit_x1&&hmsDC2_1hit_y1&&hmsDC2_1hit_u1&&hmsDC2_1hit_v1&&hmsDC2_1hit_x2
+
+
+
+
 hms1HitsLt            H.dc.Ch1.nhit <= H.dc.Ch1.maxhits && g.evtyp==1
 hms2HitsLt            H.dc.Ch2.nhit <= H.dc.Ch2.maxhits && g.evtyp==1
 hmsHitsLt             H.dc.Ch1.nhit <= H.dc.Ch1.maxhits && H.dc.Ch2.nhit <= H.dc.Ch2.maxhits && g.evtyp==1
diff --git a/DEF-files/SHMS/GEN/pstackana_report.def b/DEF-files/SHMS/GEN/pstackana_report.def
new file mode 100644
index 00000000..6d9be51d
--- /dev/null
+++ b/DEF-files/SHMS/GEN/pstackana_report.def
@@ -0,0 +1,183 @@
+# See $ANALYZER/examples/output_example.def for examples
+#
+block T.shms.*
+block P.ngcer.*
+block P.dc.*
+block P.tr.*
+block P.hod.*
+block P.hgcer.*
+block P.aero.*
+block P.cal.*
+block P.gtr.*
+
+# Noble Gas Cherenkov
+TH1F pngcer_occu 'SHMS Noble Gas Cherenkov Occupancy; Counter Number; Number of Entries' P.ngcer.adcCounter 4 0.5 4.5
+TH2F pngcer_ped_vs_cntr 'SHMS Noble Gas Cherenkov Pulse Pedestal vs. Counter Number; Counter Number;  Pulse Pedestal / 1 ADC Unit' P.ngcer.adcCounter P.ngcer.adcPed 4 0.5 4.5 1000 0 1000
+TH2F pngcer_pi_vs_cntr 'SHMS Noble Gas Cherenkov Pulse Integral vs. Counter Number; Counter Number;  Pulse Integral / 10 ADC Units' P.ngcer.adcCounter P.ngcer.adcPulseInt 4 0.5 4.5 4000 0 40000
+TH2F pngcer_amp_vs_cntr 'SHMS Noble Gas Cherenkov Pulse Amplitude vs. Counter Number; Counter Number;  Pulse Amplitude / 1 ADC Unit' P.ngcer.adcCounter P.ngcer.adcPulseAmp 4 0.5 4.5 4100 0 4100
+
+# Drift Chambers
+TH1F pdc_ref1  'SHMS DC Reference Time Slot 6 Channel 79; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF1_tdcTime  200 12000 14000
+TH1F pdc_ref2  'SHMS DC Reference Time Slot 7 Channel 79; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF2_tdcTime  200 12000 14000
+TH1F pdc_ref3  'SHMS DC Reference Time Slot 8 Channel 79; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF3_tdcTime  200 12000 14000
+TH1F pdc_ref4  'SHMS DC Reference Time Slot 9 Channel 79; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF4_tdcTime  200 12000 14000
+TH1F pdc_ref5  'SHMS DC Reference Time Slot 10 Channel 79; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF5_tdcTime  200 12000 14000
+TH1F pdc_ref6  'SHMS DC Reference Time Slot 11 Channel 47; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF6_tdcTime  200 12000 14000
+TH1F pdc_ref7  'SHMS DC Reference Time Slot 12 Channel 47; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF7_tdcTime  200 12000 14000
+TH1F pdc_ref8  'SHMS DC Reference Time Slot 13 Channel 47; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF8_tdcTime  200 12000 14000
+TH1F pdc_ref9  'SHMS DC Reference Time Slot 14 Channel 15; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF9_tdcTime  200 12000 14000
+TH1F pdc_ref10 'SHMS DC Reference Time Slot 15 Channel 47; Raw TDC Time (TDC Clicks); Counts / 10 TDC Clicks;' T.shms.pDCREF10_tdcTime 200 12000 14000
+
+TH1F pdc1u1_wirenum 'SHMS DC 1U1 Wiremap; Wire Number; Number of Entries' P.dc.1u1.wirenum 107 0.5 107.5
+TH1F pdc1u2_wirenum 'SHMS DC 1U2 Wiremap; Wire Number; Number of Entries' P.dc.1u2.wirenum 107 0.5 107.5
+TH1F pdc1x1_wirenum 'SHMS DC 1X1 Wiremap; Wire Number; Number of Entries' P.dc.1x1.wirenum  79 0.5  79.5
+TH1F pdc1x2_wirenum 'SHMS DC 1X2 Wiremap; Wire Number; Number of Entries' P.dc.1x2.wirenum  79 0.5  79.5
+TH1F pdc1v1_wirenum 'SHMS DC 1V1 Wiremap; Wire Number; Number of Entries' P.dc.1v1.wirenum 107 0.5 107.5
+TH1F pdc1v2_wirenum 'SHMS DC 1V2 Wiremap; Wire Number; Number of Entries' P.dc.1v2.wirenum 107 0.5 107.5
+
+TH1F pdc2v2_wirenum 'SHMS DC 2V2 Wiremap; Wire Number; Number of Entries' P.dc.2v2.wirenum 107 0.5 107.5
+TH1F pdc2v1_wirenum 'SHMS DC 2V1 Wiremap; Wire Number; Number of Entries' P.dc.2v1.wirenum 107 0.5 107.5
+TH1F pdc2x2_wirenum 'SHMS DC 2X2 Wiremap; Wire Number; Number of Entries' P.dc.2x2.wirenum  79 0.5  79.5
+TH1F pdc2x1_wirenum 'SHMS DC 2X1 Wiremap; Wire Number; Number of Entries' P.dc.2x1.wirenum  79 0.5  79.5
+TH1F pdc2u2_wirenum 'SHMS DC 2U2 Wiremap; Wire Number; Number of Entries' P.dc.2u2.wirenum 107 0.5 107.5
+TH1F pdc2u1_wirenum 'SHMS DC 2U1 Wiremap; Wire Number; Number of Entries' P.dc.2u1.wirenum 107 0.5 107.5
+
+TH2F pdc1u1_wirenum_vs_tdc 'SHMS DC 1U1 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.1u1.wirenum P.dc.1u1.time 107 0.5 107.5 500 0 500
+TH2F pdc1u2_wirenum_vs_tdc 'SHMS DC 1U2 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.1u2.wirenum P.dc.1u2.time 107 0.5 107.5 500 0 500
+TH2F pdc1x1_wirenum_vs_tdc 'SHMS DC 1X1 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.1x1.wirenum P.dc.1x1.time  79 0.5  79.5 500 0 500
+TH2F pdc1x2_wirenum_vs_tdc 'SHMS DC 1X2 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.1x2.wirenum P.dc.1x2.time  79 0.5  79.5 500 0 500
+TH2F pdc1v1_wirenum_vs_tdc 'SHMS DC 1V1 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.1v1.wirenum P.dc.1v1.time 107 0.5 107.5 500 0 500
+TH2F pdc1v2_wirenum_vs_tdc 'SHMS DC 1V2 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.1v2.wirenum P.dc.1v2.time 107 0.5 107.5 500 0 500
+
+TH2F pdc2v2_wirenum_vs_tdc 'SHMS DC 2V2 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.2v2.wirenum P.dc.2v2.time 107 0.5 107.5 500 0 500
+TH2F pdc2v1_wirenum_vs_tdc 'SHMS DC 2V1 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.2v1.wirenum P.dc.2v1.time 107 0.5 107.5 500 0 500
+TH2F pdc2x2_wirenum_vs_tdc 'SHMS DC 2X2 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.2x2.wirenum P.dc.2x2.time  79 0.5  79.5 500 0 500
+TH2F pdc2x1_wirenum_vs_tdc 'SHMS DC 2X1 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.2x1.wirenum P.dc.2x1.time  79 0.5  79.5 500 0 500
+TH2F pdc2u2_wirenum_vs_tdc 'SHMS DC 2U2 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.2u2.wirenum P.dc.2u2.time 107 0.5 107.5 500 0 500
+TH2F pdc2u1_wirenum_vs_tdc 'SHMS DC 2U1 Wire Number vs. TDC; Wire Number; TDC Time (ns) / 1 ns' P.dc.2u1.wirenum P.dc.2u1.time 107 0.5 107.5 500 0 500
+
+TH2F pdc1u1_wirenum_vs_resid 'SHMS 1U1 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.1u1.wirenum P.dc.residual[0] 107 0.5 107.5 200 -1.0 1.0
+TH2F pdc1u2_wirenum_vs_resid 'SHMS 1U2 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.1u2.wirenum P.dc.residual[1] 107 0.5 107.5 200 -1.0 1.0
+TH2F pdc1x1_wirenum_vs_resid 'SHMS 1X1 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.1x1.wirenum P.dc.residual[2] 79 0.5  79.5 200 -1.0 1.0
+TH2F pdc1x2_wirenum_vs_resid 'SHMS 1X2 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.1x2.wirenum P.dc.residual[3] 79 0.5  79.5 200 -1.0 1.0
+TH2F pdc1v1_wirenum_vs_resid 'SHMS 1V1 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.1v1.wirenum P.dc.residual[4] 107 0.5 107.5 200 -1.0 1.0
+TH2F pdc1v2_wirenum_vs_resid 'SHMS 1V2 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.1v2.wirenum P.dc.residual[5] 107 0.5 107.5 200 -1.0 1.0
+
+TH2F pdc2v2_wirenum_vs_resid 'SHMS 2V2 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.2v2.wirenum P.dc.residual[6] 107 0.5 107.5 200 -1.0 1.0
+TH2F pdc2v1_wirenum_vs_resid 'SHMS 2V1 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.2v1.wirenum P.dc.residual[7] 107 0.5 107.5 200 -1.0 1.0
+TH2F pdc2x2_wirenum_vs_resid 'SHMS 2X2 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.2x2.wirenum P.dc.residual[8] 79 0.5  79.5 200 -1.0 1.0
+TH2F pdc2x1_wirenum_vs_resid 'SHMS 2X1 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.2x1.wirenum P.dc.residual[9] 79 0.5  79.5 200 -1.0 1.0
+TH2F pdc2u2_wirenum_vs_resid 'SHMS 2U2 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.2u2.wirenum P.dc.residual[10] 107 0.5 107.5 200 -1.0 1.0
+TH2F pdc2u1_wirenum_vs_resid 'SHMS 2U1 DC Wire Number vs. Residuals; Wire Number; Residuals (mm)' P.dc.2u1.wirenum P.dc.residual[11] 107 0.5 107.5 200 -1.0 1.0
+
+TH2F pdc_xfp_vs_yxp 'SHMS DC Xfp vs Yxp; Yfp (cm) / 1 cm; Xfp (cm) / 1 cm' P.dc.y P.dc.x 100 -50 50 100 -50 50
+TH2F pdc_xfpp_vs_yxpp 'SHMS DC Xfpp vs Yxpp; Yfpp; Xfpp' P.dc.yp P.dc.xp 100 -1 1 100 -1 1
+
+# Hodoscopes (Positive/Left) 
+TH1F phodo_1x_pos_adc_occu 'SHMS Hodoscope 1X+ ADC Occupancy; Paddle Number; Number of Hits' P.hod.1x.posAdcCounter 13 0.5 13.5
+TH1F phodo_1y_pos_adc_occu 'SHMS Hodoscope 1Y+ ADC Occupancy; Paddle Number; Number of Hits' P.hod.1y.posAdcCounter 13 0.5 13.5 
+TH1F phodo_2x_pos_adc_occu 'SHMS Hodoscope 2X+ ADC Occupancy; Paddle Number; Number of Hits' P.hod.2x.posAdcCounter 14 0.5 14.5
+TH1F phodo_2y_pos_adc_occu 'SHMS Hodoscope 2Y+ ADC Occupancy; Paddle Number; Number of Hits' P.hod.2y.posAdcCounter 21 0.5 21.5
+TH1F phodo_1x_pos_tdc_occu 'SHMS Hodoscope 1X+ TDC Occupancy; Paddle Number; Number of Hits' P.hod.1x.posTdcCounter 13 0.5 13.5
+TH1F phodo_1y_pos_tdc_occu 'SHMS Hodoscope 1Y+ TDC Occupancy; Paddle Number; Number of Hits' P.hod.1y.posTdcCounter 13 0.5 13.5 
+TH1F phodo_2x_pos_tdc_occu 'SHMS Hodoscope 2X+ TDC Occupancy; Paddle Number; Number of Hits' P.hod.2x.posTdcCounter 14 0.5 14.5
+TH1F phodo_2y_pos_tdc_occu 'SHMS Hodoscope 2Y+ TDC Occupancy; Paddle Number; Number of Hits' P.hod.2y.posTdcCounter 21 0.5 21.5
+TH2F phodo_1x_pos_ped_vs_pad 'SHMS Hodoscope 1X+ Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.1x.posAdcCounter  P.hod.1x.posAdcPed 13 0.5 13.5 1000 0 1000
+TH2F phodo_1y_pos_ped_vs_pad 'SHMS Hodoscope 1Y+ Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.1y.posAdcCounter  P.hod.1y.posAdcPed 13 0.5 13.5 1000 0 1000
+TH2F phodo_2x_pos_ped_vs_pad 'SHMS Hodoscope 2X+ Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.2x.posAdcCounter  P.hod.2x.posAdcPed 14 0.5 14.5 1000 0 1000
+TH2F phodo_2y_pos_ped_vs_pad 'SHMS Hodoscope 2Y+ Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.2y.posAdcCounter  P.hod.2y.posAdcPed 21 0.5 21.5 1000 0 1000
+TH2F phodo_1x_pos_pi_vs_pad 'SHMS Hodoscope 1X+ Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.1x.GoodPaddle  P.hod.1x.GoodPosAdcPulseInt 13 0.5 13.5 4000 0 40000
+TH2F phodo_1y_pos_pi_vs_pad 'SHMS Hodoscope 1Y+ Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.1y.GoodPaddle  P.hod.1y.GoodPosAdcPulseInt 13 0.5 13.5 4000 0 40000
+TH2F phodo_2x_pos_pi_vs_pad 'SHMS Hodoscope 2X+ Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.2x.GoodPaddle  P.hod.2x.GoodPosAdcPulseInt 14 0.5 14.5 4000 0 40000
+TH2F phodo_2y_pos_pi_vs_pad 'SHMS Hodoscope 2Y+ Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.2y.GoodPaddle  P.hod.2y.GoodPosAdcPulseInt 21 0.5 21.5 4000 0 40000
+TH2F phodo_1x_pos_pamp_vs_pad 'SHMS Hodoscope 1X+ Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.1x.GoodPaddle  P.hod.1x.GoodPosAdcPulseAmp 13 0.5 13.5 4100 0 4100
+TH2F phodo_1y_pos_pamp_vs_pad 'SHMS Hodoscope 1Y+ Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.1y.GoodPaddle  P.hod.1y.GoodPosAdcPulseAmp 13 0.5 13.5 4100 0 4100
+TH2F phodo_2x_pos_pamp_vs_pad 'SHMS Hodoscope 2X+ Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.2x.GoodPaddle  P.hod.2x.GoodPosAdcPulseAmp 14 0.5 14.5 4100 0 4100
+TH2F phodo_2y_pos_pamp_vs_pad 'SHMS Hodoscope 2Y+ Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.2y.GoodPaddle  P.hod.2y.GoodPosAdcPulseAmp 21 0.5 21.5 4100 0 4100
+TH2F phodo_1x_pos_tdc_time_vs_pad 'SHMS Hodoscope 1X+ TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.1x.GoodPaddle  P.hod.1x.GoodPosTdcChan 13 0.5 13.5 3500 -500 3000
+TH2F phodo_1y_pos_tdc_time_vs_pad 'SHMS Hodoscope 1Y+ TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.1y.GoodPaddle  P.hod.1y.GoodPosTdcChan 13 0.5 13.5 3500 -500 3000
+TH2F phodo_2x_pos_tdc_time_vs_pad 'SHMS Hodoscope 2X+ TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.2x.GoodPaddle  P.hod.2x.GoodPosTdcChan 14 0.5 14.5 3500 -500 3000
+TH2F phodo_2y_pos_tdc_time_vs_pad 'SHMS Hodoscope 2Y+ TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.2y.GoodPaddle  P.hod.2y.GoodPosTdcChan 21 0.5 21.5 3500 -500 3000
+
+# Hodoscopes (Negative/Right)
+TH1F phodo_1x_neg_adc_occu 'SHMS Hodoscope 1X- ADC Occupancy; Paddle Number; Number of Hits' P.hod.1x.negAdcCounter 13 0.5 13.5
+TH1F phodo_1y_neg_adc_occu 'SHMS Hodoscope 1Y- ADC Occupancy; Paddle Number; Number of Hits' P.hod.1y.negAdcCounter 13 0.5 13.5 
+TH1F phodo_2x_neg_adc_occu 'SHMS Hodoscope 2X- ADC Occupancy; Paddle Number; Number of Hits' P.hod.2x.negAdcCounter 14 0.5 14.5
+TH1F phodo_2y_neg_adc_occu 'SHMS Hodoscope 2Y- ADC Occupancy; Paddle Number; Number of Hits' P.hod.2y.negAdcCounter 21 0.5 21.5
+TH1F phodo_1x_neg_tdc_occu 'SHMS Hodoscope 1X- TDC Occupancy; Paddle Number; Number of Hits' P.hod.1x.negTdcCounter 13 0.5 13.5
+TH1F phodo_1y_neg_tdc_occu 'SHMS Hodoscope 1Y- TDC Occupancy; Paddle Number; Number of Hits' P.hod.1y.negTdcCounter 13 0.5 13.5 
+TH1F phodo_2x_neg_tdc_occu 'SHMS Hodoscope 2X- TDC Occupancy; Paddle Number; Number of Hits' P.hod.2x.negTdcCounter 14 0.5 14.5
+TH1F phodo_2y_neg_tdc_occu 'SHMS Hodoscope 2Y- TDC Occupancy; Paddle Number; Number of Hits' P.hod.2y.negTdcCounter 21 0.5 21.5
+TH2F phodo_1x_neg_ped_vs_pad 'SHMS Hodoscope 1X- Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.1x.negAdcCounter  P.hod.1x.negAdcPed 13 0.5 13.5 1000 0 1000
+TH2F phodo_1y_neg_ped_vs_pad 'SHMS Hodoscope 1Y- Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.1y.negAdcCounter  P.hod.1y.negAdcPed 13 0.5 13.5 1000 0 1000
+TH2F phodo_2x_neg_ped_vs_pad 'SHMS Hodoscope 2X- Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.2x.negAdcCounter  P.hod.2x.negAdcPed 14 0.5 14.5 1000 0 1000
+TH2F phodo_2y_neg_ped_vs_pad 'SHMS Hodoscope 2Y- Pulse Pedestal vs. Paddle Number; Paddle Number; Pulse Pedestal / 1 ADC Unit' P.hod.2y.negAdcCounter  P.hod.2y.negAdcPed 21 0.5 21.5 1000 0 1000
+TH2F phodo_1x_neg_pi_vs_pad 'SHMS Hodoscope 1X- Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.1x.GoodPaddle  P.hod.1x.GoodNegAdcPulseInt 13 0.5 13.5 4000 0 40000
+TH2F phodo_1y_neg_pi_vs_pad 'SHMS Hodoscope 1Y- Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.1y.GoodPaddle  P.hod.1y.GoodNegAdcPulseInt 13 0.5 13.5 4000 0 40000
+TH2F phodo_2x_neg_pi_vs_pad 'SHMS Hodoscope 2X- Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.2x.GoodPaddle  P.hod.2x.GoodNegAdcPulseInt 14 0.5 14.5 4000 0 40000
+TH2F phodo_2y_neg_pi_vs_pad 'SHMS Hodoscope 2Y- Pulse Integral vs. Paddle Number; Paddle Number; Pulse Integral / 10 ADC Units' P.hod.2y.GoodPaddle  P.hod.2y.GoodNegAdcPulseInt 21 0.5 21.5 4000 0 40000
+TH2F phodo_1x_neg_pamp_vs_pad 'SHMS Hodoscope 1X- Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.1x.GoodPaddle  P.hod.1x.GoodNegAdcPulseAmp 13 0.5 13.5 4100 0 4100
+TH2F phodo_1y_neg_pamp_vs_pad 'SHMS Hodoscope 1Y- Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.1y.GoodPaddle  P.hod.1y.GoodNegAdcPulseAmp 13 0.5 13.5 4100 0 4100
+TH2F phodo_2x_neg_pamp_vs_pad 'SHMS Hodoscope 2X- Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.2x.GoodPaddle  P.hod.2x.GoodNegAdcPulseAmp 14 0.5 14.5 4100 0 4100
+TH2F phodo_2y_neg_pamp_vs_pad 'SHMS Hodoscope 2Y- Pulse Amplitude vs. Paddle Number; Paddle Number; Pulse Amplitude / 1 ADC Unit' P.hod.2y.GoodPaddle  P.hod.2y.GoodNegAdcPulseAmp 21 0.5 21.5 4100 0 4100
+TH2F phodo_1x_neg_tdc_time_vs_pad 'SHMS Hodoscope 1X- TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.1x.GoodPaddle  P.hod.1x.GoodNegTdcChan 13 0.5 13.5 3500 -500 3000
+TH2F phodo_1y_neg_tdc_time_vs_pad 'SHMS Hodoscope 1Y- TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.1y.GoodPaddle  P.hod.1y.GoodNegTdcChan 13 0.5 13.5 3500 -500 3000
+TH2F phodo_2x_neg_tdc_time_vs_pad 'SHMS Hodoscope 2X- TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.2x.GoodPaddle  P.hod.2x.GoodNegTdcChan 14 0.5 14.5 3500 -500 3000
+TH2F phodo_2y_neg_tdc_time_vs_pad 'SHMS Hodoscope 2Y- TDC Time vs. Paddle Number; Paddle Number; TDC Time (ns) / 1 ns' P.hod.2y.GoodPaddle  P.hod.2y.GoodNegTdcChan 21 0.5 21.5 3500 -500 3000
+
+# Heavy Gas Cherenkov
+TH1F phgcer_occu 'SHMS Heavy Gas Cherenkov Occupancy; Counter Number; Number of Entries' P.hgcer.adcCounter 4 0.5 4.5
+TH2F phgcer_ped_vs_cntr 'SHMS Heavy Gas Cherenkov Pulse Pedestal vs. Counter Number; Counter Number;  Pulse Pedestal / 1 ADC Unit' P.hgcer.adcCounter P.hgcer.adcPed 4 0.5 4.5 1000 0 10000
+TH2F phgcer_pi_vs_cntr 'SHMS Heavy Gas Cherenkov Pulse Integral vs. Counter Number; Counter Number;  Pulse Integral / 10 ADC Units' P.hgcer.adcCounter P.hgcer.adcPulseInt 4 0.5 4.5 4000 0 40000
+TH2F phgcer_amp_vs_cntr 'SHMS Heavy Gas Cherenkov Pulse Amplitude vs. Counter Number; Counter Number;  Pulse Amplitude / 1 ADC Unit' P.hgcer.adcCounter P.hgcer.adcPulseAmp 4 0.5 4.5 4100 0 4100
+
+# Aerogel
+TH1F paero_pos_occu 'SHMS Aero+ Occupancy; Counter Number; Number of Entries' P.aero.posAdcCounter 7 0.5 7.5
+TH2F paero_pos_ped_vs_cntr 'SHMS Aero+ Pulse Pedestal vs. Counter Number; Counter Number;  Pulse Pedestal / 1 ADC Unit' P.aero.posAdcCounter P.aero.posAdcPed 7 0.5 7.5 1000 0 1000
+TH2F paero_pos_pi_vs_cntr 'SHMS Aero+ Pulse Integral vs. Counter Number; Counter Number;  Pulse Integral / 10 ADC Units' P.aero.posAdcCounter P.aero.posAdcPulseInt 7 0.5 7.5 4000 0 40000
+TH2F paero_pos_amp_vs_cntr 'SHMS Aero+ Pulse Amplitude vs. Counter Number; Counter Number;  Pulse Amplitude / 1 ADC Unit' P.aero.posAdcCounter P.aero.posAdcPulseAmp 7 0.5 7.5 4100 0 4100
+TH1F paero_neg_occu 'SHMS Aero- Occupancy; Counter Number; Number of Entries' P.aero.negAdcCounter 7 0.5 7.5
+TH2F paero_neg_ped_vs_cntr 'SHMS Aero- Pulse Pedestal vs. Counter Number; Counter Number;  Pulse Pedestal / 1 ADC Unit' P.aero.negAdcCounter P.aero.negAdcPed 7 0.5 7.5 1000 0 1000
+TH2F paero_neg_pi_vs_cntr 'SHMS Aero- Pulse Integral vs. Counter Number; Counter Number;  Pulse Integral / 10 ADC Units' P.aero.negAdcCounter P.aero.negAdcPulseInt 7 0.5 7.5 4000 0 40000
+TH2F paero_neg_amp_vs_cntr 'SHMS Aero- Pulse Amplitude vs. Counter Number; Counter Number;  Pulse Amplitude / 1 ADC Unit' P.aero.negAdcCounter P.aero.negAdcPulseAmp 7 0.5 7.5 4100 0 4100
+
+# Pre-Shower Calorimeter
+TH1F pcal_prshwr_pos_occu 'SHMS Preshower+ Occupancy; Block Number; Number of Entries' P.cal.pr.posAdcCounter 14 0.5 14.5
+TH2F pcal_prshwr_pos_ped_blk 'SHMS Preshower+ Pulse Pedestal vs. Block Number; Block Number; Pulse Pedestal / 1 ADC Unit' P.cal.pr.posAdcCounter P.cal.pr.posAdcPed 14 0.5 14.5 1000 0 1000
+TH2F pcal_prshwr_pos_pi_blk 'SHMS Preshower+ Pulse Integral vs. Block Number; Block Number; Pulse Integral / 10 ADC Units' P.cal.pr.posAdcCounter P.cal.pr.posAdcPulseInt 14 0.5 14.5 4000 0 40000
+TH2F pcal_prshwr_pos_amp_blk 'SHMS Preshower+ Pulse Amplitude vs. Block Number; Block Number; Pulse Amplitude / 1 ADC Unit' P.cal.pr.posAdcCounter P.cal.pr.posAdcPulseAmp 14 0.5 14.5 4100 0 4100
+TH1F pcal_prshwr_neg_occu 'SHMS Preshower- Occupancy; Block Number; Number of Entries' P.cal.pr.negAdcCounter 14 0.5 14.5
+TH2F pcal_prshwr_neg_ped_blk 'SHMS Preshower- Pulse Pedestal vs. Block Number; Block Number; Pulse Pedestal / 1 ADC Unit' P.cal.pr.negAdcCounter P.cal.pr.negAdcPed 14 0.5 14.5 1000 0 1000
+TH2F pcal_prshwr_neg_pi_blk 'SHMS Preshower- Pulse Integral vs. Block Number; Block Number; Pulse Integral / 10 ADC Units' P.cal.pr.negAdcCounter P.cal.pr.negAdcPulseInt 14 0.5 14.5 4000 0 40000
+TH2F pcal_prshwr_neg_amp_blk 'SHMS Preshower- Pulse Amplitude vs. Block Number; Block Number; Pulse Amplitude / 1 ADC Unit' P.cal.pr.negAdcCounter P.cal.pr.negAdcPulseAmp 14 0.5 14.5 4100 0 4100 
+
+# Shower Calorimeter
+TH1F pcal_shwr_occu 'SHMS Shower Occupancy; Block Number; Number of Entries' P.cal.fly.adcCounter 224 0.5 224.5
+TH2F pcal_shwr_ped_blk 'SHMS Shower Pulse Pedestal vs. Block Number; Block Number; Pulse Pedestal / 1 ADC Unit' P.cal.fly.adcCounter P.cal.fly.adcPed 224 0.5 224.5 1000 0 1000
+TH2F pcal_shwr_pi_blk 'SHMS Shower Pulse Integral vs. Block Number; Block Number; Pulse Integral / 10 ADC Units' P.cal.fly.adcCounter P.cal.fly.adcPulseInt 224 0.5 224.5 4000 0 40000
+TH2F pcal_shwr_amp_blk 'SHMS Shower Pulse Amplitude vs. Block Number; Block Number; Pulse Amplitude / 1 ADC Unit' P.cal.fly.adcCounter P.cal.fly.adcPulseAmp 224 0.5 224.5 4100 0 4100 
+
+# Trigger Apparatus
+TH1F ptrig_pngc_sum_pped 'SHMS Noble Gas Sum FADC Pulse Pedestal; Pulse Pedestal; Number of Entries / 1 ADC Units' T.shms.pNGCSUM_adcPed 2000 0 2000
+TH1F ptrig_pngc_sum_pint 'SHMS Noble Gas Sum FADC Pulse Integral; Pulse Integral; Number of Entries / 10 ADC Units' T.shms.pNGCSUM_adcPulseInt 4000 0 40000
+TH1F ptrig_pngc_sum_pamp 'SHMS Noble Gas Sum FADC Pulse Amplitude; Pulse Amplitude; Number of Entries / 1 ADC Units' T.shms.pNGCSUM_adcPulseAmp 4100 0 4100
+TH1F ptrig_pngc_sum_ptime 'SHMS Noble Gas Sum FADC Pulse Time; Pulse Time; Number of Entries / 10 ADC Units' T.shms.pNGCSUM_adcPulseTimeRaw 1000 0 10000
+TH1F ptrig_pngc_sum_tdc 'SHMS Noble Gas Sum TDC Time; TDC Time; Number of Entries / 10 TDC Units' T.shms.pNGCSUM_tdcTime 700 -3500 3500
+
+TH1F ptrig_phgc_sum_pped 'SHMS Heavy Gas Sum FADC Pulse Pedestal; Pulse Pedestal; Number of Entries / 1 ADC Units' T.shms.pHGCSUM_adcPed 2000 0 2000
+TH1F ptrig_phgc_sum_pint 'SHMS Heavy Gas Sum FADC Pulse Integral; Pulse Integral; Number of Entries / 10 ADC Units' T.shms.pHGCSUM_adcPulseInt 4000 0 40000
+TH1F ptrig_phgc_sum_pamp 'SHMS Heavy Gas Sum FADC Pulse Amplitude; Pulse Amplitude; Number of Entries / 1 ADC Units' T.shms.pHGCSUM_adcPulseAmp 4100 0 4100
+TH1F ptrig_phgc_sum_ptime 'SHMS Heavy Gas Sum FADC Pulse Time; Pulse Time; Number of Entries / 10 ADC Units' T.shms.pHGCSUM_adcPulseTimeRaw 1000 0 10000
+TH1F ptrig_phgc_sum_tdc 'SHMS Heavy Gas Sum TDC Time; TDC Time; Number of Entries / 10 TDC Units' T.shms.pHGCSUM_tdcTime 700 -3500 3500
+
+TH1F ptrig_p1x_tdc 'SHMS p1x TDC Time; Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.p1X_tdcTime 350 0 3500
+TH1F ptrig_p1y_tdc 'SHMS p1y TDC Time; Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.p1Y_tdcTime 350 0 3500
+TH1F ptrig_p2x_tdc 'SHMS p2x TDC Time; Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.p2X_tdcTime 350 0 3500
+TH1F ptrig_p2y_tdc 'SHMS p2y TDC Time; Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.p2Y_tdcTime 350 0 3500
+
+TH1F ptrig_p1T_tdc 'SHMS p1x/p1y Coincidence TDC Time; Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.p1T_tdcTime 350 0 3500
+TH1F ptrig_p2T_tdc 'SHMS p2x/p2y Coincidence TDC Time; Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.p2T_tdcTime 350 0 3500
+
+TH1F ptrig_pT1_tdc 'SHMS p1x/p1y/p2x/p2y Coincidence TDC Time (Slot 20, Channel 15); Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.pT1_tdcTime 350 0 3500
+TH1F ptrig_pT2_tdc 'SHMS p1x/p1y/p2x/p2y Coincidence TDC Time (Slot 19, Channel 31); Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.pT2_tdcTime 350 0 3500
+TH1F ptrig_pT3_tdc 'SHMS p1x/p1y/p2x/p2y Coincidence TDC Time (Slot 19, Channel 38); Raw TDC Time (TDC Units); Counts / 10 TDC Units;' T.shms.pT3_tdcTime 350 0 3500
\ No newline at end of file
diff --git a/DEF-files/SHMS/GEN/pstackana_report_cuts.def b/DEF-files/SHMS/GEN/pstackana_report_cuts.def
new file mode 100644
index 00000000..d012b948
--- /dev/null
+++ b/DEF-files/SHMS/GEN/pstackana_report_cuts.def
@@ -0,0 +1,189 @@
+# Demo cuts for hodtest
+#
+
+Block: RawDecode
+
+Pedestal_event    g.evtyp==4
+scalar_event      g.evtyp==0
+HMS_event         g.evtyp==1
+SHMS_event         g.evtyp==1
+coin_event        g.evtyp==3
+misc_event        g.evtyp>=5
+hmscoin_event     g.evtyp==1||g.evtyp==3
+shmscoin_event     g.evtyp==2||g.evtyp==3
+all_event         g.evtyp==1||g.evtyp==2||g.evtyp==3
+RawDecode_master  1
+
+Block: Decode
+Decode_master     HMS_event
+
+Block: CoarseTracking
+CoarseTracking_master HMS_event
+
+all_trigs             g.evtyp==1 || g.evtyp==2 || g.evtyp==3
+hms_shms_trig          g.evtyp==1 || g.evtyp==2
+hms_coin_trig         g.evtyp==1 || g.evtyp==3
+
+
+shmsDC1Planes_large  (P.dc.1x1.nhit+P.dc.1u2.nhit+P.dc.1u1.nhit+P.dc.1v1.nhit+P.dc.1x2.nhit+P.dc.1v2.nhit) >20
+shmsDC2Planes_large  (P.dc.2x1.nhit+P.dc.2u2.nhit+P.dc.2u1.nhit+P.dc.2v1.nhit+P.dc.2x2.nhit+P.dc.2v2.nhit) >20
+
+shmsDC1_1hit_x1                P.dc.1x1.nhit == 1
+shmsDC1_1hit_u1                P.dc.1u1.nhit == 1
+shmsDC1_1hit_u2                P.dc.1u2.nhit == 1
+shmsDC1_1hit_v1                P.dc.1v1.nhit == 1
+shmsDC1_1hit_v2                P.dc.1v2.nhit == 1
+shmsDC1_1hit_x2                P.dc.1x2.nhit == 1
+
+shmsDC2_1hit_x1                P.dc.2x1.nhit == 1
+shmsDC2_1hit_u1                P.dc.2u1.nhit == 1
+shmsDC2_1hit_u2                P.dc.2u2.nhit == 1
+shmsDC2_1hit_v1                P.dc.2v1.nhit == 1
+shmsDC2_1hit_v2                P.dc.2v2.nhit == 1
+shmsDC2_1hit_x2                P.dc.2x2.nhit == 1
+
+h1hit1                P.dc.1x1.nhit >= 1
+h1hit2                P.dc.1u1.nhit >= 1
+h1hit3                P.dc.1u2.nhit >= 1
+h1hit4                P.dc.1v1.nhit >= 1
+h1hit5                P.dc.1v2.nhit >= 1
+h1hit6                P.dc.1x2.nhit >= 1
+
+h2hit1                P.dc.2x1.nhit >= 1
+h2hit2                P.dc.2u1.nhit >= 1
+h2hit3                P.dc.2u2.nhit >= 1
+h2hit4                P.dc.2v1.nhit >= 1
+h2hit5                P.dc.2v2.nhit >= 1
+h2hit6                P.dc.2x2.nhit >= 1
+
+shmsDC1Planes6hits shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_u2&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC2Planes6hits shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_u2&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC1_5hits_x1     shmsDC1_1hit_u1&&shmsDC1_1hit_u2&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC1_6hits_x1     h1hit1&&shmsDC1_1hit_u1&&shmsDC1_1hit_u2&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC1_5hits_u1     shmsDC1_1hit_x1&&shmsDC1_1hit_u2&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC1_6hits_u1     h1hit2&&shmsDC1_1hit_x1&&shmsDC1_1hit_u2&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC1_5hits_u2     shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC1_6hits_u2     h1hit3&&shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_x2&&shmsDC1_1hit_v1&&shmsDC1_1hit_v2
+shmsDC1_5hits_v1     shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_x2&&shmsDC1_1hit_u2&&shmsDC1_1hit_v2
+shmsDC1_6hits_v1     h1hit4&&shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_x2&&shmsDC1_1hit_u2&&shmsDC1_1hit_v2
+shmsDC1_5hits_v2     shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_x2&&shmsDC1_1hit_u2&&shmsDC1_1hit_v1
+shmsDC1_6hits_v2     h1hit5&&shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_x2&&shmsDC1_1hit_u2&&shmsDC1_1hit_v1
+shmsDC1_5hits_x2     shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_v1&&shmsDC1_1hit_u2&&shmsDC1_1hit_v2
+shmsDC1_6hits_x2     h1hit6&&shmsDC1_1hit_x1&&shmsDC1_1hit_u1&&shmsDC1_1hit_v1&&shmsDC1_1hit_u2&&shmsDC1_1hit_v2
+
+shmsDC2_5hits_x1     shmsDC2_1hit_u1&&shmsDC2_1hit_u2&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC2_6hits_x1     h2hit1&&shmsDC2_1hit_u1&&shmsDC2_1hit_u2&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC2_5hits_u1     shmsDC2_1hit_x1&&shmsDC2_1hit_u2&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC2_6hits_u1     h2hit2&&shmsDC2_1hit_x1&&shmsDC2_1hit_u2&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC2_5hits_u2     shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC2_6hits_u2     h2hit3&&shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_x2&&shmsDC2_1hit_v1&&shmsDC2_1hit_v2
+shmsDC2_5hits_v1     shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_x2&&shmsDC2_1hit_u2&&shmsDC2_1hit_v2
+shmsDC2_6hits_v1     h2hit4&&shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_x2&&shmsDC2_1hit_u2&&shmsDC2_1hit_v2
+shmsDC2_5hits_v2     shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_x2&&shmsDC2_1hit_u2&&shmsDC2_1hit_v1
+shmsDC2_6hits_v2     h2hit5&&shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_x2&&shmsDC2_1hit_u2&&shmsDC2_1hit_v1
+shmsDC2_5hits_x2     shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_v1&&shmsDC2_1hit_u2&&shmsDC2_1hit_v2
+shmsDC2_6hits_x2     h2hit6&&shmsDC2_1hit_x1&&shmsDC2_1hit_u1&&shmsDC2_1hit_v1&&shmsDC2_1hit_u2&&shmsDC2_1hit_v2
+
+
+
+
+
+shms1HitsLt            P.dc.Ch1.nhit <= P.dc.Ch1.maxhits && g.evtyp==1
+shms2HitsLt            P.dc.Ch2.nhit <= P.dc.Ch2.maxhits && g.evtyp==1
+shmsHitsLt             P.dc.Ch1.nhit <= P.dc.Ch1.maxhits && P.dc.Ch2.nhit <= P.dc.Ch2.maxhits && g.evtyp==1
+shmsDC1PlanesGT        (h1hit1 + h1hit2 + h1hit3 + h1hit4 + h1hit5 + h1hit6 )>=5
+shmsDC2PlanesGT        (h2hit1 + h2hit2 + h2hit3 + h2hit4 + h2hit5 + h2hit6 )>=5
+shmsPlanesGT           shmsDC1PlanesGT && shmsDC2PlanesGT
+shmsHitsPlanes         (P.dc.Ch1.nhit <= P.dc.Ch1.maxhits) && (P.dc.Ch2.nhit <= P.dc.Ch2.maxhits) && shmsPlanesGT
+hSpacePoints          P.dc.Ch1.spacepoints >= 1 && P.dc.Ch2.spacepoints >=1
+hSpacePointsStub      P.dc.stubtest==1 && P.dc.Ch1.spacepoints >=1 && P.dc.Ch2.spacepoints >=1
+hFoundTrack           P.dc.ntrack>0 
+hStubLT               P.dc.stubtest==1
+f1HSpacePoints        shms1HitsLt && shmsDC1PlanesGT && P.dc.Ch1.spacepoints==0 && g.evtyp==1
+f2HSpacePoints        shms2HitsLt && shmsDC2PlanesGT && P.dc.Ch2.spacepoints==0 && g.evtyp==1
+hTest1                shmsHitsPlanes && (!hSpacePoints)
+hTest2                hSpacePoints && (!hStubLT)
+
+
+
+
+
+
+Block: CoarseReconstruct
+CoarseReconstruct_master shms_event
+
+Block: Tracking
+Tracking_master  shms_event
+
+Block: Reconstruct
+Reconstruct_master shms_event
+
+shmsScinGood           P.hod.goodscinhit == 1
+
+shmsScinShould         shmsScinGood && P.cal.etotnorm > 0.7 && P.hgcer.npesum > 2.0
+shmsScinShoulde        shmsScinGood && P.hgcer.npesum > 2.0
+shmsScinShouldh        P.hod.goodscinhit == 1 && g.evtyp == 1
+
+shmsScinDid            shmsScinShould && P.dc.ntrack > 0
+shmsScinDide           shmsScinShoulde && P.dc.ntrack > 0
+shmsScinDidh           shmsScinShouldh && P.dc.ntrack > 0
+
+
+
+goodHDC1x1            P.dc.1x1.nhit > 0 && P.dc.1x1.nhit < 3
+goodHDC1u2            P.dc.1u2.nhit > 0 && P.dc.1u2.nhit < 3
+goodHDC1u1            P.dc.1u1.nhit > 0 && P.dc.1u1.nhit < 3
+goodHDC1v1            P.dc.1v1.nhit > 0 && P.dc.1v1.nhit < 3
+goodHDC1v2            P.dc.1v2.nhit > 0 && P.dc.1v2.nhit < 3
+goodHDC1x2            P.dc.1x2.nhit > 0 && P.dc.1x2.nhit < 3
+
+goodHDC2x1            P.dc.2x1.nhit > 0 && P.dc.2x1.nhit < 3
+goodHDC2u2            P.dc.2u2.nhit > 0 && P.dc.2u2.nhit < 3
+goodHDC2u1            P.dc.2u1.nhit > 0 && P.dc.2u1.nhit < 3
+goodHDC2v1            P.dc.2v1.nhit > 0 && P.dc.2v1.nhit < 3
+goodHDC2v2            P.dc.2v2.nhit > 0 && P.dc.2v2.nhit < 3
+goodHDC2x2            P.dc.2x2.nhit > 0 && P.dc.2x2.nhit < 3
+
+goodHDC1              goodHDC1x1  && goodHDC1u2 && goodHDC1u1 && goodHDC1v1 && goodHDC1v2 && goodHDC1x2 
+goodHDC2              goodHDC2x1  && goodHDC2u2 && goodHDC2u1 && goodHDC2v1 && goodHDC2v2 && goodHDC2x2 
+bothGood              goodHDC1 && goodHDC2
+
+realhdc1x1            goodHDC1x1 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc1u2            goodHDC1u2 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc1u1            goodHDC1u1 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc1v1            goodHDC1v1 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc1v2            goodHDC1v2 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2x2            goodHDC1x2 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2x1            goodHDC2x1 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2u2            goodHDC2u2 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2u1            goodHDC2u1 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2v1            goodHDC2v1 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2v2            goodHDC2v2 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+realhdc2x2            goodHDC2x2 && ((P.dc.Ch1.spacepoints+P.dc.Ch2.spacepoints)>0)
+
+hFound1Track          P.dc.ntrack == 1
+hFound2Track          P.dc.ntrack == 2
+hFound3Track          P.dc.ntrack == 3
+hFound4Track          P.dc.ntrack == 4
+
+hCleanTrack           P.gtr.index > -1
+1hCleanTrack          P.gtr.index == 0
+2hCleanTrack          P.gtr.index == 1
+3hCleanTrack          P.gtr.index == 2
+4hCleanTrack          P.gtr.index == 3
+
+anyhs1x               P.hod.1x.nhits > 0
+anyhs1y               P.hod.1y.nhits > 0
+anyhs2x               P.hod.2x.nhits > 0
+anyhs2y               P.hod.2y.nhits > 0
+
+goodhs1x              P.hod.1x.nhits > 0 && P.hod.1x.nhits < 3
+goodhs1y              P.hod.1y.nhits > 0 && P.hod.1y.nhits < 3
+goodhs1               goodhs1x && goodhs1y
+goodhs2x              P.hod.2x.nhits > 0 && P.hod.2x.nhits < 3
+goodhs2y              P.hod.2y.nhits > 0 && P.hod.2y.nhits < 3
+goodhs2               goodhs2x && goodhs2y
+goodhs1s2             goodhs1 && goodhs2
+
+Block: Physics
+Physics_master shms_event
diff --git a/PARAM/HMS/GEN/htracking.param b/PARAM/HMS/GEN/htracking.param
index e56b394c..3ee7a1ea 100644
--- a/PARAM/HMS/GEN/htracking.param
+++ b/PARAM/HMS/GEN/htracking.param
@@ -8,11 +8,11 @@ hntracks_max_fp = 10
 h_remove_sppt_if_one_y_plane = 0
 
 ; Minimum number of hits in each space point (one per chamber)
-hmin_hit = 5, 5
+hmin_hit = 4, 4
 
 ; Minimum number of pairs in each space point (one per chamber)
 ; Should be 3/3 for 4/6 tracking, and 4/4 for 5/6 tracking
-hmin_combos = 4, 4 
+hmin_combos = 3, 3 
 
 ; Minimum separation of distinct space points
 hspace_point_criterion = 1.0, 1.0
@@ -60,8 +60,11 @@ hstub_max_xpdiff = .05
 
 ; hstat_maxchisq          chisquared limit for tracks used to measure hodo. eff.
   hstat_maxchisq = 10.
+; if both hsel_using_scin = 0 and hsel_using_prune = 0 then best chi2 track is used.
 ; hsel_using_scin         uses scintillator for track selection
-  hsel_using_scin = 1
+  hsel_using_scin = 0
+; hsel_using_prune         using prune
+  hsel_using_prune = 0
 ; hstat_slop              distance from center of scin. to count as expecting hit
   hstat_slop = 2.
 ; hstat_mineff            warning level for scin. effic.
diff --git a/PARAM/HMS/HODO/hhodo.param b/PARAM/HMS/HODO/hhodo.param
index 54596af4..27b0e24f 100644
--- a/PARAM/HMS/HODO/hhodo.param
+++ b/PARAM/HMS/HODO/hhodo.param
@@ -8,19 +8,20 @@ hhodo_adc_mode=1
 ; 
 ; hhodo_tdc_offset is array of time offsets for all paddles in a plane
 ;   to move the tdc to between 0 and 4000 channels.
-  hhodo_tdc_offset = 1280, 1280, 1280, 1290
+  hhodo_tdc_offset = 1120, 1120, 1120, 1120
+;  hhodo_tdc_offset = 1000, 1000, 1000, 1000
 ; hstart_time_center  center of allowed time window (ns)
    hstart_time_center = 32.                                                     
 ; hstart_time_slop    1/2 width of time window                                  
-   hstart_time_slop = 25.                                                       
+   hstart_time_slop = 100.                                                       
 ; hscin_tdc_min       minimum tdc value in hms scin                             
-    hscin_tdc_min = 0                                                           
+    hscin_tdc_min = -500                                                           
 ; hscin_tdc_max       maximum allowed tdc value                                 
    hscin_tdc_max = 4000                                                         
 ; hscin_tdc_to_time   scin tdc time per channel                                 
    hscin_tdc_to_time = 0.1                                                  
 ; tof and you figured out good values
-   htof_tolerance = 30.0
+   htof_tolerance = 50.0
 ;                                                                               
 ; hms_tof_params                                                                
 ; hnum_scin_counters, hhodo_zpos, hhodo_center_coord, hhodo_width               
@@ -32,8 +33,7 @@ hhodo_adc_mode=1
 htofusinginvadc=1
 ;                                                                               
                                                                                 
-hhodo_pos_invadc_offset =   0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
+hhodo_pos_invadc_offset = 0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
@@ -48,57 +48,60 @@ hhodo_pos_invadc_offset =   0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
+ 0.000,   0.0000,  0.000,   0.000 
+
 ;
-hhodo_neg_invadc_offset =   0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
-;
-hhodo_pos_invadc_linear =   14.0,14.8,15.5,15.8        
-                        14.0,14.8,15.5,15.8      
-                        14.0,14.8,15.5,15.8      
-                        14.0,14.8,15.5,15.8   
-                        14.0,14.8,15.5,15.8   
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8 
-                        14.0,14.8,15.5,15.8 
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8  
-hhodo_neg_invadc_linear =   14.0,14.8,15.5,15.8        
-                        14.0,14.8,15.5,15.8      
-                        14.0,14.8,15.5,15.8      
-                        14.0,14.8,15.5,15.8   
-                        14.0,14.8,15.5,15.8   
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8 
-                        14.0,14.8,15.5,15.8 
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8  
+hhodo_neg_invadc_offset = 2.63295,0.592977,0.810207,2.17447
+1.6381,-2.44172,-0.167998,1.613
+2.12397,-1.11413,1.12234,2.70131
+2.23737,-3.22432,-0.0328571,2.88366
+1.84971,-2.55502,-0.325019,2.75559
+1.77137,-1.90664,-0.0557544,1.354
+1.86089,-1.9991,-1.08851,-2.15107
+2.74336,-2.60574,0.388706,3.63254
+1.53963,-1.67298,-1.06672,3.14031
+2.25306,-2.75735,0.900716,2.54422
+1.72962,0.0,-0.000925926,0.0
+0.136985,0.0,-1.90318,0.0
+1.06083,0.0,-4.18178,0.0
+1.92537,0.0,-0.688612,0.0
+1.36458,0.0,0.641606,0.0
+1.95569,0.0,-1.16377,0.0
  
+;
+hhodo_pos_invadc_linear = 15.0,15.0,15.0,15.0        
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+hhodo_neg_invadc_linear = 15.0,15.0,15.0,15.0        
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+
 hhodo_pos_invadc_adc =   0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
@@ -133,23 +136,23 @@ hhodo_neg_invadc_adc =   0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
 ;
-     hhodo_vel_light =  14.0,14.8,15.5,15.8        
-                        14.0,14.8,15.5,15.8      
-                        14.0,14.8,15.5,15.8      
-                        14.0,14.8,15.5,15.8   
-                        14.0,14.8,15.5,15.8   
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8 
-                        14.0,14.8,15.5,15.8 
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8
-                        14.0,14.8,15.5,15.8  
-                        14.0,14.8,15.5,15.8  
-;                                                                               
+     hhodo_vel_light =  15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+                        15.0,15.0,15.0,15.0                                     
+ ;                                                                               
       hhodo_pos_sigma = .3,.3,.3,.3,.3,.3,.3,.3                                 
                         .3,.3,.3,.3,.3,.3,.3,.3                                 
                         .3,.3,.3,.3,.3,.3,.3,.3                                 
@@ -187,5 +190,140 @@ hhodo_neg_ped_limit = 1000,1000,1000,1000,1000,1000,1000,1000
                       1000,1000,1000,1000,1000,1000,1000,1000                   
                       1000,1000,1000,1000,1000,1000,1000,1000                   
                       1000,1000,1000,1000,1000,1000,1000,1000                   
-                      1000,1000,1000,1000,1000,1000,1000,1000                   
-                                                                                
+                      1000,1000,1000,1000,1000,1000,1000,1000  
+; new param                 
+hhodo_pos_invadc_offset =   -0.00,   -0.00,   -0.70,   -0.00
+                            -0.00,   -0.00,   -0.31,   -2.63
+                            -0.00,    0.13,   -1.03,   -0.58
+                             1.43,   -0.51,   -0.87,   -0.63
+                             0.60,   -0.75,   -0.66,   -1.54
+                             1.73,   -0.66,   -0.82,   -1.46
+                             0.89,    0.08,   -0.92,   -0.88
+                             2.10,    0.20,   -0.32,   -0.39
+                             0.31,   -0.89,   -1.14,   -2.15
+                            -0.00,   -0.00,   -1.52,   -0.00
+                             0.80,   -0.00,   -0.75,   -0.00
+                            -0.25,   -0.00,   -2.36,   -0.00
+                             0.54,   -0.00,   -0.00,   -0.00
+                             0.47,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+
+hhodo_neg_invadc_offset =   -0.00,   -0.00,   -0.97,   -0.00
+                            -0.00,   -0.00,    0.06,   -2.16
+                            -0.00,   -0.58,   -1.60,   -0.95
+                            -0.09,    0.95,   -0.45,   -0.49
+                            -0.79,   -0.05,    0.21,   -1.82
+                             0.32,   -1.02,   -0.05,   -0.52
+                             0.02,    0.19,    0.90,    3.75
+                            -0.35,    0.35,    0.26,   -1.65
+                            -0.27,   -1.32,    0.33,   -2.44
+                            -1.42,   -0.00,   -1.48,   -0.00
+                             0.14,   -0.00,    0.14,   -0.00
+                             0.24,   -0.00,   -0.06,   -0.00
+                             0.16,   -0.00,   -0.00,   -0.00
+                            -0.83,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+
+hhodo_pos_invadc_linear =   15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            14.56,   15.00,   15.00,   15.00
+                            12.91,   15.00,   15.00,   15.00
+                            12.81,   14.97,   15.00,   15.00
+                            14.29,   15.00,   15.00,   15.00
+                            12.94,   14.21,   14.85,   15.00
+                            13.27,   13.60,   15.00,   15.00
+                            13.44,   15.00,   15.00,   15.00
+                            14.24,   15.00,   15.00,   15.00
+                            13.24,   15.00,   14.33,   15.00
+                            13.20,   15.00,   15.00,   15.00
+                            13.94,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+
+hhodo_neg_invadc_linear =   15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   14.56,   15.00,   15.00
+                            14.55,   14.16,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            13.47,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            14.69,   14.21,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            14.74,   15.00,   15.00,   15.00
+                            14.66,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            13.71,   15.00,   15.00,   15.00
+                            12.33,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+
+hhodo_pos_invadc_adc=    -0.00,    -0.00,   106.88,    -0.00
+                        -0.00,    -0.00,   109.67,   122.91
+                        -0.00,   102.28,   127.88,   117.82
+                       100.32,    76.55,   109.30,   139.97
+                        72.45,    90.73,   111.62,   121.49
+                        59.46,    83.45,   116.54,   123.92
+                        95.04,    91.79,   125.49,   127.74
+                        62.95,    53.50,   113.46,   106.91
+                        78.26,    49.84,   100.37,   141.06
+                        73.52,    -0.00,   101.78,    -0.00
+                        94.23,    -0.00,   129.39,    -0.00
+                        75.59,    -0.00,    94.17,    -0.00
+                        79.87,    -0.00,    -0.00,    -0.00
+                        63.90,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+
+hhodo_neg_invadc_adc=    -0.00,    -0.00,   128.32,    -0.00
+                        -0.00,    -0.00,   113.16,   159.99
+                        -0.00,    68.41,   116.51,   119.18
+                        73.18,    65.95,   112.50,   122.16
+                        96.71,    91.23,    96.00,   103.37
+                        52.93,    87.48,   103.59,   122.65
+                        72.72,    82.28,   118.40,   140.72
+                        76.58,    68.02,   104.25,   120.16
+                        73.69,    98.85,    91.95,   119.78
+                        72.26,    -0.00,    89.16,    -0.00
+                        70.89,    -0.00,   113.44,    -0.00
+                        72.26,    -0.00,   101.96,    -0.00
+                        76.14,    -0.00,    -0.00,    -0.00
+                        36.51,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+
+hhodo_pos_sigma =  100.00,  100.00,    0.28,  100.00
+                   100.00,  100.00,    0.31,    0.47
+                   100.00,    0.27,    0.33,    0.34
+                     0.26,    0.32,    0.35,    0.44
+                     0.30,    0.30,    0.33,    0.51
+                     0.38,    0.28,    0.22,    0.41
+                     0.25,    0.30,    0.32,    0.46
+                     0.35,    0.30,    0.31,    0.34
+                     0.26,    0.25,    0.24,    0.41
+                     0.27,  100.00,    0.27,  100.00
+                     0.25,  100.00,    0.37,  100.00
+                     0.26,  100.00,    0.24,  100.00
+                     0.34,  100.00,  100.00,  100.00
+                     0.37,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
+
+hhodo_neg_sigma =  100.00,  100.00,    0.32,  100.00
+                   100.00,  100.00,    0.33,    0.52
+                   100.00,    0.31,    0.35,    0.31
+                     0.25,    0.30,    0.34,    0.32
+                     0.28,    0.32,    0.27,    0.56
+                     0.36,    0.33,    0.28,    0.31
+                     0.26,    0.31,    0.37,    0.42
+                     0.32,    0.30,    0.28,    0.33
+                     0.24,    0.28,    0.20,    0.44
+                     0.27,  100.00,    0.24,  100.00
+                     0.24,  100.00,    0.29,  100.00
+                     0.25,  100.00,    0.25,  100.00
+                     0.28,  100.00,  100.00,  100.00
+                     0.33,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
diff --git a/PARAM/HMS/HODO/htofcal.param b/PARAM/HMS/HODO/htofcal.param
new file mode 100644
index 00000000..46f40459
--- /dev/null
+++ b/PARAM/HMS/HODO/htofcal.param
@@ -0,0 +1,2 @@
+hdumptof=1
+hdumptof_filename="CALIBRATION/hodo_calib/hmsfort.37"
diff --git a/PARAM/SHMS/GEN/ptracking.param b/PARAM/SHMS/GEN/ptracking.param
index 899347aa..bb63238c 100644
--- a/PARAM/SHMS/GEN/ptracking.param
+++ b/PARAM/SHMS/GEN/ptracking.param
@@ -25,7 +25,7 @@ pntracks_max_fp = 10
 ; focal plane position to link stubs to tracks
   pntracks_max_fp = 10
   pxt_track_criterion = 100.0
-  pyt_track_criterion = 2.0
+  pyt_track_criterion = 20.0
   pxpt_track_criterion = 1.0
   pypt_track_criterion = 1.0
 
@@ -56,8 +56,11 @@ pntracks_max_fp = 10
 
 ; pstat_maxchisq          chisquared limit for tracks used to measure hodo. eff.
   pstat_maxchisq = 10.
+; if both psel_using_scin = 0 and psel_using_prune = 0 then best chi2 track is used.
 ; psel_using_scin         uses scintillator for track selection
-  psel_using_scin = 1
+  psel_using_scin = 0
+; psel_using_prune         using prune
+  psel_using_prune = 0
 ; pstat_slop              distance from center of scin. to count as expecting hit
   pstat_slop = 2.
 ; pstat_mineff            warning level for scin. effic.
diff --git a/PARAM/SHMS/HODO/phodo.param b/PARAM/SHMS/HODO/phodo.param
index 0d0e6ea7..aaa4ea23 100644
--- a/PARAM/SHMS/HODO/phodo.param
+++ b/PARAM/SHMS/HODO/phodo.param
@@ -8,19 +8,19 @@ phodo_adc_mode=1
 ; 
 ; hhodo_tdc_offset is array of time offsets for all paddles in a plane
 ;   to move the tdc to between 0 and 4000 channels.
-  phodo_tdc_offset = 1450, 1550, 1550, 1550
+  phodo_tdc_offset = 1860, 2000, 2060, 2000
 ; pstart_time_center  center of allowed time window                             
    pstart_time_center = 32.                                                     
 ; hstart_time_slop    1/2 width of time window                                  
-   pstart_time_slop = 25.                                                       
+   pstart_time_slop = 100.                                                       
 ; pscin_tdc_min       minimum tdc value in hms scin                             
-    pscin_tdc_min = 0                                                           
+    pscin_tdc_min = -500                                                           
 ; pscin_tdc_max       maximum allowed tdc value                                 
-   pscin_tdc_max = 4000                                                         
+   pscin_tdc_max = 1000                                                        
 ; pscin_tdc_to_time   scin tdc time per channel                                 
    pscin_tdc_to_time = 0.1                                                   
 ; tof and you figured out good values
-   ptof_tolerance = 30.0
+   ptof_tolerance = 100.0
 ;                                                                               
 ; shms_tof_params                                                              
 ; pnum_scin_counters, phodo_zpos, phodo_center_coord, phodo_width               
@@ -32,20 +32,20 @@ phodo_adc_mode=1
 ptofusinginvadc=1
 ;                                                                               
                                                                                 
-phodo_pos_invadc_offset =   0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
+phodo_pos_invadc_offset =   -5.0000,   -5.0000,  0.000,   0.000
+ -5.0000,   -2.0000,  0.000,   0.000
+ -5.0000,   -2.0000,  +10.000,   0.000
+ -5.0000,   -4.0000,  0.000,   0.000
+ -5.0000,   -4.0000,  +10.000,   0.000
+ -5.0000,   -5.0000,  0.000,   0.000
+ -5.0000,   -6.0000,  0.000,   -14.000
+ -5.0000,   -4.0000,  0.000,   -14.000
+ -5.0000,   -5.0000,  0.000,   -14.000
+ -5.0000,   +6.0000,  0.000,   -14.000
+ -5.0000,   0.0000,  0.000,   -14.000
+ -5.0000,   +5.0000,  0.000,   -14.000
+ -5.0000,   -7.0000,  0.000,   -14.000
+ 0.000,   0.0000,  0.000,   -14.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
@@ -56,18 +56,18 @@ phodo_pos_invadc_offset =   0.000,   0.0000,  0.000,   0.000
 ;
 phodo_neg_invadc_offset =   0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
+ 0.000,   0.0000,  +10.000,   0.000
  0.000,   0.0000,  0.000,   0.000
+ 0.000,   0.0000,  +10.000,   0.000
  0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
- 0.000,   0.0000,  0.000,   0.000
+ 0.000,   0.0000,  0.000,   -14.000
+ 0.000,   0.0000,  0.000,   -14.000
+ 0.000,   0.0000,  0.000,   -14.000
+ 0.000,   +10.0000,  0.000,   -14.000
+ 0.000,   0.0000,  0.000,   -14.000
+ 0.000,   +10.0000,  0.000,   -14.000
+ 0.000,   0.0000,  0.000,   -14.000
+ 0.000,   0.0000,  0.000,  -14.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
  0.000,   0.0000,  0.000,   0.000
@@ -273,3 +273,139 @@ phodo_neg_ped_limit = 1000,1000,1000,1000
                       1000,1000,1000,1000
                       1000,1000,1000,1000                   
                                                                                
+
+phodo_pos_invadc_offset =   -0.00,   -0.00,    0.59,   -0.00
+                            -6.26,   -4.09,    0.45,   -0.00
+                            -2.48,   -1.94,   12.41,   -0.00
+                             1.98,   -2.95,    0.44,   -0.00
+                            -1.71,   -4.57,    9.75,   -0.00
+                            -2.48,   -5.36,    0.15,   -0.00
+                             0.39,   -3.34,    0.75,   -0.00
+                            -7.06,   -3.12,    0.21,   -0.00
+                            -1.75,   -3.79,    1.52,   -0.00
+                            -0.00,    5.02,    1.58,   -0.00
+                            -3.67,   -3.57,    0.80,   -0.00
+                             0.76,   11.15,    2.28,   -0.00
+                            -0.00,   -0.00,    3.28,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+
+phodo_neg_invadc_offset =   -0.00,   -0.00,   -5.36,   -0.00
+                            -7.60,   -2.32,   -5.24,   -0.00
+                             0.62,   -3.65,   15.02,   -0.00
+                            -4.07,   -3.42,   -6.21,   -0.00
+                            -2.60,   -3.61,   10.43,   -0.00
+                            -5.70,   -2.98,   -7.00,   -0.00
+                             1.23,   -2.53,   -5.65,   -0.00
+                            -2.39,   -4.13,   -5.78,   -0.00
+                            -1.38,   -3.39,   -7.54,   -0.00
+                            -2.56,    7.05,   -5.93,   -0.00
+                             1.84,   -4.38,   -3.91,   -0.00
+                            -3.23,    9.84,   -3.06,   -0.00
+                            -0.00,   -0.00,   -5.95,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+                            -0.00,   -0.00,   -0.00,   -0.00
+
+phodo_pos_invadc_linear =   15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   14.97,   15.00
+                            14.28,   13.33,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            14.76,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+
+phodo_neg_invadc_linear =   15.00,   15.00,   15.00,   15.00
+                            13.91,   14.43,   15.00,   15.00
+                            14.52,   14.76,   15.00,   15.00
+                            14.68,   14.14,   15.00,   15.00
+                            14.94,   14.70,   15.00,   15.00
+                            14.34,   14.14,   15.00,   15.00
+                            14.82,   13.94,   15.00,   15.00
+                            15.00,   14.33,   15.00,   15.00
+                            14.77,   13.76,   15.00,   15.00
+                            15.00,   14.75,   14.42,   15.00
+                            15.00,   13.69,   13.56,   15.00
+                            13.75,   13.13,   13.73,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+                            15.00,   15.00,   15.00,   15.00
+
+phodo_pos_invadc_adc=    -0.00,    -0.00,   112.14,    -0.00
+                        85.63,   100.91,    83.19,    -0.00
+                        96.42,    36.41,   116.39,    -0.00
+                       121.38,    90.00,   118.14,    -0.00
+                       114.06,    92.90,   100.01,    -0.00
+                       110.24,    92.14,   103.32,    -0.00
+                       125.76,    84.99,   122.10,    -0.00
+                        92.38,    91.90,   130.47,    -0.00
+                       116.53,    85.91,    98.54,    -0.00
+                       122.36,   111.70,   113.37,    -0.00
+                       104.33,    74.85,    80.05,    -0.00
+                       122.25,   100.68,   145.77,    -0.00
+                        -0.00,    -0.00,   134.86,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+
+phodo_neg_invadc_adc=    -0.00,    -0.00,   115.40,    -0.00
+                       100.70,    83.97,   103.44,    -0.00
+                       112.43,    84.04,   158.78,    -0.00
+                       119.43,    89.05,   118.05,    -0.00
+                       101.78,    89.03,   123.62,    -0.00
+                        97.26,    87.19,   108.87,    -0.00
+                       121.57,    78.91,   104.65,    -0.00
+                       110.95,    85.20,   170.10,    -0.00
+                       109.62,    78.24,   104.81,    -0.00
+                       113.38,   111.82,    60.35,    -0.00
+                       126.61,    78.83,    62.49,    -0.00
+                        91.82,    87.61,    62.81,    -0.00
+                        -0.00,    -0.00,   155.93,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+                        -0.00,    -0.00,    -0.00,    -0.00
+
+phodo_pos_sigma =  100.00,  100.00,    0.67,  100.00
+                     0.60,    0.57,    0.84,  100.00
+                     0.49,    0.64,    0.64,  100.00
+                     0.61,    0.50,    0.65,  100.00
+                     0.59,    0.63,    0.82,  100.00
+                     0.72,    0.56,    0.62,  100.00
+                     0.51,    0.52,    0.68,  100.00
+                     0.65,    0.56,    0.92,  100.00
+                     0.69,    0.49,    0.67,  100.00
+                     0.66,    0.60,    1.69,  100.00
+                     0.56,    0.54,    1.72,  100.00
+                     0.57,    0.51,    1.49,  100.00
+                   100.00,  100.00,    2.01,  100.00
+                   100.00,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
+
+phodo_neg_sigma =  100.00,  100.00,    0.58,  100.00
+                     0.66,    0.61,    0.74,  100.00
+                     0.53,    0.61,    0.60,  100.00
+                     0.57,    0.46,    0.91,  100.00
+                     0.55,    0.62,    0.85,  100.00
+                     0.65,    0.51,    0.67,  100.00
+                     0.49,    0.53,    0.62,  100.00
+                     0.64,    0.54,    0.85,  100.00
+                     0.65,    0.54,    0.67,  100.00
+                     0.71,    0.62,    1.27,  100.00
+                     0.75,    0.53,    1.67,  100.00
+                     0.51,    0.57,    1.33,  100.00
+                   100.00,  100.00,    2.07,  100.00
+                   100.00,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
+                   100.00,  100.00,  100.00,  100.00
diff --git a/PARAM/SHMS/HODO/phodo.pos b/PARAM/SHMS/HODO/phodo.pos
index 134675c3..fc5d3077 100644
--- a/PARAM/SHMS/HODO/phodo.pos
+++ b/PARAM/SHMS/HODO/phodo.pos
@@ -2,14 +2,14 @@ phodo_num_planes = 4
 phodo_plane_names = "1x 1y 2x 2y"
       ppathlength_central = 1800
 ; Z positions of hodoscopes
-      pscin_1x_zpos =  (89.14-11.31)
-      pscin_1y_zpos =  (108.83-11.31)
-      pscin_2x_zpos =  (310.13-11.31)
-      pscin_2y_zpos =  (329.82-11.31)
-      pscin_1x_dzpos = 2.12
-      pscin_1y_dzpos = 2.12
-      pscin_2x_dzpos = 2.12
-      pscin_2y_dzpos = 2.12
+      pscin_1x_zpos =  56.3-9.5
+      pscin_1y_zpos =  56.3+9.5
+      pscin_2x_zpos =  276.35-9.5
+      pscin_2y_zpos =  276.35+9.5
+      pscin_1x_dzpos = 1.0
+      pscin_1y_dzpos = 1.0
+      pscin_2x_dzpos = 1.0
+      pscin_2y_dzpos = 1.0
       pscin_1x_size = 8.0
       pscin_1y_size = 8.0
       pscin_2x_size = 8.0
@@ -44,19 +44,19 @@ phodo_plane_names = "1x 1y 2x 2y"
       pscin_1y_top   = -50
       pscin_1y_bot   =  50
       pscin_1y_offset=  0.0
-      pscin_1y_center= -42.
-                       -35.
-                       -28.
-                       -21.
-                       -14.
-                       -7.
+      pscin_1y_center= +42.
+                       +35.
+                       +28.
+                       +21.
+                       +14.
+                       +7.
                         0.0
-                        7.
-                        14.
-                        21.
-                        28.
-                        35.
-                        42. 
+                        -7.
+                        -14.
+                        -21.
+                        -28.
+                        -35.
+                        -42. 
       pscin_2x_left  =  55.
       pscin_2x_right =  -55.
       pscin_2x_offset=  0.0
diff --git a/PARAM/SHMS/HODO/ptofcal.param b/PARAM/SHMS/HODO/ptofcal.param
new file mode 100644
index 00000000..70d469af
--- /dev/null
+++ b/PARAM/SHMS/HODO/ptofcal.param
@@ -0,0 +1,2 @@
+pdumptof=1
+pdumptof_filename="CALIBRATION/hodo_calib/shmsfort.37"
diff --git a/SCRIPTS/HMS/replay_hms_report.C b/SCRIPTS/HMS/replay_hms_report.C
index 77978a14..249057d5 100644
--- a/SCRIPTS/HMS/replay_hms_report.C
+++ b/SCRIPTS/HMS/replay_hms_report.C
@@ -31,6 +31,8 @@ void replay_hms_report(Int_t RunNumber=0, Int_t MaxEvent=0) {
 
   // Load params for HMS trigger configuration
   gHcParms->Load("PARAM/TRIG/thms.param");
+  // Load params for HODO tof calibration. 
+  // gHcParms->Load("PARAM/HMS/HODO/htofcal.param");
 
   // Load the Hall C style detector map
   gHcDetectorMap = new THcDetectorMap();
@@ -110,10 +112,10 @@ void replay_hms_report(Int_t RunNumber=0, Int_t MaxEvent=0) {
  analyzer->SetCutFile("DEF-files/HMS/GEN/hstackana_report_cuts.def");    // optional
 
  // File to record cuts accounting information
- // analyzer->SetSummaryFile(Form("REPORT_OUTPUT/summary_%05d.report", RunNumber));    // optional
+  analyzer->SetSummaryFile(Form("REPORT_OUTPUT/HMS/summary_%05d.report", RunNumber));    // optional
 
   // Start the actual analysis.
   analyzer->Process(run);
   // Create report file from template.
-  analyzer->PrintReport("TEMPLATES/hstackana.template",Form("REPORT_OUTPUT/replay_hms_%05d.report", RunNumber));
+  analyzer->PrintReport("TEMPLATES/hstackana.template",Form("REPORT_OUTPUT/HMS/replay_hms_%05d.report", RunNumber));
 }
diff --git a/SCRIPTS/SHMS/replay_shms_report.C b/SCRIPTS/SHMS/replay_shms_report.C
new file mode 100644
index 00000000..42549df6
--- /dev/null
+++ b/SCRIPTS/SHMS/replay_shms_report.C
@@ -0,0 +1,124 @@
+void replay_shms_report(Int_t RunNumber=0, Int_t MaxEvent=0) {
+
+  // Get RunNumber and MaxEvent if not provided.
+  if(RunNumber == 0) {
+    cout << "Enter a Run Number (-1 to exit): ";
+    cin >> RunNumber;
+    if( RunNumber<=0 ) return;
+  }
+  if(MaxEvent == 0) {
+    cout << "\nNumber of Events to analyze: ";
+    cin >> MaxEvent;
+    if(MaxEvent == 0) {
+      cerr << "...Invalid entry\n";
+      exit;
+    }
+  }
+
+  // Create file name patterns.
+  const char* RunFileNamePattern = "raw/shms_all_%05d.dat";
+  const char* ROOTFileNamePattern = "ROOTfiles/shms_replay_%d.root";
+  // Add variables to global list.
+  gHcParms->Define("gen_run_number", "Run Number", RunNumber);
+  gHcParms->AddString("g_ctp_database_filename", "DBASE/standard.database");
+
+  // Load varibles from files to global list.
+  gHcParms->Load(gHcParms->GetString("g_ctp_database_filename"), RunNumber);
+
+  // g_ctp_parm_filename and g_decode_map_filename should now be defined.
+  gHcParms->Load(gHcParms->GetString("g_ctp_kinematics_filename"), RunNumber);
+  gHcParms->Load(gHcParms->GetString("g_ctp_parm_filename"));
+
+  // Load params for SHMS trigger configuration
+  gHcParms->Load("PARAM/TRIG/tshms.param");
+
+  // Load params for HODO tof calibration. 
+  //gHcParms->Load("PARAM/SHMS/HODO/ptofcal.param");
+
+ 
+  // Load the Hall C style detector map
+  gHcDetectorMap = new THcDetectorMap();
+  gHcDetectorMap->Load("MAPS/SHMS/DETEC/shms_stack.map");
+
+  // Add trigger apparatus
+  THaApparatus* TRG = new THcTrigApp("T", "TRG");
+  gHaApps->Add(TRG);
+  // Add trigger detector to trigger apparatus
+  THcTrigDet* shms = new THcTrigDet("shms", "SHMS Trigger Information");
+  TRG->AddDetector(shms);
+
+  // Set up the equipment to be analyzed.
+  THaApparatus* SHMS = new THcHallCSpectrometer("P", "SHMS");
+  gHaApps->Add(SHMS);
+  // Add Noble Gas Cherenkov to SHMS apparatus
+  THcCherenkov* ngcer = new THcCherenkov("ngcer", "Noble Gas Cherenkov");
+  SHMS->AddDetector(ngcer);
+  // Add drift chambers to SHMS apparatus
+  THcDC* dc = new THcDC("dc", "Drift Chambers");
+  SHMS->AddDetector(dc);
+  // Add hodoscope to SHMS apparatus
+  THcHodoscope* hod = new THcHodoscope("hod", "Hodoscope");
+  SHMS->AddDetector(hod);
+  // Add Heavy Gas Cherenkov to SHMS apparatus
+  THcCherenkov* hgcer = new THcCherenkov("hgcer", "Heavy Gas Cherenkov");
+  SHMS->AddDetector(hgcer);
+  // Add Heavy Gas Cherenkov to SHMS apparatus
+  THcAerogel* aero = new THcAerogel("aero", "Aerogel");
+  SHMS->AddDetector(aero);
+  // Add calorimeter to SHMS apparatus
+  THcShower* cal = new THcShower("cal", "Calorimeter");
+  SHMS->AddDetector(cal);
+
+  // Include golden track information
+  THaGoldenTrack* gtr = new THaGoldenTrack("P.gtr", "SHMS Golden Track", "P");
+  gHaPhysics->Add(gtr);
+
+  // Add handler for prestart event 125.
+  THcConfigEvtHandler* ev125 = new THcConfigEvtHandler("HC", "Config Event type 125");
+  gHaEvtHandlers->Add(ev125);
+
+  // Set up the analyzer - we use the standard one,
+  // but this could be an experiment-specific one as well.
+  // The Analyzer controls the reading of the data, executes
+  // tests/cuts, loops over Acpparatus's and PhysicsModules,
+  // and executes the output routines.
+  THcAnalyzer* analyzer = new THcAnalyzer;
+
+  // A simple event class to be output to the resulting tree.
+  // Creating your own descendant of THaEvent is one way of
+  // defining and controlling the output.
+  THaEvent* event = new THaEvent;
+
+  // Define the run(s) that we want to analyze.
+  // We just set up one, but this could be many.
+  char RunFileName[100];
+  sprintf(RunFileName, RunFileNamePattern, RunNumber);
+  THaRun* run = new THaRun(RunFileName);
+
+  // Eventually need to learn to skip over, or properly analyze
+  // the pedestal events
+  run->SetEventRange(1, MaxEvent);    // Physics Event number, does not
+                                      // include scaler or control events.
+  run->SetNscan(1);
+  run->SetDataRequired(0x7);
+  run->Print();
+
+  // Define the analysis parameters
+  TString ROOTFileName = Form(ROOTFileNamePattern, RunNumber);
+  analyzer->SetCountMode(2);    // 0 = counter is # of physics triggers
+                                // 1 = counter is # of all decode reads
+                                // 2 = counter is event number
+  analyzer->SetEvent(event);
+  analyzer->SetCrateMapFileName("MAPS/db_cratemap.dat");
+  analyzer->SetOutFile(ROOTFileName.Data());
+  analyzer->SetOdefFile("DEF-files/SHMS/GEN/pstackana_report.def");
+  analyzer->SetCutFile("DEF-files/SHMS/GEN/pstackana_report_cuts.def");    // optional
+
+  // File to record cuts accounting information
+  analyzer->SetSummaryFile(Form("REPORT_OUTPUT/SHMS/summary_%05d.report", RunNumber));    // optional
+
+  // Start the actual analysis.
+  analyzer->Process(run);
+  // Create report file from template.
+  analyzer->PrintReport("TEMPLATES/pstackana.template",Form("REPORT_OUTPUT/SHMS/replay_shms_%05d.report", RunNumber));
+}
diff --git a/TEMPLATES/hstackana.template b/TEMPLATES/hstackana.template
index 06dab002..0bffaf19 100644
--- a/TEMPLATES/hstackana.template
+++ b/TEMPLATES/hstackana.template
@@ -16,21 +16,21 @@ hmsDC2Planes_large  Counts:	  {hmsDC2Planes_large.npassed}  /all_trigs : {hmsDC2
 hmsDC1Planes6     Counts: {hmsDC1Planes6hits.npassed} /all_trigs : {hmsDC1Planes6hits.npassed/all_trigs.npassed}
 hmsDC2Planes6  	  Counts: {hmsDC2Planes6hits.npassed} /all_trigs : {hmsDC2Planes6hits.npassed/all_trigs.npassed}  
 
-	       	                      	       
-hmsDC1x1Planes5	  Counts: {hmsDC1_5hits_x1.npassed} /hmsDC1Planes6 : {hmsDC1Planes6hits.npassed/hmsDC1_5hits_x1.npassed}
-hmsDC1y1Planes5	  Counts: {hmsDC1_5hits_y1.npassed} /hmsDC1Planes6 : {hmsDC1Planes6hits.npassed/hmsDC1_5hits_y1.npassed}
-hmsDC1u1Planes5	  Counts: {hmsDC1_5hits_u1.npassed} /hmsDC1Planes6 : {hmsDC1Planes6hits.npassed/hmsDC1_5hits_u1.npassed}
-hmsDC1v1Planes5	  Counts: {hmsDC1_5hits_v1.npassed} /hmsDC1Planes6 : {hmsDC1Planes6hits.npassed/hmsDC1_5hits_v1.npassed}
-hmsDC1x2Planes5	  Counts: {hmsDC1_5hits_y2.npassed} /hmsDC1Planes6 : {hmsDC1Planes6hits.npassed/hmsDC1_5hits_y2.npassed} 
-hmsDC1y2Planes5	  Counts: {hmsDC1_5hits_x2.npassed} /hmsDC1Planes6 : {hmsDC1Planes6hits.npassed/hmsDC1_5hits_x2.npassed}
+hmsDC1x1Planes5	  Counts: {hmsDC1_5hits_x1.npassed} eff : {hmsDC1_6hits_x1.npassed/hmsDC1_5hits_x1.npassed}
+hmsDC1u1Planes5	  Counts: {hmsDC1_5hits_u1.npassed} eff : {hmsDC1_6hits_u1.npassed/hmsDC1_5hits_u1.npassed}
+hmsDC1y2Planes5	  Counts: {hmsDC1_5hits_y2.npassed} eff : {hmsDC1_6hits_y2.npassed/hmsDC1_5hits_y2.npassed}
+hmsDC1v1Planes5	  Counts: {hmsDC1_5hits_v1.npassed} eff : {hmsDC1_6hits_v1.npassed/hmsDC1_5hits_v1.npassed}
+hmsDC1y1Planes5	  Counts: {hmsDC1_5hits_y1.npassed} eff : {hmsDC1_6hits_y1.npassed/hmsDC1_5hits_y1.npassed}
+hmsDC1x2Planes5	  Counts: {hmsDC1_5hits_x2.npassed} eff : {hmsDC1_6hits_x2.npassed/hmsDC1_5hits_x2.npassed}
 
 
-hmsDC2x1Planes5	  Counts: {hmsDC2_5hits_x1.npassed}  /hmsDC1Planes6 : {hmsDC2Planes6hits.npassed/hmsDC2_5hits_x1.npassed}
-hmsDC2y1Planes5	  Counts: {hmsDC2_5hits_y1.npassed} /hmsDC1Planes6 : {hmsDC2Planes6hits.npassed/hmsDC2_5hits_y1.npassed}
-hmsDC2u1Planes5	  Counts: {hmsDC2_5hits_u1.npassed} /hmsDC1Planes6 : {hmsDC2Planes6hits.npassed/hmsDC2_5hits_u1.npassed}
-hmsDC2v1Planes5	  Counts: {hmsDC2_5hits_v1.npassed} /hmsDC1Planes6 : {hmsDC2Planes6hits.npassed/hmsDC2_5hits_v1.npassed}
-hmsDC2x2Planes5	  Counts: {hmsDC2_5hits_y2.npassed} /hmsDC1Planes6 : {hmsDC2Planes6hits.npassed/hmsDC2_5hits_y2.npassed} 
-hmsDC2y2Planes5	  Counts: {hmsDC2_5hits_x2.npassed} /hmsDC1Planes6 : {hmsDC2Planes6hits.npassed/hmsDC2_5hits_x2.npassed}
+hmsDC2x1Planes5	  Counts: {hmsDC2_5hits_x1.npassed} eff : {hmsDC2_6hits_x1.npassed/hmsDC2_5hits_x1.npassed}
+hmsDC2u1Planes5	  Counts: {hmsDC2_5hits_u1.npassed} eff : {hmsDC2_6hits_u1.npassed/hmsDC2_5hits_u1.npassed}
+hmsDC2y2Planes5	  Counts: {hmsDC2_5hits_y2.npassed} eff : {hmsDC2_6hits_y2.npassed/hmsDC2_5hits_y2.npassed}
+hmsDC2v1Planes5	  Counts: {hmsDC2_5hits_v1.npassed} eff : {hmsDC2_6hits_v1.npassed/hmsDC2_5hits_v1.npassed}
+hmsDC2y1Planes5	  Counts: {hmsDC2_5hits_y1.npassed} eff : {hmsDC2_6hits_y1.npassed/hmsDC2_5hits_y1.npassed}
+hmsDC2x2Planes5	  Counts: {hmsDC2_5hits_x2.npassed} eff : {hmsDC2_6hits_x2.npassed/hmsDC2_5hits_x2.npassed}
+	       	                      	       
 	       	   	       
 
 *****************************
diff --git a/TEMPLATES/pstackana.template b/TEMPLATES/pstackana.template
new file mode 100644
index 00000000..e1ce7848
--- /dev/null
+++ b/TEMPLATES/pstackana.template
@@ -0,0 +1,64 @@
+Run #{gen_run_number}
+           Standalone drift chamber analysis report template
+The names of the HMS drift chamber planes are: 
+{pdc_plane_names}
+Horizontal drift chamber z positions:
+Chamber 1: {pdc_zpos[0]:%6.2f} {pdc_zpos[1]:%6.2f} {pdc_zpos[2]:%6.2f} 
+           {pdc_zpos[3]:%6.2f} {pdc_zpos[4]:%6.2f} {pdc_zpos[5]:%6.2f} 
+Chamber 2: {pdc_zpos[6]:%6.2f} {pdc_zpos[7]:%6.2f} {pdc_zpos[8]:%6.2f} 
+           {pdc_zpos[9]:%6.2f} {pdc_zpos[10]:%6.2f} {pdc_zpos[11]:%6.2f}
+
+All triggers:  {all_trigs.npassed}
+ 
+shmsDC1Planes_large  Counts:  {shmsDC1Planes_large.npassed} /all_trigs : {shmsDC1Planes_large.npassed/all_trigs.npassed}
+shmsDC2Planes_large  Counts:	  {shmsDC2Planes_large.npassed}  /all_trigs : {shmsDC2Planes_large.npassed/all_trigs.npassed}  
+
+shmsDC1Planes6     Counts: {shmsDC1Planes6hits.npassed} /all_trigs : {shmsDC1Planes6hits.npassed/all_trigs.npassed}
+shmsDC2Planes6  	  Counts: {shmsDC2Planes6hits.npassed} /all_trigs : {shmsDC2Planes6hits.npassed/all_trigs.npassed}  
+
+	       	                      	       
+shmsDC1x1Planes5	  Counts: {shmsDC1_5hits_x1.npassed} eff : {shmsDC1_6hits_x1.npassed/shmsDC1_5hits_x1.npassed}
+shmsDC1u1Planes5	  Counts: {shmsDC1_5hits_u1.npassed} eff : {shmsDC1_6hits_u1.npassed/shmsDC1_5hits_u1.npassed}
+shmsDC1u2Planes5	  Counts: {shmsDC1_5hits_u2.npassed} eff : {shmsDC1_6hits_u2.npassed/shmsDC1_5hits_u2.npassed}
+shmsDC1v1Planes5	  Counts: {shmsDC1_5hits_v1.npassed} eff : {shmsDC1_6hits_v1.npassed/shmsDC1_5hits_v1.npassed}
+shmsDC1v2Planes5	  Counts: {shmsDC1_5hits_v2.npassed} eff : {shmsDC1_6hits_v2.npassed/shmsDC1_5hits_v2.npassed}
+shmsDC1x2Planes5	  Counts: {shmsDC1_5hits_x2.npassed} eff : {shmsDC1_6hits_x2.npassed/shmsDC1_5hits_x2.npassed}
+
+
+shmsDC2x1Planes5	  Counts: {shmsDC2_5hits_x1.npassed} eff : {shmsDC2_6hits_x1.npassed/shmsDC2_5hits_x1.npassed}
+shmsDC2u1Planes5	  Counts: {shmsDC2_5hits_u1.npassed} eff : {shmsDC2_6hits_u1.npassed/shmsDC2_5hits_u1.npassed}
+shmsDC2u2Planes5	  Counts: {shmsDC2_5hits_u2.npassed} eff : {shmsDC2_6hits_u2.npassed/shmsDC2_5hits_u2.npassed}
+shmsDC2v1Planes5	  Counts: {shmsDC2_5hits_v1.npassed} eff : {shmsDC2_6hits_v1.npassed/shmsDC2_5hits_v1.npassed}
+shmsDC2v2Planes5	  Counts: {shmsDC2_5hits_v2.npassed} eff : {shmsDC2_6hits_v2.npassed/shmsDC2_5hits_v2.npassed}
+shmsDC2x2Planes5	  Counts: {shmsDC2_5hits_x2.npassed} eff : {shmsDC2_6hits_x2.npassed/shmsDC2_5hits_x2.npassed}
+	       	   	       
+
+*****************************
+*shms TRACKING EFFICIENCIES *
+*****************************
+htrig                          :   {shmscoin_event.npassed}
+hhitslt = passed hits/cham     :   {shmsHitsLt.npassed}
+hhitsplanes = +planes >= 5/6   :   {shmsHitsPlanes.npassed}
+hhitsplanessps = + sps         :   {hSpacePoints.npassed}
+hhitsplanesspsstubs +stub      :   {hSpacePointsStub.npassed}
+hsfoundtrack                   :   {hFoundTrack.npassed}
+hscleantrack                   :   {hCleanTrack.npassed}
+hstublt = passed stub tests    :   {hStubLT.npassed}
+h1hitslt                       :   {shms1HitsLt.npassed}
+h2hitslt                       :   {shms2HitsLt.npassed}
+h1planesgt                     :   {shmsDC1PlanesGT.npassed}
+h2planesgt                     :   {shmsDC2PlanesGT.npassed}
+hplanesgt = gt 5 planes/cham   :   {shmsPlanesGT.npassed}
+f1hspacepoints                 :   {f1HSpacePoints.npassed}
+f2hspacepoints                 :   {f2HSpacePoints.npassed}
+htest1=p hits/planes, f sp     :   {hTest1.npassed}
+htest2=p sp, f stubs           :   {hTest2.npassed}
+hdid                           :   {shmsScinDid.npassed}
+hdide                          :   {shmsScinDide.npassed}
+hdidh                          :   {shmsScinDidh.npassed}
+hscinshould                    :   {shmsScinShould.npassed}
+hscinshoulde                   :   {shmsScinShoulde.npassed}
+hscinshouldh                   :   {shmsScinShouldh.npassed}
+SING FID TRACK EFFIC           : {shmsScinDid.npassed/(shmsScinShould.npassed+0.0001):%8.4f} +- {(sqrt(shmsScinShould.npassed-shmsScinDid.npassed)/(shmsScinShould.npassed+.0001)):%8.4f}
+E SING FID TRACK EFFIC         : {shmsScinDide.npassed/(shmsScinShoulde.npassed+0.0001):%8.4f} +- {(sqrt(shmsScinShoulde.npassed-shmsScinDide.npassed)/(shmsScinShoulde.npassed+.0001)):%8.4f}
+HADRON SING FID TRACK EFFIC    : {shmsScinDidh.npassed/(shmsScinShouldh.npassed+0.0001):%8.4f} +- {(sqrt(shmsScinShouldh.npassed-shmsScinDidh.npassed)/(shmsScinShouldh.npassed+.0001)):%8.4f}
-- 
GitLab