]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ggeom/gnohyp.F
Minor corrections after big transformer changes
[u/mrichter/AliRoot.git] / GEANT321 / ggeom / gnohyp.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:20:52  cernlib
6 * Geant
7 *
8 *
9 #include "geant321/pilot.h"
10 *CMZ :  3.21/02 29/03/94  15.41.29  by  S.Giani
11 *-- Author :
12       SUBROUTINE GNOHYP (X, PAR, IACT, SNEXT, SNXT, SAFE)
13 C.
14 C.    ******************************************************************
15 C.    *                                                                *
16 C.    *      COMPUTE DISTANCE UP TO INTERSECTION WITH HYPErboloid      *
17 C.    *      VOLUME, FROM OUTSIDE POINT X(1-3) ALONG DIRECTION X(4-6)  *
18 C.    *                                                                *
19 C.    *       PAR   (input)  : volume parameters                       *
20 C.    *                        inner radius                            *
21 C.    *                        outer radius                            *
22 C.    *                        half length in z                        *
23 C.    *                        straw stereo angle in degrees           *
24 C.    *                        r**2 = (z*tan(theta))**2 + a**2         *
25 C.    *                                                                *
26 C.    *       IACT  (input)  : action flag                             *
27 C.    *         = 0  Compute SAFE only                                 *
28 C.    *         = 1  Compute SAFE, and SNXT only if SNEXT .GT.new SAFE *
29 C.    *         = 2  Compute both SAFE and SNXT                        *
30 C.    *         = 3  Compute SNXT only                                 *
31 C.    *       SNEXT (input)  : see IACT = 1                            *
32 C.    *       SNXT  (output) : distance to volume boundary             *
33 C.    *       SAFE  (output) : shortest distance to any boundary       *
34 C.    *                                                                *
35 C.    *    ==>Called by : GNEXT, GTNEXT                                *
36 C.    *         Authors  M.J.Corden, A.Palounek                        *
37 C.    *                                                                *
38 C.    ******************************************************************
39 C.
40 #include "geant321/gconsp.inc"
41       DIMENSION X(6),PAR(4),ENDR(2)
42 *
43 *     ------------------------------------------------------------------
44 *
45       SNXT = BIG
46       TANTHS= (TAN(PAR(4)*DEGRAD))**2
47       R2 = X(1)*X(1)+X(2)*X(2)
48       ENDR(1)=SQRT(PAR(1)**2+PAR(3)**2*TANTHS)
49       ENDR(2)=SQRT(PAR(2)**2+PAR(3)**2*TANTHS)
50       SAF3=ABS(X(3))-PAR(3)
51 *
52       IF(IACT.EQ.3) GO TO 10
53 *
54 *     compute SAFE from escribed cylinders
55 *
56       R  = SQRT(R2)
57       SAF1=PAR(1)-R
58       SAF2=R-ENDR(2)
59       SAFE = MAX(0.,SAF1,SAF2,SAF3)
60 *
61       IF(IACT.EQ.0) GO TO 999
62       IF(IACT.EQ.1.AND.SAFE.GT.SNEXT) GO TO 999
63 *
64    10 CONTINUE
65 *
66 * *** Compute SNXT
67 *
68       IF((SAF3.GT.0.).AND.(X(3)*X(6).GE.0.)) GO TO 999
69 C
70 C       Compute intercept with inner & outer surfaces.
71 C
72       A = X(4)**2 + X(5)**2 - X(6)**2*TANTHS
73       B = X(1)*X(4) + X(2)*X(5) - X(3)*X(6)*TANTHS
74 C
75       DO 30 NCYL =1,2
76          C = R2 - X(3)**2*TANTHS - PAR(NCYL)**2
77          SURD = B**2 - A*C
78          IF(SURD.LE.0.0) GO TO 30
79          SURD=SQRT(SURD)
80 *
81          DO 20 IR=-1,+1,2
82             S=(-B+IR*SURD)/A
83             IF((S.LT.0.).OR.(S.GT.SNXT)) GO TO 20
84 *       Intersection point
85             ZI = X(3) + S*X(6)
86 *       Check Z limits
87             IF(ABS(ZI).GT.PAR(3)) GO TO 20
88 *       Intersection with hyperboloid ok
89             SNXT = S
90    20    CONTINUE
91    30 CONTINUE
92 *
93 * *** Intersection with Z end planes
94 *
95       IF(SAF3.LE.0.) GO TO 999
96       S    = SAF3/ABS(X(6))
97 *     Intersection point
98       XI  = X(1) + S*X(4)
99       YI  = X(2) + S*X(5)
100 *     Check R limits
101       RI  = SQRT(XI*XI + YI*YI)
102       IF(RI.LT.ENDR(1).OR.RI.GT.ENDR(2)) GO TO 999
103 *     Intersection with Z end plane ok
104       SNXT  = S
105 *
106   999 END