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

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

  ViewVC Help
Powered by ViewVC 1.1.23