/[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.15 - (hide annotations) (download)
Mon Mar 3 09:51:04 2008 UTC (16 years, 9 months ago) by mocchiut
Branch: MAIN
CVS Tags: v5r00
Changes since 1.14: +389 -337 lines
Time-walk corrections implemented

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

  ViewVC Help
Powered by ViewVC 1.1.23