/[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.5 - (show annotations) (download)
Tue Sep 12 13:58:24 2006 UTC (18 years, 2 months ago) by mocchiut
Branch: MAIN
CVS Tags: v2r00BETA
Changes since 1.4: +247 -45 lines
toftrk.for updated to use dotrack2 function

1 *****************************************************************************
2 INTEGER FUNCTION TOFTRK()
3
4 C****************************************************************************
5 C 31-08-06 WM
6 C Changed to use DOTRACK2
7 C Beta calculation: now the flightpath (instead of cos(theta)) is used
8 C Beta calculation: all 4 TDV measurements must be < 4095 (in the old
9 C routine it was (t1+t2)<8000
10 C
11 C****************************************************************************
12 IMPLICIT NONE
13 C
14 include 'input_tof.txt'
15 include 'output_tof.txt'
16 include 'tofcomm.txt'
17 C
18
19 c =======================================
20 c variables for tracking routine
21 c =======================================
22 integer NPOINT_MAX
23 parameter(NPOINT_MAX=100)
24
25 c define TOF Z-coordinates
26 integer NPTOF
27 parameter (NPTOF=6)
28 DOUBLE PRECISION ZTOF(NPTOF)
29 DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
30
31 integer itof
32
33 DOUBLE PRECISION al_p(5),
34 & xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
35 & THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
36
37
38 INTEGER IFAIL
39 REAL dx,dy,dr,ds
40 REAL t1,t2,t3,t4
41 REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2
42 REAL c1,c2,sw,sxw,w_i
43 REAL dist,dl,F
44 INTEGER icount,ievent
45
46 REAL beta_mean
47
48 INTEGER j
49
50 REAL theta12,theta13,theta23
51 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
52 REAL tofarm12
53 PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
54 REAL tofarm23
55 PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
56 REAL tofarm13
57 PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
58
59
60
61
62 INTEGER ihelp
63 REAL xkorr
64
65 REAL yl,yh,xl,xh
66 C
67 REAL hmemor(9000000)
68 INTEGER Iquest(100)
69 C
70 DATA ievent / 0 /
71
72 COMMON / pawcd / hmemor
73 save / pawcd /
74 C
75 Common / QUESTd / Iquest
76 save / questd /
77 C
78 C Begin !
79 C
80 TOFTRK = 0
81
82 *******************************************************************
83
84 ievent = ievent +1
85
86
87 offset = 1
88 slope = 2
89 left = 1
90 right = 2
91 none_ev = 0
92 none_find = 0
93 tdc_ev = 1
94 adc_ev = 1
95 itdc = 1
96 iadc = 2
97
98 do i=1,13
99 beta_a(i) = 100.
100 enddo
101
102 do i=1,4
103 do j=1,12
104 adc_c(i,j) = 1000.
105 enddo
106 enddo
107
108 do i=1,12
109 do j=1,4
110 tofmask(j,i) = 0
111 enddo
112 enddo
113
114 C------ read tracking routine
115 * igoodevent = igoodevent+1
116 * assigned input parameters for track routine
117 * 1) Z-coordinates where the trajectory is evaluated
118 do itof=1,NPTOF
119 ZIN(itof) = ZTOF(itof)
120 enddo
121 * 2) track status vector
122 C COPY THE ALFA VECTOR FROM AL_PP TO AL_P FOR THE TRACK "T"
123 do i=1,5
124 AL_P(i) = al_pp(i)
125 enddo
126
127 c write(*,*) AL_P
128
129 if (al_p(5).eq.0.) THEN
130 PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
131 GOTO 969
132 ENDIF
133 * -------- *** tracking routine *** --------
134 IFAIL = 0
135 C call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
136 call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
137
138
139 C write(*,*) (TLOUT(i),i=1,6)
140
141 if(IFAIL.ne.0)then
142 print *,' TOF - WARNING F77: tracking failed '
143 goto 969
144 endif
145 * ------------------------------------------
146
147 969 continue
148
149 C-------------------------------------------------------------
150 C------- check which paddle penetrated the track -----------
151 C-------------------------------------------------------------
152 c middle y (or x) position of the upper and middle ToF-Paddle
153 c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
154 c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
155 c DATA tof21_y/ -3.75,3.75/
156 c DATA tof22_x/ -4.5,4.5/
157 c DATA tof31_x/ -6.0,0.,6.0/
158 c DATA tof32_y/ -5.0,0.0,5.0/
159 c
160 c S11 8 paddles 33.0 x 5.1 cm
161 c S12 6 paddles 40.8 x 5.5 cm
162 c S21 2 paddles 18.0 x 7.5 cm
163 c S22 2 paddles 15.0 x 9.0 cm
164 c S31 3 paddles 15.0 x 6.0 cm
165 c S32 3 paddles 18.0 x 5.0 cm
166
167 c write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)
168 c write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)
169
170 C-------------- S11 --------------------------------------
171
172 tof11_i = none_find
173
174 yl = -33.0/2.
175 yh = 33.0/2.
176
177 if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then
178 do i=1,8
179 xl = tof11_x(i) - 5.1/2.
180 xh = tof11_x(i) + 5.1/2.
181 if ((xout(1).gt.xl).and.(xout(1).le.xh)) then
182 tof11_i=i
183 endif
184 enddo
185 endif
186
187 C-------------- S12 --------------------------------------
188
189 tof12_i = none_find
190
191 xl = -40.8/2.
192 xh = 40.8/2.
193
194 if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then
195 do i=1,6
196 yl = tof12_y(i) - 5.5/2.
197 yh = tof12_y(i) + 5.5/2.
198 if ((yout(2).gt.yl).and.(yout(2).le.yh)) then
199 tof12_i=i
200 endif
201 enddo
202 endif
203
204 C-------------- S21 --------------------------------------
205
206 tof21_i = none_find
207
208 xl = -18./2.
209 xh = 18./2.
210
211 if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then
212 do i=1,2
213 yl = tof21_y(i) - 7.5/2.
214 yh = tof21_y(i) + 7.5/2.
215 if ((yout(3).gt.yl).and.(yout(3).le.yh)) then
216 tof21_i=i
217 endif
218 enddo
219 endif
220
221 C-------------- S22 --------------------------------------
222
223 tof22_i = none_find
224
225 yl = -15./2.
226 yh = 15./2.
227
228 if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then
229 do i=1,2
230 xl = tof22_x(i) - 9.0/2.
231 xh = tof22_x(i) + 9.0/2.
232 if ((xout(4).gt.xl).and.(xout(4).le.xh)) then
233 tof22_i=i
234 endif
235 enddo
236 endif
237
238 C-------------- S31 --------------------------------------
239
240 tof31_i = none_find
241
242 yl = -15.0/2.
243 yh = 15.0/2.
244
245 if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then
246 do i=1,3
247 xl = tof31_x(i) - 6.0/2.
248 xh = tof31_x(i) + 6.0/2.
249 if ((xout(5).gt.xl).and.(xout(5).le.xh)) then
250 tof31_i=i
251 endif
252 enddo
253 endif
254
255 C-------------- S32 --------------------------------------
256
257 tof32_i = none_find
258
259 xl = -18.0/2.
260 xh = 18.0/2.
261
262 if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then
263 do i=1,3
264 yl = tof32_y(i) - 5.0/2.
265 yh = tof32_y(i) + 5.0/2.
266 if ((yout(6).gt.yl).and.(yout(6).le.yh)) then
267 tof32_i=i
268 endif
269 enddo
270 endif
271
272
273 C write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
274
275 C------------------------------------------------------------------
276 C--- calculate track position in paddle using timing difference
277 C------------------------------------------------------------------
278
279 do i=1,3
280 xtofpos(i)=100.
281 ytofpos(i)=100.
282 enddo
283 C-----------------------------S1 --------------------------------
284
285 IF (tof11_i.GT.none_find) THEN
286 ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
287 + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
288 endif
289
290 IF (tof12_i.GT.none_find) THEN
291 xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
292 + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
293 endif
294
295
296 C-----------------------------S2 --------------------------------
297
298 IF (tof21_i.GT.none_find) THEN
299 xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
300 + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
301 endif
302
303 IF (tof22_i.GT.none_find) THEN
304 ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
305 + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
306 endif
307
308
309 C-----------------------------S3 --------------------------------
310
311 IF (tof31_i.GT.none_find) THEN
312 ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
313 + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
314 endif
315
316 IF (tof32_i.GT.none_find) THEN
317 xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
318 + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
319 endif
320
321
322 do i=1,3
323 if (abs(xtofpos(i)).gt.100.) then
324 xtofpos(i)=101.
325 endif
326 if (abs(ytofpos(i)).gt.100.) then
327 ytofpos(i)=101.
328 endif
329 enddo
330
331 C----------------------------------------------------------------------
332 C--------------------Corrections on ADC-data -------------------------
333 C---------------------zenith angle theta ---------------------------
334 C----------------------------------------------------------------------
335
336
337 dx=0.
338 dy=0.
339 dr=0.
340 theta13 = 0.
341
342 if (xout(1).lt.100.) then
343 dx = xout(1)-xout(6)
344 dy = yout(1)-yout(6)
345 dr = sqrt(dx*dx+dy*dy)
346 theta13 = atan(dr/tofarm13)
347 endif
348
349
350 C----------------------------------------------------------------------
351 C------------------angle and ADC(x) correction
352 C----------------------------------------------------------------------
353 C-----------------------------S1 --------------------------------
354
355 yhelp=yout(1)
356
357 IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
358
359 i = tof11_i
360 xdummy=tof11(left,i,iadc)
361 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
362 if (tof11(left,i,iadc).lt.1000) then
363 xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
364 xkorr0=adcx11(left,i,1)
365 adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
366 endif
367
368 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
369 if (tof11(right,i,iadc).lt.1000) then
370 xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
371 xkorr0=adcx11(right,i,1)
372 adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
373 endif
374 ENDIF
375
376
377 xhelp=xout(2)
378 IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
379
380 i = tof12_i
381 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
382 if (tof12(left,i,iadc).lt.1000) then
383 xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
384 xkorr0=adcx12(left,i,1)
385 adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
386 endif
387
388 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
389 if (tof12(right,i,iadc).lt.1000) then
390 xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
391 xkorr0=adcx12(right,i,1)
392 adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
393 endif
394 ENDIF
395
396 C-----------------------------S2 --------------------------------
397
398 xhelp=xout(3)
399 IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
400
401 i = tof21_i
402 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
403 if (tof21(left,i,iadc).lt.1000) then
404 xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
405 xkorr0=adcx21(left,i,1)
406 adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
407 endif
408
409 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
410 if (tof21(right,i,iadc).lt.1000) then
411 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
412 xkorr0=adcx21(right,i,1)
413 adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
414 endif
415 ENDIF
416
417 yhelp=yout(4)
418 IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
419
420 i = tof22_i
421 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
422 if (tof22(left,i,iadc).lt.1000) then
423 xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
424 xkorr0=adcx22(left,i,1)
425 adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
426 endif
427
428 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
429 if (tof22(right,i,iadc).lt.1000) then
430 xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
431 xkorr0=adcx22(right,i,1)
432 adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
433 endif
434 ENDIF
435
436 C-----------------------------S3 --------------------------------
437
438 yhelp=yout(5)
439 IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
440
441 i = tof31_i
442 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
443 if (tof31(left,i,iadc).lt.1000) then
444 xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
445 xkorr0=adcx31(left,i,1)
446 adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
447 endif
448
449 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
450 if (tof31(right,i,iadc).lt.1000) then
451 xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
452 xkorr0=adcx31(right,i,1)
453 adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
454 endif
455 ENDIF
456
457 xhelp=xout(6)
458 IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
459
460 i = tof32_i
461 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
462 if (tof32(left,i,iadc).lt.1000) then
463 xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
464 xkorr0=adcx32(left,i,1)
465 adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
466 endif
467
468 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
469 if (tof32(right,i,iadc).lt.1000) then
470 xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
471 xkorr0=adcx32(right,i,1)
472 adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
473 endif
474 ENDIF
475
476 C-----------------------------------------------------------------------
477 C----------------------calculate Beta ------------------------------
478 C-----------------------------------------------------------------------
479 C-------------------difference of sums ---------------------------
480 C
481 C DS = (t1+t2) - t3+t4)
482 C DS = c1 + c2/beta*cos(theta)
483 C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
484 C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
485 C since TDC resolution varies slightly c2 has to be calibrated
486 C instead of cos(theta) use factor F:
487 C F = pathlength/d
488 C => beta = c2*F/(DS-c1))
489
490 dist = ZTOF(1) - ZTOF(5)
491 dl = 0.
492 DO I=1,5
493 dl = dl + TLOUT(i)
494 ENDDO
495 F = dl/dist
496
497 C S11 - S31
498 IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
499 t1 = tof11(1,tof11_i,itdc)
500 t2 = tof11(2,tof11_i,itdc)
501 t3 = tof31(1,tof31_i,itdc)
502 t4 = tof31(2,tof31_i,itdc)
503 IF ((t1.lt.4095).and.(t2.lt.4095).and.
504 & (t3.lt.4095).and.(t4.lt.4095)) THEN
505 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
506 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
507 ds = xhelp1-xhelp2
508 ihelp=(tof11_i-1)*3+tof31_i
509 c1 = k_S11S31(1,ihelp)
510 c2 = k_S11S31(2,ihelp)
511 beta_a(1) = c2*F/(ds-c1)
512 C write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
513 C------- ToF Mask - S11 - S31
514
515 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
516 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
517 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
518 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
519
520 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
521 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
522 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
523 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
524
525 ENDIF
526 ENDIF
527
528 dist = ZTOF(1) - ZTOF(6)
529 dl = 0.
530 DO I=1,6
531 dl = dl + TLOUT(i)
532 ENDDO
533 F = dl/dist
534
535 C S11 - S32
536 IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
537 t1 = tof11(1,tof11_i,itdc)
538 t2 = tof11(2,tof11_i,itdc)
539 t3 = tof32(1,tof32_i,itdc)
540 t4 = tof32(2,tof32_i,itdc)
541 IF ((t1.lt.4095).and.(t2.lt.4095).and.
542 & (t3.lt.4095).and.(t4.lt.4095)) THEN
543 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
544 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
545 ds = xhelp1-xhelp2
546 ihelp=(tof11_i-1)*3+tof32_i
547 c1 = k_S11S32(1,ihelp)
548 c2 = k_S11S32(2,ihelp)
549 beta_a(2) = c2*F/(ds-c1)
550 C write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
551
552 C------- ToF Mask - S11 - S32
553
554 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
555 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
556 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
557 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
558
559 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
560 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
561 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
562 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
563
564 C-------
565
566 ENDIF
567 ENDIF
568
569 C S12 - S31
570 dist = ZTOF(2) - ZTOF(5)
571 dl = 0.
572 DO I=2,5
573 dl = dl + TLOUT(i)
574 ENDDO
575 F = dl/dist
576
577 IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
578 t1 = tof12(1,tof12_i,itdc)
579 t2 = tof12(2,tof12_i,itdc)
580 t3 = tof31(1,tof31_i,itdc)
581 t4 = tof31(2,tof31_i,itdc)
582 IF ((t1.lt.4095).and.(t2.lt.4095).and.
583 & (t3.lt.4095).and.(t4.lt.4095)) THEN
584 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
585 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
586 ds = xhelp1-xhelp2
587 ihelp=(tof12_i-1)*3+tof31_i
588 c1 = k_S12S31(1,ihelp)
589 c2 = k_S12S31(2,ihelp)
590 beta_a(3) = c2*F/(ds-c1)
591 C write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
592
593 C------- ToF Mask - S12 - S31
594
595 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
596 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
597 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
598 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
599
600 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
601 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
602 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
603 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
604
605 C-------
606
607 ENDIF
608 ENDIF
609
610 C S12 - S32
611
612 dist = ZTOF(2) - ZTOF(6)
613 dl = 0.
614 DO I=2,6
615 dl = dl + TLOUT(i)
616 ENDDO
617 F = dl/dist
618
619 IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
620 t1 = tof12(1,tof12_i,itdc)
621 t2 = tof12(2,tof12_i,itdc)
622 t3 = tof32(1,tof32_i,itdc)
623 t4 = tof32(2,tof32_i,itdc)
624 IF ((t1.lt.4095).and.(t2.lt.4095).and.
625 & (t3.lt.4095).and.(t4.lt.4095)) THEN
626 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
627 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
628 ds = xhelp1-xhelp2
629 ihelp=(tof12_i-1)*3+tof32_i
630 c1 = k_S12S32(1,ihelp)
631 c2 = k_S12S32(2,ihelp)
632 beta_a(4) = c2*F/(ds-c1)
633 C write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
634
635 C------- ToF Mask - S12 - S32
636
637 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
638 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
639 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
640 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
641
642 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
643 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
644 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
645 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
646
647 C-------
648
649 ENDIF
650 ENDIF
651
652 C S21 - S31
653
654 dist = ZTOF(3) - ZTOF(5)
655 dl = 0.
656 DO I=3,5
657 dl = dl + TLOUT(i)
658 ENDDO
659 F = dl/dist
660
661 IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
662 t1 = tof21(1,tof21_i,itdc)
663 t2 = tof21(2,tof21_i,itdc)
664 t3 = tof31(1,tof31_i,itdc)
665 t4 = tof31(2,tof31_i,itdc)
666 IF ((t1.lt.4095).and.(t2.lt.4095).and.
667 & (t3.lt.4095).and.(t4.lt.4095)) THEN
668 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
669 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
670 ds = xhelp1-xhelp2
671 ihelp=(tof21_i-1)*3+tof31_i
672 c1 = k_S21S31(1,ihelp)
673 c2 = k_S21S31(2,ihelp)
674 beta_a(5) = c2*F/(ds-c1)
675
676 C------- ToF Mask - S21 - S31
677
678 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
679 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
680 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
681 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
682
683 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
684 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
685 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
686 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
687
688 C-------
689
690 ENDIF
691 ENDIF
692
693 C S21 - S32
694
695 dist = ZTOF(3) - ZTOF(6)
696 dl = 0.
697 DO I=3,6
698 dl = dl + TLOUT(i)
699 ENDDO
700 F = dl/dist
701
702 IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
703 t1 = tof21(1,tof21_i,itdc)
704 t2 = tof21(2,tof21_i,itdc)
705 t3 = tof32(1,tof32_i,itdc)
706 t4 = tof32(2,tof32_i,itdc)
707 IF ((t1.lt.4095).and.(t2.lt.4095).and.
708 & (t3.lt.4095).and.(t4.lt.4095)) THEN
709 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
710 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
711 ds = xhelp1-xhelp2
712 ihelp=(tof21_i-1)*3+tof32_i
713 c1 = k_S21S32(1,ihelp)
714 c2 = k_S21S32(2,ihelp)
715 beta_a(6) = c2*F/(ds-c1)
716
717 C------- ToF Mask - S21 - S32
718
719 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
720 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
721 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
722 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
723
724 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
725 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
726 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
727 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
728
729 C-------
730
731 ENDIF
732 ENDIF
733
734 C S22 - S31
735
736 dist = ZTOF(4) - ZTOF(5)
737 dl = 0.
738 DO I=4,5
739 dl = dl + TLOUT(i)
740 ENDDO
741 F = dl/dist
742
743 IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
744 t1 = tof22(1,tof22_i,itdc)
745 t2 = tof22(2,tof22_i,itdc)
746 t3 = tof31(1,tof31_i,itdc)
747 t4 = tof31(2,tof31_i,itdc)
748 IF ((t1.lt.4095).and.(t2.lt.4095).and.
749 & (t3.lt.4095).and.(t4.lt.4095)) THEN
750 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
751 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
752 ds = xhelp1-xhelp2
753 ihelp=(tof22_i-1)*3+tof31_i
754 c1 = k_S22S31(1,ihelp)
755 c2 = k_S22S31(2,ihelp)
756 beta_a(7) = c2*F/(ds-c1)
757
758 C------- ToF Mask - S22 - S31
759
760 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
761 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
762 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
763 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
764
765 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
766 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
767 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
768 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
769
770 C-------
771
772 ENDIF
773 ENDIF
774
775 C S22 - S32
776
777 dist = ZTOF(4) - ZTOF(6)
778 dl = 0.
779 DO I=4,6
780 dl = dl + TLOUT(i)
781 ENDDO
782 F = dl/dist
783
784 IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
785 t1 = tof22(1,tof22_i,itdc)
786 t2 = tof22(2,tof22_i,itdc)
787 t3 = tof32(1,tof32_i,itdc)
788 t4 = tof32(2,tof32_i,itdc)
789 IF ((t1.lt.4095).and.(t2.lt.4095).and.
790 & (t3.lt.4095).and.(t4.lt.4095)) THEN
791 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
792 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
793 ds = xhelp1-xhelp2
794 ihelp=(tof22_i-1)*3+tof32_i
795 c1 = k_S22S32(1,ihelp)
796 c2 = k_S22S32(2,ihelp)
797 beta_a(8) = c2*F/(ds-c1)
798
799 C------- ToF Mask - S22 - S32
800
801 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
802 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
803 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
804 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
805
806 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
807 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
808 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
809 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
810
811 C-------
812
813 ENDIF
814 ENDIF
815
816 C S11 - S21
817
818 dist = ZTOF(1) - ZTOF(3)
819 dl = 0.
820 DO I=1,3
821 dl = dl + TLOUT(i)
822 ENDDO
823 F = dl/dist
824
825 IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
826 t1 = tof11(1,tof11_i,itdc)
827 t2 = tof11(2,tof11_i,itdc)
828 t3 = tof21(1,tof21_i,itdc)
829 t4 = tof21(2,tof21_i,itdc)
830 IF ((t1.lt.4095).and.(t2.lt.4095).and.
831 & (t3.lt.4095).and.(t4.lt.4095)) THEN
832 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
833 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
834 ds = xhelp1-xhelp2
835 ihelp=(tof11_i-1)*2+tof21_i
836 c1 = k_S11S21(1,ihelp)
837 c2 = k_S11S21(2,ihelp)
838 beta_a(9) = c2*F/(ds-c1)
839
840 C------- ToF Mask - S11 - S21
841
842 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
843 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
844 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
845 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
846
847 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
848 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
849 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
850 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
851
852 C-------
853
854 ENDIF
855 ENDIF
856
857 C S11 - S22
858
859 dist = ZTOF(1) - ZTOF(4)
860 dl = 0.
861 DO I=1,4
862 dl = dl + TLOUT(i)
863 ENDDO
864 F = dl/dist
865
866 IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
867 t1 = tof11(1,tof11_i,itdc)
868 t2 = tof11(2,tof11_i,itdc)
869 t3 = tof22(1,tof22_i,itdc)
870 t4 = tof22(2,tof22_i,itdc)
871 IF ((t1.lt.4095).and.(t2.lt.4095).and.
872 & (t3.lt.4095).and.(t4.lt.4095)) THEN
873 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
874 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
875 ds = xhelp1-xhelp2
876 ihelp=(tof11_i-1)*2+tof22_i
877 c1 = k_S11S22(1,ihelp)
878 c2 = k_S11S22(2,ihelp)
879 beta_a(10) = c2*F/(ds-c1)
880
881 C------- ToF Mask - S11 - S22
882
883 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
884 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
885 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
886 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
887
888 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
889 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
890 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
891 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
892
893 C-------
894
895 ENDIF
896 ENDIF
897
898 C S12 - S21
899
900 dist = ZTOF(2) - ZTOF(3)
901 dl = 0.
902 DO I=2,3
903 dl = dl + TLOUT(i)
904 ENDDO
905 F = dl/dist
906
907 IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
908 t1 = tof12(1,tof12_i,itdc)
909 t2 = tof12(2,tof12_i,itdc)
910 t3 = tof21(1,tof21_i,itdc)
911 t4 = tof21(2,tof21_i,itdc)
912 IF ((t1.lt.4095).and.(t2.lt.4095).and.
913 & (t3.lt.4095).and.(t4.lt.4095)) THEN
914 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
915 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
916 ds = xhelp1-xhelp2
917 ihelp=(tof12_i-1)*2+tof21_i
918 c1 = k_S12S21(1,ihelp)
919 c2 = k_S12S21(2,ihelp)
920 beta_a(11) = c2*F/(ds-c1)
921
922 C------- ToF Mask - S12 - S21
923
924 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
925 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
926 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
927 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
928
929 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
930 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
931 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
932 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
933
934 C-------
935
936 ENDIF
937 ENDIF
938
939 C S12 - S22
940
941 dist = ZTOF(2) - ZTOF(4)
942 dl = 0.
943 DO I=2,4
944 dl = dl + TLOUT(i)
945 ENDDO
946 F = dl/dist
947
948 IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
949 t1 = tof12(1,tof12_i,itdc)
950 t2 = tof12(2,tof12_i,itdc)
951 t3 = tof22(1,tof22_i,itdc)
952 t4 = tof22(2,tof22_i,itdc)
953 IF ((t1.lt.4095).and.(t2.lt.4095).and.
954 & (t3.lt.4095).and.(t4.lt.4095)) THEN
955 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
956 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
957 ds = xhelp1-xhelp2
958 ihelp=(tof12_i-1)*2+tof22_i
959 c1 = k_S12S22(1,ihelp)
960 c2 = k_S12S22(2,ihelp)
961 beta_a(12) = c2*F/(ds-c1)
962
963 C------- ToF Mask - S12 - S22
964
965 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
966 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
967 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
968 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
969
970 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
971 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
972 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
973 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
974
975 C-------
976
977 ENDIF
978 ENDIF
979
980 C-------
981
982 icount=0
983 sw=0.
984 sxw=0.
985 beta_mean=100.
986
987 do i=1,12
988 if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
989 icount= icount+1
990 if (i.le.4) w_i=1./(0.13**2.)
991 if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
992 if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
993 sxw=sxw + beta_a(i)*w_i
994 sw =sw + w_i
995 endif
996 enddo
997
998 if (icount.gt.0) beta_mean=sxw/sw
999 beta_a(13) = beta_mean
1000
1001 C write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4)
1002
1003 RETURN
1004 END
1005
1006

  ViewVC Help
Powered by ViewVC 1.1.23