]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ghits/gsdet.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gsdet.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:11 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 GSDET(IUSET,IUDET,NV,NAMESV,NBITSV,IDTYPE
13 + ,NWHI,NWDI,ISET,IDET)
14C.
15C. ******************************************************************
16C. * *
17C. * Defines volume parameters for detector IUDET of set IUSET*
18C. * *
19C. * Input parameters *
20C. * IUSET set identifier (4 characters), user defined *
21C. * IUDET detector identifier (4 characters), name of an *
22C. * existing volume *
23C. * NV number of volume descriptors *
24C. * NAMESV vector of NV volume descriptors (4 characters) *
25C. * NBITSV vector of NV bit numbers for packing the volume *
26C. * numbers *
27C. * IDTYPE detector type, user defined *
28C. * NWHI number of words for the primary allocation of HITS *
29C. * banks *
30C. * NWDI number of words for the primary allocation of DIGI *
31C. * banks when first allocation not sufficient *
32C. * *
33C. * Output parameters *
34C. * ISET position of set in bank JSET *
35C. * IDET position of detector in bank JS=IB(JSET-ISET) *
36C. * If ISET=0 or IDET=0 error *
37C. * Remarks: *
38C. * - The vector NAMESV (length NV) contains the list of volume *
39C. * names which permit the identification of every physical *
40C. * detector with detector name IUDET. [See example in HITS *
41C. * 110]. *
42C. * - Each element of the vector NBITSV (length NV) is the *
43C. * number of bits used for packing the number of the *
44C. * corresponding volume, when building the packed identifier *
45C. * of a given physical detector. *
46C. * - For more details see the example given in GSDETH. *
47C. * - The detector type IDTYPE is not used internally by GEANT *
48C. * and can be defined by the user to distinguish quickly *
49C. * between various kinds of detectors, in the routine GUSTEP *
50C. * for example. *
51C. * *
52C. * IQ(JSET+ISET) = IUSET *
53C. * JS = LQ(JSET-ISET) + pointer to set parameters *
54C. * IQ(JS+IDET)=IUDET *
55C. * JD= LQ(JS-1) = pointer to detector IDET *
56C. * IQ(JD+1)=Total number of words to store packed volumes *
57C. * IQ(JD+2)=NV *
58C. * IQ(JD+3)=Number of words required per hit *
59C. * IQ(JD+4)=Number of different hits types *
60C. * IQ(JD+5)=Number of words required per digit *
61C. * IQ(JD+6)=Number of different digit types *
62C. * IQ(JD+7)=NWHI *
63C. * IQ(JD+8)=NWDI *
64C. * IQ(JD+9)=Number of paths through the JVOLUM tree *
65C. * IQ(JD+10)= For an alias only, IDET of main detector *
66C. * IQ(JD+2*I+9) = name of volume i = NAMESV(I) *
67C. * IQ(JD+2*I+10)= number of bits/volume = NBITSV(I) *
68C. * *
69C. * The Detector Set data structure JSET *
70C. * ------------------------------------ *
71C. * *
72C. * | JSET *
73C. * NSET ISET v NSET *
74C. * ................................................ *
75C. * | | | | | Set names| *
76C. * ................................................ *
77C. * | JS *
78C. * | *
79C. * NDET IDET v NDET *
80C. * ........................................ *
81C. * | | | | | Detector names | *
82C. * ........................................ *
83C. * | JD *
84C. * -3 -2 -1 v *
85C. * ................................................ *
86C. * | | | | | Parameters of GSDET | *
87C. * ................................................ *
88C. * | | | *
89C. * | | | JDH *
90C. * | | | *
91C. * | | | ............................. *
92C. * | | ............| Parameters of GSDETH | *
93C. * | | ............................. *
94C. * | | *
95C. * | | JDD *
96C. * | | *
97C. * | | ............................. *
98C. * | ...............| Parameters of GSDETD | *
99C. * | ............................. *
100C. * | *
101C. * | JDU *
102C. * | ............................. *
103C. * ..................| Parameters of GSDETU | *
104C. * ............................. *
105C. * JS = LQ(JSET-ISET) pointer to detector set number ISET *
106C. * The JSET data structure is filled by GSDET, GSDETH, GSDETD, *
107C. * GSDETU and eventually by GSDETA. *
108C. * *
109C. * ==>Called by : <USER>, UGEOM *
110C. * Author R.Brun ********* *
111C. * *
112C. ******************************************************************
113C.
114#include "geant321/gcbank.inc"
115#include "geant321/gcunit.inc"
116#include "geant321/gcmzfo.inc"
117 PARAMETER (NVMAX=20)
118 DIMENSION NBITSV(1),NAV(NVMAX)
119 CHARACTER*4 NAMESV,IUSET,IUDET
120 EQUIVALENCE (WS(1),NAV(1))
121C.
122C. ------------------------------------------------------------------
123C.
124 ISET=0
125 IDET=0
126 IF(NV.GT.15)GO TO 94
127C
128C Check if volume IUDET has been defined
129C
130 IF(JVOLUM.LE.0)GO TO 90
131 NVOLUM=IQ(JVOLUM-1)
132 CALL GLOOK(IUDET,IQ(JVOLUM+1),NVOLUM,IVOL)
133 IF(IVOL.EQ.0)GO TO 90
134C
135 IF(JSET.EQ.0)THEN
136C
137C Create mother JSET bank
138C
139 CALL MZBOOK(IXCONS,JSET,JSET,1,'SETS',0,0,0,5,0)
140 IQ(JSET-5)=0
141 NSET=0
142 ELSE
143 NSET=IQ(JSET-1)
144 CALL GLOOK(IUSET,IQ(JSET+1),NSET,ISET)
145 IF (ISET.NE.0) GO TO 30
146 ENDIF
147C
148C Create JS bank
149C
150 CALL MZPUSH(IXCONS,JSET,1,1,'I')
151 NSET=NSET+1
152C
153 ISET=NSET
154 CALL UCTOH(IUSET,IQ(JSET+ISET),4,4)
155 CALL MZBOOK(IXCONS,JS,JSET,-ISET,'SETS',0,0,0,5,0)
156C
157C Check if detector has already been defined
158C
159 30 JS=LQ(JSET-ISET)
160 NDET=IQ(JS-1)
161 IF(NDET.NE.0)THEN
162 CALL GLOOK(IUDET,IQ(JS+1),NDET,IDET)
163 IF(IDET.NE.0) GO TO 92
164 ENDIF
165C
166C If not, create detector bank
167C
168 CALL MZPUSH(IXCONS,JS,1,1,'I')
169 NDET=NDET+1
170 IDET=NDET
171 CALL UCTOH(IUDET,IQ(JS+IDET),4,4)
172 CALL MZBOOK(IXCONS,JD,JS,-IDET,'SEJD',4,4,10+2*NV,IOSEJD,0)
173 IQ(JD-5)=10*ISET+IDET
174C
175 NW=0
176 IF(NV.GT.0)THEN
177 CALL UCTOH(NAMESV,NAV,4,4*NV)
178 K=32
179 DO 70 I=1,NV
180 NB=NBITSV(I)
181 IF(NB.LT.0)NB=0
182 IF(NB.GE.32)NB=0
183 IQ(JD+2*I+ 9)=NAV(I)
184 IQ(JD+2*I+10)=NB
185 IF(NB.LE.0)THEN
186 NW=NW+1
187 K=32
188 ELSE
189 K=K+NB
190 IF(K.GT.32)THEN
191 K=NB
192 NW=NW+1
193 ENDIF
194 ENDIF
195 70 CONTINUE
196 ENDIF
197 80 IQ(JD+1)=NW
198 IQ(JD+2)=NV
199 IQ(JD+7)=NWHI
200 IQ(JD+8)=NWDI
201 IQ(JD+10)=0
202C
203C Now enter set,det into JVOLUM data structure
204C
205 CALL GSATT(IUDET,'SET ',ISET)
206 CALL GSATT(IUDET,'DET ',IDET)
207 CALL GSATT(IUDET,'DTYP',IDTYPE)
208 GO TO 99
209C
210C Errors
211C
212 90 WRITE(CHMAIL,1000)IUDET
213 CALL GMAIL(0,0)
214 1000 FORMAT(' ***** GSDET ERROR, VOLUME ',A4,' NOT DEFINED')
215 GO TO 99
216C
217 92 WRITE(CHMAIL,2000)IUSET,IUDET
218 CALL GMAIL(0,0)
219 2000 FORMAT(' ***** GSDET ERROR ,SET ',A4, ' DETECTOR ',A4,
220 + ' ALREADY DEFINED')
221 GO TO 99
222C
223 94 WRITE(CHMAIL,3000)NV
224 CALL GMAIL(0,0)
225 3000 FORMAT(' ***** GSDET ERROR ,SET ',A4, ' DETECTOR ',A4,
226 + ' Too many descriptors:',I5)
227C
228 99 RETURN
229 END