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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

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

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.19

  ViewVC Help
Powered by ViewVC 1.1.23