/[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.5 - (hide annotations) (download)
Wed Feb 7 08:17:17 2007 UTC (17 years, 9 months ago) by mocchiut
Branch: MAIN
Changes since 1.4: +8 -0 lines
Bug fixed: sometimes tdc_tw is incorrect due to leftover xhelp

1 mocchiut 1.4 ******************************************************************************
2     *
3     * 08-12-06 WM: adc_c-bug : The raw ADc value was multiplied with cos(theta)
4     * and AFTER that there was an if statement "if tof32(right,i,iadc) < 4095"
5     *
6     * jan-07 GF: ADCflags(4,12) inserted to flag artificial ADC values
7     * jan-07 WM: artificial ADC values created using attenuation calibration
8     * jan-07 WM: modified xtofpos flag "101". xtofpos must be inside physical
9     * dimension of the paddle +/- 10 cm
10     * jan-07 WM: if xtofpos=101 then this paddle is not used for beta
11     * calculation
12     * jan-07 WM: the definition for a "hit" is changed: Now we must have a
13     * valid TDC signal on both sides
14     * jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift
15 mocchiut 1.5 * jan-07 WM: bug removed: in some cases tdc_tw was calculated due to a
16     * leftover "xhelp" value
17 mocchiut 1.4 ******************************************************************************
18    
19 mocchiut 1.1 INTEGER FUNCTION TOFL2COM()
20     c
21     IMPLICIT NONE
22     C
23     include 'input_tof.txt'
24     include 'output_tof.txt'
25     include 'tofcomm.txt'
26    
27     INTEGER icounter
28     DATA icounter / 0/
29    
30     LOGICAL check
31     REAL secure
32    
33     INTEGER j
34     REAL xhelp_a,xhelp_t
35    
36     REAL dx,dy,dr,ds
37 mocchiut 1.4 REAL yhelp,xhelp,xhelp1,xhelp2
38 mocchiut 1.1 REAL c1,c2,sw,sxw,w_i
39     INTEGER icount
40    
41 mocchiut 1.4 c REAL xdummy
42    
43 mocchiut 1.1 INTEGER tof11_j,tof21_j,tof31_j
44     INTEGER tof12_j,tof22_j,tof32_j
45    
46 mocchiut 1.4
47 mocchiut 1.1 REAL beta_mean
48    
49    
50     c value for status of each PM-data
51     c first index : 1 = left, 2 = right
52     c second index : 1... number of paddle
53     INTEGER tof11_event(2,8),tof12_event(2,6)
54     INTEGER tof21_event(2,2),tof22_event(2,2)
55     INTEGER tof31_event(2,3),tof32_event(2,3)
56    
57    
58 mocchiut 1.4 REAL theta13
59 mocchiut 1.1 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
60     REAL tofarm12
61     PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
62     REAL tofarm23
63     PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
64     REAL tofarm13
65     PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
66 mocchiut 1.4
67     REAL hepratio
68 mocchiut 1.1
69     INTEGER ihelp
70     REAL xkorr
71    
72     C---------------------------------------
73     C
74     C Begin !
75     C
76     TOFL2COM = 0
77     C
78     C CALCULATE COMMON VARIABLES
79     C
80    
81     *******************************************************************
82     icounter = icounter + 1
83    
84     * amplitude has to be 'secure' higher than pedestal for an adc event
85     secure = 2.
86    
87 mocchiut 1.4 C ratio between helium and proton ca. 4
88     hepratio = 4.5 !
89 mocchiut 1.1 offset = 1
90     slope = 2
91     left = 1
92     right = 2
93     none_ev = 0
94     none_find = 0
95     tdc_ev = 1
96     adc_ev = 1
97     itdc = 1
98     iadc = 2
99    
100     do i=1,13
101     betatof_a(i) = 100. ! As in "troftrk.for"
102     enddo
103    
104     do i=1,4
105     do j=1,12
106     adctof_c(i,j) = 1000.
107     enddo
108     enddo
109    
110    
111     do i=1,4
112     do j=1,12
113     tdc_c(i,j) = 4095.
114     enddo
115     enddo
116    
117    
118 mocchiut 1.2 do i=1,12
119     do j=1,4
120     tofmask(j,i) = 0
121     enddo
122     enddo
123    
124    
125 mocchiut 1.4 c gf adc falg:
126     do i=1,4
127     do j=1,12
128     adcflagtof(i,j) = 0
129     enddo
130     enddo
131    
132     c gf tdc falg:
133     do i=1,4
134     do j=1,12
135     tdcflagtof(i,j) = 0
136     enddo
137     enddo
138    
139 mocchiut 1.1 c the calibration files are read in the main program from xxx_tofcalib.rz
140    
141    
142     c-------------------------get ToF data --------------------------------
143    
144     c put the adc and tdc values from ntuple into tofxx(i,j,k) variables
145    
146    
147     do j=1,8
148     tof11(1,j,2) = adc(ch11a(j),hb11a(j))
149     tof11(2,j,2) = adc(ch11b(j),hb11b(j))
150     tof11(1,j,1) = tdc(ch11a(j),hb11a(j))
151     tof11(2,j,1) = tdc(ch11b(j),hb11b(j))
152     enddo
153    
154    
155     do j=1,6
156     tof12(1,j,2) = adc(ch12a(j),hb12a(j))
157     tof12(2,j,2) = adc(ch12b(j),hb12b(j))
158     tof12(1,j,1) = tdc(ch12a(j),hb12a(j))
159     tof12(2,j,1) = tdc(ch12b(j),hb12b(j))
160     enddo
161    
162     do j=1,2
163     tof21(1,j,2) = adc(ch21a(j),hb21a(j))
164     tof21(2,j,2) = adc(ch21b(j),hb21b(j))
165     tof21(1,j,1) = tdc(ch21a(j),hb21a(j))
166     tof21(2,j,1) = tdc(ch21b(j),hb21b(j))
167     enddo
168    
169     do j=1,2
170     tof22(1,j,2) = adc(ch22a(j),hb22a(j))
171     tof22(2,j,2) = adc(ch22b(j),hb22b(j))
172     tof22(1,j,1) = tdc(ch22a(j),hb22a(j))
173     tof22(2,j,1) = tdc(ch22b(j),hb22b(j))
174     enddo
175    
176     do j=1,3
177     tof31(1,j,2) = adc(ch31a(j),hb31a(j))
178     tof31(2,j,2) = adc(ch31b(j),hb31b(j))
179     tof31(1,j,1) = tdc(ch31a(j),hb31a(j))
180     tof31(2,j,1) = tdc(ch31b(j),hb31b(j))
181     enddo
182    
183     do j=1,3
184     tof32(1,j,2) = adc(ch32a(j),hb32a(j))
185     tof32(2,j,2) = adc(ch32b(j),hb32b(j))
186     tof32(1,j,1) = tdc(ch32a(j),hb32a(j))
187     tof32(2,j,1) = tdc(ch32b(j),hb32b(j))
188     enddo
189    
190     C----------------------------------------------------------------------
191    
192     DO i = 1,8
193     if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000.
194     if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000.
195     if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000.
196     if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000.
197     ENDDO
198    
199     DO i = 1,6
200     if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000.
201     if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000.
202     if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000.
203     if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000.
204     ENDDO
205    
206    
207     DO i = 1,2
208     if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000.
209     if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000.
210     if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000.
211     if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000.
212     ENDDO
213    
214     DO i = 1,2
215     if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000.
216     if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000.
217     if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000.
218     if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000.
219     ENDDO
220    
221     DO i = 1,3
222     if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000.
223     if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000.
224     if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000.
225     if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000.
226     ENDDO
227    
228     DO i = 1,3
229     if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000.
230     if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000.
231     if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000.
232     if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
233     ENDDO
234    
235 mocchiut 1.4 C----------------------------------------------------------------------
236     C------------------ set ADC & TDC flag = 0 ------------------------
237     C----------------------------------------------------------------------
238    
239     do j=1,8
240     if (adc(ch11a(j),hb11a(j)).LT.4096)adcflagtof(ch11a(j),hb11a(j))=0
241     if (adc(ch11b(j),hb11b(j)).LT.4096)adcflagtof(ch11b(j),hb11b(j))=0
242     if (tdc(ch11a(j),hb11a(j)).LT.4096)tdcflagtof(ch11a(j),hb11a(j))=0
243     if (tdc(ch11b(j),hb11b(j)).LT.4096)tdcflagtof(ch11b(j),hb11b(j))=0
244     enddo
245     do j=1,6
246     if (adc(ch12a(j),hb12a(j)).LT.4096)adcflagtof(ch12a(j),hb12a(j))=0
247     if (adc(ch12b(j),hb12b(j)).LT.4096)adcflagtof(ch12b(j),hb12b(j))=0
248     if (tdc(ch12a(j),hb12a(j)).LT.4096)tdcflagtof(ch12a(j),hb12a(j))=0
249     if (tdc(ch12b(j),hb12b(j)).LT.4096)tdcflagtof(ch12b(j),hb12b(j))=0
250     enddo
251     do j=1,2
252     if (adc(ch21a(j),hb21a(j)).LT.4096)adcflagtof(ch21a(j),hb21a(j))=0
253     if (adc(ch21b(j),hb21b(j)).LT.4096)adcflagtof(ch21b(j),hb21b(j))=0
254     if (tdc(ch21a(j),hb21a(j)).LT.4096)tdcflagtof(ch21a(j),hb21a(j))=0
255     if (tdc(ch21b(j),hb21b(j)).LT.4096)tdcflagtof(ch21b(j),hb21b(j))=0
256     enddo
257     do j=1,2
258     if (adc(ch22a(j),hb22a(j)).LT.4096)adcflagtof(ch22a(j),hb22a(j))=0
259     if (adc(ch22b(j),hb22b(j)).LT.4096)adcflagtof(ch22b(j),hb22b(j))=0
260     if (tdc(ch22a(j),hb22a(j)).LT.4096)tdcflagtof(ch22a(j),hb22a(j))=0
261     if (tdc(ch22b(j),hb22b(j)).LT.4096)tdcflagtof(ch22b(j),hb22b(j))=0
262     enddo
263     do j=1,3
264     if (adc(ch31a(j),hb31a(j)).LT.4096)adcflagtof(ch31a(j),hb31a(j))=0
265     if (adc(ch31b(j),hb31b(j)).LT.4096)adcflagtof(ch31b(j),hb31b(j))=0
266     if (tdc(ch31a(j),hb31a(j)).LT.4096)tdcflagtof(ch31a(j),hb31a(j))=0
267     if (tdc(ch31b(j),hb31b(j)).LT.4096)tdcflagtof(ch31b(j),hb31b(j))=0
268     enddo
269     do j=1,3
270     if (adc(ch32a(j),hb32a(j)).LT.4096)adcflagtof(ch32a(j),hb32a(j))=0
271     if (adc(ch32b(j),hb32b(j)).LT.4096)adcflagtof(ch32b(j),hb32b(j))=0
272     if (tdc(ch32a(j),hb32a(j)).LT.4096)tdcflagtof(ch32a(j),hb32a(j))=0
273     if (tdc(ch32b(j),hb32b(j)).LT.4096)tdcflagtof(ch32b(j),hb32b(j))=0
274     enddo
275    
276 mocchiut 1.1 C----------------------------------------------------------------
277 mocchiut 1.4 C---------- Check PMTs 10 and 35 for strange TDC values----------
278     C----------------------------------------------------------------
279    
280     C---- S116A TDC=819
281     if (tof11(1,6,1).EQ.819) then
282     tof11(1,6,1) = 4095
283     tdcflagtof(ch11a(6),hb11a(6))=2
284     endif
285    
286     C---- S222B TDC=819
287     if (tof22(2,2,1).EQ.819) then
288     tof22(2,2,1) = 4095
289     tdcflagtof(ch22b(2),hb22b(2))=2
290     endif
291    
292    
293     C----------------------------------------------------------------
294     C------------ Check Paddles for hits -----------------------
295     C------ a "hit" means TDC values<4095 on both sides ------------
296 mocchiut 1.1 C----------------------------------------------------------------
297    
298     C upper tof S11
299     DO i = 1,8
300    
301     DO j = 1,2
302     tof11_event(j,i) = none_ev
303     IF ((tof11(j,i,itdc).LT.2000).AND.(tof11(j,i,itdc).GT.100))
304     + tof11_event(j,i) = tof11_event(j,i) + tdc_ev
305     ENDDO
306     ENDDO
307    
308     c find single paddle in upper tof with tdc and adc signal
309     tof11_i = none_find
310     tof11_j = none_find
311     check = .TRUE.
312     DO i = 1, 8
313     IF ((tof11_event(left,i).GE.1).AND.(tof11_event(right,i).GE.1))
314     + THEN
315     c check if an other paddle has also an event - then set flag
316     tof11_j = tof11_j + 2**(i-1)
317     IF (check.EQV..TRUE.) THEN
318     IF (tof11_i.EQ.none_find) THEN
319     tof11_i = i
320     ELSE
321     tof11_i = -1
322     check = .FALSE.
323     ENDIF
324     ENDIF
325     ENDIF
326     ENDDO
327    
328    
329     C upper tof S12
330     DO i = 1,6
331     DO j = 1,2
332     tof12_event(j,i) = none_ev
333     IF ((tof12(j,i,itdc).LT.2000).AND.(tof12(j,i,itdc).GT.100))
334     + tof12_event(j,i) = tof12_event(j,i) + tdc_ev
335     ENDDO
336     ENDDO
337    
338     c find single paddle in upper tof with tdc and adc signal
339     tof12_i = none_find
340     tof12_j = none_find
341     check = .TRUE.
342     DO i = 1, 6
343     IF ((tof12_event(left,i).GE.1).AND.(tof12_event(right,i).GE.1))
344     + THEN
345     c check if an other paddle has also an event - then set flag
346     tof12_j = tof12_j + 2**(i-1)
347     IF (check.EQV..TRUE.) THEN
348     IF (tof12_i.EQ.none_find) THEN
349     tof12_i = i
350     ELSE
351     tof12_i = -1
352     check = .FALSE.
353     ENDIF
354     ENDIF
355     ENDIF
356     ENDDO
357    
358    
359     C middle tof S21
360     DO i = 1,2
361     DO j = 1,2
362     tof21_event(j,i) = none_ev
363     IF ((tof21(j,i,itdc).LT.2000).AND.(tof21(j,i,itdc).GT.100))
364     + tof21_event(j,i) = tof21_event(j,i) + tdc_ev
365     ENDDO
366     ENDDO
367    
368     c find single paddle in upper tof with tdc and adc signal
369     tof21_i = none_find
370     tof21_j = none_find
371     check = .TRUE.
372     DO i = 1, 2
373     IF ((tof21_event(left,i).GE.1).AND.(tof21_event(right,i).GE.1))
374     + THEN
375     c check if an other paddle has also an event - then set flag
376     tof21_j = tof21_j + 2**(i-1)
377     IF (check.EQV..TRUE.) THEN
378     IF (tof21_i.EQ.none_find) THEN
379     tof21_i = i
380     ELSE
381     tof21_i = -1
382     check = .FALSE.
383     ENDIF
384     ENDIF
385     ENDIF
386     ENDDO
387    
388     C middle tof S22
389     DO i = 1,2
390     DO j = 1,2
391     tof22_event(j,i) = none_ev
392     IF ((tof22(j,i,itdc).LT.2000).AND.(tof22(j,i,itdc).GT.100))
393     + tof22_event(j,i) = tof22_event(j,i) + tdc_ev
394     ENDDO
395     ENDDO
396    
397     c find single paddle in upper tof with tdc and adc signal
398     tof22_i = none_find
399     tof22_j = none_find
400     check = .TRUE.
401     DO i = 1, 2
402     IF ((tof22_event(left,i).GE.1).AND.(tof22_event(right,i).GE.1))
403     + THEN
404     c check if an other paddle has also an event - then set flag
405     tof22_j = tof22_j + 2**(i-1)
406     IF (check.EQV..TRUE.) THEN
407     IF (tof22_i.EQ.none_find) THEN
408     tof22_i = i
409     ELSE
410     tof22_i = -1
411     check = .FALSE.
412     ENDIF
413     ENDIF
414     ENDIF
415     ENDDO
416    
417    
418     C bottom tof S31
419     DO i = 1,3
420     DO j = 1,2
421     tof31_event(j,i) = none_ev
422     IF ((tof31(j,i,itdc).LT.2000).AND.(tof31(j,i,itdc).GT.100))
423     + tof31_event(j,i) = tof31_event(j,i) + tdc_ev
424     ENDDO
425     ENDDO
426    
427     c find single paddle in upper tof with tdc and adc signal
428     tof31_i = none_find
429     tof31_j = none_find
430     check = .TRUE.
431     DO i = 1, 3
432     IF ((tof31_event(left,i).GE.1).AND.(tof31_event(right,i).GE.1))
433     + THEN
434     c check if an other paddle has also an event - then set flag
435     tof31_j = tof31_j + 2**(i-1)
436     IF (check.EQV..TRUE.) THEN
437     IF (tof31_i.EQ.none_find) THEN
438     tof31_i = i
439     ELSE
440     tof31_i = -1
441     check = .FALSE.
442     ENDIF
443     ENDIF
444     ENDIF
445     ENDDO
446    
447     C bottom tof S32
448     DO i = 1,3
449     DO j = 1,2
450     tof32_event(j,i) = none_ev
451     IF ((tof32(j,i,itdc).LT.2000).AND.(tof32(j,i,itdc).GT.100))
452     + tof32_event(j,i) = tof32_event(j,i) + tdc_ev
453     ENDDO
454     ENDDO
455    
456     c find single paddle in upper tof with tdc and adc signal
457     tof32_i = none_find
458     tof32_j = none_find
459     check = .TRUE.
460     DO i = 1, 3
461     IF ((tof32_event(left,i).GE.1).AND.(tof32_event(right,i).GE.1))
462     + THEN
463     c check if an other paddle has also an event - then set flag
464     tof32_j = tof32_j + 2**(i-1)
465     IF (check.EQV..TRUE.) THEN
466     IF (tof32_i.EQ.none_find) THEN
467     tof32_i = i
468     ELSE
469     tof32_i = -1
470     check = .FALSE.
471     ENDIF
472     ENDIF
473     ENDIF
474     ENDDO
475    
476     do i=1,6
477     tof_i_flag(i)=0
478     tof_j_flag(i)=0
479     enddo
480    
481     tof_i_flag(1)=tof11_i
482     tof_i_flag(2)=tof12_i
483     tof_i_flag(3)=tof21_i
484     tof_i_flag(4)=tof22_i
485     tof_i_flag(5)=tof31_i
486     tof_i_flag(6)=tof32_i
487    
488     tof_j_flag(1)=tof11_j
489     tof_j_flag(2)=tof12_j
490     tof_j_flag(3)=tof21_j
491     tof_j_flag(4)=tof22_j
492     tof_j_flag(5)=tof31_j
493     tof_j_flag(6)=tof32_j
494    
495 mocchiut 1.4
496     C------------------------------------------------------------------
497     C--- calculate track position in paddle using timing difference
498     C------------------------------------------------------------------
499    
500     do i=1,3
501     xtofpos(i)=100.
502     ytofpos(i)=100.
503     enddo
504     C-----------------------------S1 --------------------------------
505    
506     IF (tof11_i.GT.none_find) THEN
507     ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
508     + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
509     endif
510    
511     IF (tof12_i.GT.none_find) THEN
512     xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
513     + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
514     endif
515    
516    
517     C-----------------------------S2 --------------------------------
518    
519     IF (tof21_i.GT.none_find) THEN
520     xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
521     + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
522     endif
523    
524     IF (tof22_i.GT.none_find) THEN
525     ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
526     + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
527     endif
528    
529    
530     C-----------------------------S3 --------------------------------
531    
532     IF (tof31_i.GT.none_find) THEN
533     ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
534     + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
535     endif
536    
537     IF (tof32_i.GT.none_find) THEN
538     xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
539     + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
540     endif
541    
542    
543     c do i=1,3
544     c if (abs(xtofpos(i)).gt.100.) then
545     c xtofpos(i)=101.
546     c endif
547     c if (abs(ytofpos(i)).gt.100.) then
548     c ytofpos(i)=101.
549     c endif
550     c enddo
551    
552     C-- restrict TDC measurements to physical paddle dimensions +/- 10 cm
553     C-- this cut is now stronger than in the old versions
554    
555     if (abs(xtofpos(1)).gt.31.) xtofpos(1)=101.
556     if (abs(xtofpos(2)).gt.19.) xtofpos(2)=101.
557     if (abs(xtofpos(3)).gt.19.) xtofpos(3)=101.
558    
559     if (abs(ytofpos(1)).gt.26.) ytofpos(1)=101.
560     if (abs(ytofpos(2)).gt.18.) ytofpos(2)=101.
561     if (abs(ytofpos(3)).gt.18.) ytofpos(3)=101.
562    
563    
564     C----------------------------------------------------------------------
565     C--------------------- zenith angle theta ---------------------------
566     C----------------------------------------------------------------------
567    
568     dx=0.
569     dy=0.
570     dr=0.
571     theta13 = 0.
572    
573     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find))
574     & dx = xtofpos(1) - xtofpos(3)
575     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find))
576     & dy = ytofpos(1) - ytofpos(3)
577     dr = sqrt(dx*dx+dy*dy)
578     theta13 = atan(dr/tofarm13)
579    
580     C------------------------------------------------------------------
581     c dx=0.
582     c dy=0.
583     c dr=0.
584     c theta12 = 0.
585     c
586     c IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find))
587     c & dx = xtofpos(1) - xtofpos(2)
588     c IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find))
589     c & dy = ytofpos(1) - ytofpos(2)
590     c dr = sqrt(dx*dx+dy*dy)
591     c theta12 = atan(dr/tofarm12)
592     c
593     c dx=0.
594     c dy=0.
595     c dr=0.
596     c theta23 = 0.
597     c
598     c IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find))
599     c & dx = xtofpos(2) - xtofpos(3)
600     c IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find))
601     c & dy = ytofpos(2) - ytofpos(3)
602     c dr = sqrt(dx*dx+dy*dy)
603     c theta23 = atan(dr/tofarm23)
604     c
605     C---------------------------------------------------------------------
606    
607    
608     C--------------------------------------------------------------------
609     C---- if TDCleft.and.TDCright and NO ADC insert artificial ADC
610     C---- values
611     C--------------------------------------------------------------------
612     c middle y (or x) position of the upper and middle ToF-Paddle
613     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
614     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
615     c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
616     c DATA tof22_x/ -4.5,4.5/
617     c DATA tof31_x/ -6.0,0.,6.0/
618     c DATA tof32_y/ -5.0,0.0,5.0/
619    
620    
621     C---------------------------- S1 -------------------------------------
622    
623     yhelp=0.
624     if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i)
625     if (ytofpos(1).lt.100) yhelp=ytofpos(1)
626    
627     IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
628     i = tof11_i
629     if (tof11(left,i,iadc).eq.4095) then
630     xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
631     xkorr=xkorr/hepratio
632     tof11(left,i,iadc)=xkorr/cos(theta13)
633     c write(*,*) 'tofl2 left ',i, tof11(left,i,iadc)
634     adcflagtof(ch11a(i),hb11a(i)) = 1
635     endif
636     if (tof11(right,i,iadc).eq.4095) then
637     xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
638     xkorr=xkorr/hepratio
639     tof11(right,i,iadc)=xkorr/cos(theta13)
640     c write(*,*) 'tofl2 right ',i, tof11(right,i,iadc)
641     adcflagtof(ch11b(i),hb11b(i)) = 1
642     endif
643     ENDIF
644    
645     xhelp=0.
646     if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i)
647     if (xtofpos(1).lt.100) xhelp=xtofpos(1)
648    
649     IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
650     i = tof12_i
651     if (tof12(left,i,iadc).eq.4095) then
652     xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
653     xkorr=xkorr/hepratio
654     tof12(left,i,iadc) = xkorr/cos(theta13)
655     adcflagtof(ch12a(i),hb12a(i)) = 1
656     endif
657     if (tof12(right,i,iadc).eq.4095) then
658     xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
659     xkorr=xkorr/hepratio
660     tof12(right,i,iadc) = xkorr/cos(theta13)
661     adcflagtof(ch12b(i),hb12b(i)) = 1
662     endif
663     ENDIF
664    
665     C-----------------------------S2 --------------------------------
666    
667     xhelp=0.
668     if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i)
669     if (xtofpos(2).lt.100) xhelp=xtofpos(2)
670    
671     IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
672     i = tof21_i
673     if (tof21(left,i,iadc).eq.4095) then
674     xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
675     xkorr=xkorr/hepratio
676     tof21(left,i,iadc) = xkorr/cos(theta13)
677     adcflagtof(ch21a(i),hb21a(i)) = 1
678     endif
679     if (tof21(right,i,iadc).eq.4095) then
680     xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
681     xkorr=xkorr/hepratio
682     tof21(right,i,iadc) = xkorr/cos(theta13)
683     adcflagtof(ch21b(i),hb21b(i)) = 1
684     endif
685     ENDIF
686    
687    
688     yhelp=0.
689     if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i)
690     if (ytofpos(2).lt.100) yhelp=ytofpos(2)
691    
692     IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
693     i = tof22_i
694     if (tof22(left,i,iadc).eq.4095) then
695     xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
696     xkorr=xkorr/hepratio
697     tof22(left,i,iadc) = xkorr/cos(theta13)
698     adcflagtof(ch22a(i),hb22a(i)) = 1
699     endif
700     if (tof22(right,i,iadc).eq.4095) then
701     xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
702     xkorr=xkorr/hepratio
703     tof22(right,i,iadc) = xkorr/cos(theta13)
704     adcflagtof(ch22b(i),hb22b(i)) = 1
705     endif
706     ENDIF
707    
708     C-----------------------------S3 --------------------------------
709    
710     yhelp=0.
711     if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i)
712     if (ytofpos(3).lt.100) yhelp=ytofpos(3)
713    
714     IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
715     i = tof31_i
716     if (tof31(left,i,iadc).eq.4095) then
717     xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
718     xkorr=xkorr/hepratio
719     tof31(left,i,iadc) = xkorr/cos(theta13)
720     adcflagtof(ch31a(i),hb31a(i)) = 1
721     endif
722     if (tof31(right,i,iadc).eq.4095) then
723     xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
724     xkorr=xkorr/hepratio
725     tof31(right,i,iadc) = xkorr/cos(theta13)
726     adcflagtof(ch31b(i),hb31b(i)) = 1
727     endif
728     ENDIF
729    
730     xhelp=0.
731     if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i)
732     if (xtofpos(3).lt.100) xhelp=xtofpos(3)
733    
734     IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
735     i = tof32_i
736     if (tof32(left,i,iadc).eq.4095) then
737     xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
738     xkorr=xkorr/hepratio
739     tof32(left,i,iadc) = xkorr/cos(theta13)
740     adcflagtof(ch32a(i),hb32a(i)) = 1
741     endif
742     if (tof32(right,i,iadc).eq.4095) then
743     xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
744     xkorr=xkorr/hepratio
745     tof32(right,i,iadc) = xkorr/cos(theta13)
746     adcflagtof(ch32b(i),hb32b(i)) = 1
747     endif
748     ENDIF
749    
750 mocchiut 1.1
751     C--------------------------------------------------------------------
752     C--------------------Time walk correction -------------------------
753     C--------------------------------------------------------------------
754    
755     DO i=1,8
756 mocchiut 1.5 xhelp= 0.
757 mocchiut 1.1 xhelp_a = tof11(left,i,iadc)
758     xhelp_t = tof11(left,i,itdc)
759 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw11(left,i)/sqrt(xhelp_a)
760 mocchiut 1.1 tof11(left,i,itdc) = xhelp_t + xhelp
761     tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
762     xhelp_a = tof11(right,i,iadc)
763     xhelp_t = tof11(right,i,itdc)
764 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw11(right,i)/sqrt(xhelp_a)
765 mocchiut 1.1 tof11(right,i,itdc) = xhelp_t + xhelp
766     tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
767     ENDDO
768    
769     DO i=1,6
770 mocchiut 1.5 xhelp= 0.
771 mocchiut 1.1 xhelp_a = tof12(left,i,iadc)
772     xhelp_t = tof12(left,i,itdc)
773 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw12(left,i)/sqrt(xhelp_a)
774 mocchiut 1.1 tof12(left,i,itdc) = xhelp_t + xhelp
775     tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
776     xhelp_a = tof12(right,i,iadc)
777     xhelp_t = tof12(right,i,itdc)
778 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw12(right,i)/sqrt(xhelp_a)
779 mocchiut 1.1 tof12(right,i,itdc) = xhelp_t + xhelp
780     tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
781     ENDDO
782     C----
783     DO i=1,2
784 mocchiut 1.5 xhelp= 0.
785 mocchiut 1.1 xhelp_a = tof21(left,i,iadc)
786     xhelp_t = tof21(left,i,itdc)
787 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw21(left,i)/sqrt(xhelp_a)
788 mocchiut 1.1 tof21(left,i,itdc) = xhelp_t + xhelp
789     tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
790     xhelp_a = tof21(right,i,iadc)
791     xhelp_t = tof21(right,i,itdc)
792 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw21(right,i)/sqrt(xhelp_a)
793 mocchiut 1.1 tof21(right,i,itdc) = xhelp_t + xhelp
794     tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
795     ENDDO
796    
797     DO i=1,2
798 mocchiut 1.5 xhelp= 0.
799 mocchiut 1.1 xhelp_a = tof22(left,i,iadc)
800     xhelp_t = tof22(left,i,itdc)
801 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw22(left,i)/sqrt(xhelp_a)
802 mocchiut 1.1 tof22(left,i,itdc) = xhelp_t + xhelp
803     tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
804     xhelp_a = tof22(right,i,iadc)
805     xhelp_t = tof22(right,i,itdc)
806 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw22(right,i)/sqrt(xhelp_a)
807 mocchiut 1.1 tof22(right,i,itdc) = xhelp_t + xhelp
808     tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
809     ENDDO
810     C----
811    
812     DO i=1,3
813 mocchiut 1.5 xhelp= 0.
814 mocchiut 1.1 xhelp_a = tof31(left,i,iadc)
815     xhelp_t = tof31(left,i,itdc)
816 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw31(left,i)/sqrt(xhelp_a)
817 mocchiut 1.1 tof31(left,i,itdc) = xhelp_t + xhelp
818     tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
819     xhelp_a = tof31(right,i,iadc)
820     xhelp_t = tof31(right,i,itdc)
821 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw31(right,i)/sqrt(xhelp_a)
822 mocchiut 1.1 tof31(right,i,itdc) = xhelp_t + xhelp
823     tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
824     ENDDO
825    
826     DO i=1,3
827 mocchiut 1.5 xhelp= 0.
828 mocchiut 1.1 xhelp_a = tof32(left,i,iadc)
829     xhelp_t = tof32(left,i,itdc)
830 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw32(left,i)/sqrt(xhelp_a)
831 mocchiut 1.1 tof32(left,i,itdc) = xhelp_t + xhelp
832     tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
833     xhelp_a = tof32(right,i,iadc)
834     xhelp_t = tof32(right,i,itdc)
835 mocchiut 1.4 if(xhelp_a<4095) xhelp = tw32(right,i)/sqrt(xhelp_a)
836 mocchiut 1.1 tof32(right,i,itdc) = xhelp_t + xhelp
837     tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
838     ENDDO
839    
840     C----------------------------------------------------------------------
841     C------------------angle and ADC(x) correction
842     C----------------------------------------------------------------------
843     C-----------------------------S1 --------------------------------
844     c middle y (or x) position of the upper and middle ToF-Paddle
845     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
846     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
847 mocchiut 1.4 c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
848 mocchiut 1.1 c DATA tof22_x/ -4.5,4.5/
849     c DATA tof31_x/ -6.0,0.,6.0/
850     c DATA tof32_y/ -5.0,0.0,5.0/
851    
852     yhelp=0.
853     if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i)
854     if (ytofpos(1).lt.100) yhelp=ytofpos(1)
855    
856     IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
857    
858     i = tof11_i
859 mocchiut 1.3 if (tof11(left,i,iadc).lt.4095) then
860 mocchiut 1.4 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
861 mocchiut 1.1 xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
862 mocchiut 1.4 xkorr=xkorr/hepratio
863 mocchiut 1.1 adctof_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
864     endif
865    
866 mocchiut 1.3 if (tof11(right,i,iadc).lt.4095) then
867 mocchiut 1.4 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
868 mocchiut 1.1 xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
869 mocchiut 1.4 xkorr=xkorr/hepratio
870 mocchiut 1.1 adctof_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
871     endif
872     ENDIF
873    
874     xhelp=0.
875     if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i)
876     if (xtofpos(1).lt.100) xhelp=xtofpos(1)
877    
878     IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
879    
880     i = tof12_i
881 mocchiut 1.3 if (tof12(left,i,iadc).lt.4095) then
882 mocchiut 1.4 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
883 mocchiut 1.1 xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
884 mocchiut 1.4 xkorr=xkorr/hepratio
885 mocchiut 1.1 adctof_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
886     endif
887    
888 mocchiut 1.3 if (tof12(right,i,iadc).lt.4095) then
889 mocchiut 1.4 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
890 mocchiut 1.1 xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
891 mocchiut 1.4 xkorr=xkorr/hepratio
892 mocchiut 1.1 adctof_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
893     endif
894     ENDIF
895    
896     C-----------------------------S2 --------------------------------
897    
898     xhelp=0.
899     if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i)
900     if (xtofpos(2).lt.100) xhelp=xtofpos(2)
901    
902     IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
903    
904     i = tof21_i
905 mocchiut 1.3 if (tof21(left,i,iadc).lt.4095) then
906 mocchiut 1.4 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
907 mocchiut 1.1 xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
908 mocchiut 1.4 xkorr=xkorr/hepratio
909 mocchiut 1.1 adctof_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
910     endif
911    
912 mocchiut 1.3 if (tof21(right,i,iadc).lt.4095) then
913 mocchiut 1.4 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
914 mocchiut 1.1 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
915 mocchiut 1.4 xkorr=xkorr/hepratio
916 mocchiut 1.1 adctof_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
917     endif
918     ENDIF
919    
920    
921     yhelp=0.
922     if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i)
923     if (ytofpos(2).lt.100) yhelp=ytofpos(2)
924    
925     IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
926    
927     i = tof22_i
928 mocchiut 1.3 if (tof22(left,i,iadc).lt.4095) then
929 mocchiut 1.4 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
930 mocchiut 1.1 xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
931 mocchiut 1.4 xkorr=xkorr/hepratio
932 mocchiut 1.1 adctof_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
933     endif
934    
935 mocchiut 1.3 if (tof22(right,i,iadc).lt.4095) then
936 mocchiut 1.4 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
937 mocchiut 1.1 xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
938 mocchiut 1.4 xkorr=xkorr/hepratio
939 mocchiut 1.1 adctof_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
940     endif
941     ENDIF
942    
943     C-----------------------------S3 --------------------------------
944    
945     yhelp=0.
946     if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i)
947     if (ytofpos(3).lt.100) yhelp=ytofpos(3)
948    
949     IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
950    
951     i = tof31_i
952 mocchiut 1.3 if (tof31(left,i,iadc).lt.4095) then
953 mocchiut 1.4 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
954 mocchiut 1.1 xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
955 mocchiut 1.4 xkorr=xkorr/hepratio
956 mocchiut 1.1 adctof_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
957     endif
958    
959 mocchiut 1.3 if (tof31(right,i,iadc).lt.4095) then
960 mocchiut 1.4 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
961 mocchiut 1.1 xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
962 mocchiut 1.4 xkorr=xkorr/hepratio
963 mocchiut 1.1 adctof_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
964     endif
965     ENDIF
966    
967     xhelp=0.
968     if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i)
969     if (xtofpos(3).lt.100) xhelp=xtofpos(3)
970    
971     IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
972    
973     i = tof32_i
974 mocchiut 1.3 if (tof32(left,i,iadc).lt.4095) then
975 mocchiut 1.4 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
976 mocchiut 1.1 xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
977 mocchiut 1.4 xkorr=xkorr/hepratio
978 mocchiut 1.1 adctof_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
979     endif
980    
981 mocchiut 1.3 if (tof32(right,i,iadc).lt.4095) then
982 mocchiut 1.4 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
983 mocchiut 1.1 xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
984 mocchiut 1.4 xkorr=xkorr/hepratio
985 mocchiut 1.1 adctof_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
986     endif
987     ENDIF
988    
989 mocchiut 1.4
990     C--------------------------------------------------------------------
991 mocchiut 1.1 C----------------------calculate Beta ------------------------------
992 mocchiut 1.4 C--------------------------------------------------------------------
993     C-------------------difference of sums -----------------------------
994 mocchiut 1.1 C
995     C DS = (t1+t2) - t3+t4)
996     C DS = c1 + c2/beta*cos(theta)
997     C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
998     C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
999     C since TDC resolution varies slightly c2 has to be calibrated
1000    
1001     C S11 - S31
1002 mocchiut 1.4
1003     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1004     & (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1005 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1006     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1007     ds = xhelp1-xhelp2
1008     ihelp=(tof11_i-1)*3+tof31_i
1009     c1 = k_S11S31(1,ihelp)
1010     c2 = k_S11S31(2,ihelp)
1011     betatof_a(1) = c2/(cos(theta13)*(ds-c1))
1012 mocchiut 1.2
1013     C------- ToF Mask - S11 - S31
1014    
1015     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1016     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1017     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1018     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1019    
1020     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1021     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1022     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1023     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1024    
1025     C-------
1026    
1027 mocchiut 1.1 ENDIF
1028    
1029     C S11 - S32
1030 mocchiut 1.4
1031     IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1032     & (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1033 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1034     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1035     ds = xhelp1-xhelp2
1036     ihelp=(tof11_i-1)*3+tof32_i
1037     c1 = k_S11S32(1,ihelp)
1038     c2 = k_S11S32(2,ihelp)
1039     betatof_a(2) = c2/(cos(theta13)*(ds-c1))
1040 mocchiut 1.2
1041     C------- ToF Mask - S11 - S32
1042    
1043     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1044     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1045     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1046     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1047    
1048     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1049     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1050     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1051     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1052    
1053     C-------
1054    
1055 mocchiut 1.1 ENDIF
1056 mocchiut 1.2
1057 mocchiut 1.1 C S12 - S31
1058 mocchiut 1.4
1059     IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1060     & (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1061 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1062     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1063     ds = xhelp1-xhelp2
1064     ihelp=(tof12_i-1)*3+tof31_i
1065     c1 = k_S12S31(1,ihelp)
1066     c2 = k_S12S31(2,ihelp)
1067     betatof_a(3) = c2/(cos(theta13)*(ds-c1))
1068 mocchiut 1.2
1069     C------- ToF Mask - S12 - S31
1070    
1071     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1072     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1073     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1074     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1075    
1076     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1077     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1078     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1079     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1080    
1081     C-------
1082    
1083 mocchiut 1.1 ENDIF
1084 mocchiut 1.2
1085 mocchiut 1.1 C S12 - S32
1086 mocchiut 1.4
1087     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1088     & (xtofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1089 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1090     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1091     ds = xhelp1-xhelp2
1092     ihelp=(tof12_i-1)*3+tof32_i
1093     c1 = k_S12S32(1,ihelp)
1094     c2 = k_S12S32(2,ihelp)
1095     betatof_a(4) = c2/(cos(theta13)*(ds-c1))
1096 mocchiut 1.2
1097     C------- ToF Mask - S12 - S32
1098    
1099     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1100     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1101     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1102     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1103    
1104     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1105     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1106     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1107     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1108    
1109     C-------
1110    
1111 mocchiut 1.1 ENDIF
1112    
1113     C S21 - S31
1114 mocchiut 1.4
1115     IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1116     & (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1117 mocchiut 1.1 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1118     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1119     ds = xhelp1-xhelp2
1120     ihelp=(tof21_i-1)*3+tof31_i
1121     c1 = k_S21S31(1,ihelp)
1122     c2 = k_S21S31(2,ihelp)
1123 mocchiut 1.4 betatof_a(5) = c2/(cos(theta13)*(ds-c1))
1124 mocchiut 1.2
1125     C------- ToF Mask - S21 - S31
1126    
1127     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1128     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1129     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1130     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1131    
1132     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1133     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1134     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1135     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1136    
1137     C-------
1138    
1139 mocchiut 1.1 ENDIF
1140    
1141     C S21 - S32
1142 mocchiut 1.4
1143     IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1144     & (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1145 mocchiut 1.1 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1146     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1147     ds = xhelp1-xhelp2
1148     ihelp=(tof21_i-1)*3+tof32_i
1149     c1 = k_S21S32(1,ihelp)
1150     c2 = k_S21S32(2,ihelp)
1151 mocchiut 1.4 betatof_a(6) = c2/(cos(theta13)*(ds-c1))
1152 mocchiut 1.2
1153     C------- ToF Mask - S21 - S32
1154    
1155     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1156     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1157     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1158     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1159    
1160     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1161     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1162     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1163     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1164    
1165     C-------
1166    
1167 mocchiut 1.1 ENDIF
1168    
1169     C S22 - S31
1170 mocchiut 1.4
1171     IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1172     & (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1173 mocchiut 1.1 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1174     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1175     ds = xhelp1-xhelp2
1176     ihelp=(tof22_i-1)*3+tof31_i
1177     c1 = k_S22S31(1,ihelp)
1178     c2 = k_S22S31(2,ihelp)
1179     betatof_a(7) = c2/(cos(theta13)*(ds-c1))
1180 mocchiut 1.2
1181     C------- ToF Mask - S22 - S31
1182    
1183     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1184     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1185     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1186     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1187    
1188     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1189     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1190     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1191     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1192    
1193     C-------
1194    
1195 mocchiut 1.1 ENDIF
1196    
1197     C S22 - S32
1198 mocchiut 1.4
1199     IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1200     & (ytofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1201 mocchiut 1.1 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1202     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1203     ds = xhelp1-xhelp2
1204     ihelp=(tof22_i-1)*3+tof32_i
1205     c1 = k_S22S32(1,ihelp)
1206     c2 = k_S22S32(2,ihelp)
1207     betatof_a(8) = c2/(cos(theta13)*(ds-c1))
1208 mocchiut 1.2
1209     C------- ToF Mask - S22 - S32
1210    
1211     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1212     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1213     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1214     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1215    
1216     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1217     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1218     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1219     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1220    
1221     C-------
1222    
1223 mocchiut 1.1 ENDIF
1224    
1225     C S11 - S21
1226 mocchiut 1.4
1227     IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1228     & (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1229 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1230     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1231     ds = xhelp1-xhelp2
1232     ihelp=(tof11_i-1)*2+tof21_i
1233     c1 = k_S11S21(1,ihelp)
1234     c2 = k_S11S21(2,ihelp)
1235     betatof_a(9) = c2/(cos(theta13)*(ds-c1))
1236 mocchiut 1.2
1237     C------- ToF Mask - S11 - S21
1238    
1239     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1240     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1241     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1242     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1243    
1244     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1245     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1246     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1247     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1248    
1249     C-------
1250    
1251 mocchiut 1.1 ENDIF
1252    
1253     C S11 - S22
1254 mocchiut 1.4
1255     IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1256     & (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1257 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1258     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1259     ds = xhelp1-xhelp2
1260     ihelp=(tof11_i-1)*2+tof22_i
1261     c1 = k_S11S22(1,ihelp)
1262     c2 = k_S11S22(2,ihelp)
1263     betatof_a(10) = c2/(cos(theta13)*(ds-c1))
1264 mocchiut 1.2
1265     C------- ToF Mask - S11 - S22
1266    
1267     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1268     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1269     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1270     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1271    
1272     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1273     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1274     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1275     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1276    
1277     C-------
1278    
1279 mocchiut 1.1 ENDIF
1280    
1281     C S12 - S21
1282 mocchiut 1.4
1283     IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1284     & (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1285 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1286     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1287     ds = xhelp1-xhelp2
1288     ihelp=(tof12_i-1)*2+tof21_i
1289     c1 = k_S12S21(1,ihelp)
1290     c2 = k_S12S21(2,ihelp)
1291     betatof_a(11) = c2/(cos(theta13)*(ds-c1))
1292 mocchiut 1.2
1293     C------- ToF Mask - S12 - S21
1294    
1295     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1296     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1297     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1298     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1299    
1300     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1301     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1302     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1303     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1304    
1305     C-------
1306    
1307 mocchiut 1.1 ENDIF
1308    
1309     C S12 - S22
1310 mocchiut 1.4
1311     IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1312     & (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1313 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1314     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1315     ds = xhelp1-xhelp2
1316     ihelp=(tof12_i-1)*2+tof22_i
1317     c1 = k_S12S22(1,ihelp)
1318     c2 = k_S12S22(2,ihelp)
1319     betatof_a(12) = c2/(cos(theta13)*(ds-c1))
1320 mocchiut 1.2
1321     C------- ToF Mask - S12 - S22
1322    
1323     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1324     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1325     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1326     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1327    
1328     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1329     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1330     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1331     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1332    
1333     C-------
1334    
1335 mocchiut 1.1 ENDIF
1336 mocchiut 1.2
1337     C---------------------------------------------------------
1338 mocchiut 1.1
1339     icount=0
1340     sw=0.
1341     sxw=0.
1342     beta_mean=100.
1343    
1344     do i=1,12
1345     if ((betatof_a(i).gt.-1.5).and.(betatof_a(i).lt.1.5)) then
1346     icount= icount+1
1347     if (i.le.4) w_i=1./(0.13**2.)
1348     if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1349     if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1350     sxw=sxw + betatof_a(i)*w_i
1351     sw =sw + w_i
1352     endif
1353     enddo
1354    
1355     if (icount.gt.0) beta_mean=sxw/sw
1356     betatof_a(13) = beta_mean
1357    
1358 mocchiut 1.4 c write(*,*) xtofpos
1359     c write(*,*) ytofpos
1360     c write(*,*) betatof_a
1361     C write(*,*) adcflagtof
1362    
1363    
1364 mocchiut 1.1 100 continue
1365    
1366     C
1367     RETURN
1368     END
1369 mocchiut 1.4

  ViewVC Help
Powered by ViewVC 1.1.23