/[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.8 - (hide annotations) (download)
Mon Mar 31 19:24:04 2008 UTC (16 years, 8 months ago) by pam-de
Branch: MAIN
Changes since 1.7: +48 -44 lines
bug in ToF-dEdx (if check_charge>1)

1 mocchiut 1.6
2 mocchiut 1.7 C******************************************************************************
3     C
4     C 08-12-06 WM: adc_c-bug : The raw ADc value was multiplied with cos(theta)
5     C and AFTER that there was an if statement "if tof32(right,i,iadc) < 4095"
6     C
7     C jan-07 GF: ADCflags(4,12) inserted to flag artificial ADC values
8     C jan-07 WM: artificial ADC values created using attenuation calibration
9     C jan-07 WM: modified xtofpos flag "101". xtofpos must be inside physical
10     C dimension of the paddle +/- 10 cm
11     C jan-07 WM: if xtofpos=101 then this paddle is not used for beta
12     C calculation
13     C jan-07 WM: the definition for a "hit" is changed: Now we must have a
14     C valid TDC signal on both sides
15     C jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift
16     C jan-07 WM: bug removed: in some cases tdc_tw was calculated due to a
17     C leftover "xhelp" value
18     C apr-07 WM: attenuation fit curve is now a double exponential fit
19     C conversion from raw ADC to pC using calibration function
20     C variables xtr_tof and ytr_tof inserted (filled with default)
21     C jan-08 WM: Major Update: Time Walk correction introduced
22     C Additionalyl we use the information from the "check_charge"
23     C function to fill artificial ADC values and make small corrections
24     C to the k1-parameter (for Z>2)
25     C feb-08 WM: Calculation of beta(13) changed: First a mean beta is calculated,
26     C then in a second step we check the residuals of the single
27     C measurements, reject if > 10 sigma, calculate chi2 and "quality"
28     C beta is taken as good if chi2<20 and quality>10
29 pam-de 1.8 C mar-08 WM: Call to "newbeta" changed, now a flag tells the function if the
30     C call comes from "tofl2com" or form "toftrack"
31     C mar-08 WM: Bug found in dEdx if check_charge>1
32 mocchiut 1.7 C******************************************************************************
33 mocchiut 1.4
34 mocchiut 1.1 INTEGER FUNCTION TOFL2COM()
35     c
36     IMPLICIT NONE
37     C
38     include 'input_tof.txt'
39     include 'output_tof.txt'
40     include 'tofcomm.txt'
41    
42     INTEGER icounter
43     DATA icounter / 0/
44    
45     LOGICAL check
46     REAL secure
47    
48 mocchiut 1.7 INTEGER j,hitvec(6)
49 mocchiut 1.1
50     REAL dx,dy,dr,ds
51 mocchiut 1.4 REAL yhelp,xhelp,xhelp1,xhelp2
52 mocchiut 1.7 REAL c1,c2
53 mocchiut 1.1
54 mocchiut 1.7 C REAL sw,sxw,w_i
55     C INTEGER icount
56     C REAL beta_mean
57 mocchiut 1.4
58 mocchiut 1.1 INTEGER tof11_j,tof21_j,tof31_j
59     INTEGER tof12_j,tof22_j,tof32_j
60    
61     c value for status of each PM-data
62     c first index : 1 = left, 2 = right
63     c second index : 1... number of paddle
64     INTEGER tof11_event(2,8),tof12_event(2,6)
65     INTEGER tof21_event(2,2),tof22_event(2,2)
66     INTEGER tof31_event(2,3),tof32_event(2,3)
67    
68 mocchiut 1.7
69     REAL y_coor_lin11c(8,2),x_coor_lin12c(6,2)
70     REAL x_coor_lin21c(2,2),y_coor_lin22c(2,2)
71     REAL y_coor_lin31c(3,2),x_coor_lin32c(3,2)
72    
73     DATA y_coor_lin11c(1,1),y_coor_lin11c(1,2) /-20.66,-2.497/
74     DATA y_coor_lin11c(2,1),y_coor_lin11c(2,2) /-9.10, -2.52/
75     DATA y_coor_lin11c(3,1),y_coor_lin11c(3,2) /-24.07,-2.12/
76     DATA y_coor_lin11c(4,1),y_coor_lin11c(4,2) /-13.40,-2.47/
77     DATA y_coor_lin11c(5,1),y_coor_lin11c(5,2) /-31.07,-2.32/
78     DATA y_coor_lin11c(6,1),y_coor_lin11c(6,2) /-21.69,-2.63/
79     DATA y_coor_lin11c(7,1),y_coor_lin11c(7,2) /-12.37,-2.65/
80     DATA y_coor_lin11c(8,1),y_coor_lin11c(8,2) /-10.81,-3.15/
81    
82     DATA x_coor_lin12c(1,1),x_coor_lin12c(1,2) /12.96, -2.65/
83     DATA x_coor_lin12c(2,1),x_coor_lin12c(2,2) /17.12,-2.44/
84     DATA x_coor_lin12c(3,1),x_coor_lin12c(3,2) /7.26, -1.98/
85     DATA x_coor_lin12c(4,1),x_coor_lin12c(4,2) /-22.52,-2.27/
86     DATA x_coor_lin12c(5,1),x_coor_lin12c(5,2) /-18.54,-2.28/
87     DATA x_coor_lin12c(6,1),x_coor_lin12c(6,2) /-7.67,-2.15/
88    
89     DATA x_coor_lin21c(1,1),x_coor_lin21c(1,2) /22.56,-1.56/
90     DATA x_coor_lin21c(2,1),x_coor_lin21c(2,2) /13.94,-1.56/
91    
92     DATA y_coor_lin22c(1,1),y_coor_lin22c(1,2) /-24.24,-2.23/
93     DATA y_coor_lin22c(2,1),y_coor_lin22c(2,2) /-45.99,-1.68/
94    
95     DATA y_coor_lin31c(1,1),y_coor_lin31c(1,2) /-22.99,-3.54/
96     DATA y_coor_lin31c(2,1),y_coor_lin31c(2,2) /-42.28,-4.10/
97     DATA y_coor_lin31c(3,1),y_coor_lin31c(3,2) /-41.29,-3.69/
98    
99     DATA x_coor_lin32c(1,1),x_coor_lin32c(1,2) /0.961, -3.22/
100     DATA x_coor_lin32c(2,1),x_coor_lin32c(2,2) /4.98,-3.48/
101     DATA x_coor_lin32c(3,1),x_coor_lin32c(3,2) /-22.08,-3.37/
102    
103 mocchiut 1.1
104 mocchiut 1.4 REAL theta13
105 mocchiut 1.1 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
106     REAL tofarm12
107     PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
108     REAL tofarm23
109     PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
110     REAL tofarm13
111     PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
112 mocchiut 1.4
113     REAL hepratio
114 mocchiut 1.1
115     INTEGER ihelp
116 mocchiut 1.7 REAL xkorr,btemp(12)
117    
118     REAL atten,pc_adc,check_charge,newbeta
119    
120     INTEGER IZ
121     REAL k1corrA1,k1corrB1,k1corrC1
122    
123 mocchiut 1.1
124 mocchiut 1.7 INTEGER ifst
125     DATA ifst /0/
126 mocchiut 1.6
127 mocchiut 1.1 C---------------------------------------
128     C
129     C Begin !
130     C
131     TOFL2COM = 0
132     C
133     C CALCULATE COMMON VARIABLES
134     C
135 mocchiut 1.7 C-------------------------------------------------------------------
136 mocchiut 1.1
137 mocchiut 1.7 if (ifst.eq.0) then
138    
139     ifst=1
140 mocchiut 1.1
141 mocchiut 1.7 C amplitude has to be 'secure' higher than pedestal for an adc event
142     secure = 2.
143 mocchiut 1.1
144 mocchiut 1.4 C ratio between helium and proton ca. 4
145 mocchiut 1.7 hepratio = 4. !
146     offset = 1
147     slope = 2
148     left = 1
149     right = 2
150     none_ev = 0
151     none_find = 0
152     tdc_ev = 1
153     adc_ev = 1
154     itdc = 1
155     iadc = 2
156    
157     C--- These are the corrections to the k1-value for Z>2 particles
158     k1corrA1 = 0.
159     k1corrB1 = -5.0
160     k1corrC1= 8.0
161    
162    
163     ENDIF
164     C---------------------------------------------------------------------
165    
166     icounter = icounter + 1
167    
168 mocchiut 1.1
169     do i=1,13
170     betatof_a(i) = 100. ! As in "troftrk.for"
171     enddo
172    
173 mocchiut 1.7 do i=1,6
174     hitvec(i) = -1
175     enddo
176    
177 mocchiut 1.1 do i=1,4
178     do j=1,12
179     adctof_c(i,j) = 1000.
180     enddo
181     enddo
182    
183    
184     do i=1,4
185     do j=1,12
186     tdc_c(i,j) = 4095.
187     enddo
188     enddo
189    
190    
191 mocchiut 1.2 do i=1,12
192     do j=1,4
193     tofmask(j,i) = 0
194     enddo
195     enddo
196    
197    
198 mocchiut 1.4 c gf adc falg:
199     do i=1,4
200     do j=1,12
201     adcflagtof(i,j) = 0
202     enddo
203     enddo
204    
205     c gf tdc falg:
206     do i=1,4
207     do j=1,12
208     tdcflagtof(i,j) = 0
209     enddo
210     enddo
211    
212 mocchiut 1.6
213     C--- Fill xtr_tof and ytr_tof: positions from tracker at ToF layers
214     C--- since this is standalone ToF fill with default values
215     do j=1,6
216     xtr_tof(j) = 101.
217     ytr_tof(j) = 101.
218     enddo
219    
220 mocchiut 1.1 c the calibration files are read in the main program from xxx_tofcalib.rz
221    
222     c-------------------------get ToF data --------------------------------
223    
224     c put the adc and tdc values from ntuple into tofxx(i,j,k) variables
225 mocchiut 1.6 c adc valueas are then pC
226 mocchiut 1.1
227     do j=1,8
228 mocchiut 1.6 tof11(1,j,2) = pc_adc(adc(ch11a(j),hb11a(j)))
229     tof11(2,j,2) = pc_adc(adc(ch11b(j),hb11b(j)))
230     tof11(1,j,1) = (tdc(ch11a(j),hb11a(j)))
231     tof11(2,j,1) = (tdc(ch11b(j),hb11b(j)))
232 mocchiut 1.1 enddo
233    
234    
235     do j=1,6
236 mocchiut 1.6 tof12(1,j,2) = pc_adc(adc(ch12a(j),hb12a(j)))
237     tof12(2,j,2) = pc_adc(adc(ch12b(j),hb12b(j)))
238     tof12(1,j,1) = (tdc(ch12a(j),hb12a(j)))
239     tof12(2,j,1) = (tdc(ch12b(j),hb12b(j)))
240 mocchiut 1.1 enddo
241    
242     do j=1,2
243 mocchiut 1.6 tof21(1,j,2) = pc_adc(adc(ch21a(j),hb21a(j)))
244     tof21(2,j,2) = pc_adc(adc(ch21b(j),hb21b(j)))
245     tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
246     tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
247 mocchiut 1.1 enddo
248    
249     do j=1,2
250 mocchiut 1.6 tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
251     tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))
252     tof22(1,j,1) = (tdc(ch22a(j),hb22a(j)))
253     tof22(2,j,1) = (tdc(ch22b(j),hb22b(j)))
254 mocchiut 1.1 enddo
255    
256     do j=1,3
257 mocchiut 1.6 tof31(1,j,2) = pc_adc(adc(ch31a(j),hb31a(j)))
258     tof31(2,j,2) = pc_adc(adc(ch31b(j),hb31b(j)))
259     tof31(1,j,1) = (tdc(ch31a(j),hb31a(j)))
260     tof31(2,j,1) = (tdc(ch31b(j),hb31b(j)))
261 mocchiut 1.1 enddo
262    
263     do j=1,3
264 mocchiut 1.6 tof32(1,j,2) = pc_adc(adc(ch32a(j),hb32a(j)))
265     tof32(2,j,2) = pc_adc(adc(ch32b(j),hb32b(j)))
266     tof32(1,j,1) = (tdc(ch32a(j),hb32a(j)))
267     tof32(2,j,1) = (tdc(ch32b(j),hb32b(j)))
268 mocchiut 1.1 enddo
269    
270     C----------------------------------------------------------------------
271    
272     DO i = 1,8
273     if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000.
274     if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000.
275     if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000.
276     if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000.
277     ENDDO
278    
279     DO i = 1,6
280     if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000.
281     if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000.
282     if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000.
283     if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000.
284     ENDDO
285    
286    
287     DO i = 1,2
288     if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000.
289     if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000.
290     if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000.
291     if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000.
292     ENDDO
293    
294     DO i = 1,2
295     if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000.
296     if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000.
297     if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000.
298     if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000.
299     ENDDO
300    
301     DO i = 1,3
302     if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000.
303     if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000.
304     if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000.
305     if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000.
306     ENDDO
307    
308     DO i = 1,3
309     if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000.
310     if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000.
311     if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000.
312     if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
313     ENDDO
314    
315 mocchiut 1.4 C----------------------------------------------------------------------
316     C------------------ set ADC & TDC flag = 0 ------------------------
317     C----------------------------------------------------------------------
318    
319     do j=1,8
320     if (adc(ch11a(j),hb11a(j)).LT.4096)adcflagtof(ch11a(j),hb11a(j))=0
321     if (adc(ch11b(j),hb11b(j)).LT.4096)adcflagtof(ch11b(j),hb11b(j))=0
322     if (tdc(ch11a(j),hb11a(j)).LT.4096)tdcflagtof(ch11a(j),hb11a(j))=0
323     if (tdc(ch11b(j),hb11b(j)).LT.4096)tdcflagtof(ch11b(j),hb11b(j))=0
324     enddo
325     do j=1,6
326     if (adc(ch12a(j),hb12a(j)).LT.4096)adcflagtof(ch12a(j),hb12a(j))=0
327     if (adc(ch12b(j),hb12b(j)).LT.4096)adcflagtof(ch12b(j),hb12b(j))=0
328     if (tdc(ch12a(j),hb12a(j)).LT.4096)tdcflagtof(ch12a(j),hb12a(j))=0
329     if (tdc(ch12b(j),hb12b(j)).LT.4096)tdcflagtof(ch12b(j),hb12b(j))=0
330     enddo
331     do j=1,2
332     if (adc(ch21a(j),hb21a(j)).LT.4096)adcflagtof(ch21a(j),hb21a(j))=0
333     if (adc(ch21b(j),hb21b(j)).LT.4096)adcflagtof(ch21b(j),hb21b(j))=0
334     if (tdc(ch21a(j),hb21a(j)).LT.4096)tdcflagtof(ch21a(j),hb21a(j))=0
335     if (tdc(ch21b(j),hb21b(j)).LT.4096)tdcflagtof(ch21b(j),hb21b(j))=0
336     enddo
337     do j=1,2
338     if (adc(ch22a(j),hb22a(j)).LT.4096)adcflagtof(ch22a(j),hb22a(j))=0
339     if (adc(ch22b(j),hb22b(j)).LT.4096)adcflagtof(ch22b(j),hb22b(j))=0
340     if (tdc(ch22a(j),hb22a(j)).LT.4096)tdcflagtof(ch22a(j),hb22a(j))=0
341     if (tdc(ch22b(j),hb22b(j)).LT.4096)tdcflagtof(ch22b(j),hb22b(j))=0
342     enddo
343     do j=1,3
344     if (adc(ch31a(j),hb31a(j)).LT.4096)adcflagtof(ch31a(j),hb31a(j))=0
345     if (adc(ch31b(j),hb31b(j)).LT.4096)adcflagtof(ch31b(j),hb31b(j))=0
346     if (tdc(ch31a(j),hb31a(j)).LT.4096)tdcflagtof(ch31a(j),hb31a(j))=0
347     if (tdc(ch31b(j),hb31b(j)).LT.4096)tdcflagtof(ch31b(j),hb31b(j))=0
348     enddo
349     do j=1,3
350     if (adc(ch32a(j),hb32a(j)).LT.4096)adcflagtof(ch32a(j),hb32a(j))=0
351     if (adc(ch32b(j),hb32b(j)).LT.4096)adcflagtof(ch32b(j),hb32b(j))=0
352     if (tdc(ch32a(j),hb32a(j)).LT.4096)tdcflagtof(ch32a(j),hb32a(j))=0
353     if (tdc(ch32b(j),hb32b(j)).LT.4096)tdcflagtof(ch32b(j),hb32b(j))=0
354     enddo
355    
356 mocchiut 1.1 C----------------------------------------------------------------
357 mocchiut 1.4 C---------- Check PMTs 10 and 35 for strange TDC values----------
358     C----------------------------------------------------------------
359    
360     C---- S116A TDC=819
361     if (tof11(1,6,1).EQ.819) then
362     tof11(1,6,1) = 4095
363     tdcflagtof(ch11a(6),hb11a(6))=2
364     endif
365    
366     C---- S222B TDC=819
367     if (tof22(2,2,1).EQ.819) then
368     tof22(2,2,1) = 4095
369     tdcflagtof(ch22b(2),hb22b(2))=2
370     endif
371    
372     C----------------------------------------------------------------
373     C------------ Check Paddles for hits -----------------------
374     C------ a "hit" means TDC values<4095 on both sides ------------
375 mocchiut 1.1 C----------------------------------------------------------------
376    
377     C upper tof S11
378     DO i = 1,8
379    
380     DO j = 1,2
381     tof11_event(j,i) = none_ev
382     IF ((tof11(j,i,itdc).LT.2000).AND.(tof11(j,i,itdc).GT.100))
383     + tof11_event(j,i) = tof11_event(j,i) + tdc_ev
384     ENDDO
385     ENDDO
386    
387     c find single paddle in upper tof with tdc and adc signal
388     tof11_i = none_find
389     tof11_j = none_find
390     check = .TRUE.
391     DO i = 1, 8
392     IF ((tof11_event(left,i).GE.1).AND.(tof11_event(right,i).GE.1))
393     + THEN
394     c check if an other paddle has also an event - then set flag
395     tof11_j = tof11_j + 2**(i-1)
396     IF (check.EQV..TRUE.) THEN
397     IF (tof11_i.EQ.none_find) THEN
398     tof11_i = i
399     ELSE
400     tof11_i = -1
401     check = .FALSE.
402     ENDIF
403     ENDIF
404     ENDIF
405     ENDDO
406    
407    
408     C upper tof S12
409     DO i = 1,6
410     DO j = 1,2
411     tof12_event(j,i) = none_ev
412     IF ((tof12(j,i,itdc).LT.2000).AND.(tof12(j,i,itdc).GT.100))
413     + tof12_event(j,i) = tof12_event(j,i) + tdc_ev
414     ENDDO
415     ENDDO
416    
417     c find single paddle in upper tof with tdc and adc signal
418     tof12_i = none_find
419     tof12_j = none_find
420     check = .TRUE.
421     DO i = 1, 6
422     IF ((tof12_event(left,i).GE.1).AND.(tof12_event(right,i).GE.1))
423     + THEN
424     c check if an other paddle has also an event - then set flag
425     tof12_j = tof12_j + 2**(i-1)
426     IF (check.EQV..TRUE.) THEN
427     IF (tof12_i.EQ.none_find) THEN
428     tof12_i = i
429     ELSE
430     tof12_i = -1
431     check = .FALSE.
432     ENDIF
433     ENDIF
434     ENDIF
435     ENDDO
436    
437    
438     C middle tof S21
439     DO i = 1,2
440     DO j = 1,2
441     tof21_event(j,i) = none_ev
442     IF ((tof21(j,i,itdc).LT.2000).AND.(tof21(j,i,itdc).GT.100))
443     + tof21_event(j,i) = tof21_event(j,i) + tdc_ev
444     ENDDO
445     ENDDO
446    
447     c find single paddle in upper tof with tdc and adc signal
448     tof21_i = none_find
449     tof21_j = none_find
450     check = .TRUE.
451     DO i = 1, 2
452     IF ((tof21_event(left,i).GE.1).AND.(tof21_event(right,i).GE.1))
453     + THEN
454     c check if an other paddle has also an event - then set flag
455     tof21_j = tof21_j + 2**(i-1)
456     IF (check.EQV..TRUE.) THEN
457     IF (tof21_i.EQ.none_find) THEN
458     tof21_i = i
459     ELSE
460     tof21_i = -1
461     check = .FALSE.
462     ENDIF
463     ENDIF
464     ENDIF
465     ENDDO
466    
467     C middle tof S22
468     DO i = 1,2
469     DO j = 1,2
470     tof22_event(j,i) = none_ev
471     IF ((tof22(j,i,itdc).LT.2000).AND.(tof22(j,i,itdc).GT.100))
472     + tof22_event(j,i) = tof22_event(j,i) + tdc_ev
473     ENDDO
474     ENDDO
475    
476     c find single paddle in upper tof with tdc and adc signal
477     tof22_i = none_find
478     tof22_j = none_find
479     check = .TRUE.
480     DO i = 1, 2
481     IF ((tof22_event(left,i).GE.1).AND.(tof22_event(right,i).GE.1))
482     + THEN
483     c check if an other paddle has also an event - then set flag
484     tof22_j = tof22_j + 2**(i-1)
485     IF (check.EQV..TRUE.) THEN
486     IF (tof22_i.EQ.none_find) THEN
487     tof22_i = i
488     ELSE
489     tof22_i = -1
490     check = .FALSE.
491     ENDIF
492     ENDIF
493     ENDIF
494     ENDDO
495    
496    
497     C bottom tof S31
498     DO i = 1,3
499     DO j = 1,2
500     tof31_event(j,i) = none_ev
501     IF ((tof31(j,i,itdc).LT.2000).AND.(tof31(j,i,itdc).GT.100))
502     + tof31_event(j,i) = tof31_event(j,i) + tdc_ev
503     ENDDO
504     ENDDO
505    
506     c find single paddle in upper tof with tdc and adc signal
507     tof31_i = none_find
508     tof31_j = none_find
509     check = .TRUE.
510     DO i = 1, 3
511     IF ((tof31_event(left,i).GE.1).AND.(tof31_event(right,i).GE.1))
512     + THEN
513     c check if an other paddle has also an event - then set flag
514     tof31_j = tof31_j + 2**(i-1)
515     IF (check.EQV..TRUE.) THEN
516     IF (tof31_i.EQ.none_find) THEN
517     tof31_i = i
518     ELSE
519     tof31_i = -1
520     check = .FALSE.
521     ENDIF
522     ENDIF
523     ENDIF
524     ENDDO
525    
526     C bottom tof S32
527     DO i = 1,3
528     DO j = 1,2
529     tof32_event(j,i) = none_ev
530     IF ((tof32(j,i,itdc).LT.2000).AND.(tof32(j,i,itdc).GT.100))
531     + tof32_event(j,i) = tof32_event(j,i) + tdc_ev
532     ENDDO
533     ENDDO
534    
535     c find single paddle in upper tof with tdc and adc signal
536     tof32_i = none_find
537     tof32_j = none_find
538     check = .TRUE.
539     DO i = 1, 3
540     IF ((tof32_event(left,i).GE.1).AND.(tof32_event(right,i).GE.1))
541     + THEN
542     c check if an other paddle has also an event - then set flag
543     tof32_j = tof32_j + 2**(i-1)
544     IF (check.EQV..TRUE.) THEN
545     IF (tof32_i.EQ.none_find) THEN
546     tof32_i = i
547     ELSE
548     tof32_i = -1
549     check = .FALSE.
550     ENDIF
551     ENDIF
552     ENDIF
553 mocchiut 1.7 ENDDO
554 mocchiut 1.1
555 mocchiut 1.7 do i=1,6
556 mocchiut 1.1 tof_i_flag(i)=0
557     tof_j_flag(i)=0
558 mocchiut 1.7 enddo
559    
560     tof_i_flag(1)=tof11_i
561     tof_i_flag(2)=tof12_i
562     tof_i_flag(3)=tof21_i
563     tof_i_flag(4)=tof22_i
564     tof_i_flag(5)=tof31_i
565     tof_i_flag(6)=tof32_i
566    
567     tof_j_flag(1)=tof11_j
568     tof_j_flag(2)=tof12_j
569     tof_j_flag(3)=tof21_j
570     tof_j_flag(4)=tof22_j
571     tof_j_flag(5)=tof31_j
572     tof_j_flag(6)=tof32_j
573    
574     hitvec(1)=tof11_i
575     hitvec(2)=tof12_i
576     hitvec(3)=tof21_i
577     hitvec(4)=tof22_i
578     hitvec(5)=tof31_i
579     hitvec(6)=tof32_i
580 mocchiut 1.1
581 mocchiut 1.7 c write(*,*) 'tofl2com',
582     c & tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
583 mocchiut 1.1
584 mocchiut 1.4 C------------------------------------------------------------------
585 mocchiut 1.7 C-- calculate track position in paddle using timing difference
586     C-- this calculation is preliminary and uses some standard
587     C-- calibration values, but we need to find a rough position to
588     C-- be able to calculate artificial ADC values (needed for the
589     C-- timewalk...
590 mocchiut 1.4 C------------------------------------------------------------------
591    
592 mocchiut 1.7 do i=1,3
593 mocchiut 1.4 xtofpos(i)=100.
594     ytofpos(i)=100.
595 mocchiut 1.7 enddo
596    
597 mocchiut 1.4 C-----------------------------S1 --------------------------------
598    
599     IF (tof11_i.GT.none_find) THEN
600     ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
601 mocchiut 1.7 + -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
602 mocchiut 1.4 endif
603    
604     IF (tof12_i.GT.none_find) THEN
605     xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
606 mocchiut 1.7 + -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
607 mocchiut 1.4 endif
608    
609    
610     C-----------------------------S2 --------------------------------
611    
612     IF (tof21_i.GT.none_find) THEN
613     xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
614 mocchiut 1.7 + -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
615 mocchiut 1.4 endif
616    
617     IF (tof22_i.GT.none_find) THEN
618     ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
619 mocchiut 1.7 + -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
620 mocchiut 1.4 endif
621    
622    
623     C-----------------------------S3 --------------------------------
624    
625     IF (tof31_i.GT.none_find) THEN
626     ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
627 mocchiut 1.7 + -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
628 mocchiut 1.4 endif
629    
630     IF (tof32_i.GT.none_find) THEN
631     xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
632 mocchiut 1.7 + -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
633 mocchiut 1.4 endif
634    
635    
636     C----------------------------------------------------------------------
637     C--------------------- zenith angle theta ---------------------------
638     C----------------------------------------------------------------------
639    
640     dx=0.
641     dy=0.
642     dr=0.
643     theta13 = 0.
644    
645     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find))
646     & dx = xtofpos(1) - xtofpos(3)
647     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find))
648     & dy = ytofpos(1) - ytofpos(3)
649     dr = sqrt(dx*dx+dy*dy)
650     theta13 = atan(dr/tofarm13)
651    
652    
653 mocchiut 1.7 C----------------------------------------------------------------------
654     C--- check charge:
655     C--- if Z=2 we should use the attenuation curve for helium to
656     C--- fill the artificail ADC values and NOT divide by "hepratio"
657     C--- if Z>2 we should do a correction to
658     C--- the k1 constants in the beta calculation
659     C----------------------------------------------------------------------
660    
661     iz = int(check_charge(theta13,hitvec))
662     C write(*,*) 'in tofl2com',iz
663 mocchiut 1.4
664     C--------------------------------------------------------------------
665     C---- if TDCleft.and.TDCright and NO ADC insert artificial ADC
666     C---- values
667     C--------------------------------------------------------------------
668     c middle y (or x) position of the upper and middle ToF-Paddle
669     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
670     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
671     c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
672     c DATA tof22_x/ -4.5,4.5/
673     c DATA tof31_x/ -6.0,0.,6.0/
674     c DATA tof32_y/ -5.0,0.0,5.0/
675    
676    
677     C---------------------------- S1 -------------------------------------
678    
679     yhelp=0.
680     if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i)
681     if (ytofpos(1).lt.100) yhelp=ytofpos(1)
682    
683     IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
684     i = tof11_i
685 mocchiut 1.6 if (adc(ch11a(i),hb11a(i)).eq.4095) then
686     xkorr = atten(left,11,i,yhelp)
687 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
688 mocchiut 1.4 tof11(left,i,iadc)=xkorr/cos(theta13)
689     adcflagtof(ch11a(i),hb11a(i)) = 1
690     endif
691 mocchiut 1.6 if (adc(ch11b(i),hb11b(i)).eq.4095) then
692     xkorr = atten(right,11,i,yhelp)
693 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
694 mocchiut 1.4 tof11(right,i,iadc)=xkorr/cos(theta13)
695     adcflagtof(ch11b(i),hb11b(i)) = 1
696     endif
697     ENDIF
698    
699     xhelp=0.
700     if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i)
701     if (xtofpos(1).lt.100) xhelp=xtofpos(1)
702    
703     IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
704     i = tof12_i
705 mocchiut 1.6 if (adc(ch12a(i),hb12a(i)).eq.4095) then
706     xkorr = atten(left,12,i,xhelp)
707 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
708 mocchiut 1.4 tof12(left,i,iadc) = xkorr/cos(theta13)
709     adcflagtof(ch12a(i),hb12a(i)) = 1
710     endif
711 mocchiut 1.6 if (adc(ch12b(i),hb12b(i)).eq.4095) then
712     xkorr = atten(right,12,i,xhelp)
713 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
714 mocchiut 1.4 tof12(right,i,iadc) = xkorr/cos(theta13)
715     adcflagtof(ch12b(i),hb12b(i)) = 1
716     endif
717     ENDIF
718    
719     C-----------------------------S2 --------------------------------
720    
721     xhelp=0.
722     if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i)
723     if (xtofpos(2).lt.100) xhelp=xtofpos(2)
724    
725     IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
726     i = tof21_i
727 mocchiut 1.6 if (adc(ch21a(i),hb21a(i)).eq.4095) then
728     xkorr = atten(left,21,i,xhelp)
729 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
730 mocchiut 1.4 tof21(left,i,iadc) = xkorr/cos(theta13)
731     adcflagtof(ch21a(i),hb21a(i)) = 1
732     endif
733 mocchiut 1.6 if (adc(ch21b(i),hb21b(i)).eq.4095) then
734     xkorr = atten(right,21,i,xhelp)
735 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
736 mocchiut 1.4 tof21(right,i,iadc) = xkorr/cos(theta13)
737     adcflagtof(ch21b(i),hb21b(i)) = 1
738     endif
739     ENDIF
740    
741    
742     yhelp=0.
743     if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i)
744     if (ytofpos(2).lt.100) yhelp=ytofpos(2)
745    
746     IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
747     i = tof22_i
748 mocchiut 1.6 if (adc(ch22a(i),hb22a(i)).eq.4095) then
749     xkorr = atten(left,22,i,yhelp)
750 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
751 mocchiut 1.4 tof22(left,i,iadc) = xkorr/cos(theta13)
752     adcflagtof(ch22a(i),hb22a(i)) = 1
753     endif
754 mocchiut 1.6 if (adc(ch22b(i),hb22b(i)).eq.4095) then
755     xkorr = atten(right,22,i,yhelp)
756 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
757 mocchiut 1.4 tof22(right,i,iadc) = xkorr/cos(theta13)
758     adcflagtof(ch22b(i),hb22b(i)) = 1
759     endif
760     ENDIF
761    
762     C-----------------------------S3 --------------------------------
763    
764     yhelp=0.
765     if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i)
766     if (ytofpos(3).lt.100) yhelp=ytofpos(3)
767    
768     IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
769     i = tof31_i
770 mocchiut 1.6 if (adc(ch31a(i),hb31a(i)).eq.4095) then
771     xkorr = atten(left,31,i,yhelp)
772 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
773 mocchiut 1.4 tof31(left,i,iadc) = xkorr/cos(theta13)
774     adcflagtof(ch31a(i),hb31a(i)) = 1
775     endif
776 mocchiut 1.6 if (adc(ch31b(i),hb31b(i)).eq.4095) then
777     xkorr = atten(right,31,i,yhelp)
778 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
779 mocchiut 1.4 tof31(right,i,iadc) = xkorr/cos(theta13)
780     adcflagtof(ch31b(i),hb31b(i)) = 1
781     endif
782     ENDIF
783    
784     xhelp=0.
785     if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i)
786     if (xtofpos(3).lt.100) xhelp=xtofpos(3)
787    
788     IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
789     i = tof32_i
790 mocchiut 1.6 if (adc(ch32a(i),hb32a(i)).eq.4095) then
791     xkorr = atten(left,32,i,xhelp)
792 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
793 mocchiut 1.4 tof32(left,i,iadc) = xkorr/cos(theta13)
794     adcflagtof(ch32a(i),hb32a(i)) = 1
795     endif
796 mocchiut 1.6 if (adc(ch32b(i),hb32b(i)).eq.4095) then
797     xkorr = atten(right,32,i,xhelp)
798 mocchiut 1.7 if (iz.le.1) xkorr=xkorr/hepratio
799 mocchiut 1.4 tof32(right,i,iadc) = xkorr/cos(theta13)
800     adcflagtof(ch32b(i),hb32b(i)) = 1
801     endif
802     ENDIF
803    
804 mocchiut 1.1
805 mocchiut 1.7 C-------------------------------------------------------------------
806 mocchiut 1.1 C--------------------Time walk correction -------------------------
807 mocchiut 1.7 C-------------------------------------------------------------------
808     C-------------------------------------------------------------------
809     C Now there is for each hitted paddle a TDC and ADC value, if the
810     C TDC was < 4095.
811     C There might be also TDC-ADC pairs in paddles not hitted
812    
813     C-------------------------------------------------------------------
814     C If we have multiple paddles hit, so that no artificial ADC value
815     C is created, we set the raw TDC value as "tdc_c"
816     C-------------------------------------------------------------------
817     c
818     c do i=1,4
819     c do j=1,12
820     c tdc_c(i,j) = tdc(i,j)
821     c enddo
822     c enddo
823     c
824     C---- Let's correct the raw TDC value with the time walk ---------
825 mocchiut 1.1
826     DO i=1,8
827 mocchiut 1.7 if ((tdc(ch11a(i),hb11a(i)).lt.4095).and.
828     & (tof11(left,i,iadc).lt.3786)) THEN
829     xhelp = tw11(left,i)/(tof11(left,i,iadc)**0.5)
830     tof11(left,i,itdc) = tof11(left,i,itdc) + xhelp
831     tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
832     ENDIF
833    
834     if ((tdc(ch11b(i),hb11b(i)).lt.4095).and.
835     & (tof11(right,i,iadc).lt.3786)) THEN
836     xhelp = tw11(right,i)/(tof11(right,i,iadc)**0.5)
837     tof11(right,i,itdc) = tof11(right,i,itdc) + xhelp
838     tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
839     ENDIF
840 mocchiut 1.1 ENDDO
841    
842 mocchiut 1.7
843 mocchiut 1.1 DO i=1,6
844 mocchiut 1.7 if ((tdc(ch12a(i),hb12a(i)).lt.4095).and.
845     & (tof12(left,i,iadc).lt.3786)) THEN
846     xhelp = tw12(left,i)/(tof12(left,i,iadc)**0.5)
847     tof12(left,i,itdc) = tof12(left,i,itdc) + xhelp
848     tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
849     ENDIF
850    
851     if ((tdc(ch12b(i),hb12b(i)).lt.4095).and.
852     & (tof12(right,i,iadc).lt.3786)) THEN
853     xhelp = tw12(right,i)/(tof12(right,i,iadc)**0.5)
854     tof12(right,i,itdc) = tof12(right,i,itdc) + xhelp
855     tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
856     ENDIF
857 mocchiut 1.1 ENDDO
858 mocchiut 1.7
859 mocchiut 1.1 C----
860 mocchiut 1.7 DO I=1,2
861     if ((tdc(ch21a(i),hb21a(i)).lt.4095).and.
862     & (tof21(left,i,iadc).lt.3786)) THEN
863     xhelp = tw21(left,i)/(tof21(left,i,iadc)**0.5)
864     tof21(left,i,itdc) = tof21(left,i,itdc) + xhelp
865     tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
866     ENDIF
867    
868     if ((tdc(ch21b(i),hb21b(i)).lt.4095).and.
869     & (tof21(right,i,iadc).lt.3786)) THEN
870     xhelp = tw21(right,i)/(tof21(right,i,iadc)**0.5)
871     tof21(right,i,itdc) = tof21(right,i,itdc) + xhelp
872     tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
873     ENDIF
874     ENDDO
875    
876     DO I=1,2
877     if ((tdc(ch22a(i),hb22a(i)).lt.4095).and.
878     & (tof22(left,i,iadc).lt.3786)) THEN
879     xhelp = tw22(left,i)/(tof22(left,i,iadc)**0.5)
880     tof22(left,i,itdc) = tof22(left,i,itdc) + xhelp
881     tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
882     ENDIF
883    
884     if ((tdc(ch22b(i),hb22b(i)).lt.4095).and.
885     & (tof22(right,i,iadc).lt.3786)) THEN
886     xhelp = tw22(right,i)/(tof22(right,i,iadc)**0.5)
887     tof22(right,i,itdc) = tof22(right,i,itdc) + xhelp
888     tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
889     ENDIF
890 mocchiut 1.1 ENDDO
891 mocchiut 1.7
892 mocchiut 1.1 C----
893 mocchiut 1.7 DO I=1,3
894     if ((tdc(ch31a(i),hb31a(i)).lt.4095).and.
895     & (tof31(left,i,iadc).lt.3786)) THEN
896     xhelp = tw31(left,i)/(tof31(left,i,iadc)**0.5)
897     tof31(left,i,itdc) = tof31(left,i,itdc) + xhelp
898     tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
899     ENDIF
900    
901     if ((tdc(ch31b(i),hb31b(i)).lt.4095).and.
902     & (tof31(right,i,iadc).lt.3786)) THEN
903     xhelp = tw31(right,i)/(tof31(right,i,iadc)**0.5)
904     tof31(right,i,itdc) = tof31(right,i,itdc) + xhelp
905     tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
906     ENDIF
907     ENDDO
908    
909     DO I=1,3
910     if ((tdc(ch32a(i),hb32a(i)).lt.4095).and.
911     & (tof32(left,i,iadc).lt.3786)) THEN
912     xhelp = tw32(left,i)/(tof32(left,i,iadc)**0.5)
913     tof32(left,i,itdc) = tof32(left,i,itdc) + xhelp
914     tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
915     ENDIF
916    
917     if ((tdc(ch32b(i),hb32b(i)).lt.4095).and.
918     & (tof32(right,i,iadc).lt.3786)) THEN
919     xhelp = tw32(right,i)/(tof32(right,i,iadc)**0.5)
920     tof32(right,i,itdc) = tof32(right,i,itdc) + xhelp
921     tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
922     ENDIF
923     ENDDO
924    
925     C---------------------------------------------------------------
926     C--- calculate track position in paddle using timing difference
927     C--- now using the time-walk corrected TDC values
928     C---------------------------------------------------------------
929    
930     do i=1,3
931     xtofpos(i)=100.
932     ytofpos(i)=100.
933     enddo
934    
935     C-----------------------------S1 --------------------------------
936    
937     IF (tof11_i.GT.none_find) THEN
938     ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
939     + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
940     endif
941    
942     IF (tof12_i.GT.none_find) THEN
943     xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
944     + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
945     endif
946    
947    
948     C-----------------------------S2 --------------------------------
949    
950     IF (tof21_i.GT.none_find) THEN
951     xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
952     + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
953     endif
954    
955     IF (tof22_i.GT.none_find) THEN
956     ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
957     + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
958     endif
959    
960    
961     C-----------------------------S3 --------------------------------
962    
963     IF (tof31_i.GT.none_find) THEN
964     ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
965     + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
966     endif
967    
968     IF (tof32_i.GT.none_find) THEN
969     xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
970     + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
971     endif
972    
973    
974     c do i=1,3
975     c if (abs(xtofpos(i)).gt.100.) then
976     c xtofpos(i)=101.
977     c endif
978     c if (abs(ytofpos(i)).gt.100.) then
979     c ytofpos(i)=101.
980     c endif
981     c enddo
982    
983     C-- restrict TDC measurements to physical paddle dimensions +/- 10 cm
984     C-- this cut is now stronger than in the old versions
985 mocchiut 1.1
986 mocchiut 1.7 if (abs(xtofpos(1)).gt.31.) xtofpos(1)=101.
987     if (abs(xtofpos(2)).gt.19.) xtofpos(2)=101.
988     if (abs(xtofpos(3)).gt.19.) xtofpos(3)=101.
989    
990     if (abs(ytofpos(1)).gt.26.) ytofpos(1)=101.
991     if (abs(ytofpos(2)).gt.18.) ytofpos(2)=101.
992     if (abs(ytofpos(3)).gt.18.) ytofpos(3)=101.
993    
994    
995     C----------------------------------------------------------------------
996     C--------------------- zenith angle theta ---------------------------
997     C----------------------------------------------------------------------
998    
999     dx=0.
1000     dy=0.
1001     dr=0.
1002     theta13 = 0.
1003    
1004     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find))
1005     & dx = xtofpos(1) - xtofpos(3)
1006     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find))
1007     & dy = ytofpos(1) - ytofpos(3)
1008     dr = sqrt(dx*dx+dy*dy)
1009     theta13 = atan(dr/tofarm13)
1010 mocchiut 1.1
1011 mocchiut 1.7 C------------------------------------------------------------------
1012     c dx=0.
1013     c dy=0.
1014     c dr=0.
1015     c theta12 = 0.
1016     c
1017     c IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find))
1018     c & dx = xtofpos(1) - xtofpos(2)
1019     c IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find))
1020     c & dy = ytofpos(1) - ytofpos(2)
1021     c dr = sqrt(dx*dx+dy*dy)
1022     c theta12 = atan(dr/tofarm12)
1023     c
1024     c dx=0.
1025     c dy=0.
1026     c dr=0.
1027     c theta23 = 0.
1028     c
1029     c IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find))
1030     c & dx = xtofpos(2) - xtofpos(3)
1031     c IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find))
1032     c & dy = ytofpos(2) - ytofpos(3)
1033     c dr = sqrt(dx*dx+dy*dy)
1034     c theta23 = atan(dr/tofarm23)
1035     c
1036 mocchiut 1.1 C----------------------------------------------------------------------
1037     C------------------angle and ADC(x) correction
1038     C----------------------------------------------------------------------
1039     C-----------------------------S1 --------------------------------
1040     c middle y (or x) position of the upper and middle ToF-Paddle
1041     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
1042     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
1043 mocchiut 1.4 c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
1044 mocchiut 1.1 c DATA tof22_x/ -4.5,4.5/
1045     c DATA tof31_x/ -6.0,0.,6.0/
1046     c DATA tof32_y/ -5.0,0.0,5.0/
1047    
1048     yhelp=0.
1049     if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i)
1050     if (ytofpos(1).lt.100) yhelp=ytofpos(1)
1051    
1052     IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
1053    
1054     i = tof11_i
1055 mocchiut 1.6 if (tof11(left,i,iadc).lt.3786) then
1056     c if (adc(ch11a(i),hb11a(i)).lt.4095) then
1057 mocchiut 1.4 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
1058 mocchiut 1.6 xkorr = atten(left,11,i,yhelp)
1059     c write(40+i,*) yhelp,xkorr
1060 pam-de 1.8 xkorr=xkorr/hepratio
1061 mocchiut 1.1 adctof_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
1062     endif
1063    
1064 mocchiut 1.6 if (tof11(right,i,iadc).lt.3786) then
1065     c if (adc(ch11b(i),hb11b(i)).lt.4095) then
1066 mocchiut 1.4 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
1067 mocchiut 1.6 xkorr = atten(right,11,i,yhelp)
1068     c write(40+i,*) yhelp,xkorr
1069 pam-de 1.8 xkorr=xkorr/hepratio
1070 mocchiut 1.1 adctof_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
1071     endif
1072     ENDIF
1073    
1074     xhelp=0.
1075     if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i)
1076     if (xtofpos(1).lt.100) xhelp=xtofpos(1)
1077    
1078     IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
1079    
1080     i = tof12_i
1081 mocchiut 1.6 if (tof12(left,i,iadc).lt.3786) then
1082     c if (adc(ch12a(i),hb12a(i)).lt.4095) then
1083 mocchiut 1.4 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
1084 mocchiut 1.6 xkorr = atten(left,12,i,xhelp)
1085     c write(50+i,*) xhelp,xkorr
1086 pam-de 1.8 xkorr=xkorr/hepratio
1087 mocchiut 1.1 adctof_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
1088     endif
1089    
1090 mocchiut 1.6 if (tof12(right,i,iadc).lt.3786) then
1091     c if (adc(ch12b(i),hb12b(i)).lt.4095) then
1092 mocchiut 1.4 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
1093 mocchiut 1.6 xkorr = atten(right,12,i,xhelp)
1094     c write(50+i,*) xhelp,xkorr
1095 pam-de 1.8 xkorr=xkorr/hepratio
1096 mocchiut 1.1 adctof_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
1097     endif
1098     ENDIF
1099    
1100     C-----------------------------S2 --------------------------------
1101    
1102     xhelp=0.
1103     if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i)
1104     if (xtofpos(2).lt.100) xhelp=xtofpos(2)
1105    
1106     IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
1107    
1108     i = tof21_i
1109 mocchiut 1.6 if (tof21(left,i,iadc).lt.3786) then
1110     c if (adc(ch21a(i),hb21a(i)).lt.4095) then
1111 mocchiut 1.4 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
1112 mocchiut 1.6 xkorr = atten(left,21,i,xhelp)
1113     c write(60+i,*) xhelp,xkorr
1114 pam-de 1.8 xkorr=xkorr/hepratio
1115 mocchiut 1.1 adctof_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
1116     endif
1117    
1118 mocchiut 1.6 if (tof21(right,i,iadc).lt.3786) then
1119     c if (adc(ch21b(i),hb21b(i)).lt.4095) then
1120 mocchiut 1.4 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
1121 mocchiut 1.1 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
1122 mocchiut 1.6 xkorr = atten(right,21,i,xhelp)
1123     c write(60+i,*) xhelp,xkorr
1124 pam-de 1.8 xkorr=xkorr/hepratio
1125 mocchiut 1.1 adctof_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
1126     endif
1127     ENDIF
1128    
1129    
1130     yhelp=0.
1131     if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i)
1132     if (ytofpos(2).lt.100) yhelp=ytofpos(2)
1133    
1134     IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
1135    
1136     i = tof22_i
1137 mocchiut 1.6 if (tof22(left,i,iadc).lt.3786) then
1138     c if (adc(ch22a(i),hb22a(i)).lt.4095) then
1139 mocchiut 1.4 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
1140 mocchiut 1.6 xkorr = atten(left,22,i,yhelp)
1141     c write(70+i,*) yhelp,xkorr
1142 pam-de 1.8 xkorr=xkorr/hepratio
1143 mocchiut 1.1 adctof_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
1144     endif
1145    
1146 mocchiut 1.6 if (tof22(right,i,iadc).lt.3786) then
1147     c if (adc(ch22b(i),hb22b(i)).lt.4095) then
1148 mocchiut 1.4 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
1149 mocchiut 1.6 xkorr = atten(right,22,i,yhelp)
1150     c write(70+i,*) yhelp,xkorr
1151 pam-de 1.8 xkorr=xkorr/hepratio
1152 mocchiut 1.1 adctof_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
1153     endif
1154     ENDIF
1155    
1156     C-----------------------------S3 --------------------------------
1157    
1158     yhelp=0.
1159     if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i)
1160     if (ytofpos(3).lt.100) yhelp=ytofpos(3)
1161    
1162     IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
1163    
1164     i = tof31_i
1165 mocchiut 1.6 if (tof31(left,i,iadc).lt.3786) then
1166     c if (adc(ch31a(i),hb31a(i)).lt.4095) then
1167 mocchiut 1.4 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
1168 mocchiut 1.6 xkorr = atten(left,31,i,yhelp)
1169     c write(80+i,*) yhelp,xkorr
1170 pam-de 1.8 xkorr=xkorr/hepratio
1171 mocchiut 1.1 adctof_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1172     endif
1173    
1174 mocchiut 1.6 if (tof31(right,i,iadc).lt.3786) then
1175     c if (adc(ch31b(i),hb31b(i)).lt.4095) then
1176 mocchiut 1.4 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
1177 mocchiut 1.6 xkorr = atten(right,31,i,yhelp)
1178     c write(80+i,*) yhelp,xkorr
1179 pam-de 1.8 xkorr=xkorr/hepratio
1180 mocchiut 1.1 adctof_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1181     endif
1182     ENDIF
1183    
1184     xhelp=0.
1185     if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i)
1186     if (xtofpos(3).lt.100) xhelp=xtofpos(3)
1187    
1188     IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
1189    
1190     i = tof32_i
1191 mocchiut 1.6 if (tof32(left,i,iadc).lt.3786) then
1192     c if (adc(ch32a(i),hb32a(i)).lt.4095) then
1193 mocchiut 1.4 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
1194 mocchiut 1.6 xkorr = atten(left,32,i,xhelp)
1195     c write(90+i,*) xhelp,xkorr
1196 pam-de 1.8 xkorr=xkorr/hepratio
1197 mocchiut 1.1 adctof_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1198     endif
1199    
1200 mocchiut 1.6 if (tof32(right,i,iadc).lt.3786) then
1201     c if (adc(ch32b(i),hb32b(i)).lt.4095) then
1202 mocchiut 1.4 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
1203 mocchiut 1.6 xkorr = atten(right,32,i,xhelp)
1204     c write(90+i,*) xhelp,xkorr
1205 pam-de 1.8 xkorr=xkorr/hepratio
1206 mocchiut 1.1 adctof_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1207     endif
1208     ENDIF
1209    
1210 mocchiut 1.4 C--------------------------------------------------------------------
1211 mocchiut 1.1 C----------------------calculate Beta ------------------------------
1212 mocchiut 1.4 C--------------------------------------------------------------------
1213     C-------------------difference of sums -----------------------------
1214 mocchiut 1.1 C
1215     C DS = (t1+t2) - t3+t4)
1216     C DS = c1 + c2/beta*cos(theta)
1217     C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
1218     C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
1219     C since TDC resolution varies slightly c2 has to be calibrated
1220    
1221     C S11 - S31
1222 mocchiut 1.4
1223     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1224     & (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1225 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1226     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1227     ds = xhelp1-xhelp2
1228     ihelp=(tof11_i-1)*3+tof31_i
1229     c1 = k_S11S31(1,ihelp)
1230 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrA1
1231 mocchiut 1.1 c2 = k_S11S31(2,ihelp)
1232     betatof_a(1) = c2/(cos(theta13)*(ds-c1))
1233 mocchiut 1.2
1234     C------- ToF Mask - S11 - S31
1235    
1236     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1237     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1238     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1239     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1240    
1241     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1242     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1243     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1244     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1245    
1246     C-------
1247    
1248 mocchiut 1.1 ENDIF
1249    
1250     C S11 - S32
1251 mocchiut 1.4
1252     IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1253     & (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1254 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1255     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1256     ds = xhelp1-xhelp2
1257     ihelp=(tof11_i-1)*3+tof32_i
1258     c1 = k_S11S32(1,ihelp)
1259 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrA1
1260 mocchiut 1.1 c2 = k_S11S32(2,ihelp)
1261     betatof_a(2) = c2/(cos(theta13)*(ds-c1))
1262 mocchiut 1.2
1263     C------- ToF Mask - S11 - S32
1264    
1265     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1266     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1267     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1268     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1269    
1270     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1271     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1272     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1273     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1274    
1275     C-------
1276    
1277 mocchiut 1.1 ENDIF
1278 mocchiut 1.2
1279 mocchiut 1.1 C S12 - S31
1280 mocchiut 1.4
1281     IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1282     & (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1283 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1284     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1285     ds = xhelp1-xhelp2
1286     ihelp=(tof12_i-1)*3+tof31_i
1287     c1 = k_S12S31(1,ihelp)
1288 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrA1
1289 mocchiut 1.1 c2 = k_S12S31(2,ihelp)
1290     betatof_a(3) = c2/(cos(theta13)*(ds-c1))
1291 mocchiut 1.2
1292     C------- ToF Mask - S12 - S31
1293    
1294     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1295     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1296     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1297     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1298    
1299     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1300     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1301     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1302     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1303    
1304     C-------
1305    
1306 mocchiut 1.1 ENDIF
1307 mocchiut 1.2
1308 mocchiut 1.1 C S12 - S32
1309 mocchiut 1.4
1310     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1311     & (xtofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1312 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1313     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1314     ds = xhelp1-xhelp2
1315     ihelp=(tof12_i-1)*3+tof32_i
1316     c1 = k_S12S32(1,ihelp)
1317 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrA1
1318 mocchiut 1.1 c2 = k_S12S32(2,ihelp)
1319     betatof_a(4) = c2/(cos(theta13)*(ds-c1))
1320 mocchiut 1.2
1321     C------- ToF Mask - S12 - S32
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(ch32a(tof32_i),hb32a(tof32_i)) =
1329     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1330     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1331     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1332    
1333     C-------
1334    
1335 mocchiut 1.1 ENDIF
1336    
1337     C S21 - S31
1338 mocchiut 1.4
1339     IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1340     & (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1341 mocchiut 1.1 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1342     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1343     ds = xhelp1-xhelp2
1344     ihelp=(tof21_i-1)*3+tof31_i
1345     c1 = k_S21S31(1,ihelp)
1346 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrB1
1347 mocchiut 1.1 c2 = k_S21S31(2,ihelp)
1348 mocchiut 1.4 betatof_a(5) = c2/(cos(theta13)*(ds-c1))
1349 mocchiut 1.2
1350     C------- ToF Mask - S21 - S31
1351    
1352     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1353     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1354     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1355     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1356    
1357     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1358     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1359     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1360     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1361    
1362     C-------
1363    
1364 mocchiut 1.1 ENDIF
1365    
1366     C S21 - S32
1367 mocchiut 1.4
1368     IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1369     & (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1370 mocchiut 1.1 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1371     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1372     ds = xhelp1-xhelp2
1373     ihelp=(tof21_i-1)*3+tof32_i
1374     c1 = k_S21S32(1,ihelp)
1375 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrB1
1376 mocchiut 1.1 c2 = k_S21S32(2,ihelp)
1377 mocchiut 1.4 betatof_a(6) = c2/(cos(theta13)*(ds-c1))
1378 mocchiut 1.2
1379     C------- ToF Mask - S21 - S32
1380    
1381     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1382     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1383     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1384     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1385    
1386     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1387     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1388     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1389     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1390    
1391     C-------
1392    
1393 mocchiut 1.1 ENDIF
1394    
1395     C S22 - S31
1396 mocchiut 1.4
1397     IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1398     & (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1399 mocchiut 1.1 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1400     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1401     ds = xhelp1-xhelp2
1402     ihelp=(tof22_i-1)*3+tof31_i
1403     c1 = k_S22S31(1,ihelp)
1404 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrB1
1405 mocchiut 1.1 c2 = k_S22S31(2,ihelp)
1406     betatof_a(7) = c2/(cos(theta13)*(ds-c1))
1407 mocchiut 1.2
1408     C------- ToF Mask - S22 - S31
1409    
1410     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1411     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1412     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1413     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1414    
1415     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1416     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1417     tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1418     $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1419    
1420     C-------
1421    
1422 mocchiut 1.1 ENDIF
1423    
1424     C S22 - S32
1425 mocchiut 1.4
1426     IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1427     & (ytofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1428 mocchiut 1.1 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1429     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1430     ds = xhelp1-xhelp2
1431     ihelp=(tof22_i-1)*3+tof32_i
1432     c1 = k_S22S32(1,ihelp)
1433 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrB1
1434 mocchiut 1.1 c2 = k_S22S32(2,ihelp)
1435     betatof_a(8) = c2/(cos(theta13)*(ds-c1))
1436 mocchiut 1.2
1437     C------- ToF Mask - S22 - S32
1438    
1439     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1440     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1441     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1442     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1443    
1444     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1445     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1446     tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1447     $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1448    
1449     C-------
1450    
1451 mocchiut 1.1 ENDIF
1452    
1453     C S11 - S21
1454 mocchiut 1.4
1455     IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1456     & (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1457 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1458     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1459     ds = xhelp1-xhelp2
1460     ihelp=(tof11_i-1)*2+tof21_i
1461     c1 = k_S11S21(1,ihelp)
1462 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrC1
1463 mocchiut 1.1 c2 = k_S11S21(2,ihelp)
1464     betatof_a(9) = c2/(cos(theta13)*(ds-c1))
1465 mocchiut 1.2
1466     C------- ToF Mask - S11 - S21
1467    
1468     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1469     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1470     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1471     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1472    
1473     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1474     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1475     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1476     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1477    
1478     C-------
1479    
1480 mocchiut 1.1 ENDIF
1481    
1482     C S11 - S22
1483 mocchiut 1.4
1484     IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1485     & (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1486 mocchiut 1.1 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1487     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1488     ds = xhelp1-xhelp2
1489     ihelp=(tof11_i-1)*2+tof22_i
1490     c1 = k_S11S22(1,ihelp)
1491 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrC1
1492 mocchiut 1.1 c2 = k_S11S22(2,ihelp)
1493     betatof_a(10) = c2/(cos(theta13)*(ds-c1))
1494 mocchiut 1.2
1495     C------- ToF Mask - S11 - S22
1496    
1497     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1498     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1499     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1500     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1501    
1502     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1503     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1504     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1505     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1506    
1507     C-------
1508    
1509 mocchiut 1.1 ENDIF
1510    
1511     C S12 - S21
1512 mocchiut 1.4
1513     IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1514     & (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1515 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1516     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1517     ds = xhelp1-xhelp2
1518     ihelp=(tof12_i-1)*2+tof21_i
1519     c1 = k_S12S21(1,ihelp)
1520 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrC1
1521 mocchiut 1.1 c2 = k_S12S21(2,ihelp)
1522     betatof_a(11) = c2/(cos(theta13)*(ds-c1))
1523 mocchiut 1.2
1524     C------- ToF Mask - S12 - S21
1525    
1526     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1527     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1528     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1529     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1530    
1531     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1532     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1533     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1534     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1535    
1536     C-------
1537    
1538 mocchiut 1.1 ENDIF
1539    
1540     C S12 - S22
1541 mocchiut 1.4
1542     IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1543     & (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1544 mocchiut 1.1 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1545     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1546     ds = xhelp1-xhelp2
1547     ihelp=(tof12_i-1)*2+tof22_i
1548     c1 = k_S12S22(1,ihelp)
1549 mocchiut 1.7 if (iz.gt.2) c1 = c1 + k1corrC1
1550 mocchiut 1.1 c2 = k_S12S22(2,ihelp)
1551     betatof_a(12) = c2/(cos(theta13)*(ds-c1))
1552 mocchiut 1.2
1553     C------- ToF Mask - S12 - S22
1554    
1555     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1556     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1557     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1558     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1559    
1560     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1561     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1562     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1563     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1564    
1565     C-------
1566    
1567 mocchiut 1.1 ENDIF
1568 mocchiut 1.2
1569     C---------------------------------------------------------
1570 mocchiut 1.7 C
1571     C icount=0
1572     C sw=0.
1573     C sxw=0.
1574     C beta_mean=100.
1575     C
1576     C do i=1,12
1577     C if ((betatof_a(i).gt.-1.5).and.(betatof_a(i).lt.1.5)) then
1578     C icount= icount+1
1579     C if (i.le.4) w_i=1./(0.13**2.)
1580     C if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1581     C if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1582     C sxw=sxw + betatof_a(i)*w_i
1583     C sw =sw + w_i
1584     C endif
1585     C enddo
1586     C
1587     C if (icount.gt.0) beta_mean=sxw/sw
1588     C betatof_a(13) = beta_mean
1589     C
1590 pam-de 1.8
1591 mocchiut 1.7 C-------- New mean beta calculation -----------------------
1592 mocchiut 1.1
1593 mocchiut 1.7 do i=1,12
1594     btemp(i) = betatof_a(i)
1595     enddo
1596 mocchiut 1.1
1597 pam-de 1.8 betatof_a(13)=newbeta(1,btemp,hitvec,10.,10.,20.)
1598 mocchiut 1.1
1599 mocchiut 1.7 C--------------------------------------------------------------
1600     C write(*,*) betatof_a
1601 mocchiut 1.4 c write(*,*) xtofpos
1602     c write(*,*) ytofpos
1603 mocchiut 1.6 c write(*,*)'tofl2com beta', betatof_a
1604 mocchiut 1.4 C write(*,*) adcflagtof
1605 mocchiut 1.6 c write(*,*) 'tofl2com'
1606     c write(*,*) xtofpos
1607     c write(*,*) ytofpos
1608     c write(*,*) xtr_tof
1609     c write(*,*) ytr_tof
1610    
1611 mocchiut 1.1 100 continue
1612    
1613     C
1614     RETURN
1615     END
1616 mocchiut 1.4
1617 mocchiut 1.6
1618     C------------------------------------------------------------------
1619     C------------------------------------------------------------------
1620    
1621     function atten(is,ilay,ipad,x)
1622     include 'input_tof.txt'
1623     real atten
1624     real x
1625     real xmin,xmax
1626     integer ilay,ipad
1627    
1628     * S11 8 paddles 33.0 x 5.1 cm
1629     * S12 6 paddles 40.8 x 5.5 cm
1630     * S21 2 paddles 18.0 x 7.5 cm
1631     * S22 2 paddles 15.0 x 9.0 cm
1632     * S31 3 paddles 15.0 x 6.0 cm
1633     * S32 3 paddles 18.0 x 5.0 cm
1634    
1635    
1636     c if (ilay.eq.11) write(*,*) 'start ',ipad,is,adcx11(is,ipad,1),
1637     c & adcx11(is,ipad,2),adcx11(is,ipad,3),adcx11(is,ipad,4)
1638     c if (ilay.eq.12) write(*,*) 'start ',ipad,is,adcx12(is,ipad,1),
1639     c & adcx12(is,ipad,2),adcx12(is,ipad,3),adcx12(is,ipad,4)
1640    
1641    
1642     if (ilay.eq.11) xmin=-33.0/2.
1643     if (ilay.eq.11) xmax= 33.0/2.
1644     if (ilay.eq.12) xmin=-40.8/2.
1645     if (ilay.eq.12) xmax= 40.8/2.
1646    
1647     if (ilay.eq.21) xmin=-18.0/2.
1648     if (ilay.eq.21) xmax= 18.0/2.
1649     if (ilay.eq.22) xmin=-15.0/2.
1650     if (ilay.eq.22) xmax= 15.0/2.
1651    
1652     if (ilay.eq.31) xmin=-15.0/2.
1653     if (ilay.eq.31) xmax= 15.0/2.
1654     if (ilay.eq.32) xmin=-18.0/2.
1655     if (ilay.eq.32) xmax= 18.0/2.
1656    
1657     if (x .lt. xmin) x=xmin
1658     if (x .gt. xmax) x=xmax
1659    
1660    
1661     if (ilay.eq.11) atten=
1662     & adcx11(is,ipad,1)*exp(x*adcx11(is,ipad,2))
1663     & + adcx11(is,ipad,3)*exp(x*adcx11(is,ipad,4))
1664    
1665     if (ilay.eq.12) atten=
1666     & adcx12(is,ipad,1)*exp(x*adcx12(is,ipad,2))
1667     & + adcx12(is,ipad,3)*exp(x*adcx12(is,ipad,4))
1668    
1669     if (ilay.eq.21) atten=
1670     & adcx21(is,ipad,1)*exp(x*adcx21(is,ipad,2))
1671     & + adcx21(is,ipad,3)*exp(x*adcx21(is,ipad,4))
1672    
1673     if (ilay.eq.22) atten=
1674     & adcx22(is,ipad,1)*exp(x*adcx22(is,ipad,2))
1675     & + adcx22(is,ipad,3)*exp(x*adcx22(is,ipad,4))
1676    
1677     if (ilay.eq.31) atten=
1678     & adcx31(is,ipad,1)*exp(x*adcx31(is,ipad,2))
1679     & + adcx31(is,ipad,3)*exp(x*adcx31(is,ipad,4))
1680    
1681     if (ilay.eq.32) atten=
1682     & adcx32(is,ipad,1)*exp(x*adcx32(is,ipad,2))
1683     & + adcx32(is,ipad,3)*exp(x*adcx32(is,ipad,4))
1684    
1685     if (atten.gt.10000) atten=10000.
1686    
1687     end
1688    
1689     C------------------------------------------------------------------
1690     C------------------------------------------------------------------
1691    
1692     function pc_adc(ix)
1693     include 'input_tof.txt'
1694     real pc_adc
1695     integer ix
1696    
1697     pc_adc=28.0407 + 0.628929*ix
1698     & - 5.80901e-05*ix*ix + 3.14092e-08*ix*ix*ix
1699     c write(*,*) ix,pc_adc
1700     end
1701    
1702     C------------------------------------------------------------------
1703 mocchiut 1.7 C------------------------------------------------------------------
1704    
1705     function check_charge(theta,hitvec)
1706    
1707     include 'input_tof.txt'
1708     include 'tofcomm.txt'
1709    
1710     real check_charge
1711     integer hitvec(6)
1712     REAL CHARGE, theta
1713    
1714     C upper and lower limits for the helium selection
1715     REAL A_l(24),A_h(24)
1716     DATA A_l /200,190,300,210,220,200,210,60,60,120,220,
1717     & 120,160,50,300,200,120,250,350,300,350,250,280,300/
1718     DATA A_h /550,490,800,600,650,600,600,260,200,380,
1719     & 620,380,550,200,850,560,400,750,900,800,880,800,750,800/
1720    
1721     C The k1 constants for the beta calculation, only for S1-S3
1722     C k2 constant is taken to be the standard 2D/c
1723     REAL k1(84)
1724     DATA k1 /50,59.3296,28.4328,-26.0818,5.91253,-19.588,
1725     & -9.26316,24.7544,2.32465,-50.5058,-15.3195,-39.1443,
1726     & -91.2546,-58.6243,-84.5641,-63.1516,-32.2091,-58.3358,
1727     & 13.8084,45.5322,33.2416,-11.5313,51.3271,75,-14.1141,
1728     & 42.8466,15.1794,-63.6672,-6.07739,-32.164,-41.771,10.5274,
1729     & -9.46096,-81.7404,-28.783,-52.7167,-127.394,-69.6166,
1730     & -93.4655,-98.9543,-42.863,-67.8244,-19.3238,31.1221,8.7319,
1731     & -43.1627,5.55573,-14.4078,-83.4466,-47.4647,-77.8379,
1732     & -108.222,-75.986,-101.297,-96.0205,-63.1881,-90.1372,
1733     & -22.7347,8.31409,-19.6912,-7.49008,23.6979,-1.66677,
1734     & 1.81556,34.4668,6.23693,-100,-59.5861,-90.9159,-141.639,
1735     & -89.2521,-112.881,-130.199,-77.0357,-98.4632,-60.2086,
1736     & -4.82097,-29.3705,-43.6469,10.5884,-9.31304,-35.3329,
1737     & 25.2514,25.6/
1738    
1739    
1740    
1741     REAL zin(6)
1742     DATA zin /53.74, 53.04, 23.94, 23.44, -23.49, -24.34/
1743    
1744     REAL c1,c2,xhelp,xhelp1,xhelp2,ds,dist,F
1745     REAL sw,sxw,beta_mean_tof,w_i
1746     INTEGER ihelp
1747     INTEGER ipmt(4)
1748     REAL time(4),beta1(4)
1749    
1750     REAL adca(48), tdca(48)
1751    
1752     REAL a1,a2
1753     INTEGER jj
1754    
1755     C-----------------------------------------------------------
1756     C--- get data
1757     C-----------------------------------------------------------
1758    
1759     do j=1,8
1760     ih = 1 + 0 +((j-1)*2)
1761     adca(ih) = adc(ch11a(j),hb11a(j))
1762     adca(ih+1) = adc(ch11b(j),hb11b(j))
1763     tdca(ih) = tdc(ch11a(j),hb11a(j))
1764     tdca(ih+1) = tdc(ch11b(j),hb11b(j))
1765     enddo
1766    
1767     do j=1,6
1768     ih = 1 + 16+((j-1)*2)
1769     adca(ih) = adc(ch12a(j),hb12a(j))
1770     adca(ih+1) = adc(ch12b(j),hb12b(j))
1771     tdca(ih) = tdc(ch12a(j),hb12a(j))
1772     tdca(ih+1) = tdc(ch12b(j),hb12b(j))
1773     enddo
1774    
1775     do j=1,2
1776     ih = 1 + 28+((j-1)*2)
1777     adca(ih) = adc(ch21a(j),hb21a(j))
1778     adca(ih+1) = adc(ch21b(j),hb21b(j))
1779     tdca(ih) = tdc(ch21a(j),hb21a(j))
1780     tdca(ih+1) = tdc(ch21b(j),hb21b(j))
1781     enddo
1782    
1783     do j=1,2
1784     ih = 1 + 32+((j-1)*2)
1785     adca(ih) = adc(ch22a(j),hb22a(j))
1786     adca(ih+1) = adc(ch22b(j),hb22b(j))
1787     tdca(ih) = tdc(ch22a(j),hb22a(j))
1788     tdca(ih+1) = tdc(ch22b(j),hb22b(j))
1789     enddo
1790    
1791     do j=1,3
1792     ih = 1 + 36+((j-1)*2)
1793     adca(ih) = adc(ch31a(j),hb31a(j))
1794     adca(ih+1) = adc(ch31b(j),hb31b(j))
1795     tdca(ih) = tdc(ch31a(j),hb31a(j))
1796     tdca(ih+1) = tdc(ch31b(j),hb31b(j))
1797     enddo
1798    
1799     do j=1,3
1800     ih = 1 + 42+((j-1)*2)
1801     adca(ih) = adc(ch32a(j),hb32a(j))
1802     adca(ih+1) = adc(ch32b(j),hb32b(j))
1803     tdca(ih) = tdc(ch32a(j),hb32a(j))
1804     tdca(ih+1) = tdc(ch32b(j),hb32b(j))
1805     enddo
1806    
1807    
1808     c write(*,*) adca
1809     c write(*,*) tdca
1810    
1811    
1812     C============ calculate beta and select charge > Z=1 ===============
1813    
1814     ICHARGE=1
1815    
1816     C find hitted paddle by looking for ADC values on both sides
1817     C since we looking for Z>1 this gives decent results
1818    
1819     tof11_i = hitvec(1)-1
1820     tof12_i = hitvec(2)-1
1821     tof21_i = hitvec(3)-1
1822     tof22_i = hitvec(4)-1
1823     tof31_i = hitvec(5)-1
1824     tof32_i = hitvec(6)-1
1825    
1826     c write(*,*) ' in charge check'
1827     c write(*,*) theta,tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
1828    
1829     C----------------------------------------------------------------
1830    
1831     beta_help=100.
1832     beta_mean_tof=100.
1833    
1834     do jj=1,4
1835     beta1(jj) = 100.
1836     enddo
1837    
1838     C----------------------------------------------------------------
1839     C--------- S1 - S3 ---------------------------------------------
1840     C----------------------------------------------------------------
1841    
1842     C--------- S11 - S31 -------------------------------------------
1843    
1844     if ((tof11_i.gt.-1).and.(tof31_i.gt.-1)) then
1845    
1846     dist = zin(1) - zin(5)
1847     c2 = (2.*0.01*dist)/(3.E08*50.E-12)
1848     F = 1./cos(theta)
1849    
1850     ipmt(1) = (tof11_i)*2+1
1851     ipmt(2) = (tof11_i)*2+2
1852     ipmt(3) = 36+(tof31_i)*2+1
1853     ipmt(4) = 36+(tof31_i)*2+2
1854    
1855     c write(*,*) ipmt
1856    
1857     do jj=1,4
1858     time(jj) = tdca(ipmt(jj))
1859     enddo
1860    
1861     c write(*,*) time
1862    
1863     if ((time(1).lt.4095).and.(time(2).lt.4095).and.
1864     & (time(3).lt.4095).and.(time(4).lt.4095)) then
1865     xhelp1 = time(1) + time(2)
1866     xhelp2 = time(3) + time(4)
1867     ds = xhelp1-xhelp2
1868     ihelp=0+(tof11_i)*3+tof31_i
1869     c1 = k1(ihelp+1)
1870     beta1(1) = c2*F/(ds-c1);
1871     endif
1872     c write(*,*) beta1(1)
1873     endif ! tof_....
1874    
1875    
1876     C--------- S11 - S32 -------------------------------------------
1877    
1878     if ((tof11_i.gt.-1).and.(tof32_i.gt.-1)) then
1879    
1880     dist = zin(1) - zin(6)
1881     c2 = (2.*0.01*dist)/(3.E08*50.E-12)
1882     F = 1./cos(theta)
1883    
1884     ipmt(1) = (tof11_i)*2+1
1885     ipmt(2) = (tof11_i)*2+2
1886     ipmt(3) = 42+(tof32_i)*2+1
1887     ipmt(4) = 42+(tof32_i)*2+2
1888    
1889     do jj=1,4
1890     time(jj) = tdca(ipmt(jj))
1891     enddo
1892    
1893     if ((time(1).lt.4095).and.(time(2).lt.4095).and.
1894     & (time(3).lt.4095).and.(time(4).lt.4095)) then
1895     xhelp1 = time(1) + time(2)
1896     xhelp2 = time(3) + time(4)
1897     ds = xhelp1-xhelp2
1898     ihelp=24+(tof11_i)*3+tof32_i
1899     c1 = k1(ihelp+1)
1900     beta1(2) = c2*F/(ds-c1);
1901     endif
1902     endif ! tof_....
1903    
1904    
1905     C--------- S12 - S31 -------------------------------------------
1906    
1907     if ((tof12_i.gt.-1).and.(tof31_i.gt.-1)) then
1908    
1909     dist = zin(2) - zin(5)
1910     c2 = (2.*0.01*dist)/(3.E08*50.E-12)
1911     F = 1./cos(theta)
1912    
1913     ipmt(1) = 16+(tof12_i)*2+1
1914     ipmt(2) = 16+(tof12_i)*2+2
1915     ipmt(3) = 36+(tof31_i)*2+1
1916     ipmt(4) = 36+(tof31_i)*2+2
1917    
1918     do jj=1,4
1919     time(jj) = tdca(ipmt(jj))
1920     enddo
1921    
1922     if ((time(1).lt.4095).and.(time(2).lt.4095).and.
1923     & (time(3).lt.4095).and.(time(4).lt.4095)) then
1924     xhelp1 = time(1) + time(2)
1925     xhelp2 = time(3) + time(4)
1926     ds = xhelp1-xhelp2
1927     ihelp=48+(tof12_i)*3+tof31_i
1928     c1 = k1(ihelp+1)
1929     beta1(3) = c2*F/(ds-c1);
1930     endif
1931     endif ! tof_....
1932    
1933    
1934     C--------- S12 - S32 -------------------------------------------
1935    
1936     if ((tof12_i.gt.-1).and.(tof32_i.gt.-1)) then
1937    
1938     dist = zin(2) - zin(6)
1939     c2 = (2.*0.01*dist)/(3.E08*50.E-12)
1940     F = 1./cos(theta)
1941    
1942     ipmt(1) = 16+(tof12_i)*2+1
1943     ipmt(2) = 16+(tof12_i)*2+2
1944     ipmt(3) = 42+(tof32_i)*2+1
1945     ipmt(4) = 42+(tof32_i)*2+2
1946    
1947     do jj=1,4
1948     time(jj) = tdca(ipmt(jj))
1949     enddo
1950    
1951     if ((time(1).lt.4095).and.(time(2).lt.4095).and.
1952     & (time(3).lt.4095).and.(time(4).lt.4095)) then
1953     xhelp1 = time(1) + time(2)
1954     xhelp2 = time(3) + time(4)
1955     ds = xhelp1-xhelp2
1956     ihelp=56+(tof12_i)*3+tof32_i
1957     c1 = k1(ihelp+1)
1958     beta1(4) = c2*F/(ds-c1);
1959     endif
1960    
1961     endif ! tof_....
1962    
1963     c write(*,*) beta1
1964    
1965     C---- calculate beta mean, only downward going particles are interesting ----
1966    
1967     sw=0.
1968     sxw=0.
1969     beta_mean_tof=100.
1970    
1971     do jj=1,4
1972     if ((beta1(jj).gt.0.1).and.(beta1(jj).lt.2.0)) then
1973     w_i=1./(0.13*0.13)
1974     sxw=sxw + beta1(jj)*w_i
1975     sw =sw + w_i ;
1976     endif
1977     enddo
1978    
1979     if (sw.gt.0) beta_mean_tof=sxw/sw;
1980    
1981     c write(*,*) 'beta_mean_tof ',beta_mean_tof
1982    
1983     beta_help = beta_mean_tof ! pow(beta_mean_tof,1.0) gave best results
1984    
1985     CCCCC endif ! if tof11_i > -1 && ...... beta calculation
1986    
1987     C----------------------- Select charge --------------------------
1988    
1989     charge=0
1990    
1991     if ((beta_mean_tof.gt.0.2).and.(beta_mean_tof.lt.2.0)) then
1992    
1993     icount1=0
1994     icount2=0
1995     icount3=0
1996    
1997     do jj=0,23
1998     a1 = adca(2*jj+1)
1999     a2 = adca(2*jj+2)
2000     if ((a1.lt.4095).and.(a2.lt.4095)) then
2001     a1 = adca(2*jj+1)*cos(theta)
2002     a2 = adca(2*jj+2)*cos(theta)
2003     xhelp = 100000.
2004     xhelp1 = 100000.
2005     xhelp = sqrt(a1*a2) ! geometric mean
2006     xhelp1 = beta_help*xhelp
2007     C if geometric mean multiplied by beta_help is inside/outside helium
2008     C limits, increase counter
2009     if (xhelp1.lt.A_l(jj+1)) icount1=icount1+1
2010     if ((xhelp1.gt.A_l(jj+1)).and.(xhelp1.lt.A_h(jj+1)))
2011     & icount2=icount2+1
2012     if (xhelp1.gt.A_h(jj+1)) icount3=icount3+1
2013     endif
2014     enddo
2015    
2016    
2017     C if more than three paddles see the same...
2018    
2019     if (icount1 .gt. 3) charge=1
2020     if (icount2 .gt. 3) charge=2
2021     if (icount3 .gt. 3) charge=3
2022    
2023     endif ! 0.2<beta<2.0
2024    
2025     C no beta found? Sum up geometric means of paddles and derive the mean...
2026    
2027     if (beta_mean_tof.eq.100.) then
2028    
2029     xhelp = 0.
2030     icount = 0
2031    
2032     if (tof11_i.gt.-1) then
2033     jj=tof11_i
2034     a1 = adca(0+2*jj+1)
2035     a2 = adca(0+2*jj+2)
2036     if ((a1.lt.4095).and.(a2.lt.4095)) then
2037     a1 = a1*cos(theta)
2038     a2 = a2*cos(theta)
2039     xhelp = xhelp + sqrt(a1*a2)
2040     icount=icount+1
2041     endif
2042     endif
2043    
2044     if (tof12_i.gt.-1) then
2045     jj=tof12_i
2046     a1 = adca(16+2*jj+1)
2047     a2 = adca(16+2*jj+2)
2048     if ((a1.lt.4095).and.(a2.lt.4095)) then
2049     a1 = a1*cos(theta)
2050     a2 = a2*cos(theta)
2051     xhelp = xhelp + sqrt(a1*a2)
2052     icount=icount+1
2053     endif
2054     endif
2055    
2056     if (tof21_i.gt.-1) then
2057     jj=tof21_i
2058     a1 = adca(28+2*jj+1)
2059     a2 = adca(28+2*jj+2)
2060     if ((a1.lt.4095).and.(a2.lt.4095)) then
2061     a1 = a1*cos(theta)
2062     a2 = a2*cos(theta)
2063     xhelp = xhelp + sqrt(a1*a2)
2064     icount=icount+1
2065     endif
2066     endif
2067    
2068     if (tof22_i.gt.-1) then
2069     jj=tof22_i
2070     a1 = adca(32+2*jj+1)
2071     a2 = adca(32+2*jj+2)
2072     if ((a1.lt.4095).and.(a2.lt.4095)) then
2073     a1 = a1*cos(theta)
2074     a2 = a2*cos(theta)
2075     xhelp = xhelp + sqrt(a1*a2)
2076     icount=icount+1
2077     endif
2078     endif
2079    
2080     if (tof31_i.gt.-1) then
2081     jj=tof31_i
2082     a1 = adca(36+2*jj+1)
2083     a2 = adca(36+2*jj+2)
2084     if ((a1.lt.4095).and.(a2.lt.4095)) then
2085     a1 = a1*cos(theta)
2086     a2 = a2*cos(theta)
2087     xhelp = xhelp + sqrt(a1*a2)
2088     icount=icount+1
2089     endif
2090     endif
2091    
2092     if (tof32_i.gt.-1) then
2093     jj=tof32_i
2094     a1 = adca(42+2*jj+1)
2095     a2 = adca(42+2*jj+2)
2096     if ((a1.lt.4095).and.(a2.lt.4095)) then
2097     a1 = a1*cos(theta)
2098     a2 = a2*cos(theta)
2099     xhelp = xhelp + sqrt(a1*a2)
2100     icount=icount+1
2101     endif
2102     endif
2103    
2104    
2105     if (icount.gt.0) xhelp=xhelp/icount
2106     if ((icount.gt.2).and.(xhelp.gt.1500.)) charge=3
2107    
2108     endif ! beta_mean_tof.eq.100.
2109    
2110     c write(*,*) 'in function charge: ',charge
2111     check_charge = charge
2112    
2113    
2114     END
2115    
2116     C****************************************************************************
2117     C****************************************************************************
2118     C****************************************************************************
2119    
2120 pam-de 1.8 function newbeta(iflag,b,hitvec,resmax,qualitycut,chi2cut)
2121 mocchiut 1.7
2122     include 'input_tof.txt'
2123     include 'output_tof.txt'
2124     include 'tofcomm.txt'
2125    
2126     REAL newbeta
2127     REAL resmax,qualitycut,chi2cut
2128     REAL w_i(12),w_il(6),quality,res,betachi,beta_mean_inv
2129     REAL sw,sxw,b(12),beta_mean,chi2,xhelp
2130 pam-de 1.8 REAL tdcfl(4,12)
2131 mocchiut 1.7
2132 pam-de 1.8 INTEGER iflag,icount,hitvec(6)
2133 mocchiut 1.7
2134     INTEGER itop(12),ibot(12)
2135     DATA itop /1,1,2,2,3,3,4,4,1,1,2,2/
2136     DATA ibot /5,6,5,6,5,6,5,6,3,4,3,4/
2137    
2138     C====================================================================
2139    
2140     tof11_i = hitvec(1)
2141     tof12_i = hitvec(2)
2142     tof21_i = hitvec(3)
2143     tof22_i = hitvec(4)
2144     tof31_i = hitvec(5)
2145     tof32_i = hitvec(6)
2146    
2147 pam-de 1.8 if (iflag.eq.1) then ! call from tofl2com
2148     do i=1,4
2149     do j=1,12
2150     tdcfl(i,j) = tdcflagtof(i,j)
2151     enddo
2152     enddo
2153     endif
2154    
2155     if (iflag.eq.2) then ! call from toftrk
2156     do i=1,4
2157     do j=1,12
2158     tdcfl(i,j) = tdcflag(i,j)
2159     enddo
2160     enddo
2161     endif
2162    
2163 mocchiut 1.7
2164     C--- Find out ToF layers with artificial TDC values -------------
2165    
2166     do jj=1,6
2167     w_il(jj) = 1000.
2168     enddo
2169    
2170    
2171     if (tof11_i.gt.0) then
2172     if ((tofmask(ch11a(tof11_i),hb11a(tof11_i)).gt.0).or.
2173     & (tofmask(ch11b(tof11_i),hb11b(tof11_i)).gt.0)) then
2174     w_il(1)=0
2175 pam-de 1.8 i1=tdcfl(ch11a(tof11_i),hb11a(tof11_i))
2176     i2=tdcfl(ch11b(tof11_i),hb11b(tof11_i))
2177 mocchiut 1.7 if ((i1.eq.1).or.(i2.eq.1)) w_il(1) = 1 ! tdcflag
2178     endif
2179     endif
2180    
2181     if (tof12_i.gt.0) then
2182     if ((tofmask(ch12a(tof12_i),hb12a(tof12_i)).gt.0).or.
2183     & (tofmask(ch12b(tof12_i),hb12b(tof12_i)).gt.0)) then
2184     w_il(2)=0
2185 pam-de 1.8 i1=tdcfl(ch12a(tof12_i),hb12a(tof12_i))
2186     i2=tdcfl(ch12b(tof12_i),hb12b(tof12_i))
2187 mocchiut 1.7 if ((i1.eq.1).or.(i2.eq.1)) w_il(2) = 1 ! tdcflag
2188     endif
2189     endif
2190    
2191     if (tof21_i.gt.0) then
2192     if ((tofmask(ch21a(tof21_i),hb21a(tof21_i)).gt.0).or.
2193     & (tofmask(ch21b(tof21_i),hb21b(tof21_i)).gt.0)) then
2194     w_il(3)=0
2195 pam-de 1.8 i1=tdcfl(ch21a(tof21_i),hb21a(tof21_i))
2196     i2=tdcfl(ch21b(tof21_i),hb21b(tof21_i))
2197 mocchiut 1.7 if ((i1.eq.1).or.(i2.eq.1)) w_il(3) = 1 ! tdcflag
2198     endif
2199     endif
2200    
2201     if (tof22_i.gt.0) then
2202     if ((tofmask(ch22a(tof22_i),hb22a(tof22_i)).gt.0).or.
2203     & (tofmask(ch22b(tof22_i),hb22b(tof22_i)).gt.0)) then
2204     w_il(4)=0
2205 pam-de 1.8 i1=tdcfl(ch22a(tof22_i),hb22a(tof22_i))
2206     i2=tdcfl(ch22b(tof22_i),hb22b(tof22_i))
2207 mocchiut 1.7 if ((i1.eq.1).or.(i2.eq.1)) w_il(4) = 1 ! tdcflag
2208     endif
2209     endif
2210    
2211     if (tof31_i.gt.0) then
2212     if ((tofmask(ch31a(tof31_i),hb11a(tof31_i)).gt.0).or.
2213     & (tofmask(ch31b(tof31_i),hb31b(tof31_i)).gt.0)) then
2214     w_il(5)=0
2215 pam-de 1.8 i1=tdcfl(ch31a(tof31_i),hb31a(tof31_i))
2216     i2=tdcfl(ch31b(tof31_i),hb31b(tof31_i))
2217 mocchiut 1.7 if ((i1.eq.1).or.(i2.eq.1)) w_il(5) = 1 ! tdcflag
2218     endif
2219     endif
2220    
2221     if (tof32_i.gt.0) then
2222     if ((tofmask(ch32a(tof32_i),hb32a(tof32_i)).gt.0).or.
2223     & (tofmask(ch32b(tof32_i),hb32b(tof32_i)).gt.0)) then
2224     w_il(6)=0
2225 pam-de 1.8 i1=tdcfl(ch32a(tof32_i),hb32a(tof32_i))
2226     i2=tdcfl(ch32b(tof32_i),hb32b(tof32_i))
2227 mocchiut 1.7 if ((i1.eq.1).or.(i2.eq.1)) w_il(6) = 1 ! tdcflag
2228     endif
2229     endif
2230    
2231     C------------------------------------------------------------------------
2232     C--- Set weights for the 12 measurements using information for top and bottom:
2233     C--- if no measurements: weight = set to very high value=> not used
2234     C--- top or bottom artificial: weight*sqrt(2)
2235     C--- top and bottom artificial: weight*sqrt(2)*sqrt(2)
2236    
2237     DO jj=1,12
2238     if (jj.le.4) xhelp = 0.11 ! S1-S3
2239     if ((jj.gt.4).and.(jj.le.8)) xhelp = 0.18 ! S2-S3
2240     if (jj.gt.8) xhelp = 0.28 ! S1-S2
2241     if ((w_il(itop(jj)).eq.1000.).and.(w_il(ibot(jj)).eq.1000.))
2242     & xhelp = 1.E09
2243     if ((w_il(itop(jj)).eq.1).or.(w_il(ibot(jj)).eq.1.))
2244     & xhelp = xhelp*1.414
2245     if ((w_il(itop(jj)).eq.1).and.(w_il(ibot(jj)).eq.1.))
2246     & xhelp = xhelp*2.
2247     w_i(jj) = 1./xhelp
2248     ENDDO
2249    
2250     C========================================================================
2251     C--- Calculate mean beta for the first time -----------------------------
2252     C--- We are using "1/beta" since its error is gaussian ------------------
2253    
2254     icount=0
2255     sw=0.
2256     sxw=0.
2257     beta_mean=100.
2258    
2259     DO jj=1,12
2260     IF ((abs(1./b(jj)).gt.0.1).and.(abs(1./b(jj)).lt.15.)) THEN
2261     icount = icount+1
2262     sxw = sxw + (1./b(jj))*w_i(jj)*w_i(jj)
2263     sw = sw + w_i(jj)*w_i(jj)
2264     ENDIF
2265     ENDDO
2266    
2267     if (icount.gt.0) beta_mean=1./(sxw/sw)
2268     beta_mean_inv = 1./beta_mean
2269    
2270    
2271     C--- Calculate beta for the second time, use residuals of the single
2272     C--- measurements to get a chi2 value
2273    
2274     icount = 0
2275     sw = 0.
2276     sxw = 0.
2277     betachi = 100.
2278     chi2 = 0.
2279     quality = 0.
2280    
2281     DO jj=1,12
2282     IF ((abs(1./b(jj)).gt.0.1).and.(abs(1./b(jj)).lt.15.)
2283     & .and.(w_i(jj).GT.0.01)) THEN
2284     res = beta_mean_inv - (1./b(jj)) ;
2285     if (abs(res*w_i(jj)).lt.resmax) THEN
2286     chi2 = chi2 + (res*w_i(jj))**2.
2287     icount = icount+1
2288     sxw = sxw + (1./b(jj))*w_i(jj)*w_i(jj)
2289     sw = sw + w_i(jj)*w_i(jj)
2290     ENDIF
2291     ENDIF
2292     ENDDO
2293    
2294     c quality = sw
2295     quality = sqrt(sw)
2296    
2297     if (icount.eq.0) chi2 = 1000.
2298     if (icount.gt.0) chi2 = chi2/(icount)
2299    
2300     if (icount.gt.0) betachi=1./(sxw/sw);
2301    
2302     beta_mean=100.
2303     if ((chi2.lt.chi2cut).and.(quality.gt.qualitycut))
2304     & beta_mean = betachi
2305     newbeta = beta_mean
2306    
2307     END
2308    
2309     C****************************************************************************
2310    
2311 mocchiut 1.6

  ViewVC Help
Powered by ViewVC 1.1.23