]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ghits/gfpath.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gfpath.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:10 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 GFPATH (ISET, IDET, NUMBV, NLEV, LNAM, LNUM)
13C.
14C. ******************************************************************
15C. * *
16C. * Return the lists of NLEV volume names (LNAM) and numbers *
17C. * (LNUM) which identify the path through the JVOLUM data *
18C. * structure for the volume corresponding to the detector *
19C. * at position IDET in set at position ISET identified by *
20C. * the list of node identifiers given in NUMBV. *
21C. * *
22C. * NLEV is expected to be greater than 1 *
23C. * and no checks are performed on the validity of ISET/IDET *
24C. * In case of user error NLEV returns with the value 0. *
25C. * *
26C. * ==> Called by : <USER> *
27C. * Author F.Bruyant ********** *
28C. * *
29C. ******************************************************************
30C.
31#include "geant321/gcbank.inc"
32#include "geant321/gcunit.inc"
33 INTEGER LNAM(*), LNUM(*), NUMBV(*)
34C.
35C. -----------------------------------------------------------------
36C.
37 JS = LQ(JSET-ISET)
38 JD = LQ(JS-IDET)
39 NV = IQ(JD+2)
40 IPJD = JD +10 +2*NV
41 LNAM(1) = IQ(IPJD+1)
42 LNUM(1) = 1
43 NLEV = IQ(IPJD+2)
44C
45 NSOL = IQ(JD+9)
46 IF (NSOL.EQ.1) THEN
47C
48C Usual case
49C
50 I = 0
51 DO 10 N = 2,NLEV
52 IPJD = IPJD +2
53 LNAM(N) = IQ(IPJD+1)
54 LNUM(N) = 1
55 IF (IQ(IPJD+2).LE.1) GO TO 10
56 I = I +1
57 LNUM(N) = NUMBV(I)
58 10 CONTINUE
59C
60 ELSE IF (NSOL.GT.1) THEN
61C
62C Case with multiple path
63C
64 IPSTO = IPJD
65 DO 90 IS = 1,NSOL
66 IPJDD = JD +8
67 DO 30 I = 1,NV
68 IPJDD = IPJDD +2
69 IF (NUMBV(I).EQ.0) GO TO 30
70 IPJD = IPSTO
71 DO 20 N = 2,NLEV
72 IPJD = IPJD +2
73 IF (IQ(IPJD+1).EQ.IQ(IPJDD+1)) GO TO 30
74 20 CONTINUE
75 GO TO 81
76 30 CONTINUE
77C
78C Fill LNAM,LNUM
79C
80 IPJD = IPSTO
81 DO 40 N = 2,NLEV
82 IPJD = IPJD +2
83 LNAM(N) = IQ(IPJD+1)
84 LNUM(N) = 1
85 40 CONTINUE
86 IPJDD = JD +8
87 DO 60 I = 1,NV
88 IPJDD = IPJDD +2
89 IF (NUMBV(I).EQ.0) GO TO 60
90 IPJD = IPSTO
91 DO 50 N = 2,NLEV
92 IPJD = IPJD +2
93 IF (IQ(IPJD+1).NE.IQ(IPJDD+1)) GO TO 50
94 IF (NUMBV(I).GT.IQ(IPJD+2)) GO TO 991
95 LNUM(N) = NUMBV(I)
96 GO TO 60
97 50 CONTINUE
98 60 CONTINUE
99 GO TO 999
100C
101 81 IF (IS.EQ.NSOL) GO TO 991
102 IPSTO = IPSTO +2*NLEV
103 NLEV = IQ(IPSTO+2)
104C
105 90 CONTINUE
106C
107 ELSE
108C
109C User error
110C
111 GO TO 991
112C
113 ENDIF
114 GO TO 999
115C
116 991 NLEV = 0
117 WRITE (CHMAIL, 1000) IQ(JD+9)
118 CALL GMAIL(0,0)
119C
120 1000 FORMAT (' ***** GFPATH USER ERROR, IQ(JD+9)=',I2)
121C
122 999 RETURN
123 END