]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ghits/gsdetv.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gsdetv.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:21:12  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 GSDETV (IUSET, IUDET, IDTYPE, NWHI, NWDI, ISET, IDET)
13 C.
14 C.    ******************************************************************
15 C.    *                                                                *
16 C.    *       Defines detector IUDET as a member of set IUSET          *
17 C.    *     and prepares the DETector structure                        *
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.    * IDTYPE    detector type, user defined                          *
24 C.    * NWHI      number of words for primary allocation of HITS banks *
25 C.    * NWDI      number of words for primary allocation of DIGI banks *
26 C.    *                                                                *
27 C.    *             Output parameters                                  *
28 C.    * ISET      position of set in bank JSET                         *
29 C.    * IDET      position of detector in bank JS=IB(JSET-ISET)        *
30 C.    *              If ISET=0 or IDET=0  error                        *
31 C.    * Remarks:                                                       *
32 C.    * - The path through the volume tree will be automatically set   *
33 C.    *   in GGDETV,called by GGCLOS, after all volumes have been      *
34 C.    *   positionned.                                                 *
35 C.    * - The detector type  IDTYPE is not used  internally by GEANT   *
36 C.    *   and  can be  defined by  the user  to distinguish  quickly   *
37 C.    *   between various kinds of detectors,  in the routine GUSTEP   *
38 C.    *   for example.                                                 *
39 C.    *                                                                *
40 C.    *       IQ(JSET+ISET) = IUSET                                    *
41 C.    *       JS = LQ(JSET-ISET) = pointer to set IUSET                *
42 C.    *       IQ(JS+IDET)=IUDET                                        *
43 C.    *       JD= LQ(JS-1)  = pointer to detector IUDET                *
44 C.    *       IQ(JD+1)=Number of words to store packed volume numbers  *
45 C.    *       IQ(JD+2)=Number of volume descriptors                    *
46 C.    *       IQ(JD+3)=Number of words per hit                         *
47 C.    *       IQ(JD+4)=Number of elements per hit                      *
48 C.    *       IQ(JD+5)=Number of words per digitisation                *
49 C.    *       IQ(JD+6)=Number of elements per digitisation             *
50 C.    *       IQ(JD+7)=NWHI, primary size of hit bank                  *
51 C.    *       IQ(JD+8)=NWDI, primary size of digitisation bank         *
52 C.    *       IQ(JD+9)=Number of paths through the JVOLUM tree         *
53 C.    *       IQ(JD+10)=For aliases only, IDET of mother detector      *
54 C.    *       IQ(JD+11)=Name of first volume descriptor                *
55 C.    *       IQ(JD+12)=Number of bits for packing its number          *
56 C.    *       ...                                                      *
57 C.    *       IQ(JD+9+2*NV)=Name of last volume descriptor             *
58 C.    *       IQ(JD+10+2*NV)=Number of bits for packing its number     *
59 C.    *       then for each possible path                              *
60 C.    *       list of names and numbers for all levels                 *
61 C.    *       (The number of levels is entered as number attached to   *
62 C.    *       the first name which is the top of the JVOLUM tree)      *
63 C.    *                                                                *
64 C.    *            The Detector Set data structure JSET                *
65 C.    *            ------------------------------------                *
66 C.    *                                                                *
67 C.    *                                        | JSET                  *
68 C.    *    NSET            ISET                v         NSET          *
69 C.    *     ................................................           *
70 C.    *     |              | |               |  | Set names|           *
71 C.    *     ................................................           *
72 C.    *                     | JS                                       *
73 C.    *                     |                                          *
74 C.    *    NDET       IDET  v                    NDET                  *
75 C.    *     ........................................                   *
76 C.    *     |        |  |  | | Detector names      |                   *
77 C.    *     ........................................                   *
78 C.    *                  | JD                                          *
79 C.    *       -3  -2  -1 v                                             *
80 C.    *     ................................................           *
81 C.    *     |   |   |   |  | Volume parameters, in GGDETV  |           *
82 C.    *     ................................................           *
83 C.    *              JDH                                               *
84 C.    *          JDD                                                   *
85 C.    *      JDU                                                       *
86 C.    *                                                                *
87 C.    * The JSET structure is filled by GSDETV + GGDETV, and by        *
88 C.    *      GSDETH, GSDETD and GSDETU, eventually by GSDETA.          *
89 C.    *                                                                *
90 C.    *    ==>Called by : <USER>, UGEOM                                *
91 C.    *       Authors   R.Brun, F.Bruyant    **********                *
92 C.    *                                                                *
93 C.    ******************************************************************
94 C.
95 #include "geant321/gcbank.inc"
96 #include "geant321/gcunit.inc"
97 #include "geant321/gcmzfo.inc"
98       CHARACTER*4 IUSET,IUDET
99 C.
100 C.    ------------------------------------------------------------------
101 C.
102       ISET = 0
103       IDET = 0
104 C
105 C     Check if volume IUDET has been defined
106 C
107       IF (JVOLUM.LE.0) GO TO 920
108       NVOLUM = IQ(JVOLUM-1)
109       CALL GLOOK (IUDET, IQ(JVOLUM+1), NVOLUM, IVOL)
110       IF (IVOL.EQ.0) GO TO 920
111 C
112 C     Check that volume IVOL is a sensitive medium
113 C
114       JVO = LQ(JVOLUM-IVOL)
115       ITM = Q(JVO+4)
116       JTM = LQ(JTMED-ITM)
117       IF (Q(JTM+7).EQ.0.)THEN
118          WRITE (CHMAIL,1000) IUDET
119          CALL GMAIL(0,0)
120       ENDIF
121 C
122       IF (JSET.EQ.0)THEN
123 C
124 C     Create mother JSET bank
125 C
126          CALL MZBOOK (IXCONS, JSET, JSET, 1, 'SETS', 0,0,0, 5, 0)
127          IQ(JSET-5)=0
128          NSET = 0
129       ELSE
130 C
131          NSET = IQ(JSET-1)
132          CALL GLOOK (IUSET, IQ(JSET+1), NSET, ISET)
133          IF (ISET.NE.0) GO TO 30
134       ENDIF
135 C
136 C     Create JSET bank
137 C
138       CALL MZPUSH (IXCONS, JSET, 1, 1, 'I')
139       NSET = NSET +1
140 C
141       ISET = NSET
142       CALL UCTOH (IUSET, IQ(JSET+ISET), 4, 4)
143       CALL MZBOOK (IXCONS, JS, JSET, -ISET, 'SETS', 0,0,0, 5, 0)
144       IQ(JS-5) = ISET
145 C
146 C     Check if detector has already been defined
147 C
148   30  JS = LQ(JSET-ISET)
149       NDET = IQ(JS-1)
150       IF (NDET.NE.0)THEN
151          CALL GLOOK (IUDET, IQ(JS+1), NDET, IDET)
152          IF (IDET.NE.0) GO TO 930
153       ENDIF
154 C
155 C     If not, create detector bank
156 C
157       CALL MZPUSH (IXCONS, JS, 1, 1, 'I')
158       NDET = NDET +1
159       IDET = NDET
160       CALL UCTOH (IUDET, IQ(JS+IDET), 4, 4)
161       CALL MZBOOK (IXCONS, JD, JS, -IDET, 'SEJD', 4,4,100, IOSEJD, 0)
162       IQ(JD-5) = IDET
163 C
164       IQ(JD+7) = NWHI
165       IQ(JD+8) = NWDI
166       IQ(JD+9) = -1
167 C
168 C     Now enter Set/Det into JVOLUM data structure
169 C
170       CALL GSATT (IUDET, 'SET ', ISET)
171       CALL GSATT (IUDET, 'DET ', IDET)
172       CALL GSATT (IUDET, 'DTYP', IDTYPE)
173       GO TO 999
174 C
175 C     Errors
176 C
177   920 WRITE (CHMAIL,2000) IUDET
178       CALL GMAIL(0,0)
179       GO TO 999
180 C
181   930 WRITE (CHMAIL,3000)  IUSET, IUDET
182       CALL GMAIL(0,0)
183 C
184  1000 FORMAT (' ***** GSDETV - ISVOL=0 FOR DETECTOR',A4,' - WARNING!')
185  2000 FORMAT (' ***** GSDETV ERROR, VOLUME ',A4,' NOT DEFINED')
186  3000 FORMAT (' ***** GSDETV ERROR ,SET ',A4, ' DETECTOR ',A4,
187      +        ' ALREADY DEFINED')
188 C
189   999 RETURN
190       END