/[PAMELA software]/DarthVader/ToFLevel2/src/toftrk.for
ViewVC logotype

Contents of /DarthVader/ToFLevel2/src/toftrk.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (show annotations) (download)
Sat Jun 17 12:14:56 2006 UTC (18 years, 5 months ago) by mocchiut
Branch: MAIN
Branch point for: ToFLevel2
Initial revision

1 *****************************************************************************
2 INTEGER FUNCTION TOFTRK()
3 c
4 IMPLICIT NONE
5 C
6 include 'input_tof.txt'
7 include 'output_tof.txt'
8 include 'tofcomm.txt'
9 C
10
11 c =======================================
12 c variables for tracking routine
13 c =======================================
14 integer NPOINT_MAX
15 parameter(NPOINT_MAX=100)
16
17 c define TOF Z-coordinates
18 integer NPTOF
19 parameter (NPTOF=6)
20 DOUBLE PRECISION ZTOF(NPTOF)
21 DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
22
23 integer itof
24
25 DOUBLE PRECISION al_p(5),
26 & xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF)
27
28 INTEGER IFAIL
29 REAL dx,dy,dr,ds
30 REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2
31 REAL c1,c2,sw,sxw,w_i
32 INTEGER icount
33
34 REAL beta_mean
35
36
37 REAL theta12,theta13,theta23
38 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
39 REAL tofarm12
40 PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
41 REAL tofarm23
42 PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
43 REAL tofarm13
44 PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
45
46
47
48
49 INTEGER ihelp
50 REAL xkorr
51
52 REAL yl,yh,xl,xh
53 C
54 REAL hmemor(9000000)
55 INTEGER Iquest(100)
56 C
57 COMMON / pawcd / hmemor
58 save / pawcd /
59 C
60 Common / QUESTd / Iquest
61 save / questd /
62 C
63 C Begin !
64 C
65 TOFTRK = 0
66
67 *******************************************************************
68
69 offset = 1
70 slope = 2
71 left = 1
72 right = 2
73 none_ev = 0
74 none_find = 0
75 tdc_ev = 1
76 adc_ev = 1
77 itdc = 1
78 iadc = 2
79
80 do i=1,13
81 beta_a(i) = 100.
82 enddo
83
84 C------ read tracking routine
85 * igoodevent = igoodevent+1
86 * assigned input parameters for track routine
87 * 1) Z-coordinates where the trajectory is evaluated
88 do itof=1,NPTOF
89 ZIN(itof) = ZTOF(itof)
90 enddo
91 * 2) track status vector
92 C COPY THE ALFA VECTOR FROM AL_PP TO AL_P FOR THE TRACK "T"
93 do i=1,5
94 AL_P(i) = al_pp(i)
95 enddo
96 if (al_p(5).eq.0.) THEN
97 PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
98 GOTO 969
99 ENDIF
100 * -------- *** tracking routine *** --------
101 IFAIL = 0
102 call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
103 if(IFAIL.ne.0)then
104 print *,' TOF - WARNING F77: tracking failed '
105 goto 969
106 endif
107 * ------------------------------------------
108
109 969 continue
110
111 C-------------------------------------------------------------
112 C------- check which paddle penetrated the track -----------
113 C-------------------------------------------------------------
114 c middle y (or x) position of the upper and middle ToF-Paddle
115 c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
116 c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
117 c DATA tof21_y/ -3.75,3.75/
118 c DATA tof22_x/ -4.5,4.5/
119 c DATA tof31_x/ -6.0,0.,6.0/
120 c DATA tof32_y/ -5.0,0.0,5.0/
121 c
122 c S11 8 paddles 33.0 x 5.1 cm
123 c S12 6 paddles 40.8 x 5.5 cm
124 c S21 2 paddles 18.0 x 7.5 cm
125 c S22 2 paddles 15.0 x 9.0 cm
126 c S31 3 paddles 15.0 x 6.0 cm
127 c S32 3 paddles 18.0 x 5.0 cm
128
129
130 C-------------- S11 --------------------------------------
131
132 tof11_i = none_find
133
134 yl = -33.0/2.
135 yh = 33.0/2.
136
137 if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then
138 do i=1,8
139 xl = tof11_x(i) - 5.1/2.
140 xh = tof11_x(i) + 5.1/2.
141 if ((xout(1).gt.xl).and.(xout(1).le.xh)) then
142 tof11_i=i
143 endif
144 enddo
145 endif
146
147 C-------------- S12 --------------------------------------
148
149 tof12_i = none_find
150
151 xl = -40.8/2.
152 xh = 40.8/2.
153
154 if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then
155 do i=1,6
156 yl = tof12_y(i) - 5.5/2.
157 yh = tof12_y(i) + 5.5/2.
158 if ((yout(2).gt.yl).and.(yout(2).le.yh)) then
159 tof12_i=i
160 endif
161 enddo
162 endif
163
164 C-------------- S21 --------------------------------------
165
166 tof21_i = none_find
167
168 xl = -18./2.
169 xh = 18./2.
170
171 if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then
172 do i=1,2
173 yl = tof21_y(i) - 7.5/2.
174 yh = tof21_y(i) + 7.5/2.
175 if ((yout(3).gt.yl).and.(yout(3).le.yh)) then
176 tof21_i=i
177 endif
178 enddo
179 endif
180
181 C-------------- S22 --------------------------------------
182
183 tof22_i = none_find
184
185 yl = -15./2.
186 yh = 15./2.
187
188 if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then
189 do i=1,2
190 xl = tof22_x(i) - 9.0/2.
191 xh = tof22_x(i) + 9.0/2.
192 if ((xout(4).gt.xl).and.(xout(4).le.xh)) then
193 tof22_i=i
194 endif
195 enddo
196 endif
197
198 C-------------- S31 --------------------------------------
199
200 tof31_i = none_find
201
202 yl = -15.0/2.
203 yh = 15.0/2.
204
205 if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then
206 do i=1,3
207 xl = tof31_x(i) - 6.0/2.
208 xh = tof31_x(i) + 6.0/2.
209 if ((xout(5).gt.xl).and.(xout(5).le.xh)) then
210 tof31_i=i
211 endif
212 enddo
213 endif
214
215 C-------------- S32 --------------------------------------
216
217 tof32_i = none_find
218
219 xl = -18.0/2.
220 xh = 18.0/2.
221
222 if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then
223 do i=1,3
224 yl = tof32_y(i) - 5.0/2.
225 yh = tof32_y(i) + 5.0/2.
226 if ((yout(6).gt.yl).and.(yout(6).le.yh)) then
227 tof32_i=i
228 endif
229 enddo
230 endif
231
232 C----------------------------------------------------------------------
233 C--------------------Corrections on ADC-data -------------------------
234 C---------------------zenith angle theta ---------------------------
235 C----------------------------------------------------------------------
236
237
238 dx=0.
239 dy=0.
240 dr=0.
241 theta13 = 0.
242
243 if (xout(1).lt.100.) then
244 dx = xout(1)-xout(6)
245 dy = yout(1)-yout(6)
246 dr = sqrt(dx*dx+dy*dy)
247 theta13 = atan(dr/tofarm13)
248 endif
249
250
251 C----------------------------------------------------------------------
252 C------------------angle and ADC(x) correction
253 C----------------------------------------------------------------------
254 C-----------------------------S1 --------------------------------
255
256 yhelp=yout(1)
257
258 IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
259
260 i = tof11_i
261 xdummy=tof11(left,i,iadc)
262 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
263 if (tof11(left,i,iadc).lt.1000) then
264 xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
265 xkorr0=adcx11(left,i,1)
266 adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
267 endif
268
269 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
270 if (tof11(right,i,iadc).lt.1000) then
271 xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
272 xkorr0=adcx11(right,i,1)
273 adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
274 endif
275 ENDIF
276
277
278 xhelp=xout(2)
279 IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
280
281 i = tof12_i
282 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
283 if (tof12(left,i,iadc).lt.1000) then
284 xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
285 xkorr0=adcx12(left,i,1)
286 adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
287 endif
288
289 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
290 if (tof12(right,i,iadc).lt.1000) then
291 xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
292 xkorr0=adcx12(right,i,1)
293 adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
294 endif
295 ENDIF
296
297 C-----------------------------S2 --------------------------------
298
299 xhelp=xout(3)
300 IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
301
302 i = tof21_i
303 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
304 if (tof21(left,i,iadc).lt.1000) then
305 xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
306 xkorr0=adcx21(left,i,1)
307 adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
308 endif
309
310 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
311 if (tof21(right,i,iadc).lt.1000) then
312 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
313 xkorr0=adcx21(right,i,1)
314 adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
315 endif
316 ENDIF
317
318 yhelp=yout(4)
319 IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
320
321 i = tof22_i
322 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
323 if (tof22(left,i,iadc).lt.1000) then
324 xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
325 xkorr0=adcx22(left,i,1)
326 adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
327 endif
328
329 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
330 if (tof22(right,i,iadc).lt.1000) then
331 xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
332 xkorr0=adcx22(right,i,1)
333 adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
334 endif
335 ENDIF
336
337 C-----------------------------S3 --------------------------------
338
339 yhelp=yout(5)
340 IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
341
342 i = tof31_i
343 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
344 if (tof31(left,i,iadc).lt.1000) then
345 xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
346 xkorr0=adcx31(left,i,1)
347 adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
348 endif
349
350 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
351 if (tof31(right,i,iadc).lt.1000) then
352 xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
353 xkorr0=adcx31(right,i,1)
354 adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
355 endif
356 ENDIF
357
358 xhelp=xout(6)
359 IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
360
361 i = tof32_i
362 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
363 if (tof32(left,i,iadc).lt.1000) then
364 xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
365 xkorr0=adcx32(left,i,1)
366 adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
367 endif
368
369 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
370 if (tof32(right,i,iadc).lt.1000) then
371 xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
372 xkorr0=adcx32(right,i,1)
373 adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
374 endif
375 ENDIF
376
377 C-----------------------------------------------------------------------
378 C----------------------calculate Beta ------------------------------
379 C-----------------------------------------------------------------------
380 C-------------------difference of sums ---------------------------
381 C
382 C DS = (t1+t2) - t3+t4)
383 C DS = c1 + c2/beta*cos(theta)
384 C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
385 C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
386 C since TDC resolution varies slightly c2 has to be calibrated
387
388 C S11 - S31
389 IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
390 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
391 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
392 ds = xhelp1-xhelp2
393 ihelp=(tof11_i-1)*3+tof31_i
394 c1 = k_S11S31(1,ihelp)
395 c2 = k_S11S31(2,ihelp)
396 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
397 & beta_a(1) = c2/(cos(theta13)*(ds-c1))
398 ENDIF
399
400 C S11 - S32
401 IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
402 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
403 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
404 ds = xhelp1-xhelp2
405 ihelp=(tof11_i-1)*3+tof32_i
406 c1 = k_S11S32(1,ihelp)
407 c2 = k_S11S32(2,ihelp)
408 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
409 & beta_a(2) = c2/(cos(theta13)*(ds-c1))
410 ENDIF
411
412 C S12 - S31
413 IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
414 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
415 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
416 ds = xhelp1-xhelp2
417 ihelp=(tof12_i-1)*3+tof31_i
418 c1 = k_S12S31(1,ihelp)
419 c2 = k_S12S31(2,ihelp)
420 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
421 & beta_a(3) = c2/(cos(theta13)*(ds-c1))
422 ENDIF
423
424 C S12 - S32
425 IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
426 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
427 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
428 ds = xhelp1-xhelp2
429 ihelp=(tof12_i-1)*3+tof32_i
430 c1 = k_S12S32(1,ihelp)
431 c2 = k_S12S32(2,ihelp)
432 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
433 & beta_a(4) = c2/(cos(theta13)*(ds-c1))
434 ENDIF
435
436 C S21 - S31
437 IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
438 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
439 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
440 ds = xhelp1-xhelp2
441 ihelp=(tof21_i-1)*3+tof31_i
442 c1 = k_S21S31(1,ihelp)
443 c2 = k_S21S31(2,ihelp)
444 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
445 & beta_a(5) = c2/(cos(theta23)*(ds-c1))
446 ENDIF
447
448 C S21 - S32
449 IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
450 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
451 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
452 ds = xhelp1-xhelp2
453 ihelp=(tof21_i-1)*3+tof32_i
454 c1 = k_S21S32(1,ihelp)
455 c2 = k_S21S32(2,ihelp)
456 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
457 & beta_a(6) = c2/(cos(theta23)*(ds-c1))
458 ENDIF
459
460 C S22 - S31
461 IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
462 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
463 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
464 ds = xhelp1-xhelp2
465 ihelp=(tof22_i-1)*3+tof31_i
466 c1 = k_S22S31(1,ihelp)
467 c2 = k_S22S31(2,ihelp)
468 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
469 & beta_a(7) = c2/(cos(theta13)*(ds-c1))
470 ENDIF
471
472 C S22 - S32
473 IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
474 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
475 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
476 ds = xhelp1-xhelp2
477 ihelp=(tof22_i-1)*3+tof32_i
478 c1 = k_S22S32(1,ihelp)
479 c2 = k_S22S32(2,ihelp)
480 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
481 & beta_a(8) = c2/(cos(theta13)*(ds-c1))
482 ENDIF
483
484 C S11 - S21
485 IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
486 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
487 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
488 ds = xhelp1-xhelp2
489 ihelp=(tof11_i-1)*2+tof21_i
490 c1 = k_S11S21(1,ihelp)
491 c2 = k_S11S21(2,ihelp)
492 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
493 & beta_a(9) = c2/(cos(theta12)*(ds-c1))
494 ENDIF
495
496 C S11 - S22
497 IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
498 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
499 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
500 ds = xhelp1-xhelp2
501 ihelp=(tof11_i-1)*2+tof22_i
502 c1 = k_S11S22(1,ihelp)
503 c2 = k_S11S22(2,ihelp)
504 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
505 & beta_a(10) = c2/(cos(theta12)*(ds-c1))
506 ENDIF
507
508 C S12 - S21
509 IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
510 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
511 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
512 ds = xhelp1-xhelp2
513 ihelp=(tof12_i-1)*2+tof21_i
514 c1 = k_S12S21(1,ihelp)
515 c2 = k_S12S21(2,ihelp)
516 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
517 & beta_a(11) = c2/(cos(theta12)*(ds-c1))
518 ENDIF
519
520 C S12 - S22
521 IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
522 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
523 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
524 ds = xhelp1-xhelp2
525 ihelp=(tof12_i-1)*2+tof22_i
526 c1 = k_S12S22(1,ihelp)
527 c2 = k_S12S22(2,ihelp)
528 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
529 & beta_a(12) = c2/(cos(theta12)*(ds-c1))
530 ENDIF
531
532 C-------
533
534 icount=0
535 sw=0.
536 sxw=0.
537 beta_mean=100.
538
539 do i=1,12
540 if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
541 icount= icount+1
542 if (i.le.4) w_i=1./(0.13**2.)
543 if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
544 if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
545 sxw=sxw + beta_a(i)*w_i
546 sw =sw + w_i
547 endif
548 enddo
549
550 if (icount.gt.0) beta_mean=sxw/sw
551 beta_a(13) = beta_mean
552
553 RETURN
554 END
555
556

  ViewVC Help
Powered by ViewVC 1.1.23