]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ggeom/gvlong.F
Do not save CVS subdirectories
[u/mrichter/AliRoot.git] / GEANT321 / ggeom / gvlong.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:20:57 cernlib
6* Geant
7*
8*
9#include "geant321/pilot.h"
10*CMZ : 3.21/02 29/03/94 15.41.31 by S.Giani
11*-- Author :
12*
13 SUBROUTINE GVLONG (DIR, C, NC, TAU, NTAU)
14************************************************************************
15* *
16* GVLONG calculates the distance to the surface along a VP 920125 *
17* given DIRection *
18* *
19* SHOULD BE called ONLY AFTER call GVSAFE. *
20* due to some results of GVSAFE are used. *
21* Just by this reason starting XYZ point *
22* is omitted *
23* ======================================= *
24* *
25* Input : DIR - direction *
26* C - coeffs of surface (C(1) not used) *
27* NC - number of coefs *
28* *
29* Output : TAU - TAU(1:2) distances to surface in increasing order *
30* in the units of the length of DIR *
31* NTAU - number of distances (solutions) (0,1,2) *
32* *
33************************************************************************
34 COMMON /SLATE/ SLATE (40)
35 INTEGER ISLATE(40)
36 EQUIVALENCE (SLATE,ISLATE)
37 REAL C(*), DIR(3), TAU(2), CBA(3)
38 LOGICAL XLINE
39*-----------------------------------------------------------------------
40*
41* SLATE(10) is the value of S(X) = equation of the surface with
42* the point coordinates
43* SLATE(11),SLATE(12),SLATE(13) is the gradient to the surface
44*
45 NTAU = 0
46 CBA(1) = SLATE(10)
47 CBA(2) = SLATE(11)*DIR(1)+SLATE(12)*DIR(2)+SLATE(13)*DIR(3)
48*
49 CBA(3) = 0.
50 XLINE = .TRUE.
51*
52** in case of a plane
53 IF (NC.EQ.4) GO TO 200
54*
55* in case it is a simplified surface X=-C0,Y=-C0,Z=-C0, or X*2+Y*2=-C0
56*
57 IF (NC.EQ.2) THEN
58 IAX = C(2)
59 IF (IAX.NE.4) GO TO 200
60 CBA(3) = DIR(1)**2+DIR(2)**2
61 ELSE
62*
63** in case it is a surface with 7 or 10 coefficients
64 CBA(3) = DIR(1)**2*C(5)+DIR(2)**2*C(6)+DIR(3)**2*C(7)
65*
66** in case it is a surface with 10 coefficients
67 IF (NC.EQ.10) THEN
68 CBA(3) = CBA(3) + C(08)*DIR(1)*DIR(2)
69 CBA(3) = CBA(3) + C(09)*DIR(2)*DIR(3)
70 CBA(3) = CBA(3) + C(10)*DIR(3)*DIR(1)
71 ENDIF
72 ENDIF
73 XLINE = .FALSE.
74*
75 200 IF (XLINE) THEN
76*
77* in case it is a plane (4 coefficients) or a simplified surface
78*
79 IF (1.E+6*ABS(CBA(2)).LE.ABS(CBA(1))) GO TO 999
80 NTAU = 1
81 TAU(1) = - CBA(1)/CBA(2)
82 ELSE
83*
84** in case it is a surface with 7 or 10 coefficients
85 CALL GVPSQR (CBA, TAU, NTAU)
86 ENDIF
87*
88 999 NTAU = MAX(0,NTAU)
89 RETURN
90 END