]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ggeom/gntube.F
Allow any Cherenkov-like particle to be transported
[u/mrichter/AliRoot.git] / GEANT321 / ggeom / gntube.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:20:54  cernlib
6 * Geant
7 *
8 *
9 #include "geant321/pilot.h"
10 *CMZ :  3.21/02 29/03/94  15.41.30  by  S.Giani
11 *-- Author :
12       SUBROUTINE GNTUBE(X,P,IACT,IFL,SNEXT,SNXT,SAFE)
13 C.    ******************************************************************
14 C.    *                                                                *
15 C.    *      Compute distance to intersection with boundary surface of *
16 C     *      volume TUBE or TUBS, from point X(1),X(2),X(3)  INSIDE    *
17 C     *      the volume along track with direction cosines X(4),X(5),  *
18 C     *      X(6)                                                      *
19 C.    *      P     (input)  : volume parameters                        *
20 C.    *      IACT  (input)  : action flag                              *
21 C.    *         = 0  Compute SAFE only                                 *
22 C.    *         = 1  Compute SAFE, compute SNXT only if SAFE.LT.SNEXT  *
23 C.    *         = 2  Compute both SAFE and SNXT                        *
24 C.    *         = 3  Compute SNXT only                                 *
25 C.    *      IFL   (input)  : 1 for TUBE, 2 for PHI segmented TUBE     *
26 C.    *      SNEXT (input)  : see IACT = 1                             *
27 C.    *      SNXT  (output) : distance to volume boundary along track  *
28 C.    *      SAFE  (output) : not larger than scalar distance to       *
29 C.    *                       volume boundaray                         *
30 C.    *      Called by : GNEXT, GNPCON, GTNEXT                         *
31 C.    *                                                                *
32 C.    *      Authors   : Michel Maire and Rolf Nierhaus    21-JUN-1990 *
33 C.    *                                                                *
34 C.    ******************************************************************
35 C.    *                                                                *
36 C.    * 'TUBE'    is a tube. It has 3 parameters, the inside radius,   *
37 C.    *           the outside radius and the half length in z.         *
38 C.    * 'TUBS'    is a phi segment of a  tube.  It has 5 parameters,   *
39 C.    *           the same  3 as  'TUBE' plus  the phi  limits.  The   *
40 C.    *           segment  starts at  the first  limit and  includes   *
41 C.    *           increasing phi  value up  to the  second limit  or   *
42 C.    *           that plus 360 degrees.                               *
43 C.    *                                                                *
44 C.    ******************************************************************
45 #include "geant321/gconsp.inc"
46       DIMENSION X(6),P(5)
47 *
48 *     this part has to be moved outside the routine
49       IF (IFL.EQ.2) THEN
50          P4=P(4)*DEGRAD
51          P5=P(5)*DEGRAD
52          IF (P5.LT.P4) P5=P5+TWOPI
53          C1=COS(P4)
54          S1=SIN(P4)
55          C2=COS(P5)
56          S2=SIN(P5)
57          FIO=0.5*(P5+P4)
58          CFIO=COS(FIO)
59          SFIO=SIN(FIO)
60       END IF
61 *
62       SNXT=1.E10
63       R=SQRT(X(1)**2+X(2)**2)
64 *
65 *     Compute SAFE radius
66       IF (IACT.LT.3) THEN
67          SAF1=R-P(1)
68          SAF2=P(2)-R
69          SAF3=P(3)-ABS(X(3))
70          SAF4=1.E10
71          IF (IFL.EQ.2) THEN
72             IF ((X(2)*CFIO-X(1)*SFIO).LE.0.) THEN
73                SAF4=ABS(X(1)*S1-X(2)*C1)
74             ELSE
75                SAF4=ABS(X(1)*S2-X(2)*C2)
76             END IF
77          ENDIF
78          SAFE=MIN(SAF1,SAF2,SAF3,SAF4)
79          IF (IACT.EQ.0) GO TO 999
80          IF (IACT.EQ.1.AND.SNEXT.LE.SAFE) GO TO 999
81       END IF
82 *
83 *     Intersection with z-plane
84       IF (X(6).GT.1.E-20) THEN
85          SZ= (P(3)-X(3))/X(6)
86       ELSEIF (X(6).LT.-1.E-20) THEN
87          SZ=-(P(3)+X(3))/X(6)
88       ELSE
89          SZ=1.E10
90       END IF
91 *
92 *     Intersection with cylinders
93 *     Intersection point (x,y,z)
94 *     (x,y,z) is on track :    x=X(1)+t*X(4)
95 *                              y=X(2)+t*X(5)
96 *                              z=X(3)+t*X(6)
97 *     (x,y,z) is on cylinder : x**2 + y**2 = R**2
98 *
99 *     (X(4)**2+X(5)**2)*t**2
100 *     +2.*(X(1)*X(4)+X(2)*X(5))*t
101 *     +X(1)**2+X(2)**2-R**2=0
102 *
103       T1=X(4)**2+X(5)**2
104       T2=(X(1)*X(4)+X(2)*X(5))
105       T3=X(1)**2+X(2)**2
106       IF (T1.LE.0.) THEN
107 *        track parallel to the z-axis
108          SNXT=SZ
109          GO TO 999
110       ENDIF
111       B=T2/T1
112 *
113 *     Intersection with inner cylinder
114       IF (P(1).GT.0.) THEN
115          C=(T3-P(1)**2)/T1
116          D=B**2-C
117          IF (D.GE.0.) THEN
118             SR=-B-SQRT(D)
119             IF (SR.GE.0.) GO TO 101
120          END IF
121       END IF
122 *     Intersection with outer cylinder
123          C=(T3-P(2)**2)/T1
124          D=MAX(B**2-C,0.)
125          SR=-B+SQRT(D)
126 *
127 *     Intersection with phi-planes
128 *     x=r*cos(phi)=X(1)+t*X(4)
129 *     y=r*sin(phi)=X(2)+t*X(5)
130 *     z           =X(3)+t*X(6)
131 *     t=(X(2)*cos(phi)-X(1)*sin(phi))/(X(4)*sin(phi)-X(5)*cos(phi))
132   101 SFI1=1.E10
133       SFI2=1.E10
134       IF (IFL.EQ.2) THEN
135 *        track not parallel to the phi1 plane ?
136          UN=X(4)*S1-X(5)*C1
137          IF (UN.NE.0.) THEN
138             S=(X(2)*C1-X(1)*S1)/UN
139             IF (S.GE.0.) THEN
140                XI=X(1)+S*X(4)
141                YI=X(2)+S*X(5)
142                IF ((YI*CFIO-XI*SFIO).LE.0.) SFI1=S
143             END IF
144          END IF
145 *        track not parallel to the phi2 plane ?
146          UN=X(4)*S2-X(5)*C2
147          IF (UN.NE.0.) THEN
148             S=(X(2)*C2-X(1)*S2)/UN
149             IF (S.GE.0.) THEN
150                XI=X(1)+S*X(4)
151                YI=X(2)+S*X(5)
152                IF ((YI*CFIO-XI*SFIO).GE.0.) SFI2=S
153             END IF
154          END IF
155       END IF
156 *
157       SNXT=MIN(SZ,SR,SFI1,SFI2)
158   999 END