]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ggeom/gnotrp.F
This commit was generated by cvs2svn to compensate for changes in r2,
[u/mrichter/AliRoot.git] / GEANT321 / ggeom / gnotrp.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:20:53  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 GNOTRP(X,P,IACT,SNEXT,SNXT,SAFE)
13 C.
14 C.    ******************************************************************
15 C.    *                                                                *
16 C.    *     Compute distance up to intersection with 'TRAP' volume.    *
17 C.    *     from outside point X(1-3) along direction X(4-6)           *
18 C.    *                                                                *
19 C.    *     P    (input) : volume parameters                           *
20 C.    *     IACT (input) : action flag                                 *
21 C.    *         = 0  Compute SAFE only                                 *
22 C.    *         = 1  Compute SAFE, and SNXT only if SNEXT.GT.SAFE      *
23 C.    *         = 2  Compute both SAFE and SNXT                        *
24 C.    *         = 3  Compute SNXT only                                 *
25 C.    *     SNEXT (input)    : see IACT = 1                            *
26 C.    *     SNXT  (output)   : distance to volume boundary             *
27 C.    *     SAFE  (output)   : shortest distance to any boundary       *
28 C.    *                                                                *
29 C.    *     Scalar Distance to Volume.                                 *
30 C.    *     The scalar distance from a point to a hexahedron can be    *
31 C.    *     the distance from the point to a surface,                  *
32 C.    *     the distance from the point to an edge or                  *
33 C.    *     the distance from the point to a vertex.                   *
34 C.    *     Here we compute only the distances to the planes of the    *
35 C.    *     six surfaces and take the maximum.                         *
36 C.    *     Since the distances to edges or vertices can only be       *
37 C.    *     larger, this is a first approximation to                   *
38 C.    *     SAFETY, that is a value which is not larger than the       *
39 C.    *     distance from the point to the volume.                     *
40 C.    *                                                                *
41 C.    *    ==>Called by : GNEXT, GTNEXT                                *
42 C.    *         Author  R.Nierhaus  *********                          *
43 C.    *                                                                *
44 C.    ******************************************************************
45 *
46 #include "geant321/gconsp.inc"
47 *
48       DIMENSION X(6),P(35)
49 *
50       SAFE=-BIG
51       SNXT=BIG
52       DO 1 I=12,32,4
53          T1=P(I)*X(1)+P(I+1)*X(2)+P(I+2)*X(3)+P(I+3)
54          IF (SAFE.LT.T1) SAFE=T1
55     1 CONTINUE
56       IF (IACT.EQ.0.OR.(IACT.EQ.1.AND.SNEXT.LE.SAFE)) RETURN
57 *
58 *     Vector Distance to Volume.
59 *     Volume is hexahedron.
60 *     (X(1),X(2),X(3)) is outside.
61 *     P(1),P(2) ... P(11) are the standard Geant execution time
62 *     parameters for a shape 4 (TRAP) volume.
63 *     P(12) ... P(35) contain boundary surface data.
64 *     P(12),P(13),P(14),P(15) are the coefficients of the normalized
65 *     implicit plane equation for the first boundary surface.
66 *     P(16),P(17),P(18),P(19) for the second boundary surface.
67 *     P(32),P(33),P(34),P(35) for the last (sixth) boundary surface.
68 *     The first three coefficients are the components of a unit
69 *     vector pointing away from the volume.
70 *     T1 is the signed orthogonal distance of the point
71 *     (X(1),X(2),X(3)) and a boundary plane.
72 *     If this distance is negative, the track cannot enter the
73 *     volume through the corresponding face.
74 *     T2 is the cosine of the angle between the plane normal and the
75 *     track directions (X(4),X(5),X(6)).
76 *     T3 is the vector distance to the corresponding surface.
77 *
78       SNXT1=-BIG
79       DO 2 I=12,32,4
80          T1=P(I)*X(1)+P(I+1)*X(2)+P(I+2)*X(3)+P(I+3)
81          IF (0.LT.T1) THEN
82             T2=P(I)*X(4)+P(I+1)*X(5)+P(I+2)*X(6)
83             T3=-.0000001
84             IF (T2.NE.0.) T3=-T1/T2
85             IF (0..LE.T3) THEN
86                IF (SNXT1.LT.T3) SNXT1=T3
87             END IF
88          END IF
89     2 CONTINUE
90       IF (SNXT1.EQ.-BIG) RETURN
91 *
92       T=1.00001*SNXT1+.00001
93 *
94 *     (XQ,YQ,ZQ) is the intersection point of the track with
95 *     a boundary surface plane.
96 *     P(I)*XQ+P(I+1)*YQ+P(I+2)*ZQ+P(I+3) is the signed distance of
97 *     the intersection point with a boundary surface plane.
98 *     If this distance is positive for any of the six surfaces,
99 *     the intersection is not with the volume.
100 *     A small correction is applied which moves the point slightly
101 *     to the interior of the volume to protect against rounding
102 *     errors.
103 *
104       XQ=X(1)+T*X(4)
105       YQ=X(2)+T*X(5)
106       ZQ=X(3)+T*X(6)
107       DO 3 I=12,32,4
108          IF (0.LT.P(I)*XQ+P(I+1)*YQ+P(I+2)*ZQ+P(I+3)) RETURN
109     3 CONTINUE
110       SNXT=SNXT1
111 *
112       END