]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ghits/gsdeth.F
Larger BOX in case CRT is present.
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gsdeth.F
CommitLineData
fe4da5cc 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 GSDETH(IUSET,IUDET,NH,NAMESH,NBITSH,ORIG,FACT)
13C.
14C. ******************************************************************
15C. * *
16C. * Handling sensitive DETector Hit parameters *
17C. * ------------------------------------------ *
18C. * *
19C. * Defines hit parameters for detector IUDET of set IUSET. *
20C. * IUSET user set identifier *
21C. * IUDET user detector identifier *
22C. * NH number of elements per hit *
23C. * NAMESH the NH variable names for the hit elements *
24C. * NBITSH the NH bit numbers for packing the variable values *
25C. * ORIG The quantity packed in the structure JHITS for the *
26C. * Ith variable is a positive integer with NBITSH(I) *
27C. * bits and such that *
28C. * FACT IVAR(I) = (VAR(I)+ORIG(I))*FACT(I) *
29C. * The routine is used at initialisation time once the *
30C. * geometrical volumes have been defined to describe the hit *
31C. * elements and the way to do packing in memory and on tape. *
32C. * EXAMPLE *
33C. * Assume an electromagnetic calorimeter ECAL divided into 40 *
34C. * PHI sections called EPHI. Each EPHI division is again *
35C. * divided along the Z axis in 60 objects called EZRI. Each *
36C. * EZRI is finally divided into 4 lead glass blocks called *
37C. * BLOC. *
38C. * The geometrical information to describe one hit will then *
39C. * be: *
40C. * - The EPHI section number (between 1 and 40) *
41C. * - The EZRI division number (between 1 and 60) *
42C. * - The BLOC number (1 to 4) *
43C. * The variables we want to store for each hit are for example: *
44C. * - X x position of the hit in the lead glass block *
45C. * - Y y *
46C. * - Z z *
47C. * - E energy of the particle at this point *
48C. * - ELOS the energy deposited into this block *
49C. * Example of one hit in that scheme: *
50C. * EPHI 12 *
51C. * EZRI 41 *
52C. * BLOC 3 *
53C. * X 7.89 cm *
54C. * Y -345.6 cm *
55C. * Z 1234.8 cm *
56C. * E 12 Gev *
57C. * ELOS 11.85 Gev *
58C. * The FORTRAN coding to define the set/det/hits information *
59C. * could be: *
60C. * DIMENSION NAMESV(3),NBITSV(3) *
61C. * DIMENSION NAMESH(5),NBITSH(5),ORIG(5),FACT(5) *
62C. * DATA NAMESV/'EPHI','EZRI','BLOC'/ *
63C. * DATA NBITSV/6,6,3/ *
64C. * DATA NAMESH/'X ','Y ','Z ','E ','ELOS'/ *
65C. * DATA NBITSH/5*16/ *
66C. * DATA ORIG/3*1000.,0.,0./ *
67C. * DATA FACT/3*10.,2*100./ *
68C. * CALL GSDET ('ECAL','BLOC',3,NAMESV,NBITSV,2,100,100, *
69C. * + ISET,IDET) *
70C. * CALL GSDETH('ECAL','BLOC',5,NAMESH,NBITSH,ORIG,FACT) *
71C. * Returns the hit parameters for detector IUDET of set *
72C. * IUSET. All arguments are explained above. *
73C.. * *
74C. * *
75C. * JS = LQ(JSET-ISET) *
76C. * JD = LQ(JS-IDET) *
77C. * JDH= LQ(JD-1) *
78C. * IQ(JDH+4*I-3)= NAMESH(I) *
79C. * IQ(JDH+4*I-2)= NBITSH(I) *
80C. * Q(JDH+4*I-1)= ORIG(I) *
81C. * Q(JDH+4*I) = FACT(I) *
82C. * *
83C. * ==>Called by : <USER>, UGEOM *
84C. * Author R.Brun ********* *
85C. * *
86C. ******************************************************************
87C.
88#include "geant321/gcbank.inc"
89#include "geant321/gcunit.inc"
90#include "geant321/gcmzfo.inc"
91 PARAMETER (NHEMX=100)
92 DIMENSION NBITSH(1),ORIG(1),FACT(1),NAMH(NHEMX)
93 CHARACTER*4 NAMESH(1),IUSET,IUDET
94 EQUIVALENCE (WS(1),NAMH(1))
95C.
96C. ------------------------------------------------------------------
97C.
98 IF(JSET.LE.0)GO TO 90
99 NSET=IQ(JSET-1)
100 IF(NSET.LE.0)GO TO 90
101 CALL GLOOK(IUSET,IQ(JSET+1),NSET,ISET)
102 IF(ISET.LE.0)GO TO 90
103 JS=LQ(JSET-ISET)
104 NDET=IQ(JS-1)
105 IF(NDET.LE.0)GO TO 90
106 CALL GLOOK(IUDET,IQ(JS+1),NDET,IDET)
107 IF(IDET.LE.0)GO TO 90
108 JD=LQ(JS-IDET)
109C
110 CALL MZBOOK(IXCONS,JDH,JD,-1,'SJDH',0,0,4*NH,IOSJDH,0)
111C
112 NW=0
113 IF(NH.GT.0)THEN
114 CALL UCTOH(NAMESH,NAMH,4,4*NH)
115 K=32
116 DO 30 I=1,NH
117 NB=NBITSH(I)
118 IF(NB.LT.0)NB=0
119 IF(NB.GE.32)NB=0
120 IQ(JDH+4*I-3)=NAMH(I)
121 IQ(JDH+4*I-2)=NB
122 Q(JDH+4*I-1)=ORIG(I)
123 Q(JDH+4*I )=FACT(I)
124 IF(FACT(I).LE.0.)Q(JDH+4*I)=1.
125 IF(NB.LE.0)THEN
126 NW=NW+1
127 K=32
128 ELSE
129 K=K+NB
130 IF(K.GT.32)THEN
131 K=NB
132 NW=NW+1
133 ENDIF
134 ENDIF
135 30 CONTINUE
136 ENDIF
137 IQ(JD+3)=NW
138 IQ(JD+4)=NH
139 GO TO 99
140C
141C Error
142C
143 90 WRITE(CHMAIL,1000)IUSET,IUDET
144 CALL GMAIL(0,0)
145 1000 FORMAT(' ***** GSDETH ERROR FOR SET ',A4,' OR DETECTOR ',A4)
146C
147 99 RETURN
148 END