]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ghits/gfdet.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gfdet.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:09 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 GFDET(IUSET,IUDET,NV,NAMESV,NBITSV,IDTYPE
13 + ,NWHI,NWDI,ISET,IDET)
14C.
15C. ******************************************************************
16C. * *
17C. * returns volume parameters for detector IUDET of set IUSET*
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. * *
24C. * Output parameters *
25C. * NV number of volume descriptors *
26C. * NAMESV vector of NV volume descriptors (4 characters) *
27C. * NBITSV vector of NV bit numbers for packing the volume *
28C. * numbers *
29C. * IDTYPE detector type, user defined *
30C. * NWHI number of words for the primary allocation of HITS *
31C. * banks *
32C. * NWDI number of words for the primary allocation of DIGI *
33C. * banks when first allocation not sufficient *
34C. * ISET position of set in bank JSET *
35C. * IDET position of detector in bank JS=IB(JSET-ISET) *
36C. * If ISET=0 or IDET=0 error *
37C. * Remarks: *
38C. * - The vector NAMESV (length NV) contains the list of volume *
39C. * names which permit the identification of every physical *
40C. * detector with detector name IUDET. [See example in HITS *
41C. * 110]. *
42C. * - Each element of the vector NBITSV (length NV) is the *
43C. * number of bits used for packing the number of the *
44C. * corresponding volume, when building the packed identifier *
45C. * of a given physical detector. *
46C. * - Vectors NAMESV and NBITSV must be dimensionned at least *
47C. * to NV in the calling routine. *
48C. * *
49C. * ==>Called by : <USER> *
50C. * Author R.Brun , M.Maire ********* *
51C. * *
52C. ******************************************************************
53C.
54#include "geant321/gcbank.inc"
55#include "geant321/gcunit.inc"
56 DIMENSION NBITSV(1)
57 CHARACTER*4 NAMESV(1),IUSET,IUDET
58C.
59C. ------------------------------------------------------------------
60C.
61 ISET=0
62 IDET=0
63C
64C Check if detector IUDET has been defined
65C
66 IF (JSET.LE.0) GO TO 90
67 NSET = IQ(JSET-1)
68 IF (NSET.LE.0) GO TO 90
69 CALL GLOOK(IUSET,IQ(JSET+1),NSET,ISET)
70 IF (ISET.EQ.0) GO TO 90
71 JS = LQ(JSET-ISET)
72 NDET = IQ(JS-1)
73 IF (NDET.LE.0) GO TO 90
74 CALL GLOOK(IUDET,IQ(JS+1),NDET,IDET)
75 IF (IDET.EQ.0) GO TO 95
76 JD=LQ(JS-IDET)
77 NV=IQ(JD+2)
78 NWHI=IQ(JD+7)
79 NWDI=IQ(JD+8)
80C
81 IF(NV.GT.0)THEN
82 DO 10 I=1,NV
83 CALL UHTOC(IQ(JD+2*I+ 9),4,NAMESV(I),4)
84 NBITSV(I)=IQ(JD+2*I+10)
85 10 CONTINUE
86 ENDIF
87C
88 CALL GFATT(IUDET,'DTYP',IDTYPE)
89 GO TO 99
90C
91 90 WRITE (CHMAIL, 1000) IUSET
92 CALL GMAIL(0,0)
93 1000 FORMAT (' ***** GFDET ERROR SET ',A4,' NOT FOUND')
94 GO TO 99
95 95 WRITE (CHMAIL, 2000) IUSET,IUDET
96 CALL GMAIL(0,0)
97 2000 FORMAT (' ***** GFDET ERROR FOR SET ',A4,
98 + ' DETECTOR ',A4,' NOT FOUND')
99C
100 99 RETURN
101 END