]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ghits/gsdet.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gsdet.F
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)
14 C.
15 C.    ******************************************************************
16 C.    *                                                                *
17 C.    *       Defines volume parameters for detector IUDET of set IUSET*
18 C.    *                                                                *
19 C.    *             Input parameters                                   *
20 C.    * IUSET     set identifier (4 characters), user defined          *
21 C.    * IUDET     detector identifier  (4 characters),   name of  an   *
22 C.    *           existing volume                                      *
23 C.    * NV        number of volume descriptors                         *
24 C.    * NAMESV    vector of NV volume descriptors (4 characters)       *
25 C.    * NBITSV    vector of  NV bit numbers  for packing  the volume   *
26 C.    *           numbers                                              *
27 C.    * IDTYPE    detector type, user defined                          *
28 C.    * NWHI      number of words for the primary allocation of HITS   *
29 C.    *           banks                                                *
30 C.    * NWDI      number of words for the primary allocation of DIGI   *
31 C.    *           banks when first allocation not sufficient           *
32 C.    *                                                                *
33 C.    *             Output parameters                                  *
34 C.    * ISET      position of set in bank JSET                         *
35 C.    * IDET      position of detector in bank JS=IB(JSET-ISET)        *
36 C.    *              If ISET=0 or IDET=0  error                        *
37 C.    * Remarks:                                                       *
38 C.    * - The vector NAMESV (length NV)  contains the list of volume   *
39 C.    *   names which  permit the  identification of  every physical   *
40 C.    *   detector with detector name IUDET.    [See example in HITS   *
41 C.    *   110].                                                        *
42 C.    * - Each  element of  the vector  NBITSV (length  NV)  is  the   *
43 C.    *   number  of  bits  used  for  packing  the  number  of  the   *
44 C.    *   corresponding volume,  when building the packed identifier   *
45 C.    *   of a given physical detector.                                *
46 C.    * - For more details see the example given in GSDETH.            *
47 C.    * - The detector type  IDTYPE is not used  internally by GEANT   *
48 C.    *   and  can be  defined by  the user  to distinguish  quickly   *
49 C.    *   between various kinds of detectors,  in the routine GUSTEP   *
50 C.    *   for example.                                                 *
51 C.    *                                                                *
52 C.    *       IQ(JSET+ISET) = IUSET                                    *
53 C.    *       JS = LQ(JSET-ISET) + pointer to set parameters           *
54 C.    *       IQ(JS+IDET)=IUDET                                        *
55 C.    *       JD= LQ(JS-1)  = pointer to detector IDET                 *
56 C.    *       IQ(JD+1)=Total number of words to store packed volumes   *
57 C.    *       IQ(JD+2)=NV                                              *
58 C.    *       IQ(JD+3)=Number of words required per hit                *
59 C.    *       IQ(JD+4)=Number of different hits types                  *
60 C.    *       IQ(JD+5)=Number of words required per digit              *
61 C.    *       IQ(JD+6)=Number of different digit types                 *
62 C.    *       IQ(JD+7)=NWHI                                            *
63 C.    *       IQ(JD+8)=NWDI                                            *
64 C.    *       IQ(JD+9)=Number of paths through the JVOLUM tree         *
65 C.    *       IQ(JD+10)= For an alias only, IDET of main detector      *
66 C.    *       IQ(JD+2*I+9) = name of volume i = NAMESV(I)              *
67 C.    *       IQ(JD+2*I+10)= number of bits/volume = NBITSV(I)         *
68 C.    *                                                                *
69 C.    *            The Detector Set data structure JSET                *
70 C.    *            ------------------------------------                *
71 C.    *                                                                *
72 C.    *                                        | JSET                  *
73 C.    *    NSET            ISET                v         NSET          *
74 C.    *     ................................................           *
75 C.    *     |              | |               |  | Set names|           *
76 C.    *     ................................................           *
77 C.    *                     | JS                                       *
78 C.    *                     |                                          *
79 C.    *    NDET       IDET  v                    NDET                  *
80 C.    *     ........................................                   *
81 C.    *     |        |  |  | | Detector names      |                   *
82 C.    *     ........................................                   *
83 C.    *               | JD                                             *
84 C.    *      -3 -2 -1 v                                                *
85 C.    *     ................................................           *
86 C.    *     |  |  |  |  |   Parameters of GSDET            |           *
87 C.    *     ................................................           *
88 C.    *      |  |  |                                                   *
89 C.    *      |  |  |  JDH                                              *
90 C.    *      |  |  |                                                   *
91 C.    *      |  |  |           .............................           *
92 C.    *      |  |  ............| Parameters of GSDETH      |           *
93 C.    *      |  |              .............................           *
94 C.    *      |  |                                                      *
95 C.    *      |  | JDD                                                  *
96 C.    *      |  |                                                      *
97 C.    *      |  |              .............................           *
98 C.    *      |  ...............|  Parameters of GSDETD     |           *
99 C.    *      |                 .............................           *
100 C.    *      |                                                         *
101 C.    *      |  JDU                                                    *
102 C.    *      |                 .............................           *
103 C.    *      ..................| Parameters of GSDETU      |           *
104 C.    *                        .............................           *
105 C.    *  JS = LQ(JSET-ISET) pointer to detector set number ISET        *
106 C.    * The JSET data structure is filled by GSDET, GSDETH,  GSDETD,   *
107 C.    * GSDETU and eventually by GSDETA.                               *
108 C.    *                                                                *
109 C.    *    ==>Called by : <USER>, UGEOM                                *
110 C.    *       Author    R.Brun  *********                              *
111 C.    *                                                                *
112 C.    ******************************************************************
113 C.
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))
121 C.
122 C.    ------------------------------------------------------------------
123 C.
124       ISET=0
125       IDET=0
126       IF(NV.GT.15)GO TO 94
127 C
128 C             Check if volume IUDET has been defined
129 C
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
134 C
135       IF(JSET.EQ.0)THEN
136 C
137 C               Create mother JSET bank
138 C
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
147 C
148 C               Create JS bank
149 C
150       CALL MZPUSH(IXCONS,JSET,1,1,'I')
151       NSET=NSET+1
152 C
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)
156 C
157 C            Check if detector has already been defined
158 C
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
165 C
166 C                If not, create detector bank
167 C
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
174 C
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
202 C
203 C             Now enter set,det into JVOLUM data structure
204 C
205       CALL GSATT(IUDET,'SET ',ISET)
206       CALL GSATT(IUDET,'DET ',IDET)
207       CALL GSATT(IUDET,'DTYP',IDTYPE)
208       GO TO 99
209 C
210 C              Errors
211 C
212   90  WRITE(CHMAIL,1000)IUDET
213       CALL GMAIL(0,0)
214  1000 FORMAT(' ***** GSDET ERROR, VOLUME ',A4,' NOT DEFINED')
215       GO TO 99
216 C
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
222 C
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)
227 C
228   99  RETURN
229       END