/[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.8 - (hide annotations) (download)
Mon Jan 22 10:45:26 2007 UTC (17 years, 10 months ago) by mocchiut
Branch: MAIN
CVS Tags: v3r00
Changes since 1.7: +1170 -516 lines
ToF routines updated

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

  ViewVC Help
Powered by ViewVC 1.1.23