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

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.23