/[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.3 - (show annotations) (download)
Thu Aug 10 06:32:05 2006 UTC (18 years, 3 months ago) by mocchiut
Branch: MAIN
Changes since 1.2: +12 -12 lines
ToF bug fixed + new calo/tracker alignement

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 INTEGER j
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 do i=1,4
85 do j=1,12
86 adc_c(i,j) = 1000.
87 enddo
88 enddo
89
90 do i=1,12
91 do j=1,4
92 tofmask(j,i) = 0
93 enddo
94 enddo
95
96 C------ read tracking routine
97 * igoodevent = igoodevent+1
98 * assigned input parameters for track routine
99 * 1) Z-coordinates where the trajectory is evaluated
100 do itof=1,NPTOF
101 ZIN(itof) = ZTOF(itof)
102 enddo
103 * 2) track status vector
104 C COPY THE ALFA VECTOR FROM AL_PP TO AL_P FOR THE TRACK "T"
105 do i=1,5
106 AL_P(i) = al_pp(i)
107 enddo
108 if (al_p(5).eq.0.) THEN
109 PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
110 GOTO 969
111 ENDIF
112 * -------- *** tracking routine *** --------
113 IFAIL = 0
114 call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
115 if(IFAIL.ne.0)then
116 print *,' TOF - WARNING F77: tracking failed '
117 goto 969
118 endif
119 * ------------------------------------------
120
121 969 continue
122
123 C-------------------------------------------------------------
124 C------- check which paddle penetrated the track -----------
125 C-------------------------------------------------------------
126 c middle y (or x) position of the upper and middle ToF-Paddle
127 c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
128 c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
129 c DATA tof21_y/ -3.75,3.75/
130 c DATA tof22_x/ -4.5,4.5/
131 c DATA tof31_x/ -6.0,0.,6.0/
132 c DATA tof32_y/ -5.0,0.0,5.0/
133 c
134 c S11 8 paddles 33.0 x 5.1 cm
135 c S12 6 paddles 40.8 x 5.5 cm
136 c S21 2 paddles 18.0 x 7.5 cm
137 c S22 2 paddles 15.0 x 9.0 cm
138 c S31 3 paddles 15.0 x 6.0 cm
139 c S32 3 paddles 18.0 x 5.0 cm
140
141
142 C-------------- S11 --------------------------------------
143
144 tof11_i = none_find
145
146 yl = -33.0/2.
147 yh = 33.0/2.
148
149 if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then
150 do i=1,8
151 xl = tof11_x(i) - 5.1/2.
152 xh = tof11_x(i) + 5.1/2.
153 if ((xout(1).gt.xl).and.(xout(1).le.xh)) then
154 tof11_i=i
155 endif
156 enddo
157 endif
158
159 C-------------- S12 --------------------------------------
160
161 tof12_i = none_find
162
163 xl = -40.8/2.
164 xh = 40.8/2.
165
166 if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then
167 do i=1,6
168 yl = tof12_y(i) - 5.5/2.
169 yh = tof12_y(i) + 5.5/2.
170 if ((yout(2).gt.yl).and.(yout(2).le.yh)) then
171 tof12_i=i
172 endif
173 enddo
174 endif
175
176 C-------------- S21 --------------------------------------
177
178 tof21_i = none_find
179
180 xl = -18./2.
181 xh = 18./2.
182
183 if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then
184 do i=1,2
185 yl = tof21_y(i) - 7.5/2.
186 yh = tof21_y(i) + 7.5/2.
187 if ((yout(3).gt.yl).and.(yout(3).le.yh)) then
188 tof21_i=i
189 endif
190 enddo
191 endif
192
193 C-------------- S22 --------------------------------------
194
195 tof22_i = none_find
196
197 yl = -15./2.
198 yh = 15./2.
199
200 if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then
201 do i=1,2
202 xl = tof22_x(i) - 9.0/2.
203 xh = tof22_x(i) + 9.0/2.
204 if ((xout(4).gt.xl).and.(xout(4).le.xh)) then
205 tof22_i=i
206 endif
207 enddo
208 endif
209
210 C-------------- S31 --------------------------------------
211
212 tof31_i = none_find
213
214 yl = -15.0/2.
215 yh = 15.0/2.
216
217 if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then
218 do i=1,3
219 xl = tof31_x(i) - 6.0/2.
220 xh = tof31_x(i) + 6.0/2.
221 if ((xout(5).gt.xl).and.(xout(5).le.xh)) then
222 tof31_i=i
223 endif
224 enddo
225 endif
226
227 C-------------- S32 --------------------------------------
228
229 tof32_i = none_find
230
231 xl = -18.0/2.
232 xh = 18.0/2.
233
234 if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then
235 do i=1,3
236 yl = tof32_y(i) - 5.0/2.
237 yh = tof32_y(i) + 5.0/2.
238 if ((yout(6).gt.yl).and.(yout(6).le.yh)) then
239 tof32_i=i
240 endif
241 enddo
242 endif
243
244 C------------------------------------------------------------------
245 C--- calculate track position in paddle using timing difference
246 C------------------------------------------------------------------
247
248 do i=1,3
249 xtofpos(i)=100.
250 ytofpos(i)=100.
251 enddo
252 C-----------------------------S1 --------------------------------
253
254 IF (tof11_i.GT.none_find) THEN
255 ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
256 + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
257 endif
258
259 IF (tof12_i.GT.none_find) THEN
260 xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
261 + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
262 endif
263
264
265 C-----------------------------S2 --------------------------------
266
267 IF (tof21_i.GT.none_find) THEN
268 xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
269 + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
270 endif
271
272 IF (tof22_i.GT.none_find) THEN
273 ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
274 + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
275 endif
276
277
278 C-----------------------------S3 --------------------------------
279
280 IF (tof31_i.GT.none_find) THEN
281 ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
282 + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
283 endif
284
285 IF (tof32_i.GT.none_find) THEN
286 xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
287 + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
288 endif
289
290
291 do i=1,3
292 if (abs(xtofpos(i)).gt.100.) then
293 xtofpos(i)=101.
294 endif
295 if (abs(ytofpos(i)).gt.100.) then
296 ytofpos(i)=101.
297 endif
298 enddo
299
300 C----------------------------------------------------------------------
301 C--------------------Corrections on ADC-data -------------------------
302 C---------------------zenith angle theta ---------------------------
303 C----------------------------------------------------------------------
304
305
306 dx=0.
307 dy=0.
308 dr=0.
309 theta13 = 0.
310
311 if (xout(1).lt.100.) then
312 dx = xout(1)-xout(6)
313 dy = yout(1)-yout(6)
314 dr = sqrt(dx*dx+dy*dy)
315 theta13 = atan(dr/tofarm13)
316 endif
317
318
319 C----------------------------------------------------------------------
320 C------------------angle and ADC(x) correction
321 C----------------------------------------------------------------------
322 C-----------------------------S1 --------------------------------
323
324 yhelp=yout(1)
325
326 IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
327
328 i = tof11_i
329 xdummy=tof11(left,i,iadc)
330 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
331 if (tof11(left,i,iadc).lt.4095) then
332 xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
333 xkorr0=adcx11(left,i,1)
334 adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
335 endif
336
337 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
338 if (tof11(right,i,iadc).lt.4095) then
339 xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
340 xkorr0=adcx11(right,i,1)
341 adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
342 endif
343 ENDIF
344
345
346 xhelp=xout(2)
347 IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
348
349 i = tof12_i
350 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
351 if (tof12(left,i,iadc).lt.4095) then
352 xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
353 xkorr0=adcx12(left,i,1)
354 adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
355 endif
356
357 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
358 if (tof12(right,i,iadc).lt.4095) then
359 xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
360 xkorr0=adcx12(right,i,1)
361 adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
362 endif
363 ENDIF
364
365 C-----------------------------S2 --------------------------------
366
367 xhelp=xout(3)
368 IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
369
370 i = tof21_i
371 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
372 if (tof21(left,i,iadc).lt.4095) then
373 xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
374 xkorr0=adcx21(left,i,1)
375 adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
376 endif
377
378 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
379 if (tof21(right,i,iadc).lt.4095) then
380 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
381 xkorr0=adcx21(right,i,1)
382 adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
383 endif
384 ENDIF
385
386 yhelp=yout(4)
387 IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
388
389 i = tof22_i
390 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
391 if (tof22(left,i,iadc).lt.4095) then
392 xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
393 xkorr0=adcx22(left,i,1)
394 adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
395 endif
396
397 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
398 if (tof22(right,i,iadc).lt.4095) then
399 xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
400 xkorr0=adcx22(right,i,1)
401 adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
402 endif
403 ENDIF
404
405 C-----------------------------S3 --------------------------------
406
407 yhelp=yout(5)
408 IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
409
410 i = tof31_i
411 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
412 if (tof31(left,i,iadc).lt.4095) then
413 xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
414 xkorr0=adcx31(left,i,1)
415 adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
416 endif
417
418 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
419 if (tof31(right,i,iadc).lt.4095) then
420 xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
421 xkorr0=adcx31(right,i,1)
422 adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
423 endif
424 ENDIF
425
426 xhelp=xout(6)
427 IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
428
429 i = tof32_i
430 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
431 if (tof32(left,i,iadc).lt.4095) then
432 xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
433 xkorr0=adcx32(left,i,1)
434 adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
435 endif
436
437 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
438 if (tof32(right,i,iadc).lt.4095) then
439 xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
440 xkorr0=adcx32(right,i,1)
441 adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
442 endif
443 ENDIF
444
445 C-----------------------------------------------------------------------
446 C----------------------calculate Beta ------------------------------
447 C-----------------------------------------------------------------------
448 C-------------------difference of sums ---------------------------
449 C
450 C DS = (t1+t2) - t3+t4)
451 C DS = c1 + c2/beta*cos(theta)
452 C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
453 C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
454 C since TDC resolution varies slightly c2 has to be calibrated
455
456 C S11 - S31
457 IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
458 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
459 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
460 ds = xhelp1-xhelp2
461 ihelp=(tof11_i-1)*3+tof31_i
462 c1 = k_S11S31(1,ihelp)
463 c2 = k_S11S31(2,ihelp)
464 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
465 & beta_a(1) = c2/(cos(theta13)*(ds-c1))
466
467 C------- ToF Mask - S11 - S31
468
469 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
470 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
471 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
472 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
473
474 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
475 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
476 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
477 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
478
479 C-------
480
481 ENDIF
482
483 C S11 - S32
484 IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
485 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
486 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
487 ds = xhelp1-xhelp2
488 ihelp=(tof11_i-1)*3+tof32_i
489 c1 = k_S11S32(1,ihelp)
490 c2 = k_S11S32(2,ihelp)
491 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
492 & beta_a(2) = c2/(cos(theta13)*(ds-c1))
493
494 C------- ToF Mask - S11 - S32
495
496 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
497 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
498 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
499 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
500
501 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
502 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
503 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
504 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
505
506 C-------
507
508 ENDIF
509
510 C S12 - S31
511 IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
512 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
513 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
514 ds = xhelp1-xhelp2
515 ihelp=(tof12_i-1)*3+tof31_i
516 c1 = k_S12S31(1,ihelp)
517 c2 = k_S12S31(2,ihelp)
518 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
519 & beta_a(3) = c2/(cos(theta13)*(ds-c1))
520
521 C------- ToF Mask - S12 - S31
522
523 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
524 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
525 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
526 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
527
528 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
529 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
530 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
531 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
532
533 C-------
534
535 ENDIF
536
537 C S12 - S32
538 IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
539 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
540 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
541 ds = xhelp1-xhelp2
542 ihelp=(tof12_i-1)*3+tof32_i
543 c1 = k_S12S32(1,ihelp)
544 c2 = k_S12S32(2,ihelp)
545 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
546 & beta_a(4) = c2/(cos(theta13)*(ds-c1))
547
548 C------- ToF Mask - S12 - S32
549
550 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
551 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
552 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
553 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
554
555 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
556 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
557 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
558 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
559
560 C-------
561
562 ENDIF
563
564 C S21 - S31
565 IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
566 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
567 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
568 ds = xhelp1-xhelp2
569 ihelp=(tof21_i-1)*3+tof31_i
570 c1 = k_S21S31(1,ihelp)
571 c2 = k_S21S31(2,ihelp)
572 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
573 & beta_a(5) = c2/(cos(theta23)*(ds-c1))
574
575 C------- ToF Mask - S21 - S31
576
577 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
578 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
579 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
580 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
581
582 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
583 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
584 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
585 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
586
587 C-------
588
589 ENDIF
590
591 C S21 - S32
592 IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
593 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
594 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
595 ds = xhelp1-xhelp2
596 ihelp=(tof21_i-1)*3+tof32_i
597 c1 = k_S21S32(1,ihelp)
598 c2 = k_S21S32(2,ihelp)
599 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
600 & beta_a(6) = c2/(cos(theta23)*(ds-c1))
601
602 C------- ToF Mask - S21 - S32
603
604 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
605 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
606 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
607 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
608
609 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
610 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
611 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
612 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
613
614 C-------
615
616 ENDIF
617
618 C S22 - S31
619 IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
620 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
621 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
622 ds = xhelp1-xhelp2
623 ihelp=(tof22_i-1)*3+tof31_i
624 c1 = k_S22S31(1,ihelp)
625 c2 = k_S22S31(2,ihelp)
626 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
627 & beta_a(7) = c2/(cos(theta13)*(ds-c1))
628
629 C------- ToF Mask - S22 - S31
630
631 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
632 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
633 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
634 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
635
636 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
637 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
638 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
639 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
640
641 C-------
642
643 ENDIF
644
645 C S22 - S32
646 IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
647 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
648 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
649 ds = xhelp1-xhelp2
650 ihelp=(tof22_i-1)*3+tof32_i
651 c1 = k_S22S32(1,ihelp)
652 c2 = k_S22S32(2,ihelp)
653 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
654 & beta_a(8) = c2/(cos(theta13)*(ds-c1))
655
656 C------- ToF Mask - S22 - S32
657
658 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
659 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
660 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
661 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
662
663 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
664 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
665 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
666 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
667
668 C-------
669
670 ENDIF
671
672 C S11 - S21
673 IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
674 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
675 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
676 ds = xhelp1-xhelp2
677 ihelp=(tof11_i-1)*2+tof21_i
678 c1 = k_S11S21(1,ihelp)
679 c2 = k_S11S21(2,ihelp)
680 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
681 & beta_a(9) = c2/(cos(theta12)*(ds-c1))
682
683 C------- ToF Mask - S11 - S21
684
685 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
686 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
687 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
688 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
689
690 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
691 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
692 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
693 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
694
695 C-------
696
697 ENDIF
698
699 C S11 - S22
700 IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
701 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
702 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
703 ds = xhelp1-xhelp2
704 ihelp=(tof11_i-1)*2+tof22_i
705 c1 = k_S11S22(1,ihelp)
706 c2 = k_S11S22(2,ihelp)
707 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
708 & beta_a(10) = c2/(cos(theta12)*(ds-c1))
709
710 C------- ToF Mask - S11 - S22
711
712 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
713 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
714 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
715 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
716
717 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
718 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
719 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
720 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
721
722 C-------
723
724 ENDIF
725
726 C S12 - S21
727 IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
728 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
729 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
730 ds = xhelp1-xhelp2
731 ihelp=(tof12_i-1)*2+tof21_i
732 c1 = k_S12S21(1,ihelp)
733 c2 = k_S12S21(2,ihelp)
734 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
735 & beta_a(11) = c2/(cos(theta12)*(ds-c1))
736
737 C------- ToF Mask - S12 - S21
738
739 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
740 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
741 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
742 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
743
744 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
745 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
746 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
747 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
748
749 C-------
750
751 ENDIF
752
753 C S12 - S22
754 IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
755 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
756 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
757 ds = xhelp1-xhelp2
758 ihelp=(tof12_i-1)*2+tof22_i
759 c1 = k_S12S22(1,ihelp)
760 c2 = k_S12S22(2,ihelp)
761 if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))
762 & beta_a(12) = c2/(cos(theta12)*(ds-c1))
763
764 C------- ToF Mask - S12 - S22
765
766 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
767 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
768 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
769 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
770
771 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
772 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
773 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
774 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
775
776 C-------
777
778 ENDIF
779
780 C-------
781
782 icount=0
783 sw=0.
784 sxw=0.
785 beta_mean=100.
786
787 do i=1,12
788 if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
789 icount= icount+1
790 if (i.le.4) w_i=1./(0.13**2.)
791 if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
792 if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
793 sxw=sxw + beta_a(i)*w_i
794 sw =sw + w_i
795 endif
796 enddo
797
798 if (icount.gt.0) beta_mean=sxw/sw
799 beta_a(13) = beta_mean
800
801 RETURN
802 END
803
804

  ViewVC Help
Powered by ViewVC 1.1.23