]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/gdraw/gdrayt.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / gdraw / gdrayt.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:20:30 cernlib
6* Geant
7*
8*
9#include "geant321/pilot.h"
10*CMZ : 3.21/02 03/07/94 19.26.33 by S.Giani
11*-- Author :
12 SUBROUTINE GDRAYT(NAME,UTHET,UPHI,UPSI,UU0,UV0,SU,SV)
13C.
14C. ******************************************************************
15C. * *
16C. * RAY-TRACING *
17C. * This routine draws the objects, in the Jvolum data *
18C. * data structure, that are visible. The objects are drawn *
19C. * at the screen point (UU0,UV0), with the *
20C. * screen factors SU and SV acting on the U and V *
21C. * dimensions respectively; *
22C. * the object is rotated by an angle UTHET along Y-axis *
23C. * and UPHI along Z-axis and the resulting 2-D picture *
24C. * is also rotated by an angle UPSI along the line of *
25C. * projection (i.e. the normal to the 2-D view plane). *
26C. * *
27C. * Author: S.Giani. *
28C. ******************************************************************
29C.
30#include "geant321/gcbank.inc"
31#include "geant321/gcvolu.inc"
32#include "geant321/gcunit.inc"
33#include "geant321/gcdraw.inc"
34#include "geant321/gconst.inc"
35#include "geant321/gcmutr.inc"
36********************************************************************************
37#include "geant321/gcflag.inc"
38#include "geant321/gcstak.inc"
39#include "geant321/gcrayt.inc"
40#include "geant321/gcpixe.inc"
41 COMMON/INIFIR/NFIRST
42********************************************************************************
43*
44 CHARACTER*4 NAME
45
46 DIMENSION V(3),T(4,3)
47 SAVE IFIRST
48 DATA IFIRST/0/
49*
50 CALL UCTOH('PERS',IPERS,4,4)
51*
52 IF(NFIRST.EQ.0) THEN
53 CALL GDCOTA
54 NFIRST = 1
55 ENDIF
56C
57 IF (IFIRST.NE.0) GO TO 40
58C
59 IFIRST=1
60 DPHI=PI/20.
61 PHI=0.
62C
63 DO 30 I=1,40
64 GSIN(I)=SIN(PHI)
65 GCOS(I)=COS(PHI)
66 PHI=PHI+DPHI
67 30 CONTINUE
68C
69 GSIN(41)=GSIN(1)
70 GCOS(41)=GCOS(1)
71C
72 40 CONTINUE
73C
74C Theta, phi and psi angles are normalized in [0-360[ range
75C
76
77 GTHETA=MOD(ABS(UTHET),360.)
78 GPHI=MOD(ABS(UPHI),360.)
79 GPSI=MOD(ABS(UPSI),360.)
80 IMOD=0
81*
82* Set Transformation Matrix T as for CG Package
83*
84 V(1)=GTHETA
85 V(2)=GPHI
86 V(3)=GPSI
87 CALL GDCGVW(V,T)
88********************************************************************************
89 CALL ISFACI(1)
90 CALL ISFAIS(1)
91 if(iswit(9).ne.67890)CALL IGBOX(0.,20.,20.,0.)
92 DO 101 IHH=1,3
93 DO 102 JHH=1,4
94 AROTS(IHH,JHH)=T(JHH,IHH)
95 102 CONTINUE
96 101 CONTINUE
97 AROTS(4,1)=0.
98 AROTS(4,2)=0.
99 AROTS(4,3)=0.
100 AROTS(4,4)=1.
101 DO 105 IHH=1,4
102 DO 106 JHH=1,4
103 ZROTS(IHH,JHH)=AROTS(IHH,JHH)
104 106 CONTINUE
105 105 CONTINUE
106 CALL RINV(4,ZROTS,4,RRR,IFAIL)
107 IFLAPE=0
108 IF(IPERS.EQ.IPRJ)THEN
109 IFLAPE=1
110 IF(DPERS.GT.5000.)DPERS=5000.
111 FZUV=8.4+DPERS
112 FPINTX=ZROTS(1,4)+ZROTS(1,1)*
113 + 10.+ZROTS(1,2)*10.+ZROTS(1,3)*
114 + FZUV
115 FPINTY=ZROTS(2,4)+ZROTS(2,1)*
116 + 10.+ZROTS(2,2)*10.+ZROTS(2,3)*
117 + FZUV
118 FPINTZ=ZROTS(3,4)+ZROTS(3,1)*
119 + 10.+ZROTS(3,2)*10.+ZROTS(3,3)*
120 + FZUV
121 ENDIF
122 ISFILL=0
123 CALL GFIND('*','FILL',ISFILL)
124 IF(ISFILL.EQ.0)ISFILL=10
125* CALL ISMKSC(0.)
126 CALL ISMK(1)
127 IMAP=0
128 IF(NMAP.GT.4)NMAP=4
129 IF(NMAP.GT.0)THEN
130 NNIM=2
131 ELSE
132 NNIM=1
133 ENDIF
134 DO 211 IM=1,NNIM
135 IF(NMAP.GT.0)IMAP=IMAP+1
136 IF(IMAP.EQ.1)THEN
137 IF(ISFILL.LT.NMAP)ISFILL=NMAP
138 ISSAVE=ISFILL
139 IOSAVE=IOMBRA
140 ISFILL=NMAP
141 IOMBRA=0
142 ELSEIF(IMAP.EQ.2)THEN
143 ZNMAP1=1./NMAP
144 ISFILL=ISSAVE
145 IOMBRA=IOSAVE
146 ENDIF
147 UUU=1./ISFILL
148 VVV=1./ISFILL
149 IXXX=1
150 IYYY=1
151 IF(IPERS.EQ.IPRJ)THEN
152 ZUV=DPERS
153 ELSE
154 ZUV=5000.
155 ENDIF
156 LIMPRE=20*ISFILL
157*
158 XPINTS=ZROTS(1,4)+ZROTS(1,1)*
159 + UUU+ZROTS(1,2)*VVV+ZROTS(1,3)*
160 + ZUV
161 YPINTS=ZROTS(2,4)+ZROTS(2,1)*
162 + UUU+ZROTS(2,2)*VVV+ZROTS(2,3)*
163 + ZUV
164 ZPINTS=ZROTS(3,4)+ZROTS(3,1)*
165 + UUU+ZROTS(3,2)*VVV+ZROTS(3,3)*
166 + ZUV
167* print *,xpints,ypints,zpints,'vertex from gdraw'
168 ISSEEN=0
169 CALL GTRIGC
170* IEVENT=IEVENT+1
171 CALL GTRIGI
172 CALL GTRIG
173 211 CONTINUE
174*
175********************************************************************************
176*
177 999 END