(file) Return to h_scin_eff.f CVS log (file) (dir) Up to [HallC] / Analyzer / HTRACKING

  1 cdaq  1.1       SUBROUTINE H_SCIN_EFF(ABORT,errmsg)
  2           *--------------------------------------------------------
  3           *-
  4           *-   Purpose and Methods : Analyze scintillator information for each track 
  5           *-
  6           *-      Required Input BANKS     HMS_SCIN_TOF
  7           *-                               GEN_DATA_STRUCTURES
  8           *-
  9           *-   Output: ABORT           - success or failure
 10           *-         : err             - reason for failure, if any
 11           *- 
 12           * author: John Arrington
 13           * created: 2/13/95
 14           *
 15           * h_scin_eff calculates efficiencies for the hodoscope.
 16           *
 17 cdaq  1.2 * $Log: h_scin_eff.f,v $
 18 cdaq  1.7.2.1 * Revision 1.7  2002/10/02 13:42:43  saw
 19               * Check that user hists are defined before filling
 20               *
 21 saw   1.7     * Revision 1.6  1996/01/16 21:56:40  cdaq
 22               * (JRA) Fix typos
 23               *
 24 cdaq  1.6     * Revision 1.5  1995/08/31 14:44:42  cdaq
 25               * (JRA) Fill dpos (pos. track - pos. hit) histograms
 26               *
 27 cdaq  1.5     * Revision 1.4  1995/07/19  19:03:27  cdaq
 28               * (SAW) Put nint around some things for Ultrix compat.  Put h in front of
 29               *       various *good variables.
 30               *
 31 cdaq  1.4     * Revision 1.3  1995/05/22  19:39:26  cdaq
 32               * (SAW) Split gen_data_data_structures into gen, hms, sos, and coin parts"
 33               *
 34 cdaq  1.3     * Revision 1.2  1995/05/11  20:27:21  cdaq
 35               * (JRA) Add position calibration variables
 36               *
 37 cdaq  1.2     * Revision 1.1  1995/02/23  13:31:41  cdaq
 38               * Initial revision
 39               *
 40 cdaq  1.1     *--------------------------------------------------------
 41                     IMPLICIT NONE
 42               *
 43                     character*50 here
 44                     parameter (here= 'H_SCIN_EFF')
 45               *
 46                     logical ABORT
 47                     character*(*) errmsg
 48               *
 49 cdaq  1.3           INCLUDE 'hms_data_structures.cmn'
 50 cdaq  1.1           INCLUDE 'gen_constants.par'
 51                     INCLUDE 'gen_units.par'
 52                     include 'hms_scin_parms.cmn'
 53                     include 'hms_scin_tof.cmn'
 54                     include 'hms_statistics.cmn'
 55 cdaq  1.5           include 'hms_id_histid.cmn'
 56 cdaq  1.1     
 57 cdaq  1.7.2.1       integer pln,cnt,pln2
 58 cdaq  1.1           integer hit_cnt(hnum_scin_planes)
 59                     integer nhit
 60 cdaq  1.5           real dist, histval
 61                     real hit_pos(hnum_scin_planes),hit_dist(hnum_scin_planes)
 62 cdaq  1.7.2.1       real xatback,yatback
 63               
 64                     logical good_tdc_oneside(hnum_scin_planes)
 65                     logical good_tdc_bothsides(hnum_scin_planes)
 66                     logical otherthreehit
 67               
 68 cdaq  1.1           save
 69               
 70               * find counters on track, and distance from center.
 71               
 72                     if (hschi2perdeg.le.hstat_maxchisq) hstat_numevents=hstat_numevents+1
 73               
 74                     hit_pos(1)=hsx_fp + hsxp_fp*(hscin_1x_zpos+0.5*hscin_1x_dzpos)
 75                     hit_cnt(1)=nint((hit_pos(1)-hhodo_center(1,1))/hscin_1x_spacing)+1
 76 cdaq  1.4           hit_cnt(1)=max(min(hit_cnt(1),nint(hnum_scin_counters(1))),1)
 77 cdaq  1.1           hit_dist(1)=hit_pos(1)-(hscin_1x_spacing*(hit_cnt(1)-1)+hhodo_center(1,1))
 78               
 79                     hit_pos(2)=hsy_fp + hsyp_fp*(hscin_1y_zpos+0.5*hscin_1y_dzpos)
 80                     hit_cnt(2)=nint((hhodo_center(2,1)-hit_pos(2))/hscin_1y_spacing)+1
 81 cdaq  1.6           hit_cnt(2)=max(min(hit_cnt(2),nint(hnum_scin_counters(2))),1)
 82 cdaq  1.1           hit_dist(2)=hit_pos(2)-(hhodo_center(2,1)-hscin_1y_spacing*(hit_cnt(2)-1))
 83               
 84                     hit_pos(3)=hsx_fp + hsxp_fp*(hscin_2x_zpos+0.5*hscin_2x_dzpos)
 85                     hit_cnt(3)=nint((hit_pos(3)-hhodo_center(3,1))/hscin_2x_spacing)+1
 86 cdaq  1.6           hit_cnt(3)=max(min(hit_cnt(3),nint(hnum_scin_counters(3))),1)
 87 cdaq  1.1           hit_dist(3)=hit_pos(3)-(hscin_2x_spacing*(hit_cnt(3)-1)+hhodo_center(3,1))
 88               
 89                     hit_pos(4)=hsy_fp + hsyp_fp*(hscin_2y_zpos+0.5*hscin_2y_dzpos)
 90                     hit_cnt(4)=nint((hhodo_center(4,1)-hit_pos(4))/hscin_2y_spacing)+1
 91 cdaq  1.6           hit_cnt(4)=max(min(hit_cnt(4),nint(hnum_scin_counters(4))),1)
 92 cdaq  1.1           hit_dist(4)=hit_pos(4)-(hhodo_center(4,1)-hscin_2y_spacing*(hit_cnt(4)-1))
 93               
 94 cdaq  1.7.2.1       do pln=1,hnum_scin_planes
 95                       good_tdc_oneside(pln) = .false.
 96                       good_tdc_bothsides(pln) = .false.
 97                     enddo
 98               
 99               
100 cdaq  1.5     *   Fill dpos (pos. track - pos. hit) histograms
101                     do nhit=1,hscin_tot_hits
102                       pln=hscin_plane_num(nhit)
103                       histval = hhodo_center(pln,hscin_counter_num(nhit))-hit_pos(pln)
104 saw   1.7             if(hidscindpos(pln).gt.0) call hf1(hidscindpos(pln),histval,1.)
105 cdaq  1.5           enddo
106               
107 cdaq  1.2     *   Record position differences between track and center of scin. and
108 cdaq  1.1     *   increment 'should have hit' counters
109                     do pln=1,hnum_scin_planes
110 cdaq  1.2             cnt=hit_cnt(pln)
111                       dist=hit_dist(pln)
112 cdaq  1.5             if(abs(dist).le.hstat_slop .and.    !hit in middle of scin.
113 cdaq  1.1          &           hschi2perdeg.le.hstat_maxchisq) then
114 cdaq  1.2               hstat_trk(pln,cnt)=hstat_trk(pln,cnt)+1
115 cdaq  1.1             endif
116                     enddo
117               
118 cdaq  1.2           do nhit=1,hscin_tot_hits
119 cdaq  1.1             cnt=hscin_counter_num(nhit)
120                       pln=hscin_plane_num(nhit)
121               
122               *  Record the hits if track is near center of track and the chisquared of the 
123               *  track is good.
124                       if(abs(hit_dist(pln)).le.hstat_slop .and. cnt.eq.hit_cnt(pln) .and. 
125                    &          hschi2perdeg.le.hstat_maxchisq) then
126               
127                         if (hgood_tdc_pos(hsnum_fptrack,nhit)) then
128                           if (hgood_tdc_neg(hsnum_fptrack,nhit)) then    !both fired
129                             hstat_poshit(pln,hit_cnt(pln))=hstat_poshit(pln,hit_cnt(pln))+1
130                             hstat_neghit(pln,hit_cnt(pln))=hstat_neghit(pln,hit_cnt(pln))+1
131                             hstat_andhit(pln,hit_cnt(pln))=hstat_andhit(pln,hit_cnt(pln))+1
132                             hstat_orhit(pln,hit_cnt(pln))=hstat_orhit(pln,hit_cnt(pln))+1
133                           else                            !pos fired
134                             hstat_poshit(pln,hit_cnt(pln))=hstat_poshit(pln,hit_cnt(pln))+1
135                             hstat_orhit(pln,hit_cnt(pln))=hstat_orhit(pln,hit_cnt(pln))+1
136                           endif
137                         else   !no pos tdc
138                           if (hgood_tdc_neg(hsnum_fptrack,nhit)) then    !neg fired
139                             hstat_neghit(pln,hit_cnt(pln))=hstat_neghit(pln,hit_cnt(pln))+1
140 cdaq  1.1                   hstat_orhit(pln,hit_cnt(pln))=hstat_orhit(pln,hit_cnt(pln))+1
141                           endif       !if neg tdc fired.
142                         endif       !if pos tdc fired.
143               
144                       endif       !if hit was on good track.
145               
146               
147               *   Increment pos/neg/both fired.  Track indepenant, so no chisquared cut (but
148               *   note that only scintillators on the track are examined.
149               
150                       if (hgood_tdc_pos(hsnum_fptrack,nhit)) then
151                         if (hgood_tdc_neg(hsnum_fptrack,nhit)) then    !both fired
152 cdaq  1.4                 hbothgood(pln,cnt)=hbothgood(pln,cnt)+1
153 cdaq  1.1               else                            !pos fired
154 cdaq  1.4                 hposgood(pln,cnt)=hposgood(pln,cnt)+1
155 cdaq  1.1               endif
156                       else
157                         if (hgood_tdc_neg(hsnum_fptrack,nhit)) then    !neg fired
158 cdaq  1.4                 hneggood(pln,cnt)=hneggood(pln,cnt)+1
159 cdaq  1.1               endif
160                       endif
161               
162                     enddo                 !loop over hsnum_pmt_hit
163 cdaq  1.7.2.1 
164               *  Determine if one or both PMTs had a good tdc.
165                       if (hgood_tdc_pos(hsnum_fptrack,nhit) .and. 
166                    &      hgood_tdc_neg(hsnum_fptrack,nhit) ) good_tdc_bothsides(pln)=.true.
167                       if (hgood_tdc_pos(hsnum_fptrack,nhit) .or. 
168                    &      hgood_tdc_neg(hsnum_fptrack,nhit) ) good_tdc_oneside(pln)=.true.
169               
170                     enddo                 !loop over hsnum_pmt_hit
171               
172               *  For each plane, see of other 3 fired.  This means that they were enough
173               *  to form a 3/4 trigger, and so the fraction of times this plane fired is
174               *  the plane trigger efficiency.  NOTE: we only require a TDC hit, not a
175               *  TDC hit within the SCIN 3/4 trigger window, so high rates will make
176               *  this seem better than it is.  Also, make sure we're not near the edge
177               *  of the hodoscope (at the last plane), using the same hhodo_slop param. as for h_tof.f
178               *  NOTE ALSO: to make this check simpler, we are assuming that all planes
179               *  have identical active areas.  y_scin = y_cent + y_offset, so shift track
180               *  position by offset for comparing to edges.
181               
182                     xatback = hsx_fp+hsxp_fp*hscin_2y_zpos - hscin_2x_offset
183                     yatback = hsy_fp+hsyp_fp*hscin_2y_zpos - hscin_2y_offset
184 cdaq  1.7.2.1 
185                     if ( xatback.lt.(hscin_2y_bot  -2.*hhodo_slop(3))  .and.
186                    &     xatback.gt.(hscin_2y_top  +2.*hhodo_slop(3))  .and.
187                    &     yatback.lt.(hscin_2x_left -2.*hhodo_slop(3))  .and.
188                    &     yatback.gt.(hscin_2x_right+2.*hhodo_slop(3))) then
189               
190                       do pln = 1,hnum_scin_planes
191                         otherthreehit = .true.
192                         do pln2 = 1,hnum_scin_planes	!see of one of the others missed or pln2=pln
193               	    if (.not.(good_tdc_bothsides(pln2) .or. pln2.eq.pln)) then
194               	      otherthreehit = .false.
195               	    endif
196               	  enddo
197               	  if (otherthreehit) then
198               	    htrig_hodoshouldflag(pln) = .true.
199               	    if (good_tdc_bothsides(pln)) then
200                             htrig_hododidflag(pln) = .true.
201               	    else
202                             htrig_hododidflag(pln) = .false.
203               	    endif
204                         else
205 cdaq  1.7.2.1 	    htrig_hodoshouldflag(pln) = .false.
206               	    htrig_hododidflag(pln) = .false.
207               	  endif
208               	enddo
209               
210                     else		!outside of fiducial region
211                       do pln=1,hnum_scin_planes
212                         htrig_hodoshouldflag(pln) = .false.
213                         htrig_hododidflag(pln) = .false.
214                       enddo
215                     endif
216 cdaq  1.1     
217                     return
218                     end

Analyzer/Replay: Mark Jones, Documents: Stephen Wood
Powered by
ViewCVS 0.9.2-cvsgraph-1.4.0