]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ghits/gfhits.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gfhits.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:21:09  cernlib
6 * Geant
7 *
8 *
9 #include "geant321/pilot.h"
10 *CMZ :  3.21/02 29/03/94  15.41.20  by  S.Giani
11 *-- Author :
12       SUBROUTINE GFHITS(IUSET,IUDET,NVDIM,NHDIM,NHMAX,ITRS,NUMVS
13      +,                 ITRA,NUMBV,HITS,NHITS)
14 C.
15 C.    ******************************************************************
16 C.    *                                                                *
17 C.    *                                                                *
18 C.    *   Returns the  hits produced  by track ITRS  (if 0,   by all   *
19 C.    * tracks)  in the physical volume  specified by the list NUMVS   *
20 C.    * with generic volume name IUDET belonging to set IUSET.         *
21 C.    * IUSET     user set identifier                                  *
22 C.    * IUDET     user    detector   identifier    (name   of    the   *
23 C.    *           corresponding sensitive volume)                      *
24 C.    * NVDIM     1st dimension of NUMBV and NUMVS (usually =NV, the   *
25 C.    *           number of volume descriptors which permit to identify*
26 C.    *           a given detector, eventually smaller than  NV)       *
27 C.    * NHDIM     1st  dimension  of  array  HITS  (argument  NH  of   *
28 C.    *           GSDETH)                                              *
29 C.    * NHMAX     maximum number of hits to be returned                *
30 C.    * ITRS      number of  the selected  track.   If  ITRS=0,  all   *
31 C.    *           tracks are taken                                     *
32 C.    * NUMVS     is a  1-Dim array that  must contain on  input the   *
33 C.    *           geometric  path  of  the  detector  volume  to  be   *
34 C.    *           selected.    All 0  interpreted  as 'all  physical   *
35 C.    *           volumes with generic names IUDET'                    *
36 C.    * ITRA      is a 1-Dim  array that will contain  on output for   *
37 C.    *           each  hit  the  number  of  the  track  which  has   *
38 C.    *           produced it                                          *
39 C.    * NUMBV     2-Dim array that  will contain on output  for each   *
40 C.    *           hit the list of volume numbers which identify each   *
41 C.    *           physical volume.   Zeroed when no more volumes are   *
42 C.    *           stored                                               *
43 C.    * HITS      2-Dim array that will contain the NHITS hits         *
44 C.    * NHITS     returns the number of selected  hits.  In case the   *
45 C.    *           total number of hits is greater than NHMAX,  NHITS   *
46 C.    *           is set to NHMAX+1 and only NHMAX hits are returned   *
47 C.    *   - HITS(1,I)  is the element 1 for hit number I               *
48 C.    *   - NUMBV(1,I) is the volume number 1 for hit number I         *
49 C.    *   - ITRA(I)    is  the  track number  corresponding  to  hit   *
50 C.    * number I                                                       *
51 C.    *   In the calling routine the arrays NUMVS,  NUMBV,  HITS and   *
52 C.    * ITRA must be dimensioned to:                                   *
53 C.    *     NUMVS(NVDIM)                                               *
54 C.    *     NUMBV(NVDIM,NHMAX)                                         *
55 C.    *     HITS(NHDIM,NHMAX)                                          *
56 C.    *     ITRA(NHMAX)                                                *
57 C.    *                                                                *
58 C.    *    ==>Called by : <USER>, GUDIGI                               *
59 C.    *       Author    R.Brun  *********                              *
60 C.    *                                                                *
61 C.    ******************************************************************
62 C.
63 #include "geant321/gcbank.inc"
64       PARAMETER (NVMAX=20)
65       DIMENSION NUMVT(NVMAX),NUMVS(NVDIM),NUMBV(NVDIM,1),ITRA(1)
66       DIMENSION HITS(NHDIM,1)
67       EQUIVALENCE (WS(1),NUMVT(1))
68       CHARACTER*4 IUSET,IUDET
69 C.
70 C.    ------------------------------------------------------------------
71 C.
72 C             Find if selected set, detector exists
73 C
74       NHITS=0
75       IF(JHITS.LE.0)GO TO 999
76       NSET=IQ(JSET-1)
77       CALL GLOOK(IUSET,IQ(JSET+1),NSET,ISET)
78       IF(ISET.LE.0)GO TO 999
79 C
80       JS=LQ(JSET-ISET)
81       JH=LQ(JHITS-ISET)
82       IF(JS.LE.0)GO TO 999
83       IF(JH.LE.0)GO TO 999
84       NDET=IQ(JS-1)
85       CALL GLOOK(IUDET,IQ(JS+1),NDET,IDET)
86       IF(IDET.EQ.0)GO TO 999
87 C
88       JD=LQ(JS-IDET)
89       JHD=LQ(JH-IDET)
90       IF(JHD.LE.0)GO TO 999
91       JDH=LQ(JD-1)
92 C
93       ILAST=IQ(JH+IDET)
94       IF(ILAST.EQ.0)GO TO 999
95       NV=IQ(JD+2)
96       NH=IQ(JD+4)
97       NW=IQ(JD+1)+IQ(JD+3)+1
98 C
99 C
100 C             Loop on all hits
101 C
102 C
103       IHIT=0
104       DO 100 I=1,ILAST,NW
105 C
106 C             Find the selected track
107 C
108       ITRT=IQ(JHD+I)
109       IF(ITRS.NE.0 .AND. ITRS.NE.ITRT)GO TO 100
110 C
111 C             Find the selected volume
112 C             (if NO volumes exist take ALL hits)
113 C
114       NK=1
115       IF(NV.GT.0)THEN
116          K=1
117          DO 40 IV=1,NV
118             NB=IQ(JD+2*IV+10)
119             IF(NB.LE.0)THEN
120                IF(K.GT.1)THEN
121                    K=1
122                    NK=NK+1
123                ENDIF
124                IF(IV.LE.NVMAX)NUMVT(IV)=IQ(JHD+I+NK)
125                IF(IV.NE.NV)NK=NK+1
126             ELSE
127                IF(K+NB.GT.33)THEN
128                  K=1
129                  NK=NK+1
130                ENDIF
131                IF(IV.LE.NVMAX)NUMVT(IV)=IBITS(IQ(JHD+I+NK),K-1,NB)
132                K=K+NB
133             ENDIF
134             IF(IV.LE.NVDIM)THEN
135                IF(NUMVS(IV).NE.0)THEN
136                   IF(NUMVS(IV).NE.NUMVT(IV))GO TO 100
137                ENDIF
138             ENDIF
139    40    CONTINUE
140          NK=NK+1
141       ENDIF
142 C
143 C
144 C
145 C ========>   Now store track number and volume numbers and fetch hits
146 C
147       IHIT=IHIT+1
148       IF(IHIT.GT.NHMAX)GO TO 110
149 C
150       ITRA(IHIT)=ITRT
151       NVMIN=MIN(NV,NVDIM)
152       DO 55 J=1,NVDIM
153   55  NUMBV(J,IHIT)=0
154       DO 57 J=1,NVMIN
155   57  NUMBV(J,IHIT)=NUMVT(J)
156 C
157 C             Get unpacked hits
158 C             Hits origin is shifted . Division by scale factor
159 C
160       IF(NH.GT.0)THEN
161       K=1
162       DO 90 IH=1,NH
163          NB=IQ(JDH+4*IH-2)
164          IF(NB.LE.0)THEN
165             IF(K.GT.1)THEN
166                 K=1
167                 NK=NK+1
168             ENDIF
169             KHIT=IQ(JHD+I+NK)
170             NK=NK+1
171          ELSE
172             IF(K+NB.GT.33)THEN
173                K=1
174                NK=NK+1
175             ENDIF
176             KHIT=IBITS(IQ(JHD+I+NK),K-1,NB)
177             K=K+NB
178          ENDIF
179          IF(IH.LE.NHDIM)THEN
180             HITS(IH,IHIT)=FLOAT(KHIT)/Q(JDH+4*IH) - Q(JDH+4*IH-1)
181          ENDIF
182   90  CONTINUE
183       ENDIF
184  100  CONTINUE
185 C
186  110  NHITS=IHIT
187 C
188  999  RETURN
189       END