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

  1 saw   1.1       SUBROUTINE h_track_tests
  2           * 
  3           *  Derek made this in Mar 1996
  4           *
  5           *  This routine delivers some handy tracking information.  It's divided
  6           *  into three parts.  The first part looks at the chambers and their
  7           *  efficiency.  The second part defines some scintillator tests to determine
  8           *  whether the chambers should have fired.  The last part puts this info
  9           *  into different files.  Also, if you want to look at the stub tests you
 10           *  you can uncomment some lines in h_link_stubs.f to get that output.
 11           *  A final note.  Many of these tests have similar counterparts in 
 12           *  trackeff.test;  if you change something here, make sure it agrees with the
 13           *  the tests there!!
 14           *
 15 saw   1.2 * $Log: h_track_tests.f,v $
 16 jones 1.4 * Revision 1.3  2002/09/26 14:50:10  jones
 17           *    Add variables sweet1xscin,sweet1yscin,sweet2xscin,sweet2yscin
 18           *    which record which scint got hit inside the defined scint region
 19           *    Then hgoodscinhits is set to zero if front and back hodoscopes
 20           *    are abs(sweet1xscin-sweet2xscin).gt.3 or bs(sweet1yscin-sweet2yscin).gt.2
 21           *
 22 jones 1.3 * Revision 1.2  1996/09/04 13:39:02  saw
 23           * (JRA) Treat logicals as logicals
 24           *
 25 saw   1.2 * Revision 1.1  1996/05/01 20:24:29  saw
 26           * Initial revision
 27           *
 28 saw   1.1        IMPLICIT NONE
 29                  SAVE
 30 jones 1.3 
 31 saw   1.1        character*50 here
 32                  parameter (here= 'H_TRACK_TESTS')
 33 jones 1.3 
 34 saw   1.1 *       logical ABORT
 35           *       character*(*) err
 36           *       integer*4 ierr
 37           *       character*5  line_err
 38           *
 39                  INCLUDE 'hms_data_structures.cmn'
 40                  INCLUDE 'coin_data_structures.cmn'
 41                  INCLUDE 'gen_constants.par'
 42                  INCLUDE 'hms_tracking.cmn'
 43                  INCLUDE 'gen_units.par'
 44                  INCLUDE 'gen_event_info.cmn'
 45                  INCLUDE 'hms_scin_tof.cmn'
 46                  INCLUDE 'hms_scin_parms.cmn'
 47                  INCLUDE 'hms_calorimeter.cmn'
 48                  include 'hms_bypass_switches.cmn'
 49           
 50                  integer planetemp
 51                  real*4 htestbeta
 52                  integer txth,txthp,txthps,txthpss,txtft,txtct
 53           
 54                  integer i,j,count
 55 saw   1.1        integer testsum
 56                  integer hhitsweet1x,hhitsweet1y,hhitsweet2x,hhitsweet2y
 57 jones 1.3        integer sweet1xscin,sweet1yscin,sweet2xscin,sweet2yscin
 58 saw   1.1 
 59                  real*4 lastcointime
 60                  real*4 thiscointime
 61           
 62           *In c_keep_results, the cointime is updated depending on tracking information
 63           *Because we're independent of tracking here, we have to do some tricks to
 64           *update the cointime.  We set cointime=100.0 if the code hasn't updated it (ie,
 65           *it's the same as the previous event...)  First, if it's not a coincidence
 66           *event, we just set the cointime to zero.
 67           
 68                  thiscointime=0.0
 69                  if (gen_event_type.eq.3) then
 70                     thiscointime=ccointime_hms
 71                     if (thiscointime.eq.lastcointime) then
 72                        thiscointime=100.0
 73                     endif
 74                     lastcointime=ccointime_hms
 75                  endif
 76           
 77           
 78           *this next file prints out events the fail to track and why.  You can then
 79 saw   1.1 *look at them with the event display to see if they're worrisome.  If you
 80           *uncomment this line, be sure to uncomment the close statement at the end
 81           *of this file!
 82                  if (hbypass_track_eff_files.eq.0) then
 83                     open(unit=12,file='scalers/htrackeff.txt',status='unknown',
 84                $         access='append')
 85                  endif
 86 jones 1.3 
 87 saw   1.1 *this next file outputs a huge ascii file with many tracking parameters.  It
 88           *is intended for use with physica.  The order of the ouput is given in the write
 89           *statement at the end of this file.  I fyou uncomment this line, be sure to
 90           *uncomment the close statement at the end of this file!
 91                  if (hbypass_track_eff_files.eq.0) then
 92                     open(unit=14,file='scalers/htrack.out',status='unknown',
 93                $         access='append')
 94                  endif
 95           
 96           *we start by looking at the chambers.  First, we look to see if each plane fired
 97           
 98                  h1hit1 = (HDC_HITS_PER_PLANE(1).GE.1)
 99                  h1hit2 = (HDC_HITS_PER_PLANE(2).GE.1)
100                  h1hit3 = (HDC_HITS_PER_PLANE(3).GE.1)
101                  h1hit4 = (HDC_HITS_PER_PLANE(4).GE.1)
102                  h1hit5 = (HDC_HITS_PER_PLANE(5).GE.1)
103                  h1hit6 = (HDC_HITS_PER_PLANE(6).GE.1)
104                  h1hit7 = (HDC_HITS_PER_PLANE(7).GE.1)
105                  h1hit8 = (HDC_HITS_PER_PLANE(8).GE.1)
106                  h1hit9 = (HDC_HITS_PER_PLANE(9).GE.1)
107                  h1hit10 = (HDC_HITS_PER_PLANE(10).GE.1)
108 saw   1.1        h1hit11 = (HDC_HITS_PER_PLANE(11).GE.1)
109                  h1hit12 = (HDC_HITS_PER_PLANE(12).GE.1)
110           
111           *next, we see how many hits per plane there were ...
112           
113                  hnumhit1 = HDC_HITS_PER_PLANE(1)
114                  hnumhit2 = HDC_HITS_PER_PLANE(2)
115                  hnumhit3 = HDC_HITS_PER_PLANE(3)
116                  hnumhit4 = HDC_HITS_PER_PLANE(4)
117                  hnumhit5 = HDC_HITS_PER_PLANE(5)
118                  hnumhit6 = HDC_HITS_PER_PLANE(6)
119                  hnumhit7 = HDC_HITS_PER_PLANE(7)
120                  hnumhit8 = HDC_HITS_PER_PLANE(8)
121                  hnumhit9 = HDC_HITS_PER_PLANE(9)
122                  hnumhit10 = HDC_HITS_PER_PLANE(10)
123                  hnumhit11 = HDC_HITS_PER_PLANE(11)
124                  hnumhit12 = HDC_HITS_PER_PLANE(12)
125           
126                  hnumhits1 = HDC_HITS_PER_PLANE(1) + HDC_HITS_PER_PLANE(2) +
127                $      HDC_HITS_PER_PLANE(3) + HDC_HITS_PER_PLANE(4) +
128                $      HDC_HITS_PER_PLANE(5) + HDC_HITS_PER_PLANE(6) 
129 saw   1.1 
130                  hnumhits2 = HDC_HITS_PER_PLANE(7) + HDC_HITS_PER_PLANE(8) +
131                $      HDC_HITS_PER_PLANE(9) + HDC_HITS_PER_PLANE(10) +
132                $      HDC_HITS_PER_PLANE(11) + HDC_HITS_PER_PLANE(12) 
133           
134           *next we check to see if we have fewer than the max allowed hits per chamber
135           *this number should agree with the value in trackeff.test.
136           
137                  h1hitslt = hnumhits1.LE.hmax_pr_hits(1)
138                  h2hitslt = hnumhits2.LE.hmax_pr_hits(2)
139           
140           *next we check to see if we have the minimum number of planes per chamber
141           *this number should agree with the value in trackeff.test.
142           
143                  planetemp = 0
144                  if(HDC_HITS_PER_PLANE(1).GE.1) planetemp = planetemp+1
145                  if(HDC_HITS_PER_PLANE(2).GE.1) planetemp = planetemp+1
146                  if(HDC_HITS_PER_PLANE(3).GE.1) planetemp = planetemp+1
147                  if(HDC_HITS_PER_PLANE(4).GE.1) planetemp = planetemp+1
148                  if(HDC_HITS_PER_PLANE(5).GE.1) planetemp = planetemp+1
149                  if(HDC_HITS_PER_PLANE(6).GE.1) planetemp = planetemp+1
150 saw   1.1        hnumplanes1 = planetemp
151                  planetemp = 0
152                  if(HDC_HITS_PER_PLANE(7).GE.1) planetemp = planetemp+1
153                  if(HDC_HITS_PER_PLANE(8).GE.1) planetemp = planetemp+1
154                  if(HDC_HITS_PER_PLANE(9).GE.1) planetemp = planetemp+1
155                  if(HDC_HITS_PER_PLANE(10).GE.1) planetemp = planetemp+1
156                  if(HDC_HITS_PER_PLANE(11).GE.1) planetemp = planetemp+1
157                  if(HDC_HITS_PER_PLANE(12).GE.1) planetemp = planetemp+1
158                  hnumplanes2 = planetemp
159           
160                  h1planesgt = hnumplanes1.GE.hmin_hit(1)
161                  h2planesgt = hnumplanes2.GE.hmin_hit(2)
162           
163           
164           *we now fill in the chamber part of the track tests.
165           
166                  hfoundtrack = (hntracks_fp.NE.0)
167 saw   1.2        if (hfoundtrack) then
168                     htestbeta=hsbeta
169                  else
170 saw   1.1           htestbeta=0.0
171                  endif
172                  hcleantrack = (hsnum_fptrack.NE.0)
173           *hhitslt is less than max allowed hits in both chambers
174                  hhitslt = h1hitslt.AND.h2hitslt
175           *hplanesgt is at least the minimum number of planes fired per chamber
176                  hplanesgt = h1planesgt.AND.h2planesgt
177           *hspacepoints is finding at least one space point in both chambers
178                  hspacepoints = ((hnspace_points(1).GE.1).AND.(hnspace_points(2).GE.1))
179           *hstublt is passing the stub criteria for at least one spacepoint in both chambers
180 saw   1.2        hstublt = (hstubtest.ne.0)
181 saw   1.1 *hhitsplanes is passing not too many hits and not too few planes
182                  hhitsplanes = hhitslt.AND.hplanesgt
183           *hhitsplanes is that and finding a spacepoint
184                  hhitsplanessps = hhitsplanes.AND.hspacepoints
185           *hhitsplanesspsstubs is that and passing the stub tests
186                  hhitsplanesspsstubs = hhitsplanessps.AND.hstublt
187           *fXhspacepoints is pasisng htis and planes but failing to find a space point
188                  f1hspacepoints = h1hitslt.AND.h1planesgt.AND.(hnspace_points(1).EQ.0)
189                  f2hspacepoints = h2hitslt.AND.h2planesgt.AND.(hnspace_points(2).EQ.0)
190                  fhspacepoints = f1hspacepoints.OR.f2hspacepoints
191 saw   1.2        htest1 = (hhitsplanes.AND.(.not.hspacepoints))
192                  htest2 = (hspacepoints.AND.(.not.hstublt))
193 saw   1.1 
194           ************************now look at some hodoscope tests
195           *second, we move the scintillators.  here we use scintillator cuts to see
196           *if a track should have been found.
197           
198                  hnumscins1 = hscin_hits_per_plane(1)
199                  hnumscins2 = hscin_hits_per_plane(2)
200                  hnumscins3 = hscin_hits_per_plane(3)
201                  hnumscins4 = hscin_hits_per_plane(4)
202           
203           *first, fill the arrays of which scins were hit
204                  do i=1,4
205                     do j=1,hscin_1x_nr
206                        hscinhit(i,j)=0
207                     enddo
208                  enddo
209                  do i=1,hscin_tot_hits
210                     hscinhit(hscin_plane_num(i),hscin_counter_num(i))=1
211                  enddo
212           
213           
214 saw   1.1 *next, look for clusters of hits in a scin plane.  a cluster is a group of 
215           *adjacent scintillator hits separated by a non-firing scintillator.
216           *Wwe count the number of three adjacent scintillators too.  (A signle track 
217           *shouldn't fire three adjacent scintillators.
218                  do i=1,hnum_scin_planes
219                     hnclust(i)=0
220                     hthreescin(i)=0
221                  enddo
222           
223           *look for clusters in x planes... (16 scins)  !this assume both x planes have same
224           *number of scintillators.
225                  do j=1,3,2
226                     count=0
227                     if (hscinhit(j,1).EQ.1) count=count+1
228                     do i=1,(hscin_1x_nr-1)         !look for number of clusters of 1 or more hits
229                        if ((hscinhit(j,i).EQ.0).AND.(hscinhit(j,i+1).EQ.1)) count=count+1
230                     enddo
231                     hnclust(j)=count
232                     count=0
233                     do i=1,(hscin_1x_nr-2)         !look for three or more adjacent hits
234                        if ((hscinhit(j,i).EQ.1).AND.(hscinhit(j,i+1).EQ.1).AND.
235 saw   1.1      $            (hscinhit(j,i+2).EQ.1)) count=count+1
236                     enddo
237                     if (count.GT.0) hthreescin(j)=1
238                  enddo
239           *look for clusters in y planes... (10 scins)  !this assume both y planes have same
240           *number of scintillators.
241                  do j=2,4,2
242                     count=0
243                     if (hscinhit(j,1).EQ.1) count=count+1
244                     do i=1,(hscin_1y_nr-1)         !look for number of clusters of 1 or more hits
245                        if ((hscinhit(j,i).EQ.0).AND.(hscinhit(j,i+1).EQ.1)) count=count+1
246                     enddo
247                     hnclust(j)=count
248                     count=0
249                     do i=1,(hscin_1y_nr-2)         !look for three or more adjacent hits
250                        if ((hscinhit(j,i).EQ.1).AND.(hscinhit(j,i+1).EQ.1).AND.
251                $            (hscinhit(j,i+2).EQ.1)) count=count+1
252                     enddo
253                     if (count.GT.0) hthreescin(j)=1
254                  enddo
255           
256 saw   1.1 *now put some "tracking" like cuts on the hslopes, based only on scins...
257           *by "slope" here, I mean the difference in the position of scin hits in two
258           *like-planes.  For example, a track that those great straight through will 
259           *have a slope of zero.  If it moves one scin over from s1x to s2x it has an
260           *x-slope of 1...  I pick the minimum slope if there are multiple scin hits.
261                  hbestxpscin=100
262                  hbestypscin=100
263                  do i=1,hscin_1x_nr
264                     do j=1,hscin_1x_nr
265                        if ((hscinhit(1,i).EQ.1).AND.(hscinhit(3,j).EQ.1)) then
266                           hslope=abs(i-j)
267                           if (hslope.LT.hbestxpscin) hbestxpscin=hslope
268                        endif
269                     enddo
270                  enddo
271                  do i=1,hscin_1y_nr
272                     do j=1,hscin_1y_nr
273                        if ((hscinhit(2,i).EQ.1).AND.(hscinhit(4,j).EQ.1)) then
274                           hslope=abs(i-j)
275                           if (hslope.LT.hbestypscin) hbestypscin=hslope
276                        endif
277 saw   1.1           enddo
278                  enddo
279           
280           *next we mask out the edge scintillators, and look at triggers that happened
281           *at the center of the acceptance.  To change which scins are in the mask
282           *change the values of h*loscin and h*hiscin in htracking.param
283                  hhitsweet1x=0
284                  hhitsweet1y=0
285                  hhitsweet2x=0
286                  hhitsweet2y=0
287                  hgoodscinhits=0
288           *first x plane.  first see if there are hits inside the scin region
289                  do i=hxloscin(1),hxhiscin(1)
290 jones 1.3           if (hscinhit(1,i).EQ.1) then
291                        hhitsweet1x=1
292                        sweet1xscin=i
293                     endif
294 saw   1.1        enddo
295           *second x plane.  first see if there are hits inside the scin region
296                  do i=hxloscin(2),hxhiscin(2)
297 jones 1.3           if (hscinhit(3,i).EQ.1) then
298                        hhitsweet2x=1
299                        sweet2xscin=i
300                     endif
301 saw   1.1        enddo
302           
303           *first y plane.  first see if there are hits inside the scin region
304                  do i=hyloscin(1),hyhiscin(1)
305 jones 1.3           if (hscinhit(2,i).EQ.1) then
306                        hhitsweet1y=1
307                        sweet1yscin=i
308                     endif
309 saw   1.1        enddo
310           *second y plane.  first see if there are hits inside the scin region
311                  do i=hyloscin(2),hyhiscin(2)
312 jones 1.3           if (hscinhit(4,i).EQ.1) then
313                        hhitsweet2y=1
314                        sweet2yscin=i
315                     endif
316 saw   1.1        enddo
317           
318                  testsum=hhitsweet1x+hhitsweet1y+hhitsweet2x+hhitsweet2y
319           * now define a 3/4 or 4/4 trigger of only good scintillators the value
320           * is specified in htracking.param...
321 jones 1.3        if (testsum.GE.htrack_eff_test_num_scin_planes) hgoodscinhits=1
322           
323 saw   1.1 
324           *******************************************************************************
325           *     Here's where we start writing to the files.  Uncomment these lines and
326           *     the corresponding file open and close lines at the beginning and end
327           *     of this file if you want this output.  the scaler report should take
328           *     care of most people though...
329           
330           *
331                  if (hbypass_track_eff_files.eq.0) then
332                     if (hgoodscinhits.EQ.1) then
333                        write(12,*) 'sweet spot hit, event number           ',gen_event_ID_number
334                     endif
335 saw   1.2           if (.not.hhitslt) then
336 saw   1.1              write(12,*) 'too many hits, event number           ',gen_event_ID_number
337                     endif
338 saw   1.2           if (.not.hplanesgt) then
339 saw   1.1              write(12,*)  'too few planes event number                    ',
340                $            gen_event_ID_number
341                     endif
342 saw   1.2           if (hhitsplanes.AND.(.not.hspacepoints)) then
343 saw   1.1              write(12,*) 'p hits/planes, f sp # = ',gen_event_ID_number
344                     endif
345 saw   1.2           if ((.not.hfoundtrack).AND.hhitsplanessps) then
346 saw   1.1              write(12,*) 'p hits/planes/sps, f track # = ',gen_event_ID_number
347                     endif
348 saw   1.2           if (hspacepoints.AND.(.not.hstublt)) then
349 saw   1.1              write(12,*) 'p sp, f stubs # = ',gen_event_ID_number
350                     endif
351                  endif
352           
353                  
354           *the rest of this file prepares the output of htrack.out.  If you're not
355           *writing to that file, don't worry about this.
356           
357                  if (hbypass_track_eff_files.eq.0) then
358                     txth=0
359                     if (hhitslt) txth=1
360                     txthp=0
361                     if (hhitsplanes) txthp=1
362                     txthps=0
363                     if (hhitsplanessps) txthps=1
364                     txthpss=0
365                     if (hhitsplanesspsstubs) txthpss=1        
366                     txtft=0
367                     if (hfoundtrack) txtft=1
368                     txtct=0
369                     if (hcleantrack) txtct=1
370 saw   1.1           
371                     write(14,902) gen_event_ID_number,hnumhits1,hnumhits2,
372                $         hnumhit1,hnumhit2,hnumhit3,hnumhit4,
373                $         hnumhit5,hnumhit6,hnumhit7,hnumhit8,
374                $         hnumhit9,hnumhit10,hnumhit11,hnumhit12,
375                $         hnumplanes1,hnumplanes2,hnumscins1,hnumscins2,
376                $         hnumscins3,hnumscins4,hnclust(1),hnclust(2),
377                $         hnclust(3),hnclust(4),hthreescin(1),hthreescin(2),
378                $         hthreescin(3),hthreescin(4),hbestxpscin,hbestypscin,
379                $         hgoodscinhits,
380                $         txtft,txtct,hntracks_fp,hbeta_notrk,htestbeta,hcal_et,
381                $         hsshtrk,
382                $         hcer_npe_sum,hschi2perdeg,hsdelta,thiscointime
383            902      format(1x,i6,i4,i4,12(i4),2(i2),4(i3),8(i2),2(i4),i2,i2,i2,i2,f10.3,f9.3,
384                $         f9.3,f9.3,f9.3,f10.3,f10.3,f10.3)
385                     
386                     close(12)
387                     close(14)
388                 endif
389                 end

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