/[PAMELA software]/DarthVader/TrackerLevel2/src/F77/track.f
ViewVC logotype

Contents of /DarthVader/TrackerLevel2/src/F77/track.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.2 - (show annotations) (download)
Thu Jun 1 09:03:09 2006 UTC (18 years, 6 months ago) by pam-fi
Branch: MAIN
CVS Tags: v0r02, v4r00, v2r01, v1r01beta, v1r00, v1r01, v3r04, v3r05, v3r06, v3r00, v3r03, v2r00BETA
Changes since 1.1: +181 -16 lines
Tracking routine updated in order to get track projected angles and track length

1
2 *************************************************************
3 *
4 * Routines to compute the NPOINT track intersection points
5 * with planes of z-coordinate given by ZIN
6 * given the track parameters
7 *
8 * The routine is based on GRKUTA, which computes the
9 * trajectory of a charged particle in a magnetic field
10 * by solving the equations of motion with Runge-Kuta method
11 *
12 * Variables that have to be assigned when the subroutine
13 * is called:
14 *
15 * ZIN(1-NPOINT) ----> z coordinates of the planes
16 * AL_P(1-5) ----> track-parameter vector
17 *
18 * NB !!!
19 * The routine works properly only if the
20 * planes are numbered in descending order
21 *
22 * Routines:
23 *
24 * DOTRACK(NPOINT,ZIN,XOUT,YOUT,AL_P,IFAIL)
25 * - old routine
26 *
27 * DOTRACK2(NPOINT,ZIN,XOUT,YOUT,THXOUT,THYOUT,AL_P,IFAIL)
28 * - as the old one, but:
29 * -- the projected angles are given as output
30 * -- the track lengths are given as output:
31 * ---- for planes above the reference plane, the length until
32 * the lower closest plane (reference plane included)
33 * ---- for planes below the reference plane, the length until
34 * the higher closest plane (reference plane included)
35 *
36 **************************************************************
37
38 SUBROUTINE
39 $ DOTRACK2(NPOINT,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
40
41 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
42
43 DIMENSION VECT(8),VECTINI(8),VOUT(8)
44 DATA TOLL/1.d-8/
45 * tolerance in reaching the next plane during the tracking procedure
46 * -----------------------------------------------
47 * I/O parameters
48 PARAMETER (NPOINT_MAX=100)
49 DIMENSION ZIN(NPOINT_MAX)
50 DIMENSION XOUT(NPOINT_MAX),YOUT(NPOINT_MAX)
51 DIMENSION THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX)
52 DIMENSION TLOUT(NPOINT_MAX)
53 DIMENSION AL_P(5)
54 * -----------------------------------------------
55 DATA ZINI/23.5/ !z coordinate of the reference plane
56
57 * ==================================================================
58 * divide the track in two parts: below and above the reference plane
59 * ==================================================================
60 IUPDOWN=0
61 DO I=1,NPOINT
62 IF(ZIN(I).LT.ZINI)THEN
63 if(i.ne.1)IUPDOWN=I
64 GOTO 88
65 ENDIF
66 IUPDOWN=NPOINT+1
67 ENDDO
68 88 CONTINUE
69
70 * ==================================================================
71 * track from reference plane DOWN
72 * ==================================================================
73 * parameters for GRKUTA
74 IF(AL_P(5).NE.0) CHARGE=AL_P(5)/DABS(AL_P(5))
75 IF(AL_P(5).EQ.0) CHARGE=1.
76 VOUT(1)=AL_P(1)
77 VOUT(2)=AL_P(2)
78 VOUT(3)=ZINI
79 VOUT(4)=AL_P(3)*DCOS(AL_P(4))
80 VOUT(5)=AL_P(3)*DSIN(AL_P(4))
81 VOUT(6)=-1.*DSQRT(1.-AL_P(3)**2)
82 IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5))
83 IF(AL_P(5).EQ.0.) VOUT(7)=1.E8
84 DO I=MAX(IUPDOWN,1),NPOINT
85 step=vout(3)-zin(i)
86 VOUT(8)= 0
87 c$$$ print*,'DOWN ',i,' - Track from ',
88 c$$$ $ vout(3),' to ',zin(i),' step ',step
89 10 DO J=1,8
90 VECT(J)=VOUT(J)
91 VECTINI(J)=VOUT(J)
92 ENDDO
93 11 continue
94 CALL GRKUTA2(CHARGE,STEP,VECT,VOUT)
95 IF(VOUT(3).GT.VECT(3)) THEN
96 IFAIL=1
97 c$$$ PRINT *,'=== WARNING ===> tracciamento invertito (DOWN)'
98 c$$$ print*,'charge',charge
99 c$$$ print*,'vect',vect
100 c$$$ print*,'vout',vout
101 c$$$ print*,'step',step
102 RETURN
103 ENDIF
104 Z=VOUT(3)
105 IF(Z.LE.ZIN(I)+TOLL.AND.Z.GE.ZIN(I)-TOLL) GOTO 100
106 IF(Z.GT.ZIN(I)+TOLL) GOTO 10
107 IF(Z.LE.ZIN(I)-TOLL) THEN
108 STEP=STEP*(ZIN(I)-VECT(3))/(Z-VECT(3))
109 DO J=1,8
110 VECT(J)=VECTINI(J)
111 ENDDO
112 GOTO 11
113 ENDIF
114 100 XOUT(I)=VOUT(1)
115 YOUT(I)=VOUT(2)
116 ZIN(I)=VOUT(3)
117 IF(VOUT(3).ne.0)THEN
118 THXOUT(I)=DATAN(VOUT(4)/VOUT(6))*180./ACOS(-1.)
119 THYOUT(I)=DATAN(VOUT(5)/VOUT(6))*180./ACOS(-1.)
120 ENDIF
121 TLOUT(I) = VOUT(8)
122 c print*,'D ',VECT(3),VOUT(3),VOUT(8),STEP
123 ENDDO
124
125
126
127 * ==================================================================
128 * track from reference plane UP
129 * ==================================================================
130 * parameters for GRKUTA:
131 * -opposite charge
132 * -opposite momentum direction
133 IF(AL_P(5).NE.0) CHARGE=-AL_P(5)/DABS(AL_P(5))
134 IF(AL_P(5).EQ.0) CHARGE=-1.
135 VOUT(1)=AL_P(1)
136 VOUT(2)=AL_P(2)
137 VOUT(3)=ZINI
138 VOUT(4)=-AL_P(3)*DCOS(AL_P(4))
139 VOUT(5)=-AL_P(3)*DSIN(AL_P(4))
140 VOUT(6)=1.*DSQRT(1.-AL_P(3)**2)
141 IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5))
142 IF(AL_P(5).EQ.0.) VOUT(7)=1.E8
143 DO I=MIN((IUPDOWN-1),NPOINT),1,-1
144 step=vout(3)-zin(i)
145 step = -step
146 VOUT(8)=0
147 c$$$ print*,'UP ',i,' - Track from ',
148 c$$$ $ vout(3),' to ',zin(i),' step ',step
149 20 DO J=1,8
150 VECT(J)=VOUT(J)
151 VECTINI(J)=VOUT(J)
152 ENDDO
153 22 continue
154 CALL GRKUTA2(CHARGE,STEP,VECT,VOUT)
155 IF(VOUT(3).LT.VECT(3)) THEN
156 IFAIL=1
157 c$$$ PRINT *,'=== WARNING ===> tracciamento invertito (UP)'
158 c$$$ print*,'charge',charge
159 c$$$ print*,'vect',vect
160 c$$$ print*,'vout',vout
161 c$$$ print*,'step',step
162 RETURN
163 ENDIF
164 Z=VOUT(3)
165 IF(Z.LE.ZIN(I)+TOLL.AND.Z.GE.ZIN(I)-TOLL) GOTO 200
166 IF(Z.LT.ZIN(I)-TOLL) GOTO 20
167 IF(Z.GE.ZIN(I)+TOLL) THEN
168 STEP=STEP*(ZIN(I)-VECT(3))/(Z-VECT(3))
169 DO J=1,8
170 VECT(J)=VECTINI(J)
171 ENDDO
172 GOTO 22
173 ENDIF
174 200 XOUT(I)=VOUT(1)
175 YOUT(I)=VOUT(2)
176 ZIN(I)=VOUT(3)
177 IF(VOUT(3).ne.0)THEN
178 THXOUT(I)=DATAN(VOUT(4)/VOUT(6))*180./ACOS(-1.)
179 THYOUT(I)=DATAN(VOUT(5)/VOUT(6))*180./ACOS(-1.)
180 ENDIF
181 TLOUT(I) = VOUT(8)
182
183 ENDDO
184
185 RETURN
186 END
187
188 ************************************************************************
189 *
190 *
191 *
192 *
193 ************************************************************************
194 SUBROUTINE DOTRACK(NPOINT,ZIN,XOUT,YOUT,AL_P,IFAIL)
195
196 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
197
198 DIMENSION VECT(7),VECTINI(7),VOUT(7)
199 DATA TOLL/1.d-8/
200 * tolerance in reaching the next plane during the tracking procedure
201 * -----------------------------------------------
202 * I/O parameters
203 PARAMETER (NPOINT_MAX=100)
204 DIMENSION ZIN(NPOINT_MAX)
205 DIMENSION XOUT(NPOINT_MAX),YOUT(NPOINT_MAX)
206 DIMENSION AL_P(5)
207 * -----------------------------------------------
208 DATA ZINI/23.5/ !z coordinate of the reference plane
209
210 * ==================================================================
211 * divide the track in two parts: below and above the reference plane
212 * ==================================================================
213 IUPDOWN=0
214 DO I=1,NPOINT
215 IF(ZIN(I).LT.ZINI)THEN
216 if(i.ne.1)IUPDOWN=I
217 GOTO 88
218 ENDIF
219 IUPDOWN=NPOINT+1
220 ENDDO
221 88 CONTINUE
222
223 * ==================================================================
224 * track from reference plane DOWN
225 * ==================================================================
226 * parameters for GRKUTA
227 IF(AL_P(5).NE.0) CHARGE=AL_P(5)/DABS(AL_P(5))
228 IF(AL_P(5).EQ.0) CHARGE=1.
229 VOUT(1)=AL_P(1)
230 VOUT(2)=AL_P(2)
231 VOUT(3)=ZINI
232 VOUT(4)=AL_P(3)*DCOS(AL_P(4))
233 VOUT(5)=AL_P(3)*DSIN(AL_P(4))
234 VOUT(6)=-1.*DSQRT(1.-AL_P(3)**2)
235 IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5))
236 IF(AL_P(5).EQ.0.) VOUT(7)=1.E8
237 DO I=MAX(IUPDOWN,1),NPOINT
238 step=vout(3)-zin(i)
239 c$$$ print*,'DOWN ',i,' - Track from ',
240 c$$$ $ vout(3),' to ',zin(i),' step ',step
241 10 DO J=1,7
242 VECT(J)=VOUT(J)
243 VECTINI(J)=VOUT(J)
244 ENDDO
245 11 continue
246 CALL GRKUTA(CHARGE,STEP,VECT,VOUT)
247 IF(VOUT(3).GT.VECT(3)) THEN
248 IFAIL=1
249 c$$$ PRINT *,'=== WARNING ===> tracciamento invertito (DOWN)'
250 c$$$ print*,'charge',charge
251 c$$$ print*,'vect',vect
252 c$$$ print*,'vout',vout
253 c$$$ print*,'step',step
254 RETURN
255 ENDIF
256 Z=VOUT(3)
257 IF(Z.LE.ZIN(I)+TOLL.AND.Z.GE.ZIN(I)-TOLL) GOTO 100
258 IF(Z.GT.ZIN(I)+TOLL) GOTO 10
259 IF(Z.LE.ZIN(I)-TOLL) THEN
260 STEP=STEP*(ZIN(I)-VECT(3))/(Z-VECT(3))
261 DO J=1,7
262 VECT(J)=VECTINI(J)
263 ENDDO
264 GOTO 11
265 ENDIF
266 100 XOUT(I)=VOUT(1)
267 YOUT(I)=VOUT(2)
268 ZIN(I)=VOUT(3)
269 * THXOUT(I)=
270 * THYOUT(I)=
271 ENDDO
272
273
274
275 * ==================================================================
276 * track from reference plane UP
277 * ==================================================================
278 * parameters for GRKUTA:
279 * -opposite charge
280 * -opposite momentum direction
281 IF(AL_P(5).NE.0) CHARGE=-AL_P(5)/DABS(AL_P(5))
282 IF(AL_P(5).EQ.0) CHARGE=-1.
283 VOUT(1)=AL_P(1)
284 VOUT(2)=AL_P(2)
285 VOUT(3)=ZINI
286 VOUT(4)=-AL_P(3)*DCOS(AL_P(4))
287 VOUT(5)=-AL_P(3)*DSIN(AL_P(4))
288 VOUT(6)=1.*DSQRT(1.-AL_P(3)**2)
289 IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5))
290 IF(AL_P(5).EQ.0.) VOUT(7)=1.E8
291 DO I=MIN((IUPDOWN-1),NPOINT),1,-1
292 step=vout(3)-zin(i)
293 step = -step
294 c$$$ print*,'UP ',i,' - Track from ',
295 c$$$ $ vout(3),' to ',zin(i),' step ',step
296 20 DO J=1,7
297 VECT(J)=VOUT(J)
298 VECTINI(J)=VOUT(J)
299 ENDDO
300 22 continue
301 CALL GRKUTA(CHARGE,STEP,VECT,VOUT)
302 IF(VOUT(3).LT.VECT(3)) THEN
303 IFAIL=1
304 c$$$ PRINT *,'=== WARNING ===> tracciamento invertito (UP)'
305 c$$$ print*,'charge',charge
306 c$$$ print*,'vect',vect
307 c$$$ print*,'vout',vout
308 c$$$ print*,'step',step
309 RETURN
310 ENDIF
311 Z=VOUT(3)
312 IF(Z.LE.ZIN(I)+TOLL.AND.Z.GE.ZIN(I)-TOLL) GOTO 200
313 IF(Z.LT.ZIN(I)-TOLL) GOTO 20
314 IF(Z.GE.ZIN(I)+TOLL) THEN
315 STEP=STEP*(ZIN(I)-VECT(3))/(Z-VECT(3))
316 DO J=1,7
317 VECT(J)=VECTINI(J)
318 ENDDO
319 GOTO 22
320 ENDIF
321 200 XOUT(I)=VOUT(1)
322 YOUT(I)=VOUT(2)
323 ZIN(I)=VOUT(3)
324
325 ENDDO
326
327 RETURN
328 END
329

  ViewVC Help
Powered by ViewVC 1.1.23