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

Annotation of /DarthVader/ToFLevel2/src/tofl2com.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.3 - (hide annotations) (download)
Thu Aug 10 06:32:04 2006 UTC (18 years, 3 months ago) by mocchiut
Branch: MAIN
CVS Tags: v2r01, v2r00BETA
Changes since 1.2: +12 -12 lines
ToF bug fixed + new calo/tracker alignement

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

  ViewVC Help
Powered by ViewVC 1.1.23