/[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.12 by pam-de, Mon Aug 20 14:22:33 2007 UTC revision 1.21 by mocchiut, Wed Jul 14 10:00:01 2010 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 62  c     define TOF Z-coordinates Line 82  c     define TOF Z-coordinates
82       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
83       &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)       &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
84    
85          DOUBLE PRECISION dedxtrk
86          DOUBLE PRECISION deflection
87    
88        INTEGER IFAIL        INTEGER IFAIL
89  c      REAL dx,dy,dr  c      REAL dx,dy,dr
90        REAL ds        REAL ds
91        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
92        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
93        REAL c1,c2,sw,sxw,w_i        REAL yhelp1,yhelp2
94          REAL c1,c2
95    C     REAL sw,sxw,w_i
96        REAL dist,dl,F        REAL dist,dl,F
97        INTEGER icount,ievent        INTEGER ievent
98        REAL xhelp_a,xhelp_t  C      INTEGER icount
99    C      REAL beta_mean
100        REAL beta_mean        REAL btemp(12)
101        REAL hepratio        REAL hepratio
102    
103        INTEGER j        INTEGER j,hitvec(6)
104    
105        real atten,pc_adc        real atten,pc_adc,newbeta
106    C      real check_charge
107    
108    
109        REAL theta,phi        REAL theta,phi
# Line 91  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 116  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
116        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
117    
118    
119    C--- new
120          REAL xtofpre(3),ytofpre(3)
121    
122          REAL y_coor_lin11c(8,2),x_coor_lin12c(6,2)
123          REAL x_coor_lin21c(2,2),y_coor_lin22c(2,2)
124          REAL y_coor_lin31c(3,2),x_coor_lin32c(3,2)
125    
126          DATA y_coor_lin11c(1,1),y_coor_lin11c(1,2) /-20.66,-2.497/
127          DATA y_coor_lin11c(2,1),y_coor_lin11c(2,2) /-9.10, -2.52/
128          DATA y_coor_lin11c(3,1),y_coor_lin11c(3,2) /-24.07,-2.12/
129          DATA y_coor_lin11c(4,1),y_coor_lin11c(4,2) /-13.40,-2.47/
130          DATA y_coor_lin11c(5,1),y_coor_lin11c(5,2) /-31.07,-2.32/
131          DATA y_coor_lin11c(6,1),y_coor_lin11c(6,2) /-21.69,-2.63/
132          DATA y_coor_lin11c(7,1),y_coor_lin11c(7,2) /-12.37,-2.65/
133          DATA y_coor_lin11c(8,1),y_coor_lin11c(8,2) /-10.81,-3.15/
134    
135          DATA x_coor_lin12c(1,1),x_coor_lin12c(1,2) /12.96, -2.65/
136          DATA x_coor_lin12c(2,1),x_coor_lin12c(2,2) /17.12,-2.44/
137          DATA x_coor_lin12c(3,1),x_coor_lin12c(3,2) /7.26, -1.98/
138          DATA x_coor_lin12c(4,1),x_coor_lin12c(4,2) /-22.52,-2.27/
139          DATA x_coor_lin12c(5,1),x_coor_lin12c(5,2) /-18.54,-2.28/
140          DATA x_coor_lin12c(6,1),x_coor_lin12c(6,2) /-7.67,-2.15/
141    
142          DATA x_coor_lin21c(1,1),x_coor_lin21c(1,2) /22.56,-1.56/
143          DATA x_coor_lin21c(2,1),x_coor_lin21c(2,2) /13.94,-1.56/
144    
145          DATA y_coor_lin22c(1,1),y_coor_lin22c(1,2) /-24.24,-2.23/
146          DATA y_coor_lin22c(2,1),y_coor_lin22c(2,2) /-45.99,-1.68/
147    
148          DATA y_coor_lin31c(1,1),y_coor_lin31c(1,2) /-22.99,-3.54/
149          DATA y_coor_lin31c(2,1),y_coor_lin31c(2,2) /-42.28,-4.10/
150          DATA y_coor_lin31c(3,1),y_coor_lin31c(3,2) /-41.29,-3.69/
151    
152          DATA x_coor_lin32c(1,1),x_coor_lin32c(1,2) /0.961, -3.22/
153          DATA x_coor_lin32c(2,1),x_coor_lin32c(2,2) /4.98,-3.48/
154          DATA x_coor_lin32c(3,1),x_coor_lin32c(3,2) /-22.08,-3.37/
155    
156    C---
157    
158        INTEGER ihelp        INTEGER ihelp
159        REAL xkorr,xpos        REAL xkorr,xpos
160    
161          INTEGER IZ
162    
163        REAL yl,yh,xl,xh        REAL yl,yh,xl,xh
164  C  C
165        REAL hmemor(9000000)        REAL hmemor(9000000)
# Line 101  C Line 167  C
167  C  C
168        DATA ievent / 0 /        DATA ievent / 0 /
169    
170          INTEGER ifst
171          DATA ifst /0/
172    
173        COMMON / pawcd / hmemor        COMMON / pawcd / hmemor
174        save / pawcd /        save / pawcd /
175  C  C
# Line 113  C Line 182  C
182    
183  *******************************************************************  *******************************************************************
184    
185        ievent = ievent +1         if (ifst.eq.0) then
186           ifst=1
187    
188  C  ratio helium to proton ca. 4  C  ratio helium to proton ca. 4
189        hepratio = 4.        hepratio = 4.
# Line 129  C  ratio helium to proton ca. 4 Line 199  C  ratio helium to proton ca. 4
199        itdc = 1        itdc = 1
200        iadc = 2        iadc = 2
201    
202          ENDIF   ! ifst
203    
204    *******************************************************************
205    
206          ievent = ievent +1
207    
208        do i=1,13        do i=1,13
209           beta_a(i) = 100.           beta_a(i) = 100.
210        enddo        enddo
# Line 169  C  ratio helium to proton ca. 4 Line 245  C  ratio helium to proton ca. 4
245        ytr_tof(j) = 100.        ytr_tof(j) = 100.
246        enddo        enddo
247    
248    
249  C----------------------------------------------------------------------  C----------------------------------------------------------------------
250  C-------------------------get ToF data --------------------------------  C-------------------------get ToF data --------------------------------
251  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 276  c     put the adc and tdc values from nt
276           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
277           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
278        enddo        enddo
279    
280        do j=1,2        do j=1,2
281           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
282           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 357  C     COPY THE ALFA VECTOR FROM AL_PP TO
357        do i=1,5        do i=1,5
358           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
359        enddo        enddo
360          deflection = AL_P(5)
361    *     3) tracker dEdx
362          dedxtrk = trkmip
363        
364  c      write(*,*) AL_P  c      write(*,*) AL_P
365    c      write(*,*) 'Rig, Def, dEdx ',(1./AL_P(5)),AL_P(5),dedxtrk
366    
367    
368    C--  charge selection with tracker using dedx vs. deflection^2  ----
369    
370           yhelp1 = 3.5 + 4.5*deflection*deflection
371           yhelp2 = 9. + 20.*deflection*deflection
372    c       write(*,*) yhelp1,yhelp2
373    
374           iz = 0
375           if  (dedxtrk.lt.yhelp1) iz=1
376           if ((dedxtrk.gt.yhelp1).and.(dedxtrk.lt.yhelp2)) iz=2
377           if  (dedxtrk.gt.yhelp2) iz=3
378    c       write(*,*) 'tracker charge ',iz
379    
380    C--------------------------------------------------------------------
381    
382        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
383           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
384           GOTO 969           GOTO 969
385        ENDIF        ENDIF
386  *     -------- *** tracking routine *** --------  *     -------- *** tracking routine *** --------
# Line 295  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,A Line 391  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,A
391  C     write(*,*) (TLOUT(i),i=1,6)  C     write(*,*) (TLOUT(i),i=1,6)
392    
393        if(IFAIL.ne.0)then        if(IFAIL.ne.0)then
394           print *,' TOF - WARNING F77: tracking failed '  c         print *,' TOF - WARNING F77: tracking failed '
395           goto 969           goto 969
396        endif        endif
397  *     ------------------------------------------  *     ------------------------------------------
# Line 306  C---  Fill xtr_tof  and ytr_tof: positio Line 402  C---  Fill xtr_tof  and ytr_tof: positio
402        do j=1,6        do j=1,6
403        xtr_tof(j) = XOUT(j)        xtr_tof(j) = XOUT(j)
404        ytr_tof(j) = YOUT(j)        ytr_tof(j) = YOUT(j)
405    c      write(*,*) XOUT(j),YOUT(j)
406        enddo        enddo
407    
408    
# Line 396  c     S22 2 paddles  15.0 x 9.0 cm Line 493  c     S22 2 paddles  15.0 x 9.0 cm
493  c     S31 3 paddles  15.0 x 6.0 cm  c     S31 3 paddles  15.0 x 6.0 cm
494  c     S32 3 paddles  18.0 x 5.0 cm  c     S32 3 paddles  18.0 x 5.0 cm
495    
 c     write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)  
 c     write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)  
496    
497  C--------------S11 --------------------------------------  C--------------S11 --------------------------------------
498    
# Line 502  C--------------S32 --------------------- Line 597  C--------------S32 ---------------------
597        endif        endif
598    
599    
 C     write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i  
   
 C-----------------------------------------------------------------------  
 C--------------------Insert Artifical TDC Value  ---------------------  
 C     For each Paddle perform check:  
 C     if left paddle=4095  and right paddle OK => create TDC value left  
 C     if right paddle=4095  and left paddle OK => create TDC value right  
 C-----------------------------------------------------------------------  
   
 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  
600    
601  c       write(*,*)'11lb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)         hitvec(1)=tof11_i
602           hitvec(2)=tof12_i
603           hitvec(3)=tof21_i
604           hitvec(4)=tof22_i
605           hitvec(5)=tof31_i
606           hitvec(6)=tof32_i
607    
             tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)  
      &           + 2*(y_coor_lin11(tof11_i,offset)  
      &           + xpos*y_coor_lin11(tof11_i,slope))  
608    
609  c       write(*,*)'11laf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  C----------------------------------------------------------------------
610    C--- check charge:
611    C--- if Z=2 we should use the attenuation curve for helium to
612    C--- fill the artificail ADC values and NOT divide by "hepratio"
613    C--- if Z>2 we should do a correction to
614    C--- the k1 constants in the beta calculation
615    C----------------------------------------------------------------------
616    
617              tdcflag(ch11a(i),hb11a(i)) = 1         theta=0.  
618           dist = ZTOF(1) - ZTOF(5)
619           dl = 0.
620           DO I=1,5
621             dl = dl + TLOUT(i)
622           ENDDO
623           F = dl/dist
624           theta = acos(1/F)
625    
626    c       iz = int(check_charge(theta,hitvec))
627    c       write(*,*) 'in toftrk',iz
628    
         ENDIF  
          if ((tof11(2,tof11_i,itdc).EQ.4095).AND.  
      &        (tof11(1,tof11_i,itdc).LT.4095)) THEN  
629    
630  c       write(*,*)'11rb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  C-------------------------------  new  ---------------------------
631    C--  calculate track position in paddle using timing difference
632    C--  this calculation is preliminary and uses some standard
633    C--  calibration values, but we need to find a rough position to
634    C--  be able to calculate artificial ADC values (needed for the
635    C--  timewalk...
636    C------------------------------------------------------------------
637    
638              tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)         do i=1,3
639       &           - 2*(y_coor_lin11(tof11_i,offset)           xtofpre(i)=100.
640       &           + xpos*y_coor_lin11(tof11_i,slope))           ytofpre(i)=100.
641  c       write(*,*)'11raf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)         enddo
642    
643              tdcflag(ch11b(i),hb11b(i)) = 1  C-----------------------------S1 --------------------------------
          ENDIF  
       ENDIF  
644    
645  C-----------------------S12 -----------------------------------------        IF (tof11_i.GT.none_find) THEN
646          IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
647         +                             (tof11(2,tof11_i,itdc).LT.2000))
648         +   ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
649         +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
650          endif
651    
652        IF (tof12_i.GT.none_find) THEN        IF (tof12_i.GT.none_find) THEN
653           xpos = xout(2)        IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
654           i = tof12_i       +                             (tof12(2,tof12_i,itdc).LT.2000))
655           if ((tof12(1,tof12_i,itdc).EQ.4095).AND.       +   xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
656       &        (tof12(2,tof12_i,itdc).LT.4095)) THEN       +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
657              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  
658    
 C-----------------------S21 -----------------------------------------  
659    
660        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  
661    
662  C-----------------------S22 -----------------------------------------        IF (tof21_i.GT.none_find) THEN
663          IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
664         +                             (tof21(2,tof21_i,itdc).LT.2000))
665         +   xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
666         +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
667          endif
668    
669        IF (tof22_i.GT.none_find) THEN        IF (tof22_i.GT.none_find) THEN
670           xpos = yout(4)        IF ((tof22(1,tof22_i,itdc).LT.2000).AND.
671           i = tof22_i       +                             (tof22(2,tof22_i,itdc).LT.2000))
672           if ((tof22(1,tof22_i,itdc).EQ.4095).AND.       +    ytofpre(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
673       &        (tof22(2,tof22_i,itdc).LT.4095)) THEN       +    -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
674              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  
675    
 C-----------------------S31 -----------------------------------------  
676    
677        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  
678    
679  C-----------------------S32 -----------------------------------------        IF (tof31_i.GT.none_find) THEN
680          IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
681         +                             (tof31(2,tof31_i,itdc).LT.2000))
682         +   ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
683         +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
684          endif
685    
686        IF (tof32_i.GT.none_find) THEN        IF (tof32_i.GT.none_find) THEN
687           xpos = xout(6)        IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
688           i = tof32_i       +                             (tof32(2,tof32_i,itdc).LT.2000))
689           if ((tof32(1,tof32_i,itdc).EQ.4095).AND.       +   xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
690       &        (tof32(2,tof32_i,itdc).LT.4095)) THEN       +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
691              tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)        endif
692       &           + 2*(x_coor_lin32(tof32_i,offset)  
693       &           + xpos*x_coor_lin32(tof32_i,slope))  
694              tdcflag(ch32a(i),hb32a(i)) = 1  C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
695           ENDIF  
696           if ((tof32(2,tof32_i,itdc).EQ.4095).AND.          if (abs(xtofpre(1)).gt.31.)  xtofpre(1)=100.
697       &        (tof32(1,tof32_i,itdc).LT.4095)) THEN          if (abs(xtofpre(2)).gt.19.)  xtofpre(2)=100.
698              tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)          if (abs(xtofpre(3)).gt.19.)  xtofpre(3)=100.
699       &           - 2*(x_coor_lin32(tof32_i,offset)  
700       &           + xpos*x_coor_lin32(tof32_i,slope))          if (abs(ytofpre(1)).gt.26.)  ytofpre(1)=100.
701              tdcflag(ch32b(i),hb32b(i)) = 1          if (abs(ytofpre(2)).gt.18.)  ytofpre(2)=100.
702           ENDIF          if (abs(ytofpre(3)).gt.18.)  ytofpre(3)=100.
       ENDIF  
703    
704  C--------------------------------------------------------------------  C--------------------------------------------------------------------
705  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
706    C---- use the "pre" position if possible, since this gives better time
707    C---- resolution ... october 2008
708  C--------------------------------------------------------------------  C--------------------------------------------------------------------
709  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
710  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 716  c     DATA tof32_y/ -5.0,0.0,5.0/
716    
717  C----------------------------S1 -------------------------------------  C----------------------------S1 -------------------------------------
718    
719        yhelp=yout(1)  c     yhelp=yout(1)
720        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        yhelp = ytofpre(1)
721          if (yhelp.eq.100) yhelp=yout(1)
722    
723          IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
724           i = tof11_i           i = tof11_i
725           if ((tof11(left,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
726       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
727              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
728              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(THXOUT(1))/cos(phi))
 c            xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))  
729              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
730              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
731              tof11(left,i,iadc)=xkorr/cos(theta)              tof11(left,i,iadc)=xkorr/cos(theta)
732              adcflag(ch11a(i),hb11a(i)) = 1              adcflag(ch11a(i),hb11a(i)) = 1
733           endif           endif
734           if ((tof11(right,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
735       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then
736              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
737              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(THXOUT(1))/cos(phi))
 c            xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))  
738              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
739              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
740              tof11(right,i,iadc)=xkorr/cos(theta)              tof11(right,i,iadc)=xkorr/cos(theta)
741              adcflag(ch11b(i),hb11b(i)) = 1              adcflag(ch11b(i),hb11b(i)) = 1
742           endif           endif
743        ENDIF        ENDIF
744    
745        xhelp=xout(2)  c      xhelp=xout(2)
746        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        xhelp = xtofpre(1)
747          if (xhelp.eq.100) xhelp=xout(2)
748    
749          IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
750           i = tof12_i           i = tof12_i
751           if ((tof12(left,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
752       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
753              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
754              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
755  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
756              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
757              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
758              tof12(left,i,iadc) = xkorr/cos(theta)              tof12(left,i,iadc) = xkorr/cos(theta)
759              adcflag(ch12a(i),hb12a(i)) = 1              adcflag(ch12a(i),hb12a(i)) = 1
760           endif           endif
761           if ((tof12(right,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
762       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then
763              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
764              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
765  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
766              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
767              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
768              tof12(right,i,iadc) = xkorr/cos(theta)              tof12(right,i,iadc) = xkorr/cos(theta)
769              adcflag(ch12b(i),hb12b(i)) = 1              adcflag(ch12b(i),hb12b(i)) = 1
770           endif           endif
# Line 714  c            xkorr=adcx12(right,i,1)*exp Line 772  c            xkorr=adcx12(right,i,1)*exp
772    
773  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
774    
775        xhelp=xout(3)  c      xhelp=xout(3)
776        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN        xhelp = xtofpre(2)
777          if (xhelp.eq.100) xhelp=xout(3)
778    
779          IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
780           i = tof21_i           i = tof21_i
781           if ((tof21(left,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
782       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
783              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
784              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
785  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
786              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
787              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
788              tof21(left,i,iadc) = xkorr/cos(theta)              tof21(left,i,iadc) = xkorr/cos(theta)
789              adcflag(ch21a(i),hb21a(i)) = 1              adcflag(ch21a(i),hb21a(i)) = 1
790           endif           endif
791           if ((tof21(right,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
792       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then
793              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
794              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
795  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
796              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
797              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
798              tof21(right,i,iadc) = xkorr/cos(theta)              tof21(right,i,iadc) = xkorr/cos(theta)
799              adcflag(ch21b(i),hb21b(i)) = 1              adcflag(ch21b(i),hb21b(i)) = 1
800           endif           endif
801        ENDIF        ENDIF
802    
803    
804        yhelp=yout(4)  c      yhelp=yout(4)
805        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        yhelp = ytofpre(2)
806          if (yhelp.eq.100) yhelp=yout(4)
807    
808          IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
809           i = tof22_i           i = tof22_i
810           if ((tof22(left,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
811       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
812              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
813              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
814  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
815              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
816              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
817              tof22(left,i,iadc) = xkorr/cos(theta)              tof22(left,i,iadc) = xkorr/cos(theta)
818              adcflag(ch22a(i),hb22a(i)) = 1              adcflag(ch22a(i),hb22a(i)) = 1
819           endif           endif
820           if ((tof22(right,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
821       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
822              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
823              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
824  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
825              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
826              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
827              tof22(right,i,iadc) = xkorr/cos(theta)              tof22(right,i,iadc) = xkorr/cos(theta)
828              adcflag(ch22b(i),hb22b(i)) = 1              adcflag(ch22b(i),hb22b(i)) = 1
829           endif           endif
# Line 767  c            xkorr=adcx22(right,i,1)*exp Line 831  c            xkorr=adcx22(right,i,1)*exp
831    
832  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
833    
834        yhelp=yout(5)  c      yhelp=yout(5)
835        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN        yhelp = ytofpre(3)
836          if (yhelp.eq.100) yhelp=yout(5)
837    
838          IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
839           i = tof31_i           i = tof31_i
840           if ((tof31(left,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
841       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
842              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
843              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
844  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
845              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
846              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
847              tof31(left,i,iadc) = xkorr/cos(theta)              tof31(left,i,iadc) = xkorr/cos(theta)
848              adcflag(ch31a(i),hb31a(i)) = 1              adcflag(ch31a(i),hb31a(i)) = 1
849           endif           endif
850           if ((tof31(right,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
851       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then
852              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
853              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
854  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
855              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
856              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
857              tof31(right,i,iadc) = xkorr/cos(theta)              tof31(right,i,iadc) = xkorr/cos(theta)
858              adcflag(ch31b(i),hb31b(i)) = 1              adcflag(ch31b(i),hb31b(i)) = 1
859           endif           endif
860        ENDIF        ENDIF
861    
862    
863        xhelp=xout(6)  c      xhelp=xout(6)
864          xhelp = xtofpre(3)
865          if (xhelp.eq.100) xhelp=xout(6)
866    
867        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
868           i = tof32_i           i = tof32_i
869           if ((tof32(left,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
870       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then
871              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
872              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
873  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
874              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
875              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
876              tof32(left,i,iadc) = xkorr/cos(theta)              tof32(left,i,iadc) = xkorr/cos(theta)
877              adcflag(ch32a(i),hb32a(i)) = 1              adcflag(ch32a(i),hb32a(i)) = 1
878           endif           endif
879           if ((tof32(right,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
880       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then
881              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
882              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
883  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
884              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
885              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
886              tof32(right,i,iadc) = xkorr/cos(theta)              tof32(right,i,iadc) = xkorr/cos(theta)
887              adcflag(ch32b(i),hb32b(i)) = 1              adcflag(ch32b(i),hb32b(i)) = 1
888           endif           endif
889        ENDIF        ENDIF
890    
891    C-------------------------------------------------------------------
892    C Now there is for each hitted paddle a TDC and ADC value, if the
893    C TDC was < 4095.
894    C There might be also TDC-ADC pairs in paddles not hitted
895    C Let's correct the raw TDC value with the time walk
896    C-------------------------------------------------------------------
897    C--------------------Time walk correction  -------------------------
898    C-------------------------------------------------------------------
899    
900          DO i=1,8
901             if ((tdc(ch11a(i),hb11a(i)).lt.4095).and.
902         &             (tof11(left,i,iadc).lt.3786)) THEN
903             xhelp = tw11(left,i)/(tof11(left,i,iadc)**0.5)
904             tof11(left,i,itdc) = tof11(left,i,itdc) + xhelp
905             tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
906                                                  ENDIF
907    
908             if ((tdc(ch11b(i),hb11b(i)).lt.4095).and.
909         &             (tof11(right,i,iadc).lt.3786)) THEN
910             xhelp = tw11(right,i)/(tof11(right,i,iadc)**0.5)
911             tof11(right,i,itdc) = tof11(right,i,itdc) + xhelp
912             tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
913                                                 ENDIF
914          ENDDO
915    
916    
917          DO i=1,6
918             if ((tdc(ch12a(i),hb12a(i)).lt.4095).and.
919         &             (tof12(left,i,iadc).lt.3786)) THEN
920             xhelp = tw12(left,i)/(tof12(left,i,iadc)**0.5)
921             tof12(left,i,itdc) = tof12(left,i,itdc) + xhelp
922             tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
923                                                  ENDIF
924    
925             if ((tdc(ch12b(i),hb12b(i)).lt.4095).and.
926         &             (tof12(right,i,iadc).lt.3786)) THEN
927             xhelp = tw12(right,i)/(tof12(right,i,iadc)**0.5)
928             tof12(right,i,itdc) = tof12(right,i,itdc) + xhelp
929             tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
930                                                 ENDIF
931          ENDDO
932    
933    C----
934          DO I=1,2
935             if ((tdc(ch21a(i),hb21a(i)).lt.4095).and.
936         &             (tof21(left,i,iadc).lt.3786)) THEN
937             xhelp = tw21(left,i)/(tof21(left,i,iadc)**0.5)
938             tof21(left,i,itdc) = tof21(left,i,itdc) + xhelp
939             tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
940                                                  ENDIF
941    
942             if ((tdc(ch21b(i),hb21b(i)).lt.4095).and.
943         &             (tof21(right,i,iadc).lt.3786)) THEN
944             xhelp = tw21(right,i)/(tof21(right,i,iadc)**0.5)
945             tof21(right,i,itdc) = tof21(right,i,itdc) + xhelp
946             tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
947                                                 ENDIF
948          ENDDO
949    
950          DO I=1,2
951             if ((tdc(ch22a(i),hb22a(i)).lt.4095).and.
952         &             (tof22(left,i,iadc).lt.3786)) THEN
953             xhelp = tw22(left,i)/(tof22(left,i,iadc)**0.5)
954             tof22(left,i,itdc) = tof22(left,i,itdc) + xhelp
955             tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
956                                                  ENDIF
957    
958             if ((tdc(ch22b(i),hb22b(i)).lt.4095).and.
959         &             (tof22(right,i,iadc).lt.3786)) THEN
960             xhelp = tw22(right,i)/(tof22(right,i,iadc)**0.5)
961             tof22(right,i,itdc) = tof22(right,i,itdc) + xhelp
962             tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
963                                                 ENDIF
964          ENDDO
965    
966    C----
967          DO I=1,3
968             if ((tdc(ch31a(i),hb31a(i)).lt.4095).and.
969         &             (tof31(left,i,iadc).lt.3786)) THEN
970             xhelp = tw31(left,i)/(tof31(left,i,iadc)**0.5)
971             tof31(left,i,itdc) = tof31(left,i,itdc) + xhelp
972             tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
973                                                  ENDIF
974    
975             if ((tdc(ch31b(i),hb31b(i)).lt.4095).and.
976         &             (tof31(right,i,iadc).lt.3786)) THEN
977             xhelp = tw31(right,i)/(tof31(right,i,iadc)**0.5)
978             tof31(right,i,itdc) = tof31(right,i,itdc) + xhelp
979             tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
980                                                 ENDIF
981          ENDDO
982    
983          DO I=1,3
984             if ((tdc(ch32a(i),hb32a(i)).lt.4095).and.
985         &             (tof32(left,i,iadc).lt.3786)) THEN
986             xhelp = tw32(left,i)/(tof32(left,i,iadc)**0.5)
987             tof32(left,i,itdc) = tof32(left,i,itdc) + xhelp
988             tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
989                                                  ENDIF
990    
991             if ((tdc(ch32b(i),hb32b(i)).lt.4095).and.
992         &             (tof32(right,i,iadc).lt.3786)) THEN
993             xhelp = tw32(right,i)/(tof32(right,i,iadc)**0.5)
994             tof32(right,i,itdc) = tof32(right,i,itdc) + xhelp
995             tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
996                                                 ENDIF
997          ENDDO
998    
999    
1000    C-----------------------------------------------------------------------
1001    C--------------------Insert Artifical TDC Value  ---------------------
1002    C     For each Paddle perform check:
1003    C     if left paddle=4095  and right paddle OK => create TDC value left
1004    C     if right paddle=4095  and left paddle OK => create TDC value right
1005    C-----------------------------------------------------------------------
1006    
1007    C-----------------------S11 -----------------------------------------
1008    
1009          IF (tof11_i.GT.none_find) THEN
1010             xpos = yout(1)
1011             i = tof11_i
1012            if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.
1013         &          (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN
1014              tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)
1015         &           + 2*(y_coor_lin11(tof11_i,offset)
1016         &           + xpos*y_coor_lin11(tof11_i,slope))
1017                tdcflag(ch11a(i),hb11a(i)) = 1
1018            ENDIF
1019    
1020            if ((tdc(ch11b(i),hb11b(i)).EQ.4095).AND.
1021         &          (tdc(ch11a(i),hb11a(i)).LT.4095)) THEN
1022                tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)
1023         &           - 2*(y_coor_lin11(tof11_i,offset)
1024         &           + xpos*y_coor_lin11(tof11_i,slope))
1025                tdcflag(ch11b(i),hb11b(i)) = 1
1026             ENDIF
1027    
1028          ENDIF
1029    
1030    C-----------------------S12 -----------------------------------------
1031    
1032          IF (tof12_i.GT.none_find) THEN
1033             xpos = xout(2)
1034             i = tof12_i
1035            if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.
1036         &          (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN
1037                tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)
1038         &           + 2*(x_coor_lin12(tof12_i,offset)
1039         &           + xpos*x_coor_lin12(tof12_i,slope))
1040                tdcflag(ch12a(i),hb12a(i)) = 1
1041             ENDIF
1042    
1043            if ((tdc(ch12b(i),hb12b(i)).EQ.4095).AND.
1044         &          (tdc(ch12a(i),hb12a(i)).LT.4095)) THEN
1045                tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)
1046         &           - 2*(x_coor_lin12(tof12_i,offset)
1047         &           + xpos*x_coor_lin12(tof12_i,slope))
1048                tdcflag(ch12b(i),hb12b(i)) = 1
1049             ENDIF
1050          ENDIF
1051    
1052    C-----------------------S21 -----------------------------------------
1053    
1054          IF (tof21_i.GT.none_find) THEN
1055             xpos = xout(3)
1056             i = tof21_i
1057            if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.
1058         &          (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN
1059                tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)
1060         &           + 2*(x_coor_lin21(tof21_i,offset)
1061         &           + xpos*x_coor_lin21(tof21_i,slope))
1062                tdcflag(ch21a(i),hb21a(i)) = 1
1063             ENDIF
1064    
1065            if ((tdc(ch21b(i),hb21b(i)).EQ.4095).AND.
1066         &          (tdc(ch21a(i),hb21a(i)).LT.4095)) THEN
1067                tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)
1068         &           - 2*(x_coor_lin21(tof21_i,offset)
1069         &           + xpos*x_coor_lin21(tof21_i,slope))
1070                tdcflag(ch21b(i),hb21b(i)) = 1
1071             ENDIF
1072          ENDIF
1073    
1074    C-----------------------S22 -----------------------------------------
1075    
1076          IF (tof22_i.GT.none_find) THEN
1077             xpos = yout(4)
1078             i = tof22_i
1079            if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.
1080         &          (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN
1081                tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)
1082         &           + 2*(y_coor_lin22(tof22_i,offset)
1083         &           + xpos*y_coor_lin22(tof22_i,slope))
1084                tdcflag(ch22a(i),hb22a(i)) = 1
1085             ENDIF
1086    
1087            if ((tdc(ch22b(i),hb22b(i)).EQ.4095).AND.
1088         &          (tdc(ch22a(i),hb22a(i)).LT.4095)) THEN
1089                tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)
1090         &           - 2*(y_coor_lin22(tof22_i,offset)
1091         &           + xpos*y_coor_lin22(tof22_i,slope))
1092                tdcflag(ch22b(i),hb22b(i)) = 1
1093             ENDIF
1094          ENDIF
1095    
1096    C-----------------------S31 -----------------------------------------
1097    
1098          IF (tof31_i.GT.none_find) THEN
1099             xpos = yout(5)
1100             i = tof31_i
1101            if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.
1102         &          (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN
1103                tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)
1104         &           + 2*(y_coor_lin31(tof31_i,offset)
1105         &           + xpos*y_coor_lin31(tof31_i,slope))
1106                tdcflag(ch31a(i),hb31a(i)) = 1
1107             ENDIF
1108    
1109            if ((tdc(ch31b(i),hb31b(i)).EQ.4095).AND.
1110         &          (tdc(ch31a(i),hb31a(i)).LT.4095)) THEN
1111                tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)
1112         &           - 2*(y_coor_lin31(tof31_i,offset)
1113         &           + xpos*y_coor_lin31(tof31_i,slope))
1114                tdcflag(ch31b(i),hb31b(i)) = 1
1115             ENDIF
1116          ENDIF
1117    
1118    C-----------------------S32 -----------------------------------------
1119    
1120          IF (tof32_i.GT.none_find) THEN
1121             xpos = xout(6)
1122             i = tof32_i
1123            if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.
1124         &          (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN
1125                tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)
1126         &           + 2*(x_coor_lin32(tof32_i,offset)
1127         &           + xpos*x_coor_lin32(tof32_i,slope))
1128                tdcflag(ch32a(i),hb32a(i)) = 1
1129             ENDIF
1130    
1131            if ((tdc(ch32b(i),hb32b(i)).EQ.4095).AND.
1132         &          (tdc(ch32a(i),hb32a(i)).LT.4095)) THEN
1133                tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)
1134         &           - 2*(x_coor_lin32(tof32_i,offset)
1135         &           + xpos*x_coor_lin32(tof32_i,slope))
1136                tdcflag(ch32b(i),hb32b(i)) = 1
1137             ENDIF
1138          ENDIF
1139    
1140    
1141  C------------------------------------------------------------------  C------------------------------------------------------------------
1142  C---  calculate track position in paddle using timing difference  C---  calculate track position in paddle using timing difference
# Line 827  C--------------------------------------- Line 1146  C---------------------------------------
1146           xtofpos(i)=100.           xtofpos(i)=100.
1147           ytofpos(i)=100.           ytofpos(i)=100.
1148        enddo        enddo
1149    
1150  C-----------------------------S1 --------------------------------  C-----------------------------S1 --------------------------------
1151    
1152        IF (tof11_i.GT.none_find) THEN        IF (tof11_i.GT.none_find) THEN
# Line 835  C-----------------------------S1 ------- Line 1155  C-----------------------------S1 -------
1155           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.
1156       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1157          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
1158          i=tof11_i
1159        endif        endif
1160        endif        endif
1161    
# Line 844  C-----------------------------S1 ------- Line 1165  C-----------------------------S1 -------
1165           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.
1166       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1167          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
1168          i=tof12_i
1169        endif        endif
1170        endif        endif
1171    
# Line 855  C-----------------------------S2 ------- Line 1177  C-----------------------------S2 -------
1177           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.
1178       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1179          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
1180          i=tof21_i
1181        endif        endif
1182        endif        endif
1183    
# Line 864  C-----------------------------S2 ------- Line 1187  C-----------------------------S2 -------
1187           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.
1188       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1189          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
1190          i=tof22_i
1191        endif        endif
1192        endif        endif
1193    
# Line 875  C-----------------------------S3 ------- Line 1199  C-----------------------------S3 -------
1199           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.
1200       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1201          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
1202          i=tof31_i
1203        endif        endif
1204        endif        endif
1205    
# Line 884  C-----------------------------S3 ------- Line 1209  C-----------------------------S3 -------
1209           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.
1210       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1211          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
1212          i=tof32_i
1213        endif        endif
1214        endif        endif
1215    
# Line 898  c      enddo Line 1224  c      enddo
1224    
1225    
1226    
   
1227  C--------------------------------------------------------------------  C--------------------------------------------------------------------
1228  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)  
           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)  
           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)  
           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)  
           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)  
           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)  
           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 -------------------------  
1229  C-----------------angle and ADC(x) correction -----------------------  C-----------------angle and ADC(x) correction -----------------------
1230    C----------------   moved to the new dEdx routine -------------------
1231    
1232  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-----------------------------------------------------------------------  
1233  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1234  C-----------------------------------------------------------------------  C--------------------------------------------------------------------
1235  C-------------------difference of sums  ---------------------------  C---------------------difference of sums  ---------------------------
1236  C  C
1237  C     DS = (t1+t2) - t3+t4)  C     DS = (t1+t2) - t3+t4)
1238  C     DS = c1 + c2/beta*cos(theta)  C     DS = c1 + c2/beta*cos(theta)
# Line 1187  C     instead of cos(theta) use factor F Line 1243  C     instead of cos(theta) use factor F
1243  C     F =  pathlength/d  C     F =  pathlength/d
1244  C     => beta = c2*F/(DS-c1))  C     => beta = c2*F/(DS-c1))
1245    
1246    C---------------------     S11 - S31  ------------------------
1247    
1248        dist = ZTOF(1) - ZTOF(5)        dist = ZTOF(1) - ZTOF(5)
1249        dl = 0.        dl = 0.
1250        DO I=1,5        DO I=1,5
# Line 1194  C     => beta = c2*F/(DS-c1)) Line 1252  C     => beta = c2*F/(DS-c1))
1252        ENDDO        ENDDO
1253        F = dl/dist        F = dl/dist
1254    
1255  C     S11 - S31        c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1256    
1257  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1258        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1259       &    (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 1267  C      IF (tof11_i.GT.none_find.AND.tof3
1267              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1268              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1269              ihelp=(tof11_i-1)*3+tof31_i              ihelp=(tof11_i-1)*3+tof31_i
1270              c1 = k_S11S31(1,ihelp)              if (iz.le.1) c1 = k_S11S31(1,ihelp)
1271              c2 = k_S11S31(2,ihelp)              if (iz.eq.2) c1 = k_S11S31(2,ihelp)
1272                if (iz.gt.2) c1 = k_S11S31(3,ihelp)
1273    c        write(*,*)k_S11S31(1,ihelp),k_S11S31(2,ihelp),k_S11S31(3,ihelp)
1274    c        write(*,*)iz,c1,c2
1275              beta_a(1) = c2*F/(ds-c1)              beta_a(1) = c2*F/(ds-c1)
1276         write(*,*) 'S11-S31 ',c1,c2,F  c       write(*,*) 'S11-S31 ',c1,c2,F
1277         write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
1278  C-------ToF Mask - S11 - S31  C-------ToF Mask - S11 - S31
1279    
1280              tofmask(ch11a(tof11_i),hb11a(tof11_i)) =              tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
# Line 1228  C-------ToF Mask - S11 - S31 Line 1290  C-------ToF Mask - S11 - S31
1290           ENDIF           ENDIF
1291        ENDIF        ENDIF
1292    
1293    C---------------------     S11 - S32  ------------------------
1294    
1295        dist = ZTOF(1) - ZTOF(6)        dist = ZTOF(1) - ZTOF(6)
1296        dl = 0.        dl = 0.
1297        DO I=1,6        DO I=1,6
# Line 1235  C-------ToF Mask - S11 - S31 Line 1299  C-------ToF Mask - S11 - S31
1299        ENDDO        ENDDO
1300        F = dl/dist        F = dl/dist
1301    
1302  C     S11 - S32        c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1303    
1304  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1305         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1306       &    (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 1314  C      IF (tof11_i.GT.none_find.AND.tof3
1314              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1315              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1316              ihelp=(tof11_i-1)*3+tof32_i              ihelp=(tof11_i-1)*3+tof32_i
1317              c1 = k_S11S32(1,ihelp)              if (iz.le.1) c1 = k_S11S32(1,ihelp)
1318              c2 = k_S11S32(2,ihelp)              if (iz.eq.2) c1 = k_S11S32(2,ihelp)
1319                if (iz.gt.2) c1 = k_S11S32(3,ihelp)
1320              beta_a(2) = c2*F/(ds-c1)              beta_a(2) = c2*F/(ds-c1)
1321  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1322    
# Line 1271  C------- Line 1337  C-------
1337           ENDIF           ENDIF
1338        ENDIF        ENDIF
1339    
1340  C     S12 - S31  C---------------------     S12 - S31  ------------------------
1341    
1342        dist = ZTOF(2) - ZTOF(5)        dist = ZTOF(2) - ZTOF(5)
1343        dl = 0.        dl = 0.
1344        DO I=2,5        DO I=2,5
# Line 1279  C     S12 - S31 Line 1346  C     S12 - S31
1346        ENDDO        ENDDO
1347        F = dl/dist        F = dl/dist
1348    
1349          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1350    
1351  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
1352         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.
1353       &    (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 1361  C      IF (tof12_i.GT.none_find.AND.tof3
1361              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1362              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1363              ihelp=(tof12_i-1)*3+tof31_i              ihelp=(tof12_i-1)*3+tof31_i
1364              c1 = k_S12S31(1,ihelp)              if (iz.le.1) c1 = k_S12S31(1,ihelp)
1365              c2 = k_S12S31(2,ihelp)              if (iz.eq.2) c1 = k_S12S31(2,ihelp)
1366                if (iz.gt.2) c1 = k_S12S31(3,ihelp)
1367              beta_a(3) = c2*F/(ds-c1)              beta_a(3) = c2*F/(ds-c1)
1368  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1369    
# Line 1314  C------- Line 1384  C-------
1384           ENDIF           ENDIF
1385        ENDIF        ENDIF
1386    
1387  C     S12 - S32  C---------------------     S12 - S32  ------------------------
1388    
1389        dist = ZTOF(2) - ZTOF(6)        dist = ZTOF(2) - ZTOF(6)
1390        dl = 0.        dl = 0.
# Line 1322  C     S12 - S32 Line 1392  C     S12 - S32
1392           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1393        ENDDO        ENDDO
1394        F = dl/dist        F = dl/dist
1395          
1396          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1397    
1398  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
1399         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 1408  C      IF (tof12_i.GT.none_find.AND.tof3
1408              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1409              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1410              ihelp=(tof12_i-1)*3+tof32_i              ihelp=(tof12_i-1)*3+tof32_i
1411              c1 = k_S12S32(1,ihelp)              if (iz.le.1) c1 = k_S12S32(1,ihelp)
1412              c2 = k_S12S32(2,ihelp)              if (iz.eq.2) c1 = k_S12S32(2,ihelp)
1413                if (iz.gt.2) c1 = k_S12S32(3,ihelp)
1414              beta_a(4) = c2*F/(ds-c1)              beta_a(4) = c2*F/(ds-c1)
1415  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1416    
# Line 1358  C------- Line 1431  C-------
1431           ENDIF           ENDIF
1432        ENDIF        ENDIF
1433    
1434  C     S21 - S31  C---------------------     S21 - S31  ------------------------
1435    
1436        dist = ZTOF(3) - ZTOF(5)        dist = ZTOF(3) - ZTOF(5)
1437        dl = 0.        dl = 0.
# Line 1367  C     S21 - S31 Line 1440  C     S21 - S31
1440        ENDDO        ENDDO
1441        F = dl/dist        F = dl/dist
1442    
1443          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1444    
1445  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
1446         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.
1447       &    (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 1455  C      IF (tof21_i.GT.none_find.AND.tof3
1455              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1456              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1457              ihelp=(tof21_i-1)*3+tof31_i              ihelp=(tof21_i-1)*3+tof31_i
1458              c1 = k_S21S31(1,ihelp)              if (iz.le.1) c1 = k_S21S31(1,ihelp)
1459              c2 = k_S21S31(2,ihelp)              if (iz.eq.2) c1 = k_S21S31(2,ihelp)
1460                if (iz.gt.2) c1 = k_S21S31(3,ihelp)
1461              beta_a(5) = c2*F/(ds-c1)              beta_a(5) = c2*F/(ds-c1)
1462    
1463  C-------ToF Mask - S21 - S31  C-------ToF Mask - S21 - S31
# Line 1401  C------- Line 1477  C-------
1477           ENDIF           ENDIF
1478        ENDIF        ENDIF
1479    
1480  C     S21 - S32  C---------------------     S21 - S32  ------------------------
1481    
1482        dist = ZTOF(3) - ZTOF(6)        dist = ZTOF(3) - ZTOF(6)
1483        dl = 0.        dl = 0.
# Line 1410  C     S21 - S32 Line 1486  C     S21 - S32
1486        ENDDO        ENDDO
1487        F = dl/dist        F = dl/dist
1488    
1489          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1490    
1491  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
1492         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.
1493       &    (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 1501  C      IF (tof21_i.GT.none_find.AND.tof3
1501              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1502              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1503              ihelp=(tof21_i-1)*3+tof32_i              ihelp=(tof21_i-1)*3+tof32_i
1504              c1 = k_S21S32(1,ihelp)              if (iz.le.1) c1 = k_S21S32(1,ihelp)
1505              c2 = k_S21S32(2,ihelp)              if (iz.eq.2) c1 = k_S21S32(2,ihelp)
1506                if (iz.gt.2) c1 = k_S21S32(3,ihelp)
1507              beta_a(6) = c2*F/(ds-c1)              beta_a(6) = c2*F/(ds-c1)
1508    
1509  C-------ToF Mask - S21 - S32  C-------ToF Mask - S21 - S32
# Line 1444  C------- Line 1523  C-------
1523           ENDIF           ENDIF
1524        ENDIF        ENDIF
1525    
1526  C     S22 - S31  C---------------------     S22 - S31  ------------------------
1527    
1528        dist = ZTOF(4) - ZTOF(5)        dist = ZTOF(4) - ZTOF(5)
1529        dl = 0.        dl = 0.
# Line 1453  C     S22 - S31 Line 1532  C     S22 - S31
1532        ENDDO        ENDDO
1533        F = dl/dist        F = dl/dist
1534    
1535          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1536    
1537    C WM workaround
1538          dl = dl - 0.06*F
1539          F = dl/dist
1540    
1541  C      IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1542         IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1543       &    (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 1551  C      IF (tof22_i.GT.none_find.AND.tof3
1551              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1552              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1553              ihelp=(tof22_i-1)*3+tof31_i              ihelp=(tof22_i-1)*3+tof31_i
1554              c1 = k_S22S31(1,ihelp)              if (iz.le.1) c1 = k_S22S31(1,ihelp)
1555              c2 = k_S22S31(2,ihelp)              if (iz.eq.2) c1 = k_S22S31(2,ihelp)
1556                if (iz.gt.2) c1 = k_S22S31(3,ihelp)
1557              beta_a(7) = c2*F/(ds-c1)              beta_a(7) = c2*F/(ds-c1)
1558    
1559  C-------ToF Mask - S22 - S31  C-------ToF Mask - S22 - S31
# Line 1487  C------- Line 1573  C-------
1573           ENDIF           ENDIF
1574        ENDIF        ENDIF
1575    
1576  C     S22 - S32  C---------------------     S22 - S32  ------------------------
1577    
1578    
1579        dist = ZTOF(4) - ZTOF(6)        dist = ZTOF(4) - ZTOF(6)
1580        dl = 0.        dl = 0.
# Line 1495  C     S22 - S32 Line 1582  C     S22 - S32
1582           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1583        ENDDO        ENDDO
1584        F = dl/dist        F = dl/dist
1585          
1586          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1587    
1588    C WM workaround      
1589          dl = dl - 0.06*F
1590          F = dl/dist
1591    
1592    
1593  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
1594         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 1603  C      IF (tof22_i.GT.none_find.AND.tof3
1603              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1604              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1605              ihelp=(tof22_i-1)*3+tof32_i              ihelp=(tof22_i-1)*3+tof32_i
1606              c1 = k_S22S32(1,ihelp)              if (iz.le.1) c1 = k_S22S32(1,ihelp)
1607              c2 = k_S22S32(2,ihelp)              if (iz.eq.2) c1 = k_S22S32(2,ihelp)
1608                if (iz.gt.2) c1 = k_S22S32(3,ihelp)
1609              beta_a(8) = c2*F/(ds-c1)              beta_a(8) = c2*F/(ds-c1)
1610    
1611  C-------ToF Mask - S22 - S32  C-------ToF Mask - S22 - S32
# Line 1530  C------- Line 1625  C-------
1625           ENDIF           ENDIF
1626        ENDIF        ENDIF
1627    
1628  C     S11 - S21  C---------------------     S11 - S21  ------------------------
1629    
1630        dist = ZTOF(1) - ZTOF(3)        dist = ZTOF(1) - ZTOF(3)
1631        dl = 0.        dl = 0.
# Line 1539  C     S11 - S21 Line 1634  C     S11 - S21
1634        ENDDO        ENDDO
1635        F = dl/dist        F = dl/dist
1636    
1637          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1638    
1639    C WM workaround      
1640          dl = dl - 0.442*F
1641          F = dl/dist
1642    
1643  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
1644         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.
1645       &    (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 1653  C      IF (tof11_i.GT.none_find.AND.tof2
1653              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1654              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1655              ihelp=(tof11_i-1)*2+tof21_i              ihelp=(tof11_i-1)*2+tof21_i
1656              c1 = k_S11S21(1,ihelp)              if (iz.le.1) c1 = k_S11S21(1,ihelp)
1657              c2 = k_S11S21(2,ihelp)              if (iz.eq.2) c1 = k_S11S21(2,ihelp)
1658                if (iz.gt.2) c1 = k_S11S21(3,ihelp)
1659              beta_a(9) = c2*F/(ds-c1)              beta_a(9) = c2*F/(ds-c1)
1660    
1661  C-------ToF Mask - S11 - S21  C-------ToF Mask - S11 - S21
# Line 1573  C------- Line 1675  C-------
1675           ENDIF           ENDIF
1676        ENDIF        ENDIF
1677    
1678  C     S11 - S22  C---------------------     S11 - S22  ------------------------
1679    
1680        dist = ZTOF(1) - ZTOF(4)        dist = ZTOF(1) - ZTOF(4)
1681        dl = 0.        dl = 0.
# Line 1582  C     S11 - S22 Line 1684  C     S11 - S22
1684        ENDDO        ENDDO
1685        F = dl/dist        F = dl/dist
1686    
1687          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1688    
1689  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1690         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1691       &    (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 1699  C      IF (tof11_i.GT.none_find.AND.tof2
1699              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1700              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1701              ihelp=(tof11_i-1)*2+tof22_i              ihelp=(tof11_i-1)*2+tof22_i
1702              c1 = k_S11S22(1,ihelp)              if (iz.le.1) c1 = k_S11S22(1,ihelp)
1703              c2 = k_S11S22(2,ihelp)              if (iz.eq.2) c1 = k_S11S22(2,ihelp)
1704                if (iz.gt.2) c1 = k_S11S22(3,ihelp)
1705              beta_a(10) = c2*F/(ds-c1)              beta_a(10) = c2*F/(ds-c1)
1706    
1707  C-------ToF Mask - S11 - S22  C-------ToF Mask - S11 - S22
# Line 1616  C------- Line 1721  C-------
1721           ENDIF           ENDIF
1722        ENDIF        ENDIF
1723    
1724  C     S12 - S21  C---------------------     S12 - S21  ------------------------
1725    
1726        dist = ZTOF(2) - ZTOF(3)        dist = ZTOF(2) - ZTOF(3)
1727        dl = 0.        dl = 0.
# Line 1625  C     S12 - S21 Line 1730  C     S12 - S21
1730        ENDDO        ENDDO
1731        F = dl/dist        F = dl/dist
1732    
1733          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1734    
1735    C  WM workaround
1736          dl = dl - 0.442*F
1737          F = dl/dist
1738    
1739  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
1740         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.
1741       &    (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 1749  C      IF (tof12_i.GT.none_find.AND.tof2
1749              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1750              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1751              ihelp=(tof12_i-1)*2+tof21_i              ihelp=(tof12_i-1)*2+tof21_i
1752              c1 = k_S12S21(1,ihelp)              if (iz.le.1) c1 = k_S12S21(1,ihelp)
1753              c2 = k_S12S21(2,ihelp)              if (iz.eq.2) c1 = k_S12S21(2,ihelp)
1754                if (iz.gt.2) c1 = k_S12S21(3,ihelp)
1755              beta_a(11) = c2*F/(ds-c1)              beta_a(11) = c2*F/(ds-c1)
1756    
1757  C-------ToF Mask - S12 - S21  C-------ToF Mask - S12 - S21
# Line 1659  C------- Line 1771  C-------
1771           ENDIF           ENDIF
1772        ENDIF        ENDIF
1773    
1774  C     S12 - S22  C---------------------     S12 - S22  ------------------------
1775    
1776        dist = ZTOF(2) - ZTOF(4)        dist = ZTOF(2) - ZTOF(4)
1777        dl = 0.        dl = 0.
# Line 1668  C     S12 - S22 Line 1780  C     S12 - S22
1780        ENDDO        ENDDO
1781        F = dl/dist        F = dl/dist
1782    
1783          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1784    
1785  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
1786         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.
1787       &    (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 1794  C      IF (tof12_i.GT.none_find.AND.tof2
1794              xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)              xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1795              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1796              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1797              ihelp=(tof12_i-1)*2+tof22_i              ihelp=(tof12_i-1)*2+tof22_i          
1798              c1 = k_S12S22(1,ihelp)              if (iz.le.1) c1 = k_S12S22(1,ihelp)
1799              c2 = k_S12S22(2,ihelp)              if (iz.eq.2) c1 = k_S12S22(2,ihelp)
1800                if (iz.gt.2) c1 = k_S12S22(3,ihelp)
1801              beta_a(12) = c2*F/(ds-c1)              beta_a(12) = c2*F/(ds-c1)
1802    
1803  C-------ToF Mask - S12 - S22  C-------ToF Mask - S12 - S22
# Line 1703  C------- Line 1818  C-------
1818        ENDIF        ENDIF
1819    
1820  C-------  C-------
1821    C
1822    C      icount=0
1823    C      sw=0.
1824    C      sxw=0.
1825    C      beta_mean=100.
1826    C
1827    C      do i=1,12
1828    C         if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
1829    C            icount= icount+1
1830    C            if (i.le.4) w_i=1./(0.13**2.)
1831    C            if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1832    C            if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1833    C            sxw=sxw + beta_a(i)*w_i
1834    C            sw =sw + w_i
1835    C         endif
1836    C      enddo
1837    C
1838    C      if (icount.gt.0) beta_mean=sxw/sw
1839    C      beta_a(13) = beta_mean
1840    C
1841    
1842        icount=0  C-------  New mean beta  calculation
       sw=0.  
       sxw=0.  
       beta_mean=100.  
1843    
1844        do i=1,12         do i=1,12
1845           if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then           btemp(i) =  beta_a(i)
1846              icount= icount+1         enddo
1847              if (i.le.4) w_i=1./(0.13**2.)  
1848              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  
1849    
1850        if (icount.gt.0) beta_mean=sxw/sw  C-------
       beta_a(13) = beta_mean  
1851    
1852    
1853  c       IF (tof11_i.GT.none_find)  c       IF (tof11_i.GT.none_find)
# Line 1750  c      write(*,*) ytofpos Line 1876  c      write(*,*) ytofpos
1876  c      write(*,*) xtr_tof  c      write(*,*) xtr_tof
1877  c      write(*,*) ytr_tof  c      write(*,*) ytr_tof
1878    
1879    c       write(*,*) '---------  end toftrk ----------'
1880    
1881        RETURN        RETURN
1882        END        END
# Line 1760  c      write(*,*) ytr_tof Line 1886  c      write(*,*) ytr_tof
1886    
1887  C------------------------------------------------------------------  C------------------------------------------------------------------
1888    
1889    

Legend:
Removed from v.1.12  
changed lines
  Added in v.1.21

  ViewVC Help
Powered by ViewVC 1.1.23