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