]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ggeom/gneltu.F
Minor corrections after big transformer changes
[u/mrichter/AliRoot.git] / GEANT321 / ggeom / gneltu.F
CommitLineData
fe4da5cc 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 GNELTU(X,PAR,IACT,SNEXT,SNXT,SAFE)
13C
14C ****************************************************************
15C * *
16C * Compute distance up to intersection with 'ELTU' volume, *
17C * from inside point X(1-3) along direction X(4-6). *
18C * *
19C * PAR (input) : volume parameters *
20C * IACT (input) : action flag *
21C * = 0 Compute SAFE only *
22C * = 1 Compute SAFE, and SNXT only if SNEXT.gt.new SAFE *
23C * = 2 Compute both SAFE and SNXT *
24C * = 3 Compute SNXT only *
25C * SNEXT (input) : see IACT = 1 *
26C * SNXT (output) : distance to volume boundary *
27C * SAFE (output) : shortest distance to any boundary *
28C * *
29C * ==>Called by : GNEXT,GTNEXT *
30C * Author A.Solano *
31C * *
32C ****************************************************************
33C
34#include "geant321/gconsp.inc"
35C
36 DIMENSION X(6),PAR(3)
37#if !defined(CERNLIB_SINGLE)
38 DOUBLE PRECISION SAFZ1,SAFZ2,SAFR,A2,B2,X0,Y0,A,B,D1,D2
39 DOUBLE PRECISION X1,X2,X3,Y1,Y2,Y3
40 DOUBLE PRECISION SZ,XZ,YZ,U,V,W,DISCR,SQDISC,TAU1,TAU2
41#endif
42C
43 SNXT = BIG
44 SAFZ1 = PAR(3)-X(3)
45 SAFZ2 = PAR(3)+X(3)
46C
47 A2 = PAR(1)*PAR(1)
48 B2 = PAR(2)*PAR(2)
49C
50 IF(IACT.LT.3)THEN
51C
52C -----------------------------------
53C | Compute safety-distance 'SAFE' |
54C -----------------------------------
55C
56 X0 = ABS(X(1))
57 Y0 = ABS(X(2))
58C
59 A=PAR(1)
60 B=PAR(2)
61 X1=X0
62 Y1=SQRT((A-X0)*(A+X0))*B/A
63 Y2=Y0
64 X2=SQRT((B-Y0)*(B+Y0))*A/B
65 D1=(X1-X0)**2+(Y1-Y0)**2
66 D2=(X2-X0)**2+(Y2-Y0)**2
67 DO 1 I=1,8
68 IF (B.LT.A) THEN
69 X3=.5*(X1+X2)
70 Y3=SQRT((A-X3)*(A+X3))*B/A
71 ELSE
72 Y3=.5*(Y1+Y2)
73 X3=SQRT((B-Y3)*(B+Y3))*A/B
74 END IF
75 IF (D1.LT.D2) THEN
76 X2=X3
77 Y2=Y3
78 D2=(X2-X0)**2+(Y2-Y0)**2
79 ELSE
80 X1=X3
81 Y1=Y3
82 D1=(X1-X0)**2+(Y1-Y0)**2
83 END IF
84 1 CONTINUE
85 2 SAFR=SQRT(D1)-1.E-3
86*
87 SAFE = MIN(SAFZ1,SAFZ2,SAFR)
88 IF(IACT.EQ.0)GOTO 99
89 IF(IACT.EQ.1.AND.SNEXT.LT.SAFE)GOTO 99
90C
91 ENDIF
92C
93C -----------------------------------
94C | Compute vector-distance 'SNXT' |
95C -----------------------------------
96C
97C .... First check Z
98C
99 IF(X(6).GT.0.)THEN
100 SNXT = SAFZ1/X(6)
101 ELSEIF(X(6).LT.0.)THEN
102 SNXT = -SAFZ2/X(6)
103 ENDIF
104C
105C .... Then,if necessary,find the intersection of
106C the given ray(described by array X) whit
107C the cylinder.
108C Ray equation : X'(1-3) = X(1-3) + TAU*X(4-6)
109C Cylinder equation : x**2/a**2 + y**2/b**2 = 1
110C To obtain TAU,solve the quadratic equation
111C Ut**2 + 2Vt + W = 0
112C
113 SZ = SNXT
114 XZ = X(1)+X(4)*SZ
115 YZ = X(2)+X(5)*SZ
116 IF((XZ*XZ/A2+YZ*YZ/B2).LE.1)GOTO 99
117C
118 U = X(4)*X(4)*B2+X(5)*X(5)*A2
119 V = X(1)*X(4)*B2+X(2)*X(5)*A2
120 W = X(1)*X(1)*B2+X(2)*X(2)*A2-A2*B2
121 DISCR = V*V-U*W
122 IF(DISCR.LT.0.)GOTO 99
123 IF(U.EQ.0.)GOTO 99
124 SQDISC = SQRT(DISCR)
125 TAU1 = (-V+SQDISC)/U
126 TAU2 = (-V-SQDISC)/U
127C
128C .... Set SNXT to the smallest positive TAU
129C
130 IF(TAU1.LT.0.)THEN
131 IF(TAU2.LT.0.)GOTO 99
132 SNXT = TAU2
133 ELSE
134 SNXT = TAU1
135 IF(TAU2.GT.0.0.AND.TAU2.LT.TAU1)THEN
136 SNXT = TAU2
137 ENDIF
138 ENDIF
139C
140 99 END