/[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.14 by mocchiut, Thu Aug 30 07:59:25 2007 UTC revision 1.22 by mocchiut, Thu Jan 16 15:29:37 2014 UTC
# Line 35  C             at ToF layers Line 35  C             at ToF layers
35  C  aug-07 WM: artificial ADC creation revised: Now an ADC value is created  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  C             only if there is a TDC value (before ADC was created in ANY
37  C             case)  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  C
59  C****************************************************************************  C****************************************************************************
60        IMPLICIT NONE        IMPLICIT NONE
# Line 53  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,pmt_id        integer itof,pmt_id
# Line 62  c     define TOF Z-coordinates Line 83  c     define TOF Z-coordinates
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  c      REAL dx,dy,dr  c      REAL dx,dy,dr
91        REAL ds        REAL ds
92        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
93        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
94        REAL c1,c2,sw,sxw,w_i        REAL(8) yhelp1,yhelp2
95          REAL c1,c2
96    C     REAL sw,sxw,w_i
97        REAL dist,dl,F        REAL dist,dl,F
98        INTEGER icount,ievent        INTEGER ievent
99        REAL xhelp_a,xhelp_t  C      INTEGER icount
100    C      REAL beta_mean
101        REAL beta_mean        REAL btemp(12)
102        REAL hepratio        REAL hepratio
103    
104        INTEGER j        INTEGER j,hitvec(6)
105    
106        real atten,pc_adc        real atten,pc_adc,newbeta
107    C      real check_charge
108    
109    
110        REAL theta,phi        REAL theta,phi
# Line 91  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 117  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
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,xpos        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)
# Line 101  C Line 168  C
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
# Line 113  C Line 183  C
183    
184  *******************************************************************  *******************************************************************
185    
186        ievent = ievent +1         if (ifst.eq.0) then
187           ifst=1
188    
189  C  ratio helium to proton ca. 4  C  ratio helium to proton ca. 4
190        hepratio = 4.        hepratio = 4.
# Line 129  C  ratio helium to proton ca. 4 Line 200  C  ratio helium to proton ca. 4
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 169  C  ratio helium to proton ca. 4 Line 246  C  ratio helium to proton ca. 4
246        ytr_tof(j) = 100.        ytr_tof(j) = 100.
247        enddo        enddo
248    
249    
250  C----------------------------------------------------------------------  C----------------------------------------------------------------------
251  C-------------------------get ToF data --------------------------------  C-------------------------get ToF data --------------------------------
252  C     we cannot use the tofxx(x,x,x)  data  from tofl2com since it is  C     we cannot use the tofxx(x,x,x)  data  from tofl2com since it is
# Line 199  c     put the adc and tdc values from nt Line 277  c     put the adc and tdc values from nt
277           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
278           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
279        enddo        enddo
280    
281        do j=1,2        do j=1,2
282           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
283           tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))           tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))
# Line 280  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  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
# Line 304  c         print *,' TOF - WARNING F77: t Line 401  c         print *,' TOF - WARNING F77: t
401    
402  C---  Fill xtr_tof  and ytr_tof: positions from tracker at ToF layers  C---  Fill xtr_tof  and ytr_tof: positions from tracker at ToF layers
403        do j=1,6        do j=1,6
404        xtr_tof(j) = XOUT(j)        xtr_tof(j) = REAL(XOUT(j)) !EM GCC4.7
405        ytr_tof(j) = YOUT(j)        ytr_tof(j) = REAL(YOUT(j)) !EM GCC4.7
406    c      write(*,*) XOUT(j),YOUT(j)
407        enddo        enddo
408    
409    
# Line 315  C---  convert  angles to radian Line 413  C---  convert  angles to radian
413        THYOUT(j) = 3.1415927*THYOUT(j)/180.        THYOUT(j) = 3.1415927*THYOUT(j)/180.
414        enddo        enddo
415    
416        do j=1,6  c      do j=1,6 !EM GCC 4.7
417  c      write (*,*) j,THXOUT(j),THYOUT(j)  c      write (*,*) j,THXOUT(j),THYOUT(j)
418        enddo  c      enddo !EM GCC4.7
419    
420    
421  C----------------------------------------------------------------------  C----------------------------------------------------------------------
# Line 396  c     S22 2 paddles  15.0 x 9.0 cm Line 494  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    
# Line 502  C--------------S32 --------------------- Line 598  C--------------S32 ---------------------
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--------------------Insert Artifical TDC Value  ---------------------         hitvec(2)=tof12_i
604  C     For each Paddle perform check:         hitvec(3)=tof21_i
605  C     if left paddle=4095  and right paddle OK => create TDC value left         hitvec(4)=tof22_i
606  C     if right paddle=4095  and left paddle OK => create TDC value right         hitvec(5)=tof31_i
607  C-----------------------------------------------------------------------         hitvec(6)=tof32_i
   
 C-----------------------S11 -----------------------------------------  
   
       IF (tof11_i.GT.none_find) THEN  
          xpos = yout(1)  
          i = tof11_i  
          if ((tof11(1,tof11_i,itdc).EQ.4095).AND.  
      &        (tof11(2,tof11_i,itdc).LT.4095)) THEN  
   
 c       write(*,*)'11lb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  
608    
             tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)  
      &           + 2*(y_coor_lin11(tof11_i,offset)  
      &           + xpos*y_coor_lin11(tof11_i,slope))  
609    
610  c       write(*,*)'11laf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  C----------------------------------------------------------------------
611    C--- check charge:
612              tdcflag(ch11a(i),hb11a(i)) = 1  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          ENDIF  C--- if Z>2 we should do a correction to
615           if ((tof11(2,tof11_i,itdc).EQ.4095).AND.  C--- the k1 constants in the beta calculation
616       &        (tof11(1,tof11_i,itdc).LT.4095)) THEN  C----------------------------------------------------------------------
617    
618  c       write(*,*)'11rb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)         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------------------------------------------------------------------
638    
639              tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)         do i=1,3
640       &           - 2*(y_coor_lin11(tof11_i,offset)           xtofpre(i)=100.
641       &           + xpos*y_coor_lin11(tof11_i,slope))           ytofpre(i)=100.
642  c       write(*,*)'11raf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)         enddo
643    
644              tdcflag(ch11b(i),hb11b(i)) = 1  C-----------------------------S1 --------------------------------
          ENDIF  
       ENDIF  
645    
646  C-----------------------S12 -----------------------------------------        IF (tof11_i.GT.none_find) THEN
647          IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
648         +                             (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
652    
653        IF (tof12_i.GT.none_find) THEN        IF (tof12_i.GT.none_find) THEN
654           xpos = xout(2)        IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
655           i = tof12_i       +                             (tof12(2,tof12_i,itdc).LT.2000))
656           if ((tof12(1,tof12_i,itdc).EQ.4095).AND.       +   xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
657       &        (tof12(2,tof12_i,itdc).LT.4095)) THEN       +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
658              tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)        endif
      &           + 2*(x_coor_lin12(tof12_i,offset)  
      &           + xpos*x_coor_lin12(tof12_i,slope))  
             tdcflag(ch12a(i),hb12a(i)) = 1  
          ENDIF  
          if ((tof12(2,tof12_i,itdc).EQ.4095).AND.  
      &        (tof12(1,tof12_i,itdc).LT.4095)) THEN  
             tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)  
      &           - 2*(x_coor_lin12(tof12_i,offset)  
      &           + xpos*x_coor_lin12(tof12_i,slope))  
             tdcflag(ch12b(i),hb12b(i)) = 1  
          ENDIF  
       ENDIF  
659    
 C-----------------------S21 -----------------------------------------  
660    
661        IF (tof21_i.GT.none_find) THEN  C-----------------------------S2 --------------------------------
          xpos = xout(3)  
          i = tof21_i  
          if ((tof21(1,tof21_i,itdc).EQ.4095).AND.  
      &        (tof21(2,tof21_i,itdc).LT.4095)) THEN  
             tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)  
      &           + 2*(x_coor_lin21(tof21_i,offset)  
      &           + xpos*x_coor_lin21(tof21_i,slope))  
             tdcflag(ch21a(i),hb21a(i)) = 1  
          ENDIF  
          if ((tof21(2,tof21_i,itdc).EQ.4095).AND.  
      &        (tof21(1,tof21_i,itdc).LT.4095)) THEN  
             tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)  
      &           - 2*(x_coor_lin21(tof21_i,offset)  
      &           + xpos*x_coor_lin21(tof21_i,slope))  
             tdcflag(ch21b(i),hb21b(i)) = 1  
          ENDIF  
       ENDIF  
662    
663  C-----------------------S22 -----------------------------------------        IF (tof21_i.GT.none_find) THEN
664          IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
665         +                             (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
669    
670        IF (tof22_i.GT.none_find) THEN        IF (tof22_i.GT.none_find) THEN
671           xpos = yout(4)        IF ((tof22(1,tof22_i,itdc).LT.2000).AND.
672           i = tof22_i       +                             (tof22(2,tof22_i,itdc).LT.2000))
673           if ((tof22(1,tof22_i,itdc).EQ.4095).AND.       +    ytofpre(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
674       &        (tof22(2,tof22_i,itdc).LT.4095)) THEN       +    -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
675              tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)        endif
      &           + 2*(y_coor_lin22(tof22_i,offset)  
      &           + xpos*y_coor_lin22(tof22_i,slope))  
             tdcflag(ch22a(i),hb22a(i)) = 1  
          ENDIF  
          if ((tof22(2,tof22_i,itdc).EQ.4095).AND.  
      &        (tof22(1,tof22_i,itdc).LT.4095)) THEN  
             tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)  
      &           - 2*(y_coor_lin22(tof22_i,offset)  
      &           + xpos*y_coor_lin22(tof22_i,slope))  
             tdcflag(ch22b(i),hb22b(i)) = 1  
          ENDIF  
       ENDIF  
676    
 C-----------------------S31 -----------------------------------------  
677    
678        IF (tof31_i.GT.none_find) THEN  C-----------------------------S3 --------------------------------
          xpos = yout(5)  
          i = tof31_i  
          if ((tof31(1,tof31_i,itdc).EQ.4095).AND.  
      &        (tof31(2,tof31_i,itdc).LT.4095)) THEN  
             tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)  
      &           + 2*(y_coor_lin31(tof31_i,offset)  
      &           + xpos*y_coor_lin31(tof31_i,slope))  
             tdcflag(ch31a(i),hb31a(i)) = 1  
          ENDIF  
          if ((tof31(2,tof31_i,itdc).EQ.4095).AND.  
      &        (tof31(1,tof31_i,itdc).LT.4095)) THEN  
             tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)  
      &           - 2*(y_coor_lin31(tof31_i,offset)  
      &           + xpos*y_coor_lin31(tof31_i,slope))  
             tdcflag(ch31b(i),hb31b(i)) = 1  
          ENDIF  
       ENDIF  
679    
680  C-----------------------S32 -----------------------------------------        IF (tof31_i.GT.none_find) THEN
681          IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
682         +                             (tof31(2,tof31_i,itdc).LT.2000))
683         +   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)
685          endif
686    
687        IF (tof32_i.GT.none_find) THEN        IF (tof32_i.GT.none_find) THEN
688           xpos = xout(6)        IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
689           i = tof32_i       +                             (tof32(2,tof32_i,itdc).LT.2000))
690           if ((tof32(1,tof32_i,itdc).EQ.4095).AND.       +   xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
691       &        (tof32(2,tof32_i,itdc).LT.4095)) THEN       +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
692              tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)        endif
693       &           + 2*(x_coor_lin32(tof32_i,offset)  
694       &           + xpos*x_coor_lin32(tof32_i,slope))  
695              tdcflag(ch32a(i),hb32a(i)) = 1  C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
696           ENDIF  
697           if ((tof32(2,tof32_i,itdc).EQ.4095).AND.          if (abs(xtofpre(1)).gt.31.)  xtofpre(1)=100.
698       &        (tof32(1,tof32_i,itdc).LT.4095)) THEN          if (abs(xtofpre(2)).gt.19.)  xtofpre(2)=100.
699              tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)          if (abs(xtofpre(3)).gt.19.)  xtofpre(3)=100.
700       &           - 2*(x_coor_lin32(tof32_i,offset)  
701       &           + xpos*x_coor_lin32(tof32_i,slope))          if (abs(ytofpre(1)).gt.26.)  ytofpre(1)=100.
702              tdcflag(ch32b(i),hb32b(i)) = 1          if (abs(ytofpre(2)).gt.18.)  ytofpre(2)=100.
703           ENDIF          if (abs(ytofpre(3)).gt.18.)  ytofpre(3)=100.
       ENDIF  
704    
705  C--------------------------------------------------------------------  C--------------------------------------------------------------------
706  C---- if paddle hit: if we have TDC value but no ADC, create ADC value  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--------------------------------------------------------------------  C--------------------------------------------------------------------
710  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
711  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/
# Line 662  c     DATA tof32_y/ -5.0,0.0,5.0/ Line 717  c     DATA tof32_y/ -5.0,0.0,5.0/
717    
718  C----------------------------S1 -------------------------------------  C----------------------------S1 -------------------------------------
719    
720        yhelp=yout(1)  c     yhelp=yout(1)
721        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        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           if ((tof11(left,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
727       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
728              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(REAL(THYOUT(1)))/tan(REAL(THXOUT(1))))
729              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(REAL(THXOUT(1)))/cos(phi))
 c            xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))  
730              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
731              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
732              tof11(left,i,iadc)=xkorr/cos(theta)              tof11(left,i,iadc)=xkorr/cos(theta)
733              adcflag(ch11a(i),hb11a(i)) = 1              adcflag(ch11a(i),hb11a(i)) = 1
734           endif           endif
735           if ((tof11(right,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
736       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then
737              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(REAL(THYOUT(1)))/tan(REAL(THXOUT(1))))
738              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(REAL(THXOUT(1)))/cos(phi))
 c            xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))  
739              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
740              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
741              tof11(right,i,iadc)=xkorr/cos(theta)              tof11(right,i,iadc)=xkorr/cos(theta)
742              adcflag(ch11b(i),hb11b(i)) = 1              adcflag(ch11b(i),hb11b(i)) = 1
743           endif           endif
744        ENDIF        ENDIF
745    
746        xhelp=xout(2)  c      xhelp=xout(2)
747        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        xhelp = xtofpre(1)
748          if (xhelp.eq.100) xhelp=REAL(xout(2))
749    
750          IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
751           i = tof12_i           i = tof12_i
752           if ((tof12(left,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
753       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
754              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(REAL(THYOUT(2)))/tan(REAL(THXOUT(2))))
755              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(REAL(THXOUT(2)))/cos(phi))
756  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
757              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
758              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
759              tof12(left,i,iadc) = xkorr/cos(theta)              tof12(left,i,iadc) = xkorr/cos(theta)
760              adcflag(ch12a(i),hb12a(i)) = 1              adcflag(ch12a(i),hb12a(i)) = 1
761           endif           endif
762           if ((tof12(right,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
763       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then
764              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(REAL(THYOUT(2)))/tan(REAL(THXOUT(2))))
765              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(REAL(THXOUT(2)))/cos(phi))
766  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
767              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
768              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
769              tof12(right,i,iadc) = xkorr/cos(theta)              tof12(right,i,iadc) = xkorr/cos(theta)
770              adcflag(ch12b(i),hb12b(i)) = 1              adcflag(ch12b(i),hb12b(i)) = 1
771           endif           endif
# Line 714  c            xkorr=adcx12(right,i,1)*exp Line 773  c            xkorr=adcx12(right,i,1)*exp
773    
774  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
775    
776        xhelp=xout(3)  c      xhelp=xout(3)
777        IF (tof21_i.GT.none_find.AND.abs(xout(3)).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           if ((tof21(left,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
783       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
784              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(REAL(THYOUT(3)))/tan(REAL(THXOUT(3))))
785              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(REAL(THXOUT(3)))/cos(phi))
786  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
787              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
788              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
789              tof21(left,i,iadc) = xkorr/cos(theta)              tof21(left,i,iadc) = xkorr/cos(theta)
790              adcflag(ch21a(i),hb21a(i)) = 1              adcflag(ch21a(i),hb21a(i)) = 1
791           endif           endif
792           if ((tof21(right,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
793       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then
794              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(REAL(THYOUT(3)))/tan(REAL(THXOUT(3))))
795              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(REAL(THXOUT(3)))/cos(phi))
796  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
797              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
798              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
799              tof21(right,i,iadc) = xkorr/cos(theta)              tof21(right,i,iadc) = xkorr/cos(theta)
800              adcflag(ch21b(i),hb21b(i)) = 1              adcflag(ch21b(i),hb21b(i)) = 1
801           endif           endif
802        ENDIF        ENDIF
803    
804    
805        yhelp=yout(4)  c      yhelp=yout(4)
806        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        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           if ((tof22(left,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
812       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
813              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(REAL(THYOUT(4)))/tan(REAL(THXOUT(4))))
814              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(REAL(THXOUT(4)))/cos(phi))
815  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
816              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
817              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
818              tof22(left,i,iadc) = xkorr/cos(theta)              tof22(left,i,iadc) = xkorr/cos(theta)
819              adcflag(ch22a(i),hb22a(i)) = 1              adcflag(ch22a(i),hb22a(i)) = 1
820           endif           endif
821           if ((tof22(right,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
822       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
823              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(REAL(THYOUT(4)))/tan(REAL(THXOUT(4))))
824              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(REAL(THXOUT(4)))/cos(phi))
825  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
826              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
827              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
828              tof22(right,i,iadc) = xkorr/cos(theta)              tof22(right,i,iadc) = xkorr/cos(theta)
829              adcflag(ch22b(i),hb22b(i)) = 1              adcflag(ch22b(i),hb22b(i)) = 1
830           endif           endif
# Line 767  c            xkorr=adcx22(right,i,1)*exp Line 832  c            xkorr=adcx22(right,i,1)*exp
832    
833  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
834    
835        yhelp=yout(5)  c      yhelp=yout(5)
836        IF (tof31_i.GT.none_find.AND.abs(yout(5)).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           if ((tof31(left,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
842       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
843              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(REAL(THYOUT(5)))/tan(REAL(THXOUT(5))))
844              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(REAL(THXOUT(5)))/cos(phi))
845  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
846              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
847              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
848              tof31(left,i,iadc) = xkorr/cos(theta)              tof31(left,i,iadc) = xkorr/cos(theta)
849              adcflag(ch31a(i),hb31a(i)) = 1              adcflag(ch31a(i),hb31a(i)) = 1
850           endif           endif
851           if ((tof31(right,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
852       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then
853              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(REAL(THYOUT(5)))/tan(REAL(THXOUT(5))))
854              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(REAL(THXOUT(5)))/cos(phi))
855  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
856              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
857              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
858              tof31(right,i,iadc) = xkorr/cos(theta)              tof31(right,i,iadc) = xkorr/cos(theta)
859              adcflag(ch31b(i),hb31b(i)) = 1              adcflag(ch31b(i),hb31b(i)) = 1
860           endif           endif
861        ENDIF        ENDIF
862    
863    
864        xhelp=xout(6)  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        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
869           i = tof32_i           i = tof32_i
870           if ((tof32(left,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
871       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then
872              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(REAL(THYOUT(6)))/tan(REAL(THXOUT(6))))
873              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(REAL(THXOUT(6)))/cos(phi))
874  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
875              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
876              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
877              tof32(left,i,iadc) = xkorr/cos(theta)              tof32(left,i,iadc) = xkorr/cos(theta)
878              adcflag(ch32a(i),hb32a(i)) = 1              adcflag(ch32a(i),hb32a(i)) = 1
879           endif           endif
880           if ((tof32(right,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
881       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then
882              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(REAL(THYOUT(6)))/tan(REAL(THXOUT(6))))
883              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(REAL(THXOUT(6)))/cos(phi))
884  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
885              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
886              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
887              tof32(right,i,iadc) = xkorr/cos(theta)              tof32(right,i,iadc) = xkorr/cos(theta)
888              adcflag(ch32b(i),hb32b(i)) = 1              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-----------------------------------------------------------------------
1002    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-----------------------------------------------------------------------
1007    
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------------------------------------------------------------------  C------------------------------------------------------------------
1143  C---  calculate track position in paddle using timing difference  C---  calculate track position in paddle using timing difference
# Line 827  C--------------------------------------- Line 1147  C---------------------------------------
1147           xtofpos(i)=100.           xtofpos(i)=100.
1148           ytofpos(i)=100.           ytofpos(i)=100.
1149        enddo        enddo
1150    
1151  C-----------------------------S1 --------------------------------  C-----------------------------S1 --------------------------------
1152    
1153        IF (tof11_i.GT.none_find) THEN        IF (tof11_i.GT.none_find) THEN
# Line 835  C-----------------------------S1 ------- Line 1156  C-----------------------------S1 -------
1156           ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.           ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
1157       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1158          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
1159          i=tof11_i
1160        endif        endif
1161        endif        endif
1162    
# Line 844  C-----------------------------S1 ------- Line 1166  C-----------------------------S1 -------
1166           xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.           xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
1167       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1168          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
1169          i=tof12_i
1170        endif        endif
1171        endif        endif
1172    
# Line 855  C-----------------------------S2 ------- Line 1178  C-----------------------------S2 -------
1178           xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.           xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
1179       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1180          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
1181          i=tof21_i
1182        endif        endif
1183        endif        endif
1184    
# Line 864  C-----------------------------S2 ------- Line 1188  C-----------------------------S2 -------
1188           ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.           ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
1189       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1190          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
1191          i=tof22_i
1192        endif        endif
1193        endif        endif
1194    
# Line 875  C-----------------------------S3 ------- Line 1200  C-----------------------------S3 -------
1200           ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.           ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
1201       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1202          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
1203          i=tof31_i
1204        endif        endif
1205        endif        endif
1206    
# Line 884  C-----------------------------S3 ------- Line 1210  C-----------------------------S3 -------
1210           xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.           xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
1211       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1212          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
1213          i=tof32_i
1214        endif        endif
1215        endif        endif
1216    
# Line 898  c      enddo Line 1225  c      enddo
1225    
1226    
1227    
   
1228  C--------------------------------------------------------------------  C--------------------------------------------------------------------
1229  C--------------------Time walk correction  -------------------------  C-------------------Corrections on ADC-data -------------------------
 C--------------------------------------------------------------------  
   
   
       DO i=1,8  
          xhelp= 0.  
          xhelp_a = tof11(left,i,iadc)  
          xhelp_t = tof11(left,i,itdc)  
 c          if (xhelp_a .eq.0) write (*,*) 'trk 11 ',i,xhelp_a  
   
          if(xhelp_a<3786) xhelp = tw11(left,i)/sqrt(xhelp_a)  
          tof11(left,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)  
          xhelp_a = tof11(right,i,iadc)  
          xhelp_t = tof11(right,i,itdc)  
          if(xhelp_a<3786) xhelp = tw11(right,i)/sqrt(xhelp_a)  
          tof11(right,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)  
       ENDDO  
   
       DO i=1,6  
          xhelp= 0.  
          xhelp_a = tof12(left,i,iadc)  
          xhelp_t = tof12(left,i,itdc)  
 c          if (xhelp_a .eq.0) write (*,*) 'trk 12 ',i,xhelp_a  
          if(xhelp_a<3786) xhelp = tw12(left,i)/sqrt(xhelp_a)  
          tof12(left,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)  
          xhelp_a = tof12(right,i,iadc)  
          xhelp_t = tof12(right,i,itdc)  
          if(xhelp_a<3786) xhelp = tw12(right,i)/sqrt(xhelp_a)  
          tof12(right,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)  
       ENDDO  
 C----  
       DO i=1,2  
          xhelp= 0.  
          xhelp_a = tof21(left,i,iadc)  
          xhelp_t = tof21(left,i,itdc)  
 c          if (xhelp_a .eq.0) write (*,*) ' trk 21 ',i,xhelp_a  
   
          if(xhelp_a<3786) xhelp = tw21(left,i)/sqrt(xhelp_a)  
          tof21(left,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)  
          xhelp_a = tof21(right,i,iadc)  
          xhelp_t = tof21(right,i,itdc)  
          if(xhelp_a<3786) xhelp = tw21(right,i)/sqrt(xhelp_a)  
          tof21(right,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)  
       ENDDO  
   
       DO i=1,2  
          xhelp= 0.  
          xhelp_a = tof22(left,i,iadc)  
          xhelp_t = tof22(left,i,itdc)  
 c          if (xhelp_a .eq.0) write (*,*) ' trk 22 ',i,xhelp_a  
          if(xhelp_a<3786) xhelp = tw22(left,i)/sqrt(xhelp_a)  
          tof22(left,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)  
          xhelp_a = tof22(right,i,iadc)  
          xhelp_t = tof22(right,i,itdc)  
          if(xhelp_a<3786) xhelp = tw22(right,i)/sqrt(xhelp_a)  
          tof22(right,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)  
       ENDDO  
 C----  
   
       DO i=1,3  
          xhelp= 0.  
          xhelp_a = tof31(left,i,iadc)  
          xhelp_t = tof31(left,i,itdc)  
 c          if (xhelp_a .eq.0) write (*,*) ' trk 31 ',i,xhelp_a  
   
          if(xhelp_a<3786) xhelp = tw31(left,i)/sqrt(xhelp_a)  
          tof31(left,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)  
          xhelp_a = tof31(right,i,iadc)  
          xhelp_t = tof31(right,i,itdc)  
          if(xhelp_a<3786) xhelp = tw31(right,i)/sqrt(xhelp_a)  
          tof31(right,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)  
       ENDDO  
   
       DO i=1,3  
          xhelp= 0.  
          xhelp_a = tof32(left,i,iadc)  
          xhelp_t = tof32(left,i,itdc)  
 c          if (xhelp_a .eq.0) write (*,*) ' trk 32 ',i,xhelp_a  
   
          if(xhelp_a<3786) xhelp = tw32(left,i)/sqrt(xhelp_a)  
          tof32(left,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)  
          xhelp_a = tof32(right,i,iadc)  
          xhelp_t = tof32(right,i,itdc)  
          if(xhelp_a<3786) xhelp = tw32(right,i)/sqrt(xhelp_a)  
          tof32(right,i,itdc) = xhelp_t  + xhelp  
          tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)  
       ENDDO  
   
   
 C---------------------------------------------------------------------  
 C--------------------Corrections on ADC-data -------------------------  
1230  C-----------------angle and ADC(x) correction -----------------------  C-----------------angle and ADC(x) correction -----------------------
1231    C----------------   moved to the new dEdx routine -------------------
1232    
1233  C-----------------------------S1 -------------------------------------  C--------------------------------------------------------------------
   
       yhelp=yout(1)  
   
       phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))  
       theta = atan(tan(THXOUT(1))/cos(phi))  
   
       IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN  
   
          i = tof11_i  
   
          if (tof11(left,i,iadc).lt.3786) then  
 c         if (adc(ch11a(i),hb11a(i)).lt.4095) then  
             tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)  
 c            xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))  
             xkorr = atten(left,11,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr  
          endif  
   
   
          if (tof11(right,i,iadc).lt.3786) then  
 c         if (adc(ch11b(i),hb11b(i)).lt.4095) then  
             tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)  
 c            xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))  
             xkorr = atten(right,11,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
   
       xhelp=xout(2)  
       phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))  
       theta = atan(tan(THXOUT(2))/cos(phi))  
 c      write(*,*) 'theta12 ',theta  
       IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN  
   
          i = tof12_i  
          if (tof12(left,i,iadc).lt.3786) then  
 c         if (adc(ch12a(i),hb12a(i)).lt.4095) then  
             tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)  
 c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  
             xkorr = atten(left,12,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr  
          endif  
   
          if (tof12(right,i,iadc).lt.3786) then  
 c         if (adc(ch12b(i),hb12b(i)).lt.4095) then  
             tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)  
 c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  
             xkorr = atten(right,12,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
 C-----------------------------S2 --------------------------------  
   
       xhelp=xout(3)  
       phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))  
       theta = atan(tan(THXOUT(3))/cos(phi))  
 c      write(*,*) 'theta21 ',theta  
       IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN  
   
          i = tof21_i  
          if (tof21(left,i,iadc).lt.3786) then  
 c         if (adc(ch21a(i),hb21a(i)).lt.4095) then  
             tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)  
 c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  
             xkorr = atten(left,21,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr  
          endif  
   
          if (tof21(right,i,iadc).lt.3786) then  
 c         if (adc(ch21b(i),hb21b(i)).lt.4095) then  
             tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)  
 c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  
             xkorr = atten(right,21,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
       yhelp=yout(4)  
       phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))  
       theta = atan(tan(THXOUT(4))/cos(phi))  
 c      write(*,*) 'theta22 ',theta  
   
       IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN  
   
          i = tof22_i  
          if (tof22(left,i,iadc).lt.3786) then  
 c         if (adc(ch22a(i),hb22a(i)).lt.4095) then  
             tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)  
 c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  
             xkorr = atten(left,22,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr  
          endif  
   
          if (tof22(right,i,iadc).lt.3786) then  
 c         if (adc(ch22b(i),hb22b(i)).lt.4095) then  
             tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)  
 c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  
             xkorr = atten(right,22,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
 C-----------------------------S3 --------------------------------  
   
       yhelp=yout(5)  
       phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))  
       theta = atan(tan(THXOUT(5))/cos(phi))  
 c      write(*,*) 'theta31 ',theta  
   
       IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN  
   
          i = tof31_i  
          if (tof31(left,i,iadc).lt.3786) then  
 c         if (adc(ch31a(i),hb31a(i)).lt.4095) then  
             tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)  
 c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  
             xkorr = atten(left,31,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr  
          endif  
   
          if (tof31(right,i,iadc).lt.3786) then  
 c         if (adc(ch31b(i),hb31b(i)).lt.4095) then  
             tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)  
 c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  
             xkorr = atten(right,31,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
       xhelp=xout(6)  
       phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))  
       theta = atan(tan(THXOUT(6))/cos(phi))  
 c      write(*,*) 'theta32 ',theta  
   
       IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN  
   
          i = tof32_i  
          if (tof32(left,i,iadc).lt.3786) then  
 c         if (adc(ch32a(i),hb32a(i)).lt.4095) then  
             tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)  
 c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  
             xkorr = atten(left,32,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr  
          endif  
   
          if (tof32(right,i,iadc).lt.3786) then  
 c         if (adc(ch32b(i),hb32b(i)).lt.4095) then  
             tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)  
 c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  
             xkorr = atten(right,32,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
 C-----------------------------------------------------------------------  
1234  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1235  C-----------------------------------------------------------------------  C--------------------------------------------------------------------
1236  C-------------------difference of sums  ---------------------------  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 1187  C     instead of cos(theta) use factor F Line 1244  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    C---------------------     S11 - S31  ------------------------
1248    
1249        dist = ZTOF(1) - ZTOF(5)        dist = ZTOF(1) - ZTOF(5)
1250        dl = 0.        dl = 0.
1251        DO I=1,5        DO I=1,5
1252           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1253        ENDDO        ENDDO
1254        F = dl/dist        F = dl/dist
1255    
1256  C     S11 - S31        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  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.        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1260       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1208  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1268  C      IF (tof11_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S11S31(3,ihelp)
1274    c        write(*,*)k_S11S31(1,ihelp),k_S11S31(2,ihelp),k_S11S31(3,ihelp)
1275    c        write(*,*)iz,c1,c2
1276              beta_a(1) = c2*F/(ds-c1)              beta_a(1) = c2*F/(ds-c1)
1277  c       write(*,*) 'S11-S31 ',c1,c2,F  c       write(*,*) 'S11-S31 ',c1,c2,F
1278  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
# Line 1228  C-------ToF Mask - S11 - S31 Line 1291  C-------ToF Mask - S11 - S31
1291           ENDIF           ENDIF
1292        ENDIF        ENDIF
1293    
1294    C---------------------     S11 - S32  ------------------------
1295    
1296        dist = ZTOF(1) - ZTOF(6)        dist = ZTOF(1) - ZTOF(6)
1297        dl = 0.        dl = 0.
1298        DO I=1,6        DO I=1,6
1299           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1300        ENDDO        ENDDO
1301        F = dl/dist        F = dl/dist
1302    
1303  C     S11 - S32        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  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.         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1307       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
# Line 1249  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1315  C      IF (tof11_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S11S32(3,ihelp)
1321              beta_a(2) = c2*F/(ds-c1)              beta_a(2) = c2*F/(ds-c1)
1322  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1323    
# Line 1271  C------- Line 1338  C-------
1338           ENDIF           ENDIF
1339        ENDIF        ENDIF
1340    
1341  C     S12 - S31  C---------------------     S12 - S31  ------------------------
1342    
1343        dist = ZTOF(2) - ZTOF(5)        dist = ZTOF(2) - ZTOF(5)
1344        dl = 0.        dl = 0.
1345        DO I=2,5        DO I=2,5
1346           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1347        ENDDO        ENDDO
1348        F = dl/dist        F = dl/dist
1349    
1350          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1351    
1352  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1353         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1354       &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1292  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1362  C      IF (tof12_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S12S31(3,ihelp)
1368              beta_a(3) = c2*F/(ds-c1)              beta_a(3) = c2*F/(ds-c1)
1369  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1370    
# Line 1314  C------- Line 1385  C-------
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  C      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.         IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
# Line 1336  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1409  C      IF (tof12_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S12S32(3,ihelp)
1415              beta_a(4) = c2*F/(ds-c1)              beta_a(4) = c2*F/(ds-c1)
1416  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1417    
# Line 1358  C------- Line 1432  C-------
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  C      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.         IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1448       &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1380  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1456  C      IF (tof21_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S21S31(3,ihelp)
1462              beta_a(5) = c2*F/(ds-c1)              beta_a(5) = c2*F/(ds-c1)
1463    
1464  C-------ToF Mask - S21 - S31  C-------ToF Mask - S21 - S31
# Line 1401  C------- Line 1478  C-------
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  C      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.         IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1494       &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN       &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
# Line 1423  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1502  C      IF (tof21_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S21S32(3,ihelp)
1508              beta_a(6) = c2*F/(ds-c1)              beta_a(6) = c2*F/(ds-c1)
1509    
1510  C-------ToF Mask - S21 - S32  C-------ToF Mask - S21 - S32
# Line 1444  C------- Line 1524  C-------
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          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  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.         IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1544       &    (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1466  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1552  C      IF (tof22_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S22S31(3,ihelp)
1558              beta_a(7) = c2*F/(ds-c1)              beta_a(7) = c2*F/(ds-c1)
1559    
1560  C-------ToF Mask - S22 - S31  C-------ToF Mask - S22 - S31
# Line 1487  C------- Line 1574  C-------
1574           ENDIF           ENDIF
1575        ENDIF        ENDIF
1576    
1577  C     S22 - S32  C---------------------     S22 - S32  ------------------------
1578    
1579    
1580        dist = ZTOF(4) - ZTOF(6)        dist = ZTOF(4) - ZTOF(6)
1581        dl = 0.        dl = 0.
1582        DO I=4,6        DO I=4,6
1583           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1584        ENDDO        ENDDO
1585        F = dl/dist        F = dl/dist
1586          
1587          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1588    
1589    C WM workaround      
1590          dl = dl - 0.06*F
1591          F = dl/dist
1592    
1593    
1594  C      IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1595         IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
# Line 1509  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1604  C      IF (tof22_i.GT.none_find.AND.tof3
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                if (iz.gt.2) c1 = k_S22S32(3,ihelp)
1610              beta_a(8) = c2*F/(ds-c1)              beta_a(8) = c2*F/(ds-c1)
1611    
1612  C-------ToF Mask - S22 - S32  C-------ToF Mask - S22 - S32
# Line 1530  C------- Line 1626  C-------
1626           ENDIF           ENDIF
1627        ENDIF        ENDIF
1628    
1629  C     S11 - S21  C---------------------     S11 - S21  ------------------------
1630    
1631        dist = ZTOF(1) - ZTOF(3)        dist = ZTOF(1) - ZTOF(3)
1632        dl = 0.        dl = 0.
1633        DO I=1,3        DO I=1,3
1634           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1635        ENDDO        ENDDO
1636        F = dl/dist        F = dl/dist
1637    
1638          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1639    
1640    C WM workaround      
1641          dl = dl - 0.442*F
1642          F = dl/dist
1643    
1644  C      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.         IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1646       &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
# Line 1552  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1654  C      IF (tof11_i.GT.none_find.AND.tof2
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                if (iz.gt.2) c1 = k_S11S21(3,ihelp)
1660              beta_a(9) = c2*F/(ds-c1)              beta_a(9) = c2*F/(ds-c1)
1661    
1662  C-------ToF Mask - S11 - S21  C-------ToF Mask - S11 - S21
# Line 1573  C------- Line 1676  C-------
1676           ENDIF           ENDIF
1677        ENDIF        ENDIF
1678    
1679  C     S11 - S22  C---------------------     S11 - S22  ------------------------
1680    
1681        dist = ZTOF(1) - ZTOF(4)        dist = ZTOF(1) - ZTOF(4)
1682        dl = 0.        dl = 0.
1683        DO I=1,4        DO I=1,4
1684           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1685        ENDDO        ENDDO
1686        F = dl/dist        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  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.         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1692       &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
# Line 1595  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1700  C      IF (tof11_i.GT.none_find.AND.tof2
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                if (iz.gt.2) c1 = k_S11S22(3,ihelp)
1706              beta_a(10) = c2*F/(ds-c1)              beta_a(10) = c2*F/(ds-c1)
1707    
1708  C-------ToF Mask - S11 - S22  C-------ToF Mask - S11 - S22
# Line 1616  C------- Line 1722  C-------
1722           ENDIF           ENDIF
1723        ENDIF        ENDIF
1724    
1725  C     S12 - S21  C---------------------     S12 - S21  ------------------------
1726    
1727        dist = ZTOF(2) - ZTOF(3)        dist = ZTOF(2) - ZTOF(3)
1728        dl = 0.        dl = 0.
1729        DO I=2,3        DO I=2,3
1730           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1731        ENDDO        ENDDO
1732        F = dl/dist        F = dl/dist
1733    
1734          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1735    
1736    C  WM workaround
1737          dl = dl - 0.442*F
1738          F = dl/dist
1739    
1740  C      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.         IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1742       &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
# Line 1638  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1750  C      IF (tof12_i.GT.none_find.AND.tof2
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                if (iz.gt.2) c1 = k_S12S21(3,ihelp)
1756              beta_a(11) = c2*F/(ds-c1)              beta_a(11) = c2*F/(ds-c1)
1757    
1758  C-------ToF Mask - S12 - S21  C-------ToF Mask - S12 - S21
# Line 1659  C------- Line 1772  C-------
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  C      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.         IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1788       &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
# Line 1680  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1795  C      IF (tof12_i.GT.none_find.AND.tof2
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                if (iz.gt.2) c1 = k_S12S22(3,ihelp)
1802              beta_a(12) = c2*F/(ds-c1)              beta_a(12) = c2*F/(ds-c1)
1803    
1804  C-------ToF Mask - S12 - S22  C-------ToF Mask - S12 - S22
# Line 1703  C------- Line 1819  C-------
1819        ENDIF        ENDIF
1820    
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
       sw=0.  
       sxw=0.  
       beta_mean=100.  
1844    
1845        do i=1,12         do i=1,12
1846           if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then           btemp(i) =  beta_a(i)
1847              icount= icount+1         enddo
1848              if (i.le.4) w_i=1./(0.13**2.)  
1849              if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)         beta_a(13)=newbeta(2,btemp,hitvec,10.,10.,20.)
             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  
1850    
1851        if (icount.gt.0) beta_mean=sxw/sw  C-------
       beta_a(13) = beta_mean  
1852    
1853    
1854  c       IF (tof11_i.GT.none_find)  c       IF (tof11_i.GT.none_find)
# Line 1750  c      write(*,*) ytofpos Line 1877  c      write(*,*) ytofpos
1877  c      write(*,*) xtr_tof  c      write(*,*) xtr_tof
1878  c      write(*,*) ytr_tof  c      write(*,*) ytr_tof
1879    
1880    c       write(*,*) '---------  end toftrk ----------'
1881    
1882        RETURN        RETURN
1883        END        END
# Line 1760  c      write(*,*) ytr_tof Line 1887  c      write(*,*) ytr_tof
1887    
1888  C------------------------------------------------------------------  C------------------------------------------------------------------
1889    
1890    

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

  ViewVC Help
Powered by ViewVC 1.1.23