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

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

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

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

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

  ViewVC Help
Powered by ViewVC 1.1.23