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

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

  ViewVC Help
Powered by ViewVC 1.1.23