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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.17 - (hide annotations) (download)
Fri Apr 18 18:55:55 2008 UTC (16 years, 7 months ago) by mocchiut
Branch: MAIN
Changes since 1.16: +20 -2 lines
ToF upgrade and bugs fixed, Calorimeter crosstalk bugs fixed, new ToF calibrations

1 mocchiut 1.1 *****************************************************************************
2     INTEGER FUNCTION TOFTRK()
3 mocchiut 1.5
4     C****************************************************************************
5 mocchiut 1.8 C 31-08-06 WM
6     C Changed to use DOTRACK2
7     C Beta calculation: now the flightpath (instead of cos(theta)) is used
8     C Beta calculation: all 4 TDV measurements must be < 4095 (in the old
9     C routine it was (t1+t2)<8000
10 pam-de 1.12 C
11     C 08-12-06 WM:
12 mocchiut 1.8 C adc_c-bug : The raw ADC value was multiplied with cos(theta)
13     C and AFTER that there was an if statement "if tof32(right,i,iadc) < 4095"
14 pam-de 1.12 C
15     C jan-07 GF: ADC/TDCflags(4,12) inserted to flag artificial ADC/TDC
16 mocchiut 1.8 C values
17     C jan-07 WM: artificial ADC values created using attenuation calibration
18     C jan-07 WM: artificial TDC values created using xy_coor calibration
19     C jan-07 WM: modified xtofpos flag "101". xtofpos must be inside physical
20     C dimension of the paddle +/- 10 cm
21     C jan-07 WM: if xtofpos=101 then this paddle is not used for beta
22     C calculation
23 pam-de 1.12 C jan-07 WM: in the xtofpos calculation a check for TDC.ne.4095 was
24     C inserted. In the old code one would still calculate a
25 mocchiut 1.8 C xtofpos-value even if the TDC information was missing
26     C jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift
27 mocchiut 1.10 C jan-05 WM: bug fixed: calculation of zenith angles using DOTRACK2
28 mocchiut 1.9 C was incorrect
29 mocchiut 1.10 C jan-07 WM: bug fixed: in some cases tdc_tw was calculated due to a
30     C leftover "xhelp" value
31 mocchiut 1.11 C apr-07 WM: attenuation fit curve is now a double exponential fit
32     C conversion from raw ADC to pC using calibration function
33 pam-de 1.12 C new variables xtr_tof(6) and ytr_tof(6) give track position
34 mocchiut 1.11 C at ToF layers
35 pam-de 1.12 C aug-07 WM: artificial ADC creation revised: Now an ADC value is created
36     C only if there is a TDC value (before ADC was created in ANY
37     C case)
38 mocchiut 1.15 C jan-08 WM: Major Update: Time Walk correction introduced
39     C Additionally we use the information from the "check_charge"
40     C function to fill artificial ADC values and make small corrections
41     C to the k1-parameter (for Z>2)
42     C feb-08 WM: Calculation of beta(13) changed: First a mean beta is calculated,
43     C then in a second step we check the residuals of the single
44     C measurements, reject if > 10 sigma, calculate chi2 and "quality"
45     C beta is taken as good if chi2<20 and quality>10
46     C The function "newbeta" is located in "tofl2com.for"
47 pam-de 1.16 C mar-08 WM: Call to "newbeta" changed, now a flag tells the function if the
48     C call comes from "tofl2com" or form "toftrack"
49     C mar-08 WM: Bug found in dEdx if check_charge>1
50 mocchiut 1.17 C apr-08 WM: Bug found in S22 artificial ADC, mismatch found between the track
51     C length from DOTRACK2 and "GetLength" method for 4 combinations
52 mocchiut 1.5 C****************************************************************************
53 mocchiut 1.1 IMPLICIT NONE
54 pam-de 1.12 C
55 mocchiut 1.1 include 'input_tof.txt'
56     include 'output_tof.txt'
57     include 'tofcomm.txt'
58 pam-de 1.12 C
59    
60 mocchiut 1.1 c =======================================
61     c variables for tracking routine
62     c =======================================
63     integer NPOINT_MAX
64     parameter(NPOINT_MAX=100)
65    
66     c define TOF Z-coordinates
67     integer NPTOF
68     parameter (NPTOF=6)
69     DOUBLE PRECISION ZTOF(NPTOF)
70     DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
71    
72 mocchiut 1.8 integer itof,pmt_id
73 mocchiut 1.1
74     DOUBLE PRECISION al_p(5),
75 mocchiut 1.5 & xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
76     & THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
77    
78 mocchiut 1.1
79     INTEGER IFAIL
80 mocchiut 1.9 c REAL dx,dy,dr
81 mocchiut 1.8 REAL ds
82 mocchiut 1.5 REAL t1,t2,t3,t4
83 mocchiut 1.8 REAL yhelp,xhelp,xhelp1,xhelp2
84 mocchiut 1.15 REAL c1,c2
85     C REAL sw,sxw,w_i
86 pam-de 1.12 REAL dist,dl,F
87 mocchiut 1.15 INTEGER ievent
88     C INTEGER icount
89     C REAL beta_mean
90     REAL btemp(12)
91 mocchiut 1.8 REAL hepratio
92 pam-de 1.12
93 mocchiut 1.15 INTEGER j,hitvec(6)
94 mocchiut 1.1
95 mocchiut 1.15 real atten,pc_adc,check_charge,newbeta
96 mocchiut 1.11
97    
98 mocchiut 1.8 REAL theta,phi
99 mocchiut 1.1 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
100     REAL tofarm12
101     PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
102 pam-de 1.12 REAL tofarm23
103 mocchiut 1.8 PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
104 mocchiut 1.1 REAL tofarm13
105 mocchiut 1.8 PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
106 mocchiut 1.1
107 pam-de 1.12
108 mocchiut 1.1 INTEGER ihelp
109 mocchiut 1.8 REAL xkorr,xpos
110 mocchiut 1.1
111 mocchiut 1.15 INTEGER IZ
112     REAL k1corrA1,k1corrB1,k1corrC1
113    
114 mocchiut 1.1 REAL yl,yh,xl,xh
115 pam-de 1.12 C
116 mocchiut 1.1 REAL hmemor(9000000)
117     INTEGER Iquest(100)
118 pam-de 1.12 C
119 mocchiut 1.5 DATA ievent / 0 /
120    
121 mocchiut 1.15 INTEGER ifst
122     DATA ifst /0/
123    
124 mocchiut 1.1 COMMON / pawcd / hmemor
125     save / pawcd /
126 pam-de 1.12 C
127 mocchiut 1.1 Common / QUESTd / Iquest
128     save / questd /
129 pam-de 1.12 C
130 mocchiut 1.1 C Begin !
131 pam-de 1.12 C
132 mocchiut 1.1 TOFTRK = 0
133    
134     *******************************************************************
135    
136 mocchiut 1.15 if (ifst.eq.0) then
137     ifst=1
138 mocchiut 1.5
139 mocchiut 1.8 C ratio helium to proton ca. 4
140 mocchiut 1.11 hepratio = 4.
141 mocchiut 1.5
142 mocchiut 1.1 offset = 1
143     slope = 2
144     left = 1
145     right = 2
146     none_ev = 0
147     none_find = 0
148     tdc_ev = 1
149     adc_ev = 1
150     itdc = 1
151     iadc = 2
152    
153 mocchiut 1.15
154     k1corrA1 = 0.
155     k1corrB1 = -5.0
156     k1corrC1= 8.0
157    
158     ENDIF ! ifst
159    
160     *******************************************************************
161    
162     ievent = ievent +1
163    
164 mocchiut 1.1 do i=1,13
165     beta_a(i) = 100.
166     enddo
167    
168 mocchiut 1.2 do i=1,4
169     do j=1,12
170     adc_c(i,j) = 1000.
171     enddo
172     enddo
173    
174     do i=1,12
175     do j=1,4
176     tofmask(j,i) = 0
177     enddo
178     enddo
179    
180 mocchiut 1.8 do i=1,4
181     do j=1,12
182     adcflag(i,j) = 0
183     enddo
184     enddo
185    
186     do i=1,4
187     do j=1,12
188     tdcflag(i,j) = 0
189     enddo
190     enddo
191    
192     pmt_id=0
193    
194 mocchiut 1.9 do j=1,6
195     THXOUT(j) = 0.
196     THYOUT(j) = 0.
197     enddo
198    
199 mocchiut 1.11 do j=1,6
200     xtr_tof(j) = 100.
201     ytr_tof(j) = 100.
202     enddo
203    
204 mocchiut 1.15
205 mocchiut 1.8 C----------------------------------------------------------------------
206     C-------------------------get ToF data --------------------------------
207     C we cannot use the tofxx(x,x,x) data from tofl2com since it is
208 pam-de 1.12 C manipulated (Time-walk, artificila ADc and TDC values using ToF
209 mocchiut 1.8 C standalone information
210     C----------------------------------------------------------------------
211    
212 mocchiut 1.11 c put the adc and tdc values from ntuple into tofxx(i,j,k) variables
213 mocchiut 1.8
214     do j=1,8
215 mocchiut 1.11 tof11(1,j,2) = pc_adc(adc(ch11a(j),hb11a(j)))
216     tof11(2,j,2) = pc_adc(adc(ch11b(j),hb11b(j)))
217     tof11(1,j,1) = (tdc(ch11a(j),hb11a(j)))
218     tof11(2,j,1) = (tdc(ch11b(j),hb11b(j)))
219 mocchiut 1.8 enddo
220    
221    
222     do j=1,6
223 mocchiut 1.11 tof12(1,j,2) = pc_adc(adc(ch12a(j),hb12a(j)))
224     tof12(2,j,2) = pc_adc(adc(ch12b(j),hb12b(j)))
225     tof12(1,j,1) = (tdc(ch12a(j),hb12a(j)))
226     tof12(2,j,1) = (tdc(ch12b(j),hb12b(j)))
227 mocchiut 1.8 enddo
228    
229     do j=1,2
230 mocchiut 1.11 tof21(1,j,2) = pc_adc(adc(ch21a(j),hb21a(j)))
231     tof21(2,j,2) = pc_adc(adc(ch21b(j),hb21b(j)))
232     tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
233     tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
234 mocchiut 1.8 enddo
235    
236     do j=1,2
237 mocchiut 1.11 tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
238     tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))
239     tof22(1,j,1) = (tdc(ch22a(j),hb22a(j)))
240     tof22(2,j,1) = (tdc(ch22b(j),hb22b(j)))
241 mocchiut 1.8 enddo
242    
243     do j=1,3
244 mocchiut 1.11 tof31(1,j,2) = pc_adc(adc(ch31a(j),hb31a(j)))
245     tof31(2,j,2) = pc_adc(adc(ch31b(j),hb31b(j)))
246     tof31(1,j,1) = (tdc(ch31a(j),hb31a(j)))
247     tof31(2,j,1) = (tdc(ch31b(j),hb31b(j)))
248 mocchiut 1.8 enddo
249    
250     do j=1,3
251 mocchiut 1.11 tof32(1,j,2) = pc_adc(adc(ch32a(j),hb32a(j)))
252     tof32(2,j,2) = pc_adc(adc(ch32b(j),hb32b(j)))
253     tof32(1,j,1) = (tdc(ch32a(j),hb32a(j)))
254     tof32(2,j,1) = (tdc(ch32b(j),hb32b(j)))
255 mocchiut 1.8 enddo
256    
257     C----------------------------------------------------------------------
258    
259     DO i = 1,8
260     if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000.
261     if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000.
262     if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000.
263     if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000.
264     ENDDO
265    
266     DO i = 1,6
267     if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000.
268     if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000.
269     if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000.
270     if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000.
271     ENDDO
272    
273    
274     DO i = 1,2
275     if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000.
276     if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000.
277     if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000.
278     if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000.
279     ENDDO
280    
281     DO i = 1,2
282     if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000.
283     if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000.
284     if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000.
285     if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000.
286     ENDDO
287    
288     DO i = 1,3
289     if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000.
290     if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000.
291     if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000.
292     if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000.
293     ENDDO
294    
295     DO i = 1,3
296     if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000.
297     if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000.
298     if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000.
299     if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
300     ENDDO
301    
302 mocchiut 1.11 C----------------------------------------------------------------------
303 mocchiut 1.8
304     C------read tracking routine
305 mocchiut 1.1 * igoodevent = igoodevent+1
306     * assigned input parameters for track routine
307     * 1) Z-coordinates where the trajectory is evaluated
308     do itof=1,NPTOF
309     ZIN(itof) = ZTOF(itof)
310     enddo
311     * 2) track status vector
312     C COPY THE ALFA VECTOR FROM AL_PP TO AL_P FOR THE TRACK "T"
313     do i=1,5
314     AL_P(i) = al_pp(i)
315     enddo
316 mocchiut 1.5
317 mocchiut 1.9 c write(*,*) AL_P
318 mocchiut 1.5
319 mocchiut 1.1 if (al_p(5).eq.0.) THEN
320 mocchiut 1.14 c PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
321 mocchiut 1.1 GOTO 969
322     ENDIF
323     * -------- *** tracking routine *** --------
324     IFAIL = 0
325 mocchiut 1.8 C call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
326 mocchiut 1.5 call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
327    
328 mocchiut 1.8 C write(*,*) (TLOUT(i),i=1,6)
329 mocchiut 1.5
330 mocchiut 1.1 if(IFAIL.ne.0)then
331 mocchiut 1.14 c print *,' TOF - WARNING F77: tracking failed '
332 mocchiut 1.1 goto 969
333     endif
334     * ------------------------------------------
335    
336 mocchiut 1.8 969 continue
337    
338 mocchiut 1.11 C--- Fill xtr_tof and ytr_tof: positions from tracker at ToF layers
339     do j=1,6
340     xtr_tof(j) = XOUT(j)
341 pam-de 1.12 ytr_tof(j) = YOUT(j)
342 mocchiut 1.11 enddo
343    
344    
345 mocchiut 1.9 C--- convert angles to radian
346     do j=1,6
347     THXOUT(j) = 3.1415927*THXOUT(j)/180.
348     THYOUT(j) = 3.1415927*THYOUT(j)/180.
349     enddo
350    
351     do j=1,6
352     c write (*,*) j,THXOUT(j),THYOUT(j)
353     enddo
354    
355 mocchiut 1.8
356     C----------------------------------------------------------------------
357     C------------------ set ADC & TDC flag = 0 ------------------------
358     C----------------------------------------------------------------------
359    
360     do j=1,8
361     if (adc(ch11a(j),hb11a(j)).LT.4096)adcflagtof(ch11a(j),hb11a(j))=0
362     if (adc(ch11b(j),hb11b(j)).LT.4096)adcflagtof(ch11b(j),hb11b(j))=0
363     if (tdc(ch11a(j),hb11a(j)).LT.4096)tdcflagtof(ch11a(j),hb11a(j))=0
364     if (tdc(ch11b(j),hb11b(j)).LT.4096)tdcflagtof(ch11b(j),hb11b(j))=0
365     enddo
366     do j=1,6
367     if (adc(ch12a(j),hb12a(j)).LT.4096)adcflagtof(ch12a(j),hb12a(j))=0
368     if (adc(ch12b(j),hb12b(j)).LT.4096)adcflagtof(ch12b(j),hb12b(j))=0
369     if (tdc(ch12a(j),hb12a(j)).LT.4096)tdcflagtof(ch12a(j),hb12a(j))=0
370     if (tdc(ch12b(j),hb12b(j)).LT.4096)tdcflagtof(ch12b(j),hb12b(j))=0
371     enddo
372     do j=1,2
373     if (adc(ch21a(j),hb21a(j)).LT.4096)adcflagtof(ch21a(j),hb21a(j))=0
374     if (adc(ch21b(j),hb21b(j)).LT.4096)adcflagtof(ch21b(j),hb21b(j))=0
375     if (tdc(ch21a(j),hb21a(j)).LT.4096)tdcflagtof(ch21a(j),hb21a(j))=0
376     if (tdc(ch21b(j),hb21b(j)).LT.4096)tdcflagtof(ch21b(j),hb21b(j))=0
377     enddo
378     do j=1,2
379     if (adc(ch22a(j),hb22a(j)).LT.4096)adcflagtof(ch22a(j),hb22a(j))=0
380     if (adc(ch22b(j),hb22b(j)).LT.4096)adcflagtof(ch22b(j),hb22b(j))=0
381     if (tdc(ch22a(j),hb22a(j)).LT.4096)tdcflagtof(ch22a(j),hb22a(j))=0
382     if (tdc(ch22b(j),hb22b(j)).LT.4096)tdcflagtof(ch22b(j),hb22b(j))=0
383     enddo
384     do j=1,3
385     if (adc(ch31a(j),hb31a(j)).LT.4096)adcflagtof(ch31a(j),hb31a(j))=0
386     if (adc(ch31b(j),hb31b(j)).LT.4096)adcflagtof(ch31b(j),hb31b(j))=0
387     if (tdc(ch31a(j),hb31a(j)).LT.4096)tdcflagtof(ch31a(j),hb31a(j))=0
388     if (tdc(ch31b(j),hb31b(j)).LT.4096)tdcflagtof(ch31b(j),hb31b(j))=0
389     enddo
390     do j=1,3
391     if (adc(ch32a(j),hb32a(j)).LT.4096)adcflagtof(ch32a(j),hb32a(j))=0
392     if (adc(ch32b(j),hb32b(j)).LT.4096)adcflagtof(ch32b(j),hb32b(j))=0
393     if (tdc(ch32a(j),hb32a(j)).LT.4096)tdcflagtof(ch32a(j),hb32a(j))=0
394     if (tdc(ch32b(j),hb32b(j)).LT.4096)tdcflagtof(ch32b(j),hb32b(j))=0
395     enddo
396    
397    
398     C----------------------------------------------------------------
399     C---------- Check PMTs 10 and 35 for strange TDC values----------
400     C----------------------------------------------------------------
401    
402     C---- S116A TDC=819
403     if (tof11(1,6,1).EQ.819) then
404     tof11(1,6,1) = 4095
405     tdcflagtof(ch11a(6),hb11a(6))=2
406     endif
407 pam-de 1.12
408 mocchiut 1.8 C---- S222B TDC=819
409     if (tof22(2,2,1).EQ.819) then
410     tof22(2,2,1) = 4095
411     tdcflagtof(ch22b(2),hb22b(2))=2
412     endif
413 pam-de 1.12
414 mocchiut 1.1 C-------------------------------------------------------------
415 mocchiut 1.8 C-------check which paddle penetrated the track -----------
416 mocchiut 1.1 C-------------------------------------------------------------
417 mocchiut 1.8 c middle y (or x) position of the upper and middle ToF-Paddle
418     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
419     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
420     c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
421     c DATA tof22_x/ -4.5,4.5/
422     c DATA tof31_x/ -6.0,0.,6.0/
423     c DATA tof32_y/ -5.0,0.0,5.0/
424 pam-de 1.12 c
425 mocchiut 1.8 c S11 8 paddles 33.0 x 5.1 cm
426     c S12 6 paddles 40.8 x 5.5 cm
427     c S21 2 paddles 18.0 x 7.5 cm
428     c S22 2 paddles 15.0 x 9.0 cm
429     c S31 3 paddles 15.0 x 6.0 cm
430     c S32 3 paddles 18.0 x 5.0 cm
431 mocchiut 1.1
432 mocchiut 1.8 c write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)
433     c write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)
434 mocchiut 1.1
435 mocchiut 1.8 C--------------S11 --------------------------------------
436 mocchiut 1.1
437     tof11_i = none_find
438    
439     yl = -33.0/2.
440     yh = 33.0/2.
441    
442     if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then
443 mocchiut 1.8 do i=1,8
444     xl = tof11_x(i) - 5.1/2.
445     xh = tof11_x(i) + 5.1/2.
446     if ((xout(1).gt.xl).and.(xout(1).le.xh)) then
447     tof11_i=i
448     endif
449     enddo
450 mocchiut 1.1 endif
451    
452 mocchiut 1.8 C--------------S12 --------------------------------------
453 mocchiut 1.1
454     tof12_i = none_find
455 pam-de 1.12
456 mocchiut 1.1 xl = -40.8/2.
457     xh = 40.8/2.
458    
459     if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then
460 mocchiut 1.8 do i=1,6
461     yl = tof12_y(i) - 5.5/2.
462     yh = tof12_y(i) + 5.5/2.
463     if ((yout(2).gt.yl).and.(yout(2).le.yh)) then
464     tof12_i=i
465     endif
466     enddo
467 mocchiut 1.1 endif
468    
469 mocchiut 1.8 C--------------S21 --------------------------------------
470 mocchiut 1.1
471     tof21_i = none_find
472 pam-de 1.12
473 mocchiut 1.1 xl = -18./2.
474     xh = 18./2.
475    
476     if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then
477 mocchiut 1.8 do i=1,2
478     yl = tof21_y(i) - 7.5/2.
479     yh = tof21_y(i) + 7.5/2.
480     if ((yout(3).gt.yl).and.(yout(3).le.yh)) then
481     tof21_i=i
482     endif
483     enddo
484 mocchiut 1.1 endif
485    
486 mocchiut 1.8 C--------------S22 --------------------------------------
487 mocchiut 1.1
488     tof22_i = none_find
489 pam-de 1.12
490 mocchiut 1.1 yl = -15./2.
491     yh = 15./2.
492    
493     if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then
494 mocchiut 1.8 do i=1,2
495     xl = tof22_x(i) - 9.0/2.
496     xh = tof22_x(i) + 9.0/2.
497     if ((xout(4).gt.xl).and.(xout(4).le.xh)) then
498     tof22_i=i
499     endif
500     enddo
501 mocchiut 1.1 endif
502    
503 mocchiut 1.8 C--------------S31 --------------------------------------
504 mocchiut 1.1
505     tof31_i = none_find
506 pam-de 1.12
507 mocchiut 1.1 yl = -15.0/2.
508     yh = 15.0/2.
509    
510     if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then
511 mocchiut 1.8 do i=1,3
512     xl = tof31_x(i) - 6.0/2.
513     xh = tof31_x(i) + 6.0/2.
514     if ((xout(5).gt.xl).and.(xout(5).le.xh)) then
515     tof31_i=i
516     endif
517     enddo
518 mocchiut 1.1 endif
519    
520 mocchiut 1.8 C--------------S32 --------------------------------------
521 mocchiut 1.1
522     tof32_i = none_find
523 pam-de 1.12
524 mocchiut 1.1 xl = -18.0/2.
525     xh = 18.0/2.
526    
527     if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then
528 mocchiut 1.8 do i=1,3
529     yl = tof32_y(i) - 5.0/2.
530     yh = tof32_y(i) + 5.0/2.
531     if ((yout(6).gt.yl).and.(yout(6).le.yh)) then
532     tof32_i=i
533     endif
534     enddo
535 mocchiut 1.1 endif
536    
537 mocchiut 1.5
538 mocchiut 1.8 C write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
539    
540 mocchiut 1.15 hitvec(1)=tof11_i
541     hitvec(2)=tof12_i
542     hitvec(3)=tof21_i
543     hitvec(4)=tof22_i
544     hitvec(5)=tof31_i
545     hitvec(6)=tof32_i
546 mocchiut 1.8
547 mocchiut 1.15 c write(*,*) 'toftrk ',
548     c & tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
549 mocchiut 1.8
550 mocchiut 1.15 C----------------------------------------------------------------------
551     C--- check charge:
552     C--- if Z=2 we should use the attenuation curve for helium to
553     C--- fill the artificail ADC values and NOT divide by "hepratio"
554     C--- if Z>2 we should do a correction to
555     C--- the k1 constants in the beta calculation
556     C----------------------------------------------------------------------
557 mocchiut 1.8
558 mocchiut 1.15 theta=0.
559     dist = ZTOF(1) - ZTOF(5)
560     dl = 0.
561     DO I=1,5
562     dl = dl + TLOUT(i)
563     ENDDO
564     F = dl/dist
565     theta = acos(1/F)
566 mocchiut 1.8
567 mocchiut 1.15 iz = int(check_charge(theta,hitvec))
568     c write(*,*) 'in toftrk',iz
569 mocchiut 1.8
570     C--------------------------------------------------------------------
571 pam-de 1.12 C---- if paddle hit: if we have TDC value but no ADC, create ADC value
572 mocchiut 1.8 C--------------------------------------------------------------------
573     c middle y (or x) position of the upper and middle ToF-Paddle
574     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
575     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
576     c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
577     c DATA tof22_x/ -4.5,4.5/
578     c DATA tof31_x/ -6.0,0.,6.0/
579     c DATA tof32_y/ -5.0,0.0,5.0/
580    
581     C----------------------------S1 -------------------------------------
582    
583     yhelp=yout(1)
584     IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN
585     i = tof11_i
586 mocchiut 1.15 if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
587 pam-de 1.12 & (adc(ch11a(i),hb11a(i)).eq.4095)) then
588 mocchiut 1.9 phi = atan(tan(THYOUT(1))/tan(THXOUT(1)))
589 mocchiut 1.8 theta = atan(tan(THXOUT(1))/cos(phi))
590 mocchiut 1.11 xkorr = atten(left,11,i,yhelp)
591 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
592 mocchiut 1.8 tof11(left,i,iadc)=xkorr/cos(theta)
593     adcflag(ch11a(i),hb11a(i)) = 1
594     endif
595 mocchiut 1.15 if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
596 pam-de 1.12 & (adc(ch11b(i),hb11b(i)).eq.4095)) then
597 mocchiut 1.9 phi = atan(tan(THYOUT(1))/tan(THXOUT(1)))
598 mocchiut 1.8 theta = atan(tan(THXOUT(1))/cos(phi))
599 mocchiut 1.11 xkorr = atten(right,11,i,yhelp)
600 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
601 mocchiut 1.8 tof11(right,i,iadc)=xkorr/cos(theta)
602     adcflag(ch11b(i),hb11b(i)) = 1
603     endif
604     ENDIF
605    
606     xhelp=xout(2)
607     IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN
608     i = tof12_i
609 mocchiut 1.15 if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
610 pam-de 1.12 & (adc(ch12a(i),hb12a(i)).eq.4095)) then
611 mocchiut 1.9 phi = atan(tan(THYOUT(2))/tan(THXOUT(2)))
612 mocchiut 1.8 theta = atan(tan(THXOUT(2))/cos(phi))
613 mocchiut 1.11 c xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
614     xkorr = atten(left,12,i,xhelp)
615 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
616 mocchiut 1.8 tof12(left,i,iadc) = xkorr/cos(theta)
617     adcflag(ch12a(i),hb12a(i)) = 1
618     endif
619 mocchiut 1.15 if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
620 pam-de 1.12 & (adc(ch12b(i),hb12b(i)).eq.4095)) then
621 mocchiut 1.9 phi = atan(tan(THYOUT(2))/tan(THXOUT(2)))
622 mocchiut 1.8 theta = atan(tan(THXOUT(2))/cos(phi))
623 mocchiut 1.11 c xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
624     xkorr = atten(right,12,i,xhelp)
625 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
626 mocchiut 1.8 tof12(right,i,iadc) = xkorr/cos(theta)
627     adcflag(ch12b(i),hb12b(i)) = 1
628     endif
629     ENDIF
630    
631     C-----------------------------S2 --------------------------------
632    
633     xhelp=xout(3)
634     IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN
635     i = tof21_i
636 mocchiut 1.15 if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
637 pam-de 1.12 & (adc(ch21a(i),hb21a(i)).eq.4095)) then
638 mocchiut 1.9 phi = atan(tan(THYOUT(3))/tan(THXOUT(3)))
639 mocchiut 1.8 theta = atan(tan(THXOUT(3))/cos(phi))
640 mocchiut 1.11 c xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
641     xkorr = atten(left,21,i,xhelp)
642 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
643 mocchiut 1.8 tof21(left,i,iadc) = xkorr/cos(theta)
644     adcflag(ch21a(i),hb21a(i)) = 1
645     endif
646 mocchiut 1.15 if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
647 pam-de 1.12 & (adc(ch21b(i),hb21b(i)).eq.4095)) then
648 mocchiut 1.9 phi = atan(tan(THYOUT(3))/tan(THXOUT(3)))
649 mocchiut 1.8 theta = atan(tan(THXOUT(3))/cos(phi))
650 mocchiut 1.11 c xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
651     xkorr = atten(right,21,i,xhelp)
652 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
653 mocchiut 1.8 tof21(right,i,iadc) = xkorr/cos(theta)
654     adcflag(ch21b(i),hb21b(i)) = 1
655     endif
656     ENDIF
657    
658    
659     yhelp=yout(4)
660     IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN
661     i = tof22_i
662 mocchiut 1.15 if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
663 pam-de 1.12 & (adc(ch22a(i),hb22a(i)).eq.4095)) then
664 mocchiut 1.9 phi = atan(tan(THYOUT(4))/tan(THXOUT(4)))
665 mocchiut 1.8 theta = atan(tan(THXOUT(4))/cos(phi))
666 mocchiut 1.11 c xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
667     xkorr = atten(left,22,i,yhelp)
668 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
669 mocchiut 1.8 tof22(left,i,iadc) = xkorr/cos(theta)
670     adcflag(ch22a(i),hb22a(i)) = 1
671     endif
672 mocchiut 1.17 if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
673 pam-de 1.12 & (adc(ch22b(i),hb22b(i)).eq.4095)) then
674 mocchiut 1.9 phi = atan(tan(THYOUT(4))/tan(THXOUT(4)))
675 mocchiut 1.8 theta = atan(tan(THXOUT(4))/cos(phi))
676 mocchiut 1.11 c xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
677     xkorr = atten(right,22,i,yhelp)
678 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
679 mocchiut 1.8 tof22(right,i,iadc) = xkorr/cos(theta)
680     adcflag(ch22b(i),hb22b(i)) = 1
681     endif
682     ENDIF
683    
684     C-----------------------------S3 --------------------------------
685    
686     yhelp=yout(5)
687     IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN
688     i = tof31_i
689 mocchiut 1.15 if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
690 pam-de 1.12 & (adc(ch31a(i),hb31a(i)).eq.4095)) then
691 mocchiut 1.9 phi = atan(tan(THYOUT(5))/tan(THXOUT(5)))
692 mocchiut 1.8 theta = atan(tan(THXOUT(5))/cos(phi))
693 mocchiut 1.11 c xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
694     xkorr = atten(left,31,i,yhelp)
695 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
696 mocchiut 1.8 tof31(left,i,iadc) = xkorr/cos(theta)
697     adcflag(ch31a(i),hb31a(i)) = 1
698     endif
699 mocchiut 1.15 if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
700 pam-de 1.12 & (adc(ch31b(i),hb31b(i)).eq.4095)) then
701 mocchiut 1.9 phi = atan(tan(THYOUT(5))/tan(THXOUT(5)))
702 mocchiut 1.8 theta = atan(tan(THXOUT(5))/cos(phi))
703 mocchiut 1.11 c xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
704     xkorr = atten(right,31,i,yhelp)
705 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
706 mocchiut 1.8 tof31(right,i,iadc) = xkorr/cos(theta)
707     adcflag(ch31b(i),hb31b(i)) = 1
708     endif
709     ENDIF
710    
711    
712     xhelp=xout(6)
713     IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
714     i = tof32_i
715 mocchiut 1.15 if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
716 pam-de 1.12 & (adc(ch32a(i),hb32a(i)).eq.4095)) then
717 mocchiut 1.9 phi = atan(tan(THYOUT(6))/tan(THXOUT(6)))
718 mocchiut 1.8 theta = atan(tan(THXOUT(6))/cos(phi))
719 mocchiut 1.11 c xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
720     xkorr = atten(left,32,i,xhelp)
721 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
722 mocchiut 1.8 tof32(left,i,iadc) = xkorr/cos(theta)
723     adcflag(ch32a(i),hb32a(i)) = 1
724     endif
725 mocchiut 1.15 if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
726 pam-de 1.12 & (adc(ch32b(i),hb32b(i)).eq.4095)) then
727 mocchiut 1.9 phi = atan(tan(THYOUT(6))/tan(THXOUT(6)))
728 mocchiut 1.8 theta = atan(tan(THXOUT(6))/cos(phi))
729 mocchiut 1.11 c xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
730     xkorr = atten(right,32,i,xhelp)
731 mocchiut 1.15 if (iz.le.1) xkorr=xkorr/hepratio
732 mocchiut 1.8 tof32(right,i,iadc) = xkorr/cos(theta)
733     adcflag(ch32b(i),hb32b(i)) = 1
734     endif
735     ENDIF
736    
737 mocchiut 1.15 C-------------------------------------------------------------------
738     C Now there is for each hitted paddle a TDC and ADC value, if the
739     C TDC was < 4095.
740     C There might be also TDC-ADC pairs in paddles not hitted
741     C Let's correct the raw TDC value with the time walk
742     C-------------------------------------------------------------------
743     C--------------------Time walk correction -------------------------
744     C-------------------------------------------------------------------
745    
746     DO i=1,8
747     if ((tdc(ch11a(i),hb11a(i)).lt.4095).and.
748     & (tof11(left,i,iadc).lt.3786)) THEN
749     xhelp = tw11(left,i)/(tof11(left,i,iadc)**0.5)
750     tof11(left,i,itdc) = tof11(left,i,itdc) + xhelp
751     tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
752     ENDIF
753    
754     if ((tdc(ch11b(i),hb11b(i)).lt.4095).and.
755     & (tof11(right,i,iadc).lt.3786)) THEN
756     xhelp = tw11(right,i)/(tof11(right,i,iadc)**0.5)
757     tof11(right,i,itdc) = tof11(right,i,itdc) + xhelp
758     tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
759     ENDIF
760     ENDDO
761    
762    
763     DO i=1,6
764     if ((tdc(ch12a(i),hb12a(i)).lt.4095).and.
765     & (tof12(left,i,iadc).lt.3786)) THEN
766     xhelp = tw12(left,i)/(tof12(left,i,iadc)**0.5)
767     tof12(left,i,itdc) = tof12(left,i,itdc) + xhelp
768     tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
769     ENDIF
770    
771     if ((tdc(ch12b(i),hb12b(i)).lt.4095).and.
772     & (tof12(right,i,iadc).lt.3786)) THEN
773     xhelp = tw12(right,i)/(tof12(right,i,iadc)**0.5)
774     tof12(right,i,itdc) = tof12(right,i,itdc) + xhelp
775     tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
776     ENDIF
777     ENDDO
778    
779     C----
780     DO I=1,2
781     if ((tdc(ch21a(i),hb21a(i)).lt.4095).and.
782     & (tof21(left,i,iadc).lt.3786)) THEN
783     xhelp = tw21(left,i)/(tof21(left,i,iadc)**0.5)
784     tof21(left,i,itdc) = tof21(left,i,itdc) + xhelp
785     tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
786     ENDIF
787    
788     if ((tdc(ch21b(i),hb21b(i)).lt.4095).and.
789     & (tof21(right,i,iadc).lt.3786)) THEN
790     xhelp = tw21(right,i)/(tof21(right,i,iadc)**0.5)
791     tof21(right,i,itdc) = tof21(right,i,itdc) + xhelp
792     tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
793     ENDIF
794     ENDDO
795    
796     DO I=1,2
797     if ((tdc(ch22a(i),hb22a(i)).lt.4095).and.
798     & (tof22(left,i,iadc).lt.3786)) THEN
799     xhelp = tw22(left,i)/(tof22(left,i,iadc)**0.5)
800     tof22(left,i,itdc) = tof22(left,i,itdc) + xhelp
801     tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
802     ENDIF
803    
804     if ((tdc(ch22b(i),hb22b(i)).lt.4095).and.
805     & (tof22(right,i,iadc).lt.3786)) THEN
806     xhelp = tw22(right,i)/(tof22(right,i,iadc)**0.5)
807     tof22(right,i,itdc) = tof22(right,i,itdc) + xhelp
808     tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
809     ENDIF
810     ENDDO
811    
812     C----
813     DO I=1,3
814     if ((tdc(ch31a(i),hb31a(i)).lt.4095).and.
815     & (tof31(left,i,iadc).lt.3786)) THEN
816     xhelp = tw31(left,i)/(tof31(left,i,iadc)**0.5)
817     tof31(left,i,itdc) = tof31(left,i,itdc) + xhelp
818     tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
819     ENDIF
820    
821     if ((tdc(ch31b(i),hb31b(i)).lt.4095).and.
822     & (tof31(right,i,iadc).lt.3786)) THEN
823     xhelp = tw31(right,i)/(tof31(right,i,iadc)**0.5)
824     tof31(right,i,itdc) = tof31(right,i,itdc) + xhelp
825     tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
826     ENDIF
827     ENDDO
828    
829     DO I=1,3
830     if ((tdc(ch32a(i),hb32a(i)).lt.4095).and.
831     & (tof32(left,i,iadc).lt.3786)) THEN
832     xhelp = tw32(left,i)/(tof32(left,i,iadc)**0.5)
833     tof32(left,i,itdc) = tof32(left,i,itdc) + xhelp
834     tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
835     ENDIF
836    
837     if ((tdc(ch32b(i),hb32b(i)).lt.4095).and.
838     & (tof32(right,i,iadc).lt.3786)) THEN
839     xhelp = tw32(right,i)/(tof32(right,i,iadc)**0.5)
840     tof32(right,i,itdc) = tof32(right,i,itdc) + xhelp
841     tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
842     ENDIF
843     ENDDO
844    
845    
846     C-----------------------------------------------------------------------
847     C--------------------Insert Artifical TDC Value ---------------------
848     C For each Paddle perform check:
849     C if left paddle=4095 and right paddle OK => create TDC value left
850     C if right paddle=4095 and left paddle OK => create TDC value right
851     C-----------------------------------------------------------------------
852    
853     C-----------------------S11 -----------------------------------------
854    
855     IF (tof11_i.GT.none_find) THEN
856     xpos = yout(1)
857     i = tof11_i
858     if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.
859     & (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN
860     tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)
861     & + 2*(y_coor_lin11(tof11_i,offset)
862     & + xpos*y_coor_lin11(tof11_i,slope))
863     tdcflag(ch11a(i),hb11a(i)) = 1
864     ENDIF
865    
866     if ((tdc(ch11b(i),hb11b(i)).EQ.4095).AND.
867     & (tdc(ch11a(i),hb11a(i)).LT.4095)) THEN
868     tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)
869     & - 2*(y_coor_lin11(tof11_i,offset)
870     & + xpos*y_coor_lin11(tof11_i,slope))
871     tdcflag(ch11b(i),hb11b(i)) = 1
872     ENDIF
873    
874     ENDIF
875    
876     C-----------------------S12 -----------------------------------------
877    
878     IF (tof12_i.GT.none_find) THEN
879     xpos = xout(2)
880     i = tof12_i
881     if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.
882     & (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN
883     tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)
884     & + 2*(x_coor_lin12(tof12_i,offset)
885     & + xpos*x_coor_lin12(tof12_i,slope))
886     tdcflag(ch12a(i),hb12a(i)) = 1
887     ENDIF
888    
889     if ((tdc(ch12b(i),hb12b(i)).EQ.4095).AND.
890     & (tdc(ch12a(i),hb12a(i)).LT.4095)) THEN
891     tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)
892     & - 2*(x_coor_lin12(tof12_i,offset)
893     & + xpos*x_coor_lin12(tof12_i,slope))
894     tdcflag(ch12b(i),hb12b(i)) = 1
895     ENDIF
896     ENDIF
897    
898     C-----------------------S21 -----------------------------------------
899    
900     IF (tof21_i.GT.none_find) THEN
901     xpos = xout(3)
902     i = tof21_i
903     if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.
904     & (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN
905     tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)
906     & + 2*(x_coor_lin21(tof21_i,offset)
907     & + xpos*x_coor_lin21(tof21_i,slope))
908     tdcflag(ch21a(i),hb21a(i)) = 1
909     ENDIF
910    
911     if ((tdc(ch21b(i),hb21b(i)).EQ.4095).AND.
912     & (tdc(ch21a(i),hb21a(i)).LT.4095)) THEN
913     tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)
914     & - 2*(x_coor_lin21(tof21_i,offset)
915     & + xpos*x_coor_lin21(tof21_i,slope))
916     tdcflag(ch21b(i),hb21b(i)) = 1
917     ENDIF
918     ENDIF
919    
920     C-----------------------S22 -----------------------------------------
921    
922     IF (tof22_i.GT.none_find) THEN
923     xpos = yout(4)
924     i = tof22_i
925     if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.
926     & (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN
927     tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)
928     & + 2*(y_coor_lin22(tof22_i,offset)
929     & + xpos*y_coor_lin22(tof22_i,slope))
930     tdcflag(ch22a(i),hb22a(i)) = 1
931     ENDIF
932    
933     if ((tdc(ch22b(i),hb22b(i)).EQ.4095).AND.
934     & (tdc(ch22a(i),hb22a(i)).LT.4095)) THEN
935     tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)
936     & - 2*(y_coor_lin22(tof22_i,offset)
937     & + xpos*y_coor_lin22(tof22_i,slope))
938     tdcflag(ch22b(i),hb22b(i)) = 1
939     ENDIF
940     ENDIF
941    
942     C-----------------------S31 -----------------------------------------
943    
944     IF (tof31_i.GT.none_find) THEN
945     xpos = yout(5)
946     i = tof31_i
947     if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.
948     & (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN
949     tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)
950     & + 2*(y_coor_lin31(tof31_i,offset)
951     & + xpos*y_coor_lin31(tof31_i,slope))
952     tdcflag(ch31a(i),hb31a(i)) = 1
953     ENDIF
954    
955     if ((tdc(ch31b(i),hb31b(i)).EQ.4095).AND.
956     & (tdc(ch31a(i),hb31a(i)).LT.4095)) THEN
957     tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)
958     & - 2*(y_coor_lin31(tof31_i,offset)
959     & + xpos*y_coor_lin31(tof31_i,slope))
960     tdcflag(ch31b(i),hb31b(i)) = 1
961     ENDIF
962     ENDIF
963    
964     C-----------------------S32 -----------------------------------------
965    
966     IF (tof32_i.GT.none_find) THEN
967     xpos = xout(6)
968     i = tof32_i
969     if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.
970     & (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN
971     tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)
972     & + 2*(x_coor_lin32(tof32_i,offset)
973     & + xpos*x_coor_lin32(tof32_i,slope))
974     tdcflag(ch32a(i),hb32a(i)) = 1
975     ENDIF
976    
977     if ((tdc(ch32b(i),hb32b(i)).EQ.4095).AND.
978     & (tdc(ch32a(i),hb32a(i)).LT.4095)) THEN
979     tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)
980     & - 2*(x_coor_lin32(tof32_i,offset)
981     & + xpos*x_coor_lin32(tof32_i,slope))
982     tdcflag(ch32b(i),hb32b(i)) = 1
983     ENDIF
984     ENDIF
985    
986 mocchiut 1.5
987 mocchiut 1.2 C------------------------------------------------------------------
988     C--- calculate track position in paddle using timing difference
989     C------------------------------------------------------------------
990    
991     do i=1,3
992     xtofpos(i)=100.
993     ytofpos(i)=100.
994 pam-de 1.12 enddo
995 mocchiut 1.15
996 mocchiut 1.2 C-----------------------------S1 --------------------------------
997 pam-de 1.12
998 mocchiut 1.2 IF (tof11_i.GT.none_find) THEN
999 mocchiut 1.8 IF ((tof11(1,tof11_i,itdc).NE.4095).AND.
1000     & (tof11(2,tof11_i,itdc).NE.4095)) THEN
1001 mocchiut 1.2 ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
1002     + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1003 mocchiut 1.8 if (abs(ytofpos(1)).gt.26.) ytofpos(1)=101.
1004     endif
1005 mocchiut 1.2 endif
1006    
1007     IF (tof12_i.GT.none_find) THEN
1008 mocchiut 1.8 IF ((tof12(1,tof12_i,itdc).NE.4095).AND.
1009     & (tof12(2,tof12_i,itdc).NE.4095)) THEN
1010 mocchiut 1.2 xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
1011     + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1012 mocchiut 1.8 if (abs(xtofpos(1)).gt.31.) xtofpos(1)=101.
1013 mocchiut 1.2 endif
1014 pam-de 1.12 endif
1015    
1016 mocchiut 1.2 C-----------------------------S2 --------------------------------
1017 pam-de 1.12
1018 mocchiut 1.2 IF (tof21_i.GT.none_find) THEN
1019 mocchiut 1.8 IF ((tof21(1,tof21_i,itdc).NE.4095).AND.
1020     & (tof21(2,tof21_i,itdc).NE.4095)) THEN
1021 mocchiut 1.2 xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
1022     + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1023 pam-de 1.12 if (abs(xtofpos(2)).gt.19.) xtofpos(2)=101.
1024 mocchiut 1.8 endif
1025 mocchiut 1.2 endif
1026 mocchiut 1.8
1027 mocchiut 1.2 IF (tof22_i.GT.none_find) THEN
1028 mocchiut 1.8 IF ((tof22(1,tof22_i,itdc).NE.4095).AND.
1029     & (tof22(2,tof22_i,itdc).NE.4095)) THEN
1030 mocchiut 1.2 ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
1031     + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1032 mocchiut 1.8 if (abs(ytofpos(2)).gt.18.) ytofpos(2)=101.
1033 mocchiut 1.2 endif
1034 pam-de 1.12 endif
1035    
1036 mocchiut 1.2 C-----------------------------S3 --------------------------------
1037 pam-de 1.12
1038 mocchiut 1.2 IF (tof31_i.GT.none_find) THEN
1039 mocchiut 1.8 IF ((tof31(1,tof31_i,itdc).NE.4095).AND.
1040     & (tof31(2,tof31_i,itdc).NE.4095)) THEN
1041 mocchiut 1.2 ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
1042     + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1043 mocchiut 1.8 if (abs(ytofpos(3)).gt.18.) ytofpos(3)=101.
1044     endif
1045 mocchiut 1.2 endif
1046 mocchiut 1.8
1047 mocchiut 1.2 IF (tof32_i.GT.none_find) THEN
1048 mocchiut 1.8 IF ((tof32(1,tof32_i,itdc).NE.4095).AND.
1049     & (tof32(2,tof32_i,itdc).NE.4095)) THEN
1050 mocchiut 1.2 xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
1051     + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1052 mocchiut 1.8 if (abs(xtofpos(3)).gt.19.) xtofpos(3)=101.
1053 mocchiut 1.2 endif
1054 pam-de 1.12 endif
1055    
1056 mocchiut 1.8 c do i=1,3
1057     c if (abs(xtofpos(i)).gt.100.) then
1058     c xtofpos(i)=101.
1059     c endif
1060     c if (abs(ytofpos(i)).gt.100.) then
1061     c ytofpos(i)=101.
1062     c endif
1063 pam-de 1.12 c enddo
1064    
1065 mocchiut 1.8
1066    
1067     C---------------------------------------------------------------------
1068     C--------------------Corrections on ADC-data -------------------------
1069     C-----------------angle and ADC(x) correction -----------------------
1070 mocchiut 1.1
1071 mocchiut 1.8 C-----------------------------S1 -------------------------------------
1072 mocchiut 1.1
1073     yhelp=yout(1)
1074 mocchiut 1.9
1075     phi = atan(tan(THYOUT(1))/tan(THXOUT(1)))
1076 mocchiut 1.8 theta = atan(tan(THXOUT(1))/cos(phi))
1077 mocchiut 1.1
1078     IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
1079    
1080     i = tof11_i
1081 pam-de 1.12
1082 mocchiut 1.11 if (tof11(left,i,iadc).lt.3786) then
1083 pam-de 1.12 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)
1084 mocchiut 1.11 xkorr = atten(left,11,i,yhelp)
1085 pam-de 1.16 xkorr=xkorr/hepratio
1086 mocchiut 1.1 adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
1087     endif
1088    
1089 pam-de 1.12
1090 mocchiut 1.11 if (tof11(right,i,iadc).lt.3786) then
1091 mocchiut 1.8 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)
1092 mocchiut 1.11 xkorr = atten(right,11,i,yhelp)
1093 pam-de 1.16 xkorr=xkorr/hepratio
1094 mocchiut 1.1 adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
1095     endif
1096     ENDIF
1097    
1098    
1099     xhelp=xout(2)
1100 mocchiut 1.9 phi = atan(tan(THYOUT(2))/tan(THXOUT(2)))
1101 mocchiut 1.8 theta = atan(tan(THXOUT(2))/cos(phi))
1102 mocchiut 1.15
1103 mocchiut 1.1 IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
1104     i = tof12_i
1105 mocchiut 1.11 if (tof12(left,i,iadc).lt.3786) then
1106 mocchiut 1.8 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)
1107 mocchiut 1.11 xkorr = atten(left,12,i,xhelp)
1108 pam-de 1.16 xkorr=xkorr/hepratio
1109 mocchiut 1.1 adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
1110     endif
1111    
1112 mocchiut 1.11 if (tof12(right,i,iadc).lt.3786) then
1113 mocchiut 1.8 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)
1114 mocchiut 1.11 xkorr = atten(right,12,i,xhelp)
1115 pam-de 1.16 xkorr=xkorr/hepratio
1116 mocchiut 1.1 adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
1117     endif
1118     ENDIF
1119    
1120     C-----------------------------S2 --------------------------------
1121    
1122     xhelp=xout(3)
1123 mocchiut 1.9 phi = atan(tan(THYOUT(3))/tan(THXOUT(3)))
1124 mocchiut 1.8 theta = atan(tan(THXOUT(3))/cos(phi))
1125 mocchiut 1.15
1126 mocchiut 1.1 IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
1127     i = tof21_i
1128 mocchiut 1.11 if (tof21(left,i,iadc).lt.3786) then
1129 mocchiut 1.8 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)
1130 mocchiut 1.11 xkorr = atten(left,21,i,xhelp)
1131 pam-de 1.16 xkorr=xkorr/hepratio
1132 mocchiut 1.1 adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
1133     endif
1134    
1135 mocchiut 1.11 if (tof21(right,i,iadc).lt.3786) then
1136 mocchiut 1.8 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)
1137 mocchiut 1.11 xkorr = atten(right,21,i,xhelp)
1138 pam-de 1.16 xkorr=xkorr/hepratio
1139 mocchiut 1.1 adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
1140     endif
1141     ENDIF
1142    
1143     yhelp=yout(4)
1144 mocchiut 1.9 phi = atan(tan(THYOUT(4))/tan(THXOUT(4)))
1145 mocchiut 1.8 theta = atan(tan(THXOUT(4))/cos(phi))
1146    
1147 mocchiut 1.1 IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
1148     i = tof22_i
1149 mocchiut 1.11 if (tof22(left,i,iadc).lt.3786) then
1150 mocchiut 1.8 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)
1151 mocchiut 1.11 xkorr = atten(left,22,i,yhelp)
1152 pam-de 1.16 xkorr=xkorr/hepratio
1153 mocchiut 1.1 adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
1154     endif
1155    
1156 mocchiut 1.11 if (tof22(right,i,iadc).lt.3786) then
1157 mocchiut 1.8 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)
1158 mocchiut 1.11 xkorr = atten(right,22,i,yhelp)
1159 pam-de 1.16 xkorr=xkorr/hepratio
1160 mocchiut 1.1 adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
1161     endif
1162     ENDIF
1163    
1164     C-----------------------------S3 --------------------------------
1165    
1166     yhelp=yout(5)
1167 mocchiut 1.9 phi = atan(tan(THYOUT(5))/tan(THXOUT(5)))
1168 mocchiut 1.8 theta = atan(tan(THXOUT(5))/cos(phi))
1169 pam-de 1.12
1170 mocchiut 1.1 IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
1171    
1172     i = tof31_i
1173 mocchiut 1.11 if (tof31(left,i,iadc).lt.3786) then
1174 mocchiut 1.8 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)
1175 mocchiut 1.11 xkorr = atten(left,31,i,yhelp)
1176 pam-de 1.16 xkorr=xkorr/hepratio
1177 mocchiut 1.1 adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1178     endif
1179    
1180 mocchiut 1.11 if (tof31(right,i,iadc).lt.3786) then
1181 mocchiut 1.8 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)
1182 mocchiut 1.11 xkorr = atten(right,31,i,yhelp)
1183 pam-de 1.16 xkorr=xkorr/hepratio
1184 mocchiut 1.1 adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1185     endif
1186     ENDIF
1187    
1188     xhelp=xout(6)
1189 mocchiut 1.9 phi = atan(tan(THYOUT(6))/tan(THXOUT(6)))
1190 mocchiut 1.8 theta = atan(tan(THXOUT(6))/cos(phi))
1191    
1192 mocchiut 1.1 IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
1193     i = tof32_i
1194 mocchiut 1.11 if (tof32(left,i,iadc).lt.3786) then
1195 mocchiut 1.8 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)
1196 mocchiut 1.11 xkorr = atten(left,32,i,xhelp)
1197 pam-de 1.16 xkorr=xkorr/hepratio
1198 mocchiut 1.1 adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1199     endif
1200    
1201 mocchiut 1.11 if (tof32(right,i,iadc).lt.3786) then
1202 mocchiut 1.8 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)
1203 mocchiut 1.11 xkorr = atten(right,32,i,xhelp)
1204 pam-de 1.16 xkorr=xkorr/hepratio
1205 mocchiut 1.1 adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1206     endif
1207     ENDIF
1208    
1209 mocchiut 1.15
1210 mocchiut 1.1 C-----------------------------------------------------------------------
1211     C----------------------calculate Beta ------------------------------
1212     C-----------------------------------------------------------------------
1213     C-------------------difference of sums ---------------------------
1214 pam-de 1.12 C
1215 mocchiut 1.1 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 mocchiut 1.5 C instead of cos(theta) use factor F:
1221 pam-de 1.12 C F = pathlength/d
1222 mocchiut 1.5 C => beta = c2*F/(DS-c1))
1223    
1224 mocchiut 1.8 dist = ZTOF(1) - ZTOF(5)
1225     dl = 0.
1226     DO I=1,5
1227     dl = dl + TLOUT(i)
1228     ENDDO
1229 pam-de 1.12 F = dl/dist
1230 mocchiut 1.1
1231     C S11 - S31
1232 mocchiut 1.8 C IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1233     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1234     & (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1235 mocchiut 1.5 t1 = tof11(1,tof11_i,itdc)
1236     t2 = tof11(2,tof11_i,itdc)
1237     t3 = tof31(1,tof31_i,itdc)
1238     t4 = tof31(2,tof31_i,itdc)
1239 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1240     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1241 mocchiut 1.8 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1242     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1243     ds = xhelp1-xhelp2
1244     ihelp=(tof11_i-1)*3+tof31_i
1245     c1 = k_S11S31(1,ihelp)
1246 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrA1
1247 pam-de 1.12 c2 = k_S11S31(2,ihelp)
1248 mocchiut 1.8 beta_a(1) = c2*F/(ds-c1)
1249 mocchiut 1.13 c write(*,*) 'S11-S31 ',c1,c2,F
1250     c write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
1251 mocchiut 1.8 C-------ToF Mask - S11 - S31
1252    
1253     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1254     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1255     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1256     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1257    
1258     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1259     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1260 pam-de 1.12 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1261 mocchiut 1.8 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1262    
1263     ENDIF
1264     ENDIF
1265    
1266     dist = ZTOF(1) - ZTOF(6)
1267     dl = 0.
1268     DO I=1,6
1269     dl = dl + TLOUT(i)
1270     ENDDO
1271 pam-de 1.12 F = dl/dist
1272    
1273 mocchiut 1.1 C S11 - S32
1274 mocchiut 1.8 C IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1275     IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1276     & (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1277 mocchiut 1.5 t1 = tof11(1,tof11_i,itdc)
1278     t2 = tof11(2,tof11_i,itdc)
1279     t3 = tof32(1,tof32_i,itdc)
1280     t4 = tof32(2,tof32_i,itdc)
1281 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1282     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1283 mocchiut 1.8 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1284     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1285     ds = xhelp1-xhelp2
1286     ihelp=(tof11_i-1)*3+tof32_i
1287     c1 = k_S11S32(1,ihelp)
1288 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrA1
1289 pam-de 1.12 c2 = k_S11S32(2,ihelp)
1290 mocchiut 1.8 beta_a(2) = c2*F/(ds-c1)
1291     C write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1292    
1293     C-------ToF Mask - S11 - S32
1294    
1295     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1296     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1297     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1298     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1299    
1300     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1301     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1302 pam-de 1.12 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1303 mocchiut 1.8 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1304 mocchiut 1.2
1305 mocchiut 1.8 C-------
1306 mocchiut 1.2
1307 mocchiut 1.8 ENDIF
1308 mocchiut 1.5 ENDIF
1309 mocchiut 1.1
1310     C S12 - S31
1311 mocchiut 1.8 dist = ZTOF(2) - ZTOF(5)
1312     dl = 0.
1313     DO I=2,5
1314     dl = dl + TLOUT(i)
1315     ENDDO
1316 pam-de 1.12 F = dl/dist
1317 mocchiut 1.8
1318     C IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1319     IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1320     & (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1321 mocchiut 1.5 t1 = tof12(1,tof12_i,itdc)
1322     t2 = tof12(2,tof12_i,itdc)
1323     t3 = tof31(1,tof31_i,itdc)
1324     t4 = tof31(2,tof31_i,itdc)
1325 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1326     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1327 mocchiut 1.8 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1328     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1329     ds = xhelp1-xhelp2
1330     ihelp=(tof12_i-1)*3+tof31_i
1331     c1 = k_S12S31(1,ihelp)
1332 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrA1
1333 mocchiut 1.8 c2 = k_S12S31(2,ihelp)
1334     beta_a(3) = c2*F/(ds-c1)
1335     C write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1336    
1337     C-------ToF Mask - S12 - S31
1338    
1339     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1340     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1341     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1342     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1343    
1344     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1345     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1346 pam-de 1.12 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1347 mocchiut 1.8 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1348 mocchiut 1.2
1349 mocchiut 1.8 C-------
1350 mocchiut 1.2
1351 mocchiut 1.8 ENDIF
1352 mocchiut 1.5 ENDIF
1353 mocchiut 1.1
1354     C S12 - S32
1355 mocchiut 1.5
1356 mocchiut 1.8 dist = ZTOF(2) - ZTOF(6)
1357     dl = 0.
1358     DO I=2,6
1359     dl = dl + TLOUT(i)
1360     ENDDO
1361 pam-de 1.12 F = dl/dist
1362 mocchiut 1.8
1363     C IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1364     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1365     & (xtofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1366 mocchiut 1.5 t1 = tof12(1,tof12_i,itdc)
1367     t2 = tof12(2,tof12_i,itdc)
1368     t3 = tof32(1,tof32_i,itdc)
1369     t4 = tof32(2,tof32_i,itdc)
1370 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1371     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1372 mocchiut 1.8 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1373     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1374     ds = xhelp1-xhelp2
1375     ihelp=(tof12_i-1)*3+tof32_i
1376     c1 = k_S12S32(1,ihelp)
1377 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrA1
1378 mocchiut 1.8 c2 = k_S12S32(2,ihelp)
1379     beta_a(4) = c2*F/(ds-c1)
1380     C write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1381    
1382     C-------ToF Mask - S12 - S32
1383    
1384     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1385     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1386     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1387     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1388    
1389     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1390     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1391 pam-de 1.12 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1392 mocchiut 1.8 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1393 mocchiut 1.2
1394 mocchiut 1.8 C-------
1395 mocchiut 1.2
1396 mocchiut 1.8 ENDIF
1397 mocchiut 1.5 ENDIF
1398 mocchiut 1.1
1399     C S21 - S31
1400 mocchiut 1.5
1401 mocchiut 1.8 dist = ZTOF(3) - ZTOF(5)
1402     dl = 0.
1403     DO I=3,5
1404     dl = dl + TLOUT(i)
1405     ENDDO
1406 pam-de 1.12 F = dl/dist
1407 mocchiut 1.8
1408     C IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1409     IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1410     & (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1411 mocchiut 1.5 t1 = tof21(1,tof21_i,itdc)
1412     t2 = tof21(2,tof21_i,itdc)
1413     t3 = tof31(1,tof31_i,itdc)
1414     t4 = tof31(2,tof31_i,itdc)
1415 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1416     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1417 mocchiut 1.8 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1418     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1419     ds = xhelp1-xhelp2
1420     ihelp=(tof21_i-1)*3+tof31_i
1421     c1 = k_S21S31(1,ihelp)
1422 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrB1
1423 mocchiut 1.8 c2 = k_S21S31(2,ihelp)
1424     beta_a(5) = c2*F/(ds-c1)
1425    
1426     C-------ToF Mask - S21 - S31
1427    
1428     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1429     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1430     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1431     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1432    
1433     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1434     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1435 pam-de 1.12 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1436 mocchiut 1.8 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1437 mocchiut 1.2
1438 mocchiut 1.8 C-------
1439 mocchiut 1.2
1440 mocchiut 1.8 ENDIF
1441 mocchiut 1.5 ENDIF
1442 mocchiut 1.1
1443     C S21 - S32
1444 mocchiut 1.5
1445 mocchiut 1.8 dist = ZTOF(3) - ZTOF(6)
1446     dl = 0.
1447     DO I=3,6
1448     dl = dl + TLOUT(i)
1449     ENDDO
1450 pam-de 1.12 F = dl/dist
1451 mocchiut 1.8
1452     C IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1453     IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1454     & (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1455 mocchiut 1.5 t1 = tof21(1,tof21_i,itdc)
1456     t2 = tof21(2,tof21_i,itdc)
1457     t3 = tof32(1,tof32_i,itdc)
1458     t4 = tof32(2,tof32_i,itdc)
1459 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1460     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1461 mocchiut 1.8 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1462     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1463     ds = xhelp1-xhelp2
1464     ihelp=(tof21_i-1)*3+tof32_i
1465     c1 = k_S21S32(1,ihelp)
1466 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrB1
1467 mocchiut 1.8 c2 = k_S21S32(2,ihelp)
1468     beta_a(6) = c2*F/(ds-c1)
1469    
1470     C-------ToF Mask - S21 - S32
1471    
1472     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1473     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1474     tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1475     $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1476    
1477     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1478     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1479 pam-de 1.12 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1480 mocchiut 1.8 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1481 mocchiut 1.2
1482 mocchiut 1.8 C-------
1483 mocchiut 1.2
1484 mocchiut 1.8 ENDIF
1485 mocchiut 1.5 ENDIF
1486 mocchiut 1.1
1487     C S22 - S31
1488 mocchiut 1.5
1489 mocchiut 1.8 dist = ZTOF(4) - ZTOF(5)
1490     dl = 0.
1491     DO I=4,5
1492     dl = dl + TLOUT(i)
1493     ENDDO
1494 pam-de 1.12 F = dl/dist
1495 mocchiut 1.17
1496     C WM workaround
1497     dl = dl - 0.06*F
1498     F = dl/dist
1499 mocchiut 1.8
1500     C IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1501     IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1502     & (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1503 mocchiut 1.5 t1 = tof22(1,tof22_i,itdc)
1504     t2 = tof22(2,tof22_i,itdc)
1505     t3 = tof31(1,tof31_i,itdc)
1506     t4 = tof31(2,tof31_i,itdc)
1507 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1508     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1509 mocchiut 1.8 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1510     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1511     ds = xhelp1-xhelp2
1512     ihelp=(tof22_i-1)*3+tof31_i
1513     c1 = k_S22S31(1,ihelp)
1514 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrB1
1515 mocchiut 1.8 c2 = k_S22S31(2,ihelp)
1516     beta_a(7) = c2*F/(ds-c1)
1517    
1518     C-------ToF Mask - S22 - S31
1519    
1520     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1521     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1522     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1523     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1524    
1525     tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1526     $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1527 pam-de 1.12 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1528 mocchiut 1.8 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1529 mocchiut 1.2
1530 mocchiut 1.8 C-------
1531 mocchiut 1.2
1532 mocchiut 1.8 ENDIF
1533 mocchiut 1.5 ENDIF
1534 pam-de 1.12
1535 mocchiut 1.1 C S22 - S32
1536 mocchiut 1.5
1537 mocchiut 1.8 dist = ZTOF(4) - ZTOF(6)
1538     dl = 0.
1539     DO I=4,6
1540     dl = dl + TLOUT(i)
1541     ENDDO
1542 pam-de 1.12 F = dl/dist
1543 mocchiut 1.17
1544     C WM workaround
1545     dl = dl - 0.06*F
1546     F = dl/dist
1547    
1548 mocchiut 1.8
1549     C IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1550     IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1551     & (ytofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1552 mocchiut 1.5 t1 = tof22(1,tof22_i,itdc)
1553     t2 = tof22(2,tof22_i,itdc)
1554     t3 = tof32(1,tof32_i,itdc)
1555     t4 = tof32(2,tof32_i,itdc)
1556 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1557     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1558 mocchiut 1.8 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1559     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1560     ds = xhelp1-xhelp2
1561     ihelp=(tof22_i-1)*3+tof32_i
1562     c1 = k_S22S32(1,ihelp)
1563 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrB1
1564 mocchiut 1.8 c2 = k_S22S32(2,ihelp)
1565     beta_a(8) = c2*F/(ds-c1)
1566    
1567     C-------ToF Mask - S22 - S32
1568    
1569     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1570     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1571     tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1572     $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1573    
1574     tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1575     $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1576 pam-de 1.12 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1577 mocchiut 1.8 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1578 mocchiut 1.2
1579 mocchiut 1.8 C-------
1580 mocchiut 1.2
1581 mocchiut 1.8 ENDIF
1582 mocchiut 1.5 ENDIF
1583 mocchiut 1.1
1584     C S11 - S21
1585 mocchiut 1.5
1586 mocchiut 1.8 dist = ZTOF(1) - ZTOF(3)
1587     dl = 0.
1588     DO I=1,3
1589     dl = dl + TLOUT(i)
1590     ENDDO
1591 pam-de 1.12 F = dl/dist
1592 mocchiut 1.8
1593 mocchiut 1.17 C WM workaround
1594     dl = dl - 0.442*F
1595     F = dl/dist
1596    
1597 mocchiut 1.8 C IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1598     IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1599     & (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1600 mocchiut 1.5 t1 = tof11(1,tof11_i,itdc)
1601     t2 = tof11(2,tof11_i,itdc)
1602     t3 = tof21(1,tof21_i,itdc)
1603     t4 = tof21(2,tof21_i,itdc)
1604 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1605     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1606 mocchiut 1.8 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1607     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1608     ds = xhelp1-xhelp2
1609     ihelp=(tof11_i-1)*2+tof21_i
1610     c1 = k_S11S21(1,ihelp)
1611 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrC1
1612 mocchiut 1.8 c2 = k_S11S21(2,ihelp)
1613     beta_a(9) = c2*F/(ds-c1)
1614    
1615     C-------ToF Mask - S11 - S21
1616    
1617     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1618     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1619     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1620     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1621    
1622     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1623     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1624 pam-de 1.12 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1625 mocchiut 1.8 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1626 mocchiut 1.2
1627 mocchiut 1.8 C-------
1628 mocchiut 1.2
1629 mocchiut 1.8 ENDIF
1630 mocchiut 1.5 ENDIF
1631 pam-de 1.12
1632 mocchiut 1.1 C S11 - S22
1633 mocchiut 1.5
1634 mocchiut 1.8 dist = ZTOF(1) - ZTOF(4)
1635     dl = 0.
1636     DO I=1,4
1637     dl = dl + TLOUT(i)
1638     ENDDO
1639 pam-de 1.12 F = dl/dist
1640 mocchiut 1.8
1641     C IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1642     IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1643     & (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1644 mocchiut 1.5 t1 = tof11(1,tof11_i,itdc)
1645     t2 = tof11(2,tof11_i,itdc)
1646     t3 = tof22(1,tof22_i,itdc)
1647     t4 = tof22(2,tof22_i,itdc)
1648 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1649     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1650 mocchiut 1.8 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1651     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1652     ds = xhelp1-xhelp2
1653     ihelp=(tof11_i-1)*2+tof22_i
1654     c1 = k_S11S22(1,ihelp)
1655 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrC1
1656 mocchiut 1.8 c2 = k_S11S22(2,ihelp)
1657     beta_a(10) = c2*F/(ds-c1)
1658    
1659     C-------ToF Mask - S11 - S22
1660    
1661     tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1662     $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1663     tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1664     $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1665    
1666     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1667     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1668 pam-de 1.12 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1669 mocchiut 1.8 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1670 mocchiut 1.2
1671 mocchiut 1.8 C-------
1672 mocchiut 1.2
1673 mocchiut 1.8 ENDIF
1674 mocchiut 1.5 ENDIF
1675 mocchiut 1.1
1676     C S12 - S21
1677 mocchiut 1.5
1678 mocchiut 1.8 dist = ZTOF(2) - ZTOF(3)
1679     dl = 0.
1680     DO I=2,3
1681     dl = dl + TLOUT(i)
1682     ENDDO
1683 pam-de 1.12 F = dl/dist
1684 mocchiut 1.8
1685 mocchiut 1.17 C WM workaround
1686     dl = dl - 0.442*F
1687     F = dl/dist
1688    
1689 mocchiut 1.8 C IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1690     IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1691     & (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1692 mocchiut 1.5 t1 = tof12(1,tof12_i,itdc)
1693     t2 = tof12(2,tof12_i,itdc)
1694     t3 = tof21(1,tof21_i,itdc)
1695     t4 = tof21(2,tof21_i,itdc)
1696 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1697     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1698 mocchiut 1.8 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1699     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1700     ds = xhelp1-xhelp2
1701     ihelp=(tof12_i-1)*2+tof21_i
1702     c1 = k_S12S21(1,ihelp)
1703 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrC1
1704 mocchiut 1.8 c2 = k_S12S21(2,ihelp)
1705     beta_a(11) = c2*F/(ds-c1)
1706    
1707     C-------ToF Mask - S12 - S21
1708    
1709     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1710     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1711     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1712     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1713    
1714     tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1715     $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1716 pam-de 1.12 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1717 mocchiut 1.8 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1718 mocchiut 1.2
1719 mocchiut 1.8 C-------
1720 mocchiut 1.2
1721 mocchiut 1.8 ENDIF
1722 mocchiut 1.5 ENDIF
1723 mocchiut 1.1
1724     C S12 - S22
1725 mocchiut 1.5
1726 mocchiut 1.8 dist = ZTOF(2) - ZTOF(4)
1727     dl = 0.
1728     DO I=2,4
1729     dl = dl + TLOUT(i)
1730     ENDDO
1731 pam-de 1.12 F = dl/dist
1732 mocchiut 1.8
1733     C IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1734     IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1735     & (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1736 mocchiut 1.5 t1 = tof12(1,tof12_i,itdc)
1737     t2 = tof12(2,tof12_i,itdc)
1738     t3 = tof22(1,tof22_i,itdc)
1739     t4 = tof22(2,tof22_i,itdc)
1740 pam-de 1.12 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1741     & (t3.lt.4095).and.(t4.lt.4095)) THEN
1742 mocchiut 1.8 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1743     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1744     ds = xhelp1-xhelp2
1745     ihelp=(tof12_i-1)*2+tof22_i
1746     c1 = k_S12S22(1,ihelp)
1747 mocchiut 1.15 if (iz.gt.2) c1 = c1 + k1corrC1
1748 mocchiut 1.8 c2 = k_S12S22(2,ihelp)
1749     beta_a(12) = c2*F/(ds-c1)
1750    
1751     C-------ToF Mask - S12 - S22
1752    
1753     tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1754     $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1755     tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1756     $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1757    
1758     tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1759     $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1760 pam-de 1.12 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1761 mocchiut 1.8 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1762 mocchiut 1.2
1763 mocchiut 1.8 C-------
1764 mocchiut 1.2
1765 mocchiut 1.8 ENDIF
1766 mocchiut 1.5 ENDIF
1767 pam-de 1.12
1768 mocchiut 1.1 C-------
1769 mocchiut 1.15 C
1770     C icount=0
1771     C sw=0.
1772     C sxw=0.
1773     C beta_mean=100.
1774     C
1775     C do i=1,12
1776     C if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
1777     C icount= icount+1
1778     C if (i.le.4) w_i=1./(0.13**2.)
1779     C if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1780     C if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1781     C sxw=sxw + beta_a(i)*w_i
1782     C sw =sw + w_i
1783     C endif
1784     C enddo
1785     C
1786     C if (icount.gt.0) beta_mean=sxw/sw
1787     C beta_a(13) = beta_mean
1788     C
1789 pam-de 1.16
1790 mocchiut 1.15 C------- New mean beta calculation
1791 mocchiut 1.1
1792 mocchiut 1.15 do i=1,12
1793     btemp(i) = beta_a(i)
1794     enddo
1795 mocchiut 1.1
1796 pam-de 1.16 beta_a(13)=newbeta(2,btemp,hitvec,10.,10.,20.)
1797 pam-de 1.12
1798 mocchiut 1.15 C-------
1799 mocchiut 1.1
1800 mocchiut 1.8
1801 pam-de 1.12 c IF (tof11_i.GT.none_find)
1802 mocchiut 1.8 c & write(*,*) '11 ',tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
1803 pam-de 1.12 c IF (tof12_i.GT.none_find)
1804 mocchiut 1.8 c & write(*,*) '12 ',tof12(1,tof12_i,itdc),tof12(2,tof12_i,itdc)
1805    
1806 pam-de 1.12 c IF (tof21_i.GT.none_find)
1807 mocchiut 1.8 c & write(*,*) '21 ',tof21(1,tof21_i,itdc),tof21(2,tof21_i,itdc)
1808 pam-de 1.12 c IF (tof22_i.GT.none_find)
1809 mocchiut 1.8 c & write(*,*) '22 ',tof22(1,tof22_i,itdc),tof22(2,tof22_i,itdc)
1810    
1811 pam-de 1.12 c IF (tof31_i.GT.none_find)
1812 mocchiut 1.8 c & write(*,*) '31 ',tof31(1,tof31_i,itdc),tof31(2,tof31_i,itdc)
1813 pam-de 1.12 c IF (tof32_i.GT.none_find)
1814 mocchiut 1.8 c & write(*,*) '32 ',tof32(1,tof32_i,itdc),tof32(2,tof32_i,itdc)
1815    
1816     c write(*,*) xtofpos
1817     c write(*,*) ytofpos
1818 mocchiut 1.11 C write(*,*)'toftrk beta', beta_a
1819 mocchiut 1.8 C write(*,*) adcflagtof
1820 mocchiut 1.11 C write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4)
1821     c write(*,*) 'toftrk'
1822     c write(*,*) xtofpos
1823     c write(*,*) ytofpos
1824     c write(*,*) xtr_tof
1825     c write(*,*) ytr_tof
1826 mocchiut 1.8
1827    
1828 mocchiut 1.1 RETURN
1829     END
1830    
1831    
1832 mocchiut 1.8
1833 mocchiut 1.11
1834     C------------------------------------------------------------------
1835 pam-de 1.12
1836 pam-de 1.16

  ViewVC Help
Powered by ViewVC 1.1.23