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

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.20

  ViewVC Help
Powered by ViewVC 1.1.23