]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ggeom/gnhype.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / ggeom / gnhype.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 GNHYPE (X, PAR, IACT, SNEXT, SNXT, SAFE)
13C.
14C. ******************************************************************
15C. * *
16C. * COMPUTE DISTANCE UP TO INTERSECTION WITH HYPErboloid *
17C. * VOLUME FROM INSIDE POINT X(1-3) ALONG DIRECTION X(4-6) *
18C. * *
19C. * PAR (input) : volume parameters *
20C. * inner radius *
21C. * outer radius *
22C. * half length in z *
23C. * straw stereo angle in degrees *
24C. * r**2 = (z*tan(theta))**2 + a**2 *
25C. * *
26C. * IACT (input) : action flag *
27C. * = 0 Compute SAFE only *
28C. * = 1 Compute SAFE, and SNXT only if SNEXT .GT.new SAFE *
29C. * = 2 Compute both SAFE and SNXT *
30C. * = 3 Compute SNXT only *
31C. * SNEXT (input) : see IACT = 1 *
32C. * SNXT (output) : distance to volume boundary *
33C. * SAFE (output) : shortest distance to any boundary *
34C. * *
35C. * ==>Called by : GNEXT, GTNEXT *
36C. * Authors M.J. Corden, A.Palounek *
37C. * *
38C. ******************************************************************
39C.
40#include "geant321/gconsp.inc"
41 DIMENSION X(6),PAR(4)
42
43C-------------------------------------------------------------
44
45 SNXT = BIG
46 R2 = X(1)*X(1) + X(2)*X(2)
47 TANTHS=(TAN(PAR(4)*DEGRAD))**2
48
49C -------------------------------------------------
50C | Compute safety-distance 'SAFE' (P.Weidhaas) |
51C -------------------------------------------------
52
53 SAFZ1 = PAR(3) - X(3)
54 SAFZ2 = PAR(3) + X(3)
55
56 IF (IACT .LT. 3) THEN
57
58C tube version:
59C R = SQRT (R2)
60C IF (PAR(1).NE.0.) THEN
61C SAFR1 = R - PAR(1)
62C ELSE
63C SAFR1 = BIG
64C ENDIF
65C SAFR2 = PAR(2) - R
66C
67C SAFE = MIN (SAFZ1, SAFZ2, SAFR1, SAFR2)
68C
69C simple, safe choice for hyperboloid for now:
70 SAFE=0.
71C
72 IF (IACT .EQ. 0) GO TO 999
73 IF (IACT .EQ. 1) THEN
74 IF (SNEXT .LT. SAFE) GO TO 999
75 ENDIF
76 ENDIF
77
78C ------------------------------------------------
79C | Compute vector-distance 'SNXT' (McPherson) |
80C ------------------------------------------------
81
82C
83C Compute intersection with z-boundaries.
84C
85 IF(X(6).GT.0.)THEN
86 SNXT=SAFZ1/X(6)
87 ELSEIF(X(6).LT.0.)THEN
88 SNXT=-SAFZ2/X(6)
89 ENDIF
90C
91C Compute intercepts with inner & outer curved surfaces:
92C
93 A = X(4)**2 + X(5)**2 - X(6)**2*TANTHS
94 B = X(1)*X(4) + X(2)*X(5) - X(3)*X(6)*TANTHS
95
96 DO 38 NCYL =1,2
97 C = R2 - X(3)**2*TANTHS - PAR(NCYL)**2
98 SURD = B**2 - A*C
99 IF(SURD.GT.0.) THEN
100 SURD=SQRT(SURD)
101 DIST1=(-B+SURD)/A
102 IF(DIST1.GT.0.) SNXT=MIN(SNXT,DIST1)
103 DIST2=(-B-SURD)/A
104 IF(DIST2.GT.0.) SNXT=MIN(SNXT,DIST2)
105C not necessary to compute intercept with outer surface
106C if there is a positive intercept with inner surface:
107 IF(DIST1.GT.0. .OR. DIST2.GT.0.) GO TO 999
108 ENDIF
109 38 CONTINUE
110C
111 999 CONTINUE
112 END