]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/gdraw/gdcgvw.F
100 parameters now allowed for geant shapes
[u/mrichter/AliRoot.git] / GEANT321 / gdraw / gdcgvw.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:20:21  cernlib
6 * Geant
7 *
8 *
9 #include "geant321/pilot.h"
10 *CMZ :  3.21/03 29/08/94  11.37.51  by  S.Giani
11 *-- Author :
12 *
13       SUBROUTINE GDCGVW (VPAR,VMA)
14 C.
15 C.    ******************************************************************
16 C.    *                                                                *
17 C.    *  Subroutine evaluates the Viewing Matrix from Viewing Angles   *
18 C.    *                                                                *
19 C.    *  Input Parameters:                                             *
20 C.    *                                                                *
21 C.    *     VPAR(3) : Viewing Angles (VPAR(1)=THETA, VPAR(2)=PHI,      *
22 C.    *               VPAR(3)=PSI)                                     *
23 C.    *                                                                *
24 C.    *  Output Parameters:                                            *
25 C.    *                                                                *
26 C.    *     VMA(4,3): Viewing Matrix                                   *
27 C.    *                                                                *
28 C.    *    ==>Called by :   GDINIT,GDRAW                               *
29 C.    *                                                                *
30 C.    *       Author : J.Salt     *********                            *
31 C.    *                                                                *
32 C.    ******************************************************************
33 C.
34 #include "geant321/gcdraw.inc"
35 #include "geant321/gconsp.inc"
36 *
37       DIMENSION  VPAR(3),AMTR(4,4),VMA(4,3)
38       DIMENSION  VL(3),VM(3),VN(3)
39       COMMON/PROSP/SVN(3)
40 *.______________________________________
41 *
42 *      CALL ISCLIP(1)
43       IERR=0
44       DO 20 KK=1,4
45          DO 10 JJ=1,4
46             AMTR(KK,JJ)=0.
47    10    CONTINUE
48    20 CONTINUE
49 *
50 *         Normalise theta, phi and psi angles to [0-360] range
51 *
52       THETA = MOD(ABS(VPAR(1)),180.)
53       PHI = MOD(ABS(VPAR(2)),360.)
54       PSI = MOD(ABS(VPAR(3)),360.)
55 *
56 *         Ensure theta is in the range [0-180]
57 *
58       IF (THETA.GT.180.) THEN
59          PHI = PHI + 180.
60          THETA = 360. - THETA
61       ENDIF
62       SINPSI = SIN(PSI * DEGRAD)
63       COSPSI = COS(PSI * DEGRAD)
64       ST = SIN(THETA * DEGRAD)
65       CT = COS(THETA * DEGRAD)
66       SP = SIN(PHI * DEGRAD)
67       CP = COS(PHI * DEGRAD)
68 *
69 *         VN is new nu axis
70 *
71       VN(1) = ST * CP
72       SVN(1)=VN(1)
73       VN(2) = ST * SP
74       SVN(2)=VN(2)
75       VN(3) = CT
76       SVN(3)=VN(3)
77 *
78       IF (ABS(VN(2)).LT.0.99999) THEN
79 *
80 *         Y-axis is default mu axis (view up vector)
81 *
82          VM(1) = 0.
83          VM(2) = 1.
84          VM(3) = 0.
85 *
86 *           Define new lambda axis
87 *
88          VL(1)=VM(2)*VN(3)-VM(3)*VN(2)
89          VL(2)=VM(3)*VN(1)-VM(1)*VN(3)
90          VL(3)=VM(1)*VN(2)-VM(2)*VN(1)
91          VAVL=SQRT(VL(1)**2+VL(2)**2+VL(3)**2)
92          VL(1)=VL(1)/VAVL
93          VL(2)=VL(2)/VAVL
94          VL(3)=VL(3)/VAVL
95 *
96 *           Define new mu axis
97 *
98          VM(1)=VN(2)*VL(3)-VN(3)*VL(2)
99          VM(2)=VN(3)*VL(1)-VN(1)*VL(3)
100          VM(3)=VN(1)*VL(2)-VN(2)*VL(1)
101 *
102       ELSE
103 *
104 *           Special case when observer line of sight is along mu:
105 *           in this case one chooses arbitrarily the vertical axis of the
106 *           plane of projection as the lambda axis and the horizontal axis
107 *           as the nu axis
108 *
109          VL(1) = 0.
110          VL(2) = 0.
111          VL(3) = 1.
112          VM(1) = 1.
113          VM(2) = 0.
114          VM(3) = 0.
115       ENDIF
116 *
117 *         Get the view up vector by rotating the mu axis
118 *         PSI degrees in the view plane (= mu-nu plane)
119 *
120       VUPX = COSPSI * VM(1) + SINPSI * VL(1)
121       VUPY = COSPSI * VM(2) + SINPSI * VL(2)
122       VUPZ = COSPSI * VM(3) + SINPSI * VL(3)
123 *
124 *      Values for View Reference Point in NDC (CSw =1)
125 *
126       VRPX = 0.5
127       VRPY = 0.5
128       VRPZ = 0.5
129       VPNX = VN(1)
130       VPNY = VN(2)
131       VPNZ = VN(3)
132 *
133 *           Evaluate view matrix
134 *
135       CALL GDCGEM(VRPX,VRPY,VRPZ,VUPX,VUPY, VUPZ,VPNX, VPNY,VPNZ,IERR,
136      +AMTR)
137 *
138       IF (IERR.NE.0)RETURN
139 *
140       VMA(1,1)=AMTR(1,1)*GSCU
141       VMA(2,1)=AMTR(1,2)*GSCU
142       VMA(3,1)=AMTR(1,3)*GSCU
143       VMA(4,1)=GU0
144 *
145       VMA(1,2)=AMTR(2,1)*GSCV
146       VMA(2,2)=AMTR(2,2)*GSCV
147       VMA(3,2)=AMTR(2,3)*GSCV
148       VMA(4,2)=GV0
149 *
150       DO 30  K=1,4
151          VMA(K,3)=AMTR(3,K)
152    30 CONTINUE
153 *
154       END