]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ghits/gfpath.F
This commit was generated by cvs2svn to compensate for changes in r2,
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gfpath.F
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)
13 C.
14 C.    ******************************************************************
15 C.    *                                                                *
16 C.    *      Return the lists of NLEV volume names (LNAM) and numbers  *
17 C.    *      (LNUM) which identify the path through the JVOLUM data    *
18 C.    *      structure for the volume corresponding to the detector    *
19 C.    *      at position IDET in set at position ISET identified by    *
20 C.    *      the list of node identifiers given in NUMBV.              *
21 C.    *                                                                *
22 C.    *      NLEV is expected to be greater than 1                     *
23 C.    *      and no checks are performed on the validity of ISET/IDET  *
24 C.    *      In case of user error NLEV returns with the value 0.      *
25 C.    *                                                                *
26 C.    *   ==> Called by : <USER>                                       *
27 C.    *         Author  F.Bruyant  **********                          *
28 C.    *                                                                *
29 C.    ******************************************************************
30 C.
31 #include "geant321/gcbank.inc"
32 #include "geant321/gcunit.inc"
33       INTEGER  LNAM(*), LNUM(*), NUMBV(*)
34 C.
35 C.    -----------------------------------------------------------------
36 C.
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)
44 C
45       NSOL = IQ(JD+9)
46       IF (NSOL.EQ.1) THEN
47 C
48 C       Usual case
49 C
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
59 C
60       ELSE IF (NSOL.GT.1) THEN
61 C
62 C       Case with multiple path
63 C
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
77 C
78 C         Fill LNAM,LNUM
79 C
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
100 C
101    81     IF (IS.EQ.NSOL)  GO TO 991
102           IPSTO = IPSTO +2*NLEV
103           NLEV = IQ(IPSTO+2)
104 C
105    90   CONTINUE
106 C
107       ELSE
108 C
109 C       User error
110 C
111         GO TO 991
112 C
113       ENDIF
114       GO TO 999
115 C
116   991 NLEV = 0
117       WRITE (CHMAIL, 1000) IQ(JD+9)
118       CALL GMAIL(0,0)
119 C
120  1000 FORMAT (' ***** GFPATH USER ERROR, IQ(JD+9)=',I2)
121 C
122   999 RETURN
123       END