/[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.6 - (hide annotations) (download)
Mon Apr 30 15:46:30 2007 UTC (17 years, 7 months ago) by mocchiut
Branch: MAIN
CVS Tags: v4r00, v3r04, v3r05, v3r06, v3r03
Changes since 1.5: +239 -90 lines
Tof code upgraded, new tof calibration

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

  ViewVC Help
Powered by ViewVC 1.1.23