]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ghits/gsdetd.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gsdetd.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 GSDETD(IUSET,IUDET,ND,NAMESD,NBITSD)
13C.
14C. ******************************************************************
15C. * *
16C. * Handling sensitive DETector Digitisation parameters *
17C. * --------------------------------------------------- *
18C. * *
19C. * Defines digitisation parameters for detector IUDET of set *
20C. * IUSET. *
21C. * IUSET user set identifier *
22C. * IUDET user detector identifier *
23C. * ND number of elements per digitisation *
24C. * NAMESD the ND variable names for the digitisation *
25C. * elements *
26C. * NBITSD the ND bit numbers for packing the variable *
27C. * values. *
28C. * The routine is used at initialisation time once the *
29C. * geometrical volumes have been defined to describe the *
30C. * digitisation elements and the way to do packing in memory *
31C. * and on tape. Let us use the same example as in GSDETH. The *
32C. * non geometrical information we want to store for each *
33C. * digitisation is for example: *
34C. * - ADC pulse height in a lead glass block. *
35C. * Example of one digitisation in that scheme: *
36C. * EPHI 12 *
37C. * EZRI 41 *
38C. * BLOC 3 *
39C. * ADC 789 *
40C. * The FORTRAN coding to define the digitisation information *
41C. * could be: *
42C. * DATA NAMESD/'ADC '/ *
43C. * DATA NBITSD/16/ *
44C. * CALL GSDETD('ECAL','BLOC',1,NAMESD,NBITSD) *
45C. * Returns the digitisation parameters for detector IUDET of *
46C. * set IUSET. All arguments as explained in GSDETD. *
47C.. * *
48C. * JS = LQ(JSET-ISET) *
49C. * JD = LQ(JS-IDET) *
50C. * JDD= LQ(JD-2) *
51C. * IQ(JDD+2*I-1)=NAMESD(I) *
52C. * IQ(JDD+2*I) =NBITSD(I) *
53C. * *
54C. * ==>Called by : <USER>, UGEOM *
55C. * Author R.Brun ********* *
56C. * *
57C. ******************************************************************
58C.
59#include "geant321/gcbank.inc"
60#include "geant321/gcunit.inc"
61#include "geant321/gcmzfo.inc"
62 PARAMETER (NDEMX=100)
63 DIMENSION NBITSD(1),NAMD(NDEMX)
64 CHARACTER*4 NAMESD(1),IUSET,IUDET
65 EQUIVALENCE (WS(1),NAMD(1))
66C.
67C. ------------------------------------------------------------------
68C.
69 IF(JSET.LE.0)GO TO 90
70 NSET=IQ(JSET-1)
71 IF(NSET.LE.0)GO TO 90
72 CALL GLOOK(IUSET,IQ(JSET+1),NSET,ISET)
73 IF(ISET.LE.0)GO TO 90
74 JS=LQ(JSET-ISET)
75 NDET=IQ(JS-1)
76 IF(NDET.LE.0)GO TO 90
77 CALL GLOOK(IUDET,IQ(JS+1),NDET,IDET)
78 IF(IDET.LE.0)GO TO 90
79 JD=LQ(JS-IDET)
80C
81 CALL MZBOOK(IXCONS,JDD,JD,-2,'SJDD',0,0,2*ND,IOSJDD,0)
82C
83 NW=0
84 IF(ND.GT.0)THEN
85 CALL UCTOH(NAMESD,NAMD,4,4*ND)
86 K=32
87 DO 30 I=1,ND
88 NB=NBITSD(I)
89 IF(NB.LT.0)NB=0
90 IF(NB.GE.32)NB=0
91 IQ(JDD+2*I-1)=NAMD(I)
92 IQ(JDD+2*I )=NB
93 IF(NB.LE.0)THEN
94 NW=NW+1
95 K=32
96 ELSE
97 K=K+NB
98 IF(K.GT.32)THEN
99 K=NB
100 NW=NW+1
101 ENDIF
102 ENDIF
103 30 CONTINUE
104 ENDIF
105 IQ(JD+5)=NW
106 IQ(JD+6)=ND
107 GO TO 99
108C
109C Error
110C
111 90 WRITE(CHMAIL,1000)IUSET,IUDET
112 CALL GMAIL(0,0)
113 1000 FORMAT(' ***** GSDETD ERROR FOR SET ',A4,' OR DETECTOR ',A4)
114C
115 99 RETURN
116 END