]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/gdraw/gdfr3d.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / gdraw / gdfr3d.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:20:23 cernlib
6* Geant
7*
8*
9#include "geant321/pilot.h"
10*CMZ : 3.21/02 29/03/94 15.41.26 by S.Giani
11*-- Author :
12 SUBROUTINE GDFR3D(X,NPOINT,U,V)
13C.
14C. ******************************************************************
15C. * *
16C. * Routine to convert the N 3D points given by array X *
17C. * to the 2D points in U and V *
18C. * *
19C. * If IGMR=1 then 3D points are not projected onto *
20C. * U-V plane but used to build the APOLLO-GMR 3D structure *
21C. * *
22C. * ITR3D = 0 for standard projection; *
23C. * <> 0 for rotation + projection i.e. R-Z projection *
24C. * with sign of R located in ITRSGN [ITR3D] *
25C. * *
26C. * *
27C. * Steps from 3D to 2D when NPOINT>0 : *
28C. * *
29C. * a) for volumes (IOBJ=1) : *
30C. * transformation of the 3D point (x',y',z') in DRS *
31C. * (Daughter Reference System) into the 3D point (x,y,z) *
32C. * in MARS (MAster Reference System); *
33C. * *
34C. * for tracks/hits (IOBJ<>1) after GDRVOL with NRS<>0 : *
35C. * transformation of the 3D point (x',y',z') in MARS *
36C. * into the 3D point (x,y,z) in DRS; *
37C. * *
38C. * for tracks/hits (IOBJ<>1) after GDRAW/GDRAWC : *
39C. * nothing *
40C. * *
41C. * b) transformation of the 3D point (x,y,z) in MARS/DRS *
42C. * into the 3D point (xx,yy,zz) in PRS (Projection *
43C. * Reference System); PRS has its z axis along *
44C. * the observer's line of sight (going to into the eye) *
45C. * *
46C. * c) transformation of the 3D point (xx,yy,zz) in PRS *
47C. * into the 2D point (u,v) in the plane normal to the *
48C. * observer's line of sight; at that stage if ITR3D=0 *
49C. * (standard projection) then u=xx and v=yy, *
50C. * but if ITR3D <> 0 (rotation + projection i.e. R-Z) *
51C. * then the 3D point (xx,yy,zz) in PRS is rotated along *
52C. * xx axis until it is onto the xx-yy plane and finally *
53C. * u=xx (unchanged by the rotation) and v=yy *
54C. * *
55C. * ==>Called by : <USER>, GDAHIT, GDARC, GDAXIS, GDCIRC, *
56C. * GDCIRR, GDCIRY, GDCUT, GDCXYZ, GDLINE, *
57C. * GDPART, GDRECT, GDSURF, GDXYZ *
58C. * Authors : R.Brun, P.Zanarini ********* *
59C. * *
60C. ******************************************************************
61C.
62#include "geant321/gcvolu.inc"
63#include "geant321/gcdraw.inc"
64 DIMENSION XC(3),XYZ(3),VL(3),VM(3),VN(3),X(3,1),U(1),V(1)
65 DIMENSION XP(3,50)
66 SAVE VL,VM,VN
67C
68C.
69C. ------------------------------------------------------------------
70C.
71 CALL UCTOH('PERS',IPERS,4,4)
72C
73 IF(NPOINT.EQ.0)GO TO 100
74 N=NPOINT
75 IF(NPOINT.LT.0)N=-NPOINT
76 IF(NGVIEW.NE.0) GO TO 40
77C
78C First call compute the rotation matrix
79C
80 PH = ABS(MOD(GPHI,360.))
81 THET = ABS(MOD(GTHETA,360.))
82 IF(THET.LE.180.)GO TO 10
83 PH = PH + 180.
84 THET = 360. - THET
85C
86 10 ST = SIN(THET * 0.017453)
87 CT = COS(THET * 0.017453)
88 SP = SIN(PH * 0.017453)
89 CP = COS(PH * 0.017453)
90C
91C VN is new nu axis
92C
93 VN(1) = ST * CP
94 VN(2) = ST * SP
95 VN(3) = CT
96C
97 IF(ABS(VN(2)).GT.0.99999)GO TO 20
98C
99 VM(1) = 0.
100 VM(2) = 1.
101 VM(3) = 0.
102C
103C Define new lambda axis
104C
105 CALL CROSS(VM,VN,VL)
106 CALL VUNIT(VL,VL,3)
107C
108C Define new mu axis
109C
110 CALL CROSS(VN,VL,VM)
111 GO TO 30
112C
113C Special case when observer line of sight is along mu:
114C in this case one chooses arbitrarily the vertical axis of
115C plane of projection as the lambda axis and the horizontal
116C as the nu axis
117C
118 20 VL(1) = 0.
119 VL(2) = 0.
120 VL(3) = 1.
121 VM(1) = 1.
122 VM(2) = 0.
123 VM(3) = 0.
124 30 CONTINUE
125C
126 NGVIEW=1
127C
128 40 CONTINUE
129C
130C Begin of a call with viewing tranformation unchanged (NGVI
131C
132 DO 90 I=1,N
133C
134 IF (NPOINT.LT.0) THEN
135C
136C NPOINT < 0 : X is in MARS
137C
138 IF (IGMR.EQ.1) THEN
139 DO 50 J=1,3
140 50 XP(J,I)=X(J,I)
141 GO TO 90
142 ENDIF
143C
144C Transform X (MARS) in XYZ (PRS)
145C i.e. project onto U,V,W
146C
147 XYZ(1)=X(1,I)*VL(1)+X(2,I)*VL(2)+X(3,I)*VL(3)
148 XYZ(2)=X(1,I)*VM(1)+X(2,I)*VM(2)+X(3,I)*VM(3)
149 XYZ(3)=X(1,I)*VN(1)+X(2,I)*VN(2)+X(3,I)*VN(3)
150C
151 ELSE
152C
153 IF (IOBJ.NE.1) THEN
154C
155C NPOINT > 0 and IOBJ <> 1 : X belongs to a track or hit or
156C so it must be transformed from MARS to last DRS used by GD
157C (otherwise GTRAN0 and GRMAT0 are the unitary transformatio
158C and X is still expressed in MARS)
159C
160 CALL GTRNSF(X(1,I),GTRAN0,GRMAT0,XC)
161C
162 ELSE
163C
164C NPOINT > 0 and IOBJ = 1 : X belongs to a volume,
165C so it must be transformed from DRS to MARS
166C
167 CALL GINROT(X(1,I),GRMAT(1,NLEVEL),XC)
168 DO 60 J=1,3
169 60 XC(J)=XC(J)+GTRAN(J,NLEVEL)
170C
171 ENDIF
172C
173 IF (IGMR.EQ.1) THEN
174 DO 70 J=1,3
175 70 XP(J,I)=XC(J)
176 GO TO 90
177 ENDIF
178C
179C Transform XC (MARS or DRS) in XYZ (PRS)
180C i.e. project onto U,V,W
181C
182 XYZ(1)=XC(1)*VL(1)+XC(2)*VL(2)+XC(3)*VL(3)
183 XYZ(2)=XC(1)*VM(1)+XC(2)*VM(2)+XC(3)*VM(3)
184 XYZ(3)=XC(1)*VN(1)+XC(2)*VN(2)+XC(3)*VN(3)
185C
186 ENDIF
187C
188C Scale, shift and rotate in in U and V
189C
190 80 CONTINUE
191C
192C R-Z projection ?
193C
194 IF (ITR3D.NE.0) CALL GDTHRZ(XYZ)
195C
196C Perspective projection ?
197C
198 IF (IPRJ.EQ.IPERS) THEN
199 IF (XYZ(3).GE.DPERS) XYZ(3)=DPERS-0.0001
200 XYZ(1)=XYZ(1)*DPERS/(DPERS-XYZ(3))
201 XYZ(2)=XYZ(2)*DPERS/(DPERS-XYZ(3))
202 ENDIF
203C
204 UU=XYZ(1)*GSCU
205 VV=XYZ(2)*GSCV
206 U(I)=GU0+UU*COSPSI-VV*SINPSI
207 V(I)=GV0+UU*SINPSI+VV*COSPSI
208C
209C Zoom processing
210C
211 U(I)=U(I)*GZUA+GZUB+GZUC
212 V(I)=V(I)*GZVA+GZVB+GZVC
213C
214 90 CONTINUE
215C
216 IF (IGMR.EQ.1) CALL GM3POL(XP,N)
217C
218 100 CONTINUE
219 END