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

 1 cdaq  1.1       subroutine h_choose_single_hit(ABORT,err,nspace_points,
 2                &       space_point_hits)
 3           *--------------------------------------------------------
 4           *-
 5           *-   Purpose and Methods :  This routine looks at all hits in a space
 6           *-                          point. If two hits are in the same plane it
 7           *-                          rejects the one with the longer drift time
 8           *-
 9           *-
10           *-   Output: ABORT           - success or failure
11           *-         : err             - reason for failure, if any
12           *- 
13           *-   Created 28-JUN-1994   D. F. Geesaman
14 cdaq  1.2 * $Log: h_choose_single_hit.f,v $
15 cdaq  1.4 * Revision 1.3  1995/05/22 19:39:07  cdaq
16           * (SAW) Split gen_data_data_structures into gen, hms, sos, and coin parts"
17           *
18 cdaq  1.3 * Revision 1.2  1994/10/11  20:20:52  cdaq
19           * (JRA) Fix bug that allowed two hits on a single plane
20           *
21 cdaq  1.2 * Revision 1.1  1994/06/30  02:40:17  cdaq
22           * Initial revision
23           *
24 cdaq  1.1 *--------------------------------------------------------
25                 IMPLICIT NONE
26                 SAVE
27           *
28                 character*50 here
29                 parameter (here= 'h_choose_single_hit')
30                 integer*4 nspace_points
31           *
32                 logical ABORT
33                 character*(*) err
34           *
35 cdaq  1.3       INCLUDE 'hms_data_structures.cmn'
36 cdaq  1.1       INCLUDE 'gen_constants.par'
37                 INCLUDE 'gen_units.par'
38                 include 'hms_tracking.cmn'
39                 include 'hms_geometry.cmn'
40           
41           *
42                 integer*4 space_point_hits(hmax_space_points,hmax_hits_per_point+2)
43           *
44           *     local variables
45 cdaq  1.2       integer*4 point,startnum,finalnum,goodhit(hmax_dc_hits)
46                 integer*4 plane1,plane2,hit1,hit2,drifttime1,drifttime2
47 cdaq  1.1       integer*4 hits(hmax_hits_per_point)
48                 integer*4 j,k
49                 
50           *
51           *     temporary initialization
52                 ABORT= .FALSE.
53                 err=' '
54           *
55           *
56           *     loop over all space points
57 cdaq  1.4       do point =1,nspace_points
58                   startnum = space_point_hits(point,1)
59                   finalnum=0
60 cdaq  1.2           
61 cdaq  1.4         do j=3,startnum+2
62                     goodhit(j) = 1
63                   enddo
64 cdaq  1.2           
65 cdaq  1.4         do j=3,startnum+1
66                     hit1 = space_point_hits(point,j)
67                     plane1 = hdc_plane_num(hit1)
68                     drifttime1 = hdc_drift_time(hit1)
69                     do k=j+1,startnum+2
70                       hit2 = space_point_hits(point,k)
71                       plane2 = hdc_plane_num(hit2)
72                       drifttime2 = hdc_drift_time(hit2)
73                       if(plane1 .eq. plane2 ) then
74                         if(drifttime1.gt.drifttime2) then
75                           goodhit(j) = 0
76                         else                      !if equal times, choose 1st hit(arbitrary)
77                           goodhit(k) = 0
78                         endif
79                       endif                       ! end test on equal planes
80                     enddo                         ! end loop on k
81                   enddo                           ! end loop on j
82                   do j=3,startnum+2
83                     if(goodhit(j).gt.0) then
84                       finalnum = finalnum + 1
85                       hits(finalnum)=space_point_hits(point,j)
86 cdaq  1.4           endif                         ! end check on good hit
87                   enddo
88 cdaq  1.1 *     copy good hits to space_point_hits
89 cdaq  1.4         space_point_hits(point,1) = finalnum
90                   do j = 1, finalnum
91                     space_point_hits(point,j+2) = hits(j)
92                   enddo                           ! end of copy 
93                 enddo                             ! end loop on space points
94 cdaq  1.2 *     
95 cdaq  1.1       return
96                 end

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