/[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.19 by mocchiut, Mon Nov 23 09:50:51 2009 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  C
57  C****************************************************************************  C****************************************************************************
58        IMPLICIT NONE        IMPLICIT NONE
# Line 68  c      REAL dx,dy,dr Line 86  c      REAL dx,dy,dr
86        REAL ds        REAL ds
87        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
88        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
89        REAL c1,c2,sw,sxw,w_i        REAL c1,c2
90    C     REAL sw,sxw,w_i
91        REAL dist,dl,F        REAL dist,dl,F
92        INTEGER icount,ievent        INTEGER ievent
93        REAL xhelp_a,xhelp_t  C      INTEGER icount
94    C      REAL beta_mean
95        REAL beta_mean        REAL btemp(12)
96        REAL hepratio        REAL hepratio
97    
98        INTEGER j        INTEGER j,hitvec(6)
99    
100        real atten,pc_adc        real atten,pc_adc,check_charge,newbeta
101    
102    
103        REAL theta,phi        REAL theta,phi
# Line 91  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 110  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
110        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
111    
112    
113    C--- new
114          REAL xtofpre(3),ytofpre(3)
115    
116          REAL y_coor_lin11c(8,2),x_coor_lin12c(6,2)
117          REAL x_coor_lin21c(2,2),y_coor_lin22c(2,2)
118          REAL y_coor_lin31c(3,2),x_coor_lin32c(3,2)
119    
120          DATA y_coor_lin11c(1,1),y_coor_lin11c(1,2) /-20.66,-2.497/
121          DATA y_coor_lin11c(2,1),y_coor_lin11c(2,2) /-9.10, -2.52/
122          DATA y_coor_lin11c(3,1),y_coor_lin11c(3,2) /-24.07,-2.12/
123          DATA y_coor_lin11c(4,1),y_coor_lin11c(4,2) /-13.40,-2.47/
124          DATA y_coor_lin11c(5,1),y_coor_lin11c(5,2) /-31.07,-2.32/
125          DATA y_coor_lin11c(6,1),y_coor_lin11c(6,2) /-21.69,-2.63/
126          DATA y_coor_lin11c(7,1),y_coor_lin11c(7,2) /-12.37,-2.65/
127          DATA y_coor_lin11c(8,1),y_coor_lin11c(8,2) /-10.81,-3.15/
128    
129          DATA x_coor_lin12c(1,1),x_coor_lin12c(1,2) /12.96, -2.65/
130          DATA x_coor_lin12c(2,1),x_coor_lin12c(2,2) /17.12,-2.44/
131          DATA x_coor_lin12c(3,1),x_coor_lin12c(3,2) /7.26, -1.98/
132          DATA x_coor_lin12c(4,1),x_coor_lin12c(4,2) /-22.52,-2.27/
133          DATA x_coor_lin12c(5,1),x_coor_lin12c(5,2) /-18.54,-2.28/
134          DATA x_coor_lin12c(6,1),x_coor_lin12c(6,2) /-7.67,-2.15/
135    
136          DATA x_coor_lin21c(1,1),x_coor_lin21c(1,2) /22.56,-1.56/
137          DATA x_coor_lin21c(2,1),x_coor_lin21c(2,2) /13.94,-1.56/
138    
139          DATA y_coor_lin22c(1,1),y_coor_lin22c(1,2) /-24.24,-2.23/
140          DATA y_coor_lin22c(2,1),y_coor_lin22c(2,2) /-45.99,-1.68/
141    
142          DATA y_coor_lin31c(1,1),y_coor_lin31c(1,2) /-22.99,-3.54/
143          DATA y_coor_lin31c(2,1),y_coor_lin31c(2,2) /-42.28,-4.10/
144          DATA y_coor_lin31c(3,1),y_coor_lin31c(3,2) /-41.29,-3.69/
145    
146          DATA x_coor_lin32c(1,1),x_coor_lin32c(1,2) /0.961, -3.22/
147          DATA x_coor_lin32c(2,1),x_coor_lin32c(2,2) /4.98,-3.48/
148          DATA x_coor_lin32c(3,1),x_coor_lin32c(3,2) /-22.08,-3.37/
149    
150    C---
151    
152        INTEGER ihelp        INTEGER ihelp
153        REAL xkorr,xpos        REAL xkorr,xpos
154    
155          INTEGER IZ
156          REAL k1corrA1,k1corrB1,k1corrC1
157    
158        REAL yl,yh,xl,xh        REAL yl,yh,xl,xh
159  C  C
160        REAL hmemor(9000000)        REAL hmemor(9000000)
# Line 101  C Line 162  C
162  C  C
163        DATA ievent / 0 /        DATA ievent / 0 /
164    
165          INTEGER ifst
166          DATA ifst /0/
167    
168        COMMON / pawcd / hmemor        COMMON / pawcd / hmemor
169        save / pawcd /        save / pawcd /
170  C  C
# Line 113  C Line 177  C
177    
178  *******************************************************************  *******************************************************************
179    
180        ievent = ievent +1         if (ifst.eq.0) then
181           ifst=1
182    
183  C  ratio helium to proton ca. 4  C  ratio helium to proton ca. 4
184        hepratio = 4.        hepratio = 4.
# Line 129  C  ratio helium to proton ca. 4 Line 194  C  ratio helium to proton ca. 4
194        itdc = 1        itdc = 1
195        iadc = 2        iadc = 2
196    
197    
198          k1corrA1 = 0.
199          k1corrB1 = -5.0
200          k1corrC1=  8.0
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 282  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 359  C     COPY THE ALFA VECTOR FROM AL_PP TO
359        enddo        enddo
360    
361  c      write(*,*) AL_P  c      write(*,*) AL_P
362    c      write(*,*) 'Rigidity ',(1./AL_P(5))
363    
364        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
365           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
366           GOTO 969           GOTO 969
367        ENDIF        ENDIF
368  *     -------- *** tracking routine *** --------  *     -------- *** tracking routine *** --------
# Line 295  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,A Line 373  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,A
373  C     write(*,*) (TLOUT(i),i=1,6)  C     write(*,*) (TLOUT(i),i=1,6)
374    
375        if(IFAIL.ne.0)then        if(IFAIL.ne.0)then
376           print *,' TOF - WARNING F77: tracking failed '  c         print *,' TOF - WARNING F77: tracking failed '
377           goto 969           goto 969
378        endif        endif
379  *     ------------------------------------------  *     ------------------------------------------
# Line 306  C---  Fill xtr_tof  and ytr_tof: positio Line 384  C---  Fill xtr_tof  and ytr_tof: positio
384        do j=1,6        do j=1,6
385        xtr_tof(j) = XOUT(j)        xtr_tof(j) = XOUT(j)
386        ytr_tof(j) = YOUT(j)        ytr_tof(j) = YOUT(j)
387    c      write(*,*) XOUT(j),YOUT(j)
388        enddo        enddo
389    
390    
# Line 396  c     S22 2 paddles  15.0 x 9.0 cm Line 475  c     S22 2 paddles  15.0 x 9.0 cm
475  c     S31 3 paddles  15.0 x 6.0 cm  c     S31 3 paddles  15.0 x 6.0 cm
476  c     S32 3 paddles  18.0 x 5.0 cm  c     S32 3 paddles  18.0 x 5.0 cm
477    
 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)  
478    
479  C--------------S11 --------------------------------------  C--------------S11 --------------------------------------
480    
# Line 502  C--------------S32 --------------------- Line 579  C--------------S32 ---------------------
579        endif        endif
580    
581    
 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  
582    
583  c       write(*,*)'11lb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)         hitvec(1)=tof11_i
584           hitvec(2)=tof12_i
585           hitvec(3)=tof21_i
586           hitvec(4)=tof22_i
587           hitvec(5)=tof31_i
588           hitvec(6)=tof32_i
589    
             tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)  
      &           + 2*(y_coor_lin11(tof11_i,offset)  
      &           + xpos*y_coor_lin11(tof11_i,slope))  
590    
591  c       write(*,*)'11laf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  C----------------------------------------------------------------------
592    C--- check charge:
593    C--- if Z=2 we should use the attenuation curve for helium to
594    C--- fill the artificail ADC values and NOT divide by "hepratio"
595    C--- if Z>2 we should do a correction to
596    C--- the k1 constants in the beta calculation
597    C----------------------------------------------------------------------
598    
599              tdcflag(ch11a(i),hb11a(i)) = 1         theta=0.  
600           dist = ZTOF(1) - ZTOF(5)
601           dl = 0.
602           DO I=1,5
603             dl = dl + TLOUT(i)
604           ENDDO
605           F = dl/dist
606           theta = acos(1/F)
607    
608           iz = int(check_charge(theta,hitvec))
609    c       write(*,*) 'in toftrk',iz
610    
         ENDIF  
          if ((tof11(2,tof11_i,itdc).EQ.4095).AND.  
      &        (tof11(1,tof11_i,itdc).LT.4095)) THEN  
611    
612  c       write(*,*)'11rb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  C-------------------------------  new  ---------------------------
613    C--  calculate track position in paddle using timing difference
614    C--  this calculation is preliminary and uses some standard
615    C--  calibration values, but we need to find a rough position to
616    C--  be able to calculate artificial ADC values (needed for the
617    C--  timewalk...
618    C------------------------------------------------------------------
619    
620              tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)         do i=1,3
621       &           - 2*(y_coor_lin11(tof11_i,offset)           xtofpre(i)=100.
622       &           + xpos*y_coor_lin11(tof11_i,slope))           ytofpre(i)=100.
623  c       write(*,*)'11raf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)         enddo
624    
625              tdcflag(ch11b(i),hb11b(i)) = 1  C-----------------------------S1 --------------------------------
          ENDIF  
       ENDIF  
626    
627  C-----------------------S12 -----------------------------------------        IF (tof11_i.GT.none_find) THEN
628          IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
629         +                             (tof11(2,tof11_i,itdc).LT.2000))
630         +    ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
631         +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
632          endif
633    
634        IF (tof12_i.GT.none_find) THEN        IF (tof12_i.GT.none_find) THEN
635           xpos = xout(2)        IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
636           i = tof12_i       +                             (tof12(2,tof12_i,itdc).LT.2000))
637           if ((tof12(1,tof12_i,itdc).EQ.4095).AND.       +    xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
638       &        (tof12(2,tof12_i,itdc).LT.4095)) THEN       +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
639              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  
640    
 C-----------------------S21 -----------------------------------------  
641    
642        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  
643    
644  C-----------------------S22 -----------------------------------------        IF (tof21_i.GT.none_find) THEN
645          IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
646         +                             (tof21(2,tof21_i,itdc).LT.2000))
647         +    xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
648         +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
649          endif
650    
651        IF (tof22_i.GT.none_find) THEN        IF (tof22_i.GT.none_find) THEN
652           xpos = yout(4)        IF ((tof22(1,tof22_i,itdc).LT.2000).AND.
653           i = tof22_i       +                             (tof22(2,tof22_i,itdc).LT.2000))
654           if ((tof22(1,tof22_i,itdc).EQ.4095).AND.       +    ytofpre(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
655       &        (tof22(2,tof22_i,itdc).LT.4095)) THEN       +    -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
656              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  
657    
 C-----------------------S31 -----------------------------------------  
658    
659        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  
660    
661  C-----------------------S32 -----------------------------------------        IF (tof31_i.GT.none_find) THEN
662          IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
663         +                             (tof31(2,tof31_i,itdc).LT.2000))
664         +    ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
665         +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
666          endif
667    
668        IF (tof32_i.GT.none_find) THEN        IF (tof32_i.GT.none_find) THEN
669           xpos = xout(6)        IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
670           i = tof32_i       +                             (tof32(2,tof32_i,itdc).LT.2000))
671           if ((tof32(1,tof32_i,itdc).EQ.4095).AND.       +    xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
672       &        (tof32(2,tof32_i,itdc).LT.4095)) THEN       +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
673              tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)        endif
674       &           + 2*(x_coor_lin32(tof32_i,offset)  
675       &           + xpos*x_coor_lin32(tof32_i,slope))  
676              tdcflag(ch32a(i),hb32a(i)) = 1  C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
677           ENDIF  
678           if ((tof32(2,tof32_i,itdc).EQ.4095).AND.          if (abs(xtofpre(1)).gt.31.)  xtofpre(1)=100.
679       &        (tof32(1,tof32_i,itdc).LT.4095)) THEN          if (abs(xtofpre(2)).gt.19.)  xtofpre(2)=100.
680              tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)          if (abs(xtofpre(3)).gt.19.)  xtofpre(3)=100.
681       &           - 2*(x_coor_lin32(tof32_i,offset)  
682       &           + xpos*x_coor_lin32(tof32_i,slope))          if (abs(ytofpre(1)).gt.26.)  ytofpre(1)=100.
683              tdcflag(ch32b(i),hb32b(i)) = 1          if (abs(ytofpre(2)).gt.18.)  ytofpre(2)=100.
684           ENDIF          if (abs(ytofpre(3)).gt.18.)  ytofpre(3)=100.
       ENDIF  
685    
686  C--------------------------------------------------------------------  C--------------------------------------------------------------------
687  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
688    C---- use the "pre" position if possible, since this gives better time
689    C---- resolution ... october 2008
690  C--------------------------------------------------------------------  C--------------------------------------------------------------------
691  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
692  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 698  c     DATA tof32_y/ -5.0,0.0,5.0/
698    
699  C----------------------------S1 -------------------------------------  C----------------------------S1 -------------------------------------
700    
701        yhelp=yout(1)  c     yhelp=yout(1)
702        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        yhelp = ytofpre(1)
703          if (yhelp.eq.100) yhelp=yout(1)
704    
705          IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
706           i = tof11_i           i = tof11_i
707           if ((tof11(left,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
708       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
709              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
710              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))  
711              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
712              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
713              tof11(left,i,iadc)=xkorr/cos(theta)              tof11(left,i,iadc)=xkorr/cos(theta)
714              adcflag(ch11a(i),hb11a(i)) = 1              adcflag(ch11a(i),hb11a(i)) = 1
715           endif           endif
716           if ((tof11(right,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
717       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then
718              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
719              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))  
720              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
721              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
722              tof11(right,i,iadc)=xkorr/cos(theta)              tof11(right,i,iadc)=xkorr/cos(theta)
723              adcflag(ch11b(i),hb11b(i)) = 1              adcflag(ch11b(i),hb11b(i)) = 1
724           endif           endif
725        ENDIF        ENDIF
726    
727        xhelp=xout(2)  c      xhelp=xout(2)
728        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        xhelp = xtofpre(1)
729          if (xhelp.eq.100) xhelp=xout(2)
730    
731          IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
732           i = tof12_i           i = tof12_i
733           if ((tof12(left,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
734       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
735              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
736              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
737  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
738              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
739              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
740              tof12(left,i,iadc) = xkorr/cos(theta)              tof12(left,i,iadc) = xkorr/cos(theta)
741              adcflag(ch12a(i),hb12a(i)) = 1              adcflag(ch12a(i),hb12a(i)) = 1
742           endif           endif
743           if ((tof12(right,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
744       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then
745              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
746              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
747  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
748              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
749              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
750              tof12(right,i,iadc) = xkorr/cos(theta)              tof12(right,i,iadc) = xkorr/cos(theta)
751              adcflag(ch12b(i),hb12b(i)) = 1              adcflag(ch12b(i),hb12b(i)) = 1
752           endif           endif
# Line 714  c            xkorr=adcx12(right,i,1)*exp Line 754  c            xkorr=adcx12(right,i,1)*exp
754    
755  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
756    
757        xhelp=xout(3)  c      xhelp=xout(3)
758        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN        xhelp = xtofpre(2)
759          if (xhelp.eq.100) xhelp=xout(3)
760    
761          IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
762           i = tof21_i           i = tof21_i
763           if ((tof21(left,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
764       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
765              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
766              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
767  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
768              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
769              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
770              tof21(left,i,iadc) = xkorr/cos(theta)              tof21(left,i,iadc) = xkorr/cos(theta)
771              adcflag(ch21a(i),hb21a(i)) = 1              adcflag(ch21a(i),hb21a(i)) = 1
772           endif           endif
773           if ((tof21(right,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
774       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then
775              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
776              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
777  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
778              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
779              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
780              tof21(right,i,iadc) = xkorr/cos(theta)              tof21(right,i,iadc) = xkorr/cos(theta)
781              adcflag(ch21b(i),hb21b(i)) = 1              adcflag(ch21b(i),hb21b(i)) = 1
782           endif           endif
783        ENDIF        ENDIF
784    
785    
786        yhelp=yout(4)  c      yhelp=yout(4)
787        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        yhelp = ytofpre(2)
788          if (yhelp.eq.100) yhelp=yout(4)
789    
790          IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
791           i = tof22_i           i = tof22_i
792           if ((tof22(left,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
793       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
794              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
795              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
796  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
797              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
798              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
799              tof22(left,i,iadc) = xkorr/cos(theta)              tof22(left,i,iadc) = xkorr/cos(theta)
800              adcflag(ch22a(i),hb22a(i)) = 1              adcflag(ch22a(i),hb22a(i)) = 1
801           endif           endif
802           if ((tof22(right,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
803       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
804              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
805              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
806  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
807              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
808              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
809              tof22(right,i,iadc) = xkorr/cos(theta)              tof22(right,i,iadc) = xkorr/cos(theta)
810              adcflag(ch22b(i),hb22b(i)) = 1              adcflag(ch22b(i),hb22b(i)) = 1
811           endif           endif
# Line 767  c            xkorr=adcx22(right,i,1)*exp Line 813  c            xkorr=adcx22(right,i,1)*exp
813    
814  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
815    
816        yhelp=yout(5)  c      yhelp=yout(5)
817        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN        yhelp = ytofpre(3)
818          if (yhelp.eq.100) yhelp=yout(5)
819    
820          IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
821           i = tof31_i           i = tof31_i
822           if ((tof31(left,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
823       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
824              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
825              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
826  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
827              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
828              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
829              tof31(left,i,iadc) = xkorr/cos(theta)              tof31(left,i,iadc) = xkorr/cos(theta)
830              adcflag(ch31a(i),hb31a(i)) = 1              adcflag(ch31a(i),hb31a(i)) = 1
831           endif           endif
832           if ((tof31(right,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
833       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then
834              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
835              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
836  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
837              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
838              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
839              tof31(right,i,iadc) = xkorr/cos(theta)              tof31(right,i,iadc) = xkorr/cos(theta)
840              adcflag(ch31b(i),hb31b(i)) = 1              adcflag(ch31b(i),hb31b(i)) = 1
841           endif           endif
842        ENDIF        ENDIF
843    
844    
845        xhelp=xout(6)  c      xhelp=xout(6)
846          xhelp = xtofpre(3)
847          if (xhelp.eq.100) xhelp=xout(6)
848    
849        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
850           i = tof32_i           i = tof32_i
851           if ((tof32(left,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
852       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then
853              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
854              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
855  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
856              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
857              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
858              tof32(left,i,iadc) = xkorr/cos(theta)              tof32(left,i,iadc) = xkorr/cos(theta)
859              adcflag(ch32a(i),hb32a(i)) = 1              adcflag(ch32a(i),hb32a(i)) = 1
860           endif           endif
861           if ((tof32(right,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
862       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then
863              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
864              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
865  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
866              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
867              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
868              tof32(right,i,iadc) = xkorr/cos(theta)              tof32(right,i,iadc) = xkorr/cos(theta)
869              adcflag(ch32b(i),hb32b(i)) = 1              adcflag(ch32b(i),hb32b(i)) = 1
870           endif           endif
871        ENDIF        ENDIF
872    
873    C-------------------------------------------------------------------
874    C Now there is for each hitted paddle a TDC and ADC value, if the
875    C TDC was < 4095.
876    C There might be also TDC-ADC pairs in paddles not hitted
877    C Let's correct the raw TDC value with the time walk
878    C-------------------------------------------------------------------
879    C--------------------Time walk correction  -------------------------
880    C-------------------------------------------------------------------
881    
882          DO i=1,8
883             if ((tdc(ch11a(i),hb11a(i)).lt.4095).and.
884         &             (tof11(left,i,iadc).lt.3786)) THEN
885             xhelp = tw11(left,i)/(tof11(left,i,iadc)**0.5)
886             tof11(left,i,itdc) = tof11(left,i,itdc) + xhelp
887             tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
888                                                  ENDIF
889    
890             if ((tdc(ch11b(i),hb11b(i)).lt.4095).and.
891         &             (tof11(right,i,iadc).lt.3786)) THEN
892             xhelp = tw11(right,i)/(tof11(right,i,iadc)**0.5)
893             tof11(right,i,itdc) = tof11(right,i,itdc) + xhelp
894             tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
895                                                 ENDIF
896          ENDDO
897    
898    
899          DO i=1,6
900             if ((tdc(ch12a(i),hb12a(i)).lt.4095).and.
901         &             (tof12(left,i,iadc).lt.3786)) THEN
902             xhelp = tw12(left,i)/(tof12(left,i,iadc)**0.5)
903             tof12(left,i,itdc) = tof12(left,i,itdc) + xhelp
904             tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
905                                                  ENDIF
906    
907             if ((tdc(ch12b(i),hb12b(i)).lt.4095).and.
908         &             (tof12(right,i,iadc).lt.3786)) THEN
909             xhelp = tw12(right,i)/(tof12(right,i,iadc)**0.5)
910             tof12(right,i,itdc) = tof12(right,i,itdc) + xhelp
911             tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
912                                                 ENDIF
913          ENDDO
914    
915    C----
916          DO I=1,2
917             if ((tdc(ch21a(i),hb21a(i)).lt.4095).and.
918         &             (tof21(left,i,iadc).lt.3786)) THEN
919             xhelp = tw21(left,i)/(tof21(left,i,iadc)**0.5)
920             tof21(left,i,itdc) = tof21(left,i,itdc) + xhelp
921             tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
922                                                  ENDIF
923    
924             if ((tdc(ch21b(i),hb21b(i)).lt.4095).and.
925         &             (tof21(right,i,iadc).lt.3786)) THEN
926             xhelp = tw21(right,i)/(tof21(right,i,iadc)**0.5)
927             tof21(right,i,itdc) = tof21(right,i,itdc) + xhelp
928             tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
929                                                 ENDIF
930          ENDDO
931    
932          DO I=1,2
933             if ((tdc(ch22a(i),hb22a(i)).lt.4095).and.
934         &             (tof22(left,i,iadc).lt.3786)) THEN
935             xhelp = tw22(left,i)/(tof22(left,i,iadc)**0.5)
936             tof22(left,i,itdc) = tof22(left,i,itdc) + xhelp
937             tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
938                                                  ENDIF
939    
940             if ((tdc(ch22b(i),hb22b(i)).lt.4095).and.
941         &             (tof22(right,i,iadc).lt.3786)) THEN
942             xhelp = tw22(right,i)/(tof22(right,i,iadc)**0.5)
943             tof22(right,i,itdc) = tof22(right,i,itdc) + xhelp
944             tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
945                                                 ENDIF
946          ENDDO
947    
948    C----
949          DO I=1,3
950             if ((tdc(ch31a(i),hb31a(i)).lt.4095).and.
951         &             (tof31(left,i,iadc).lt.3786)) THEN
952             xhelp = tw31(left,i)/(tof31(left,i,iadc)**0.5)
953             tof31(left,i,itdc) = tof31(left,i,itdc) + xhelp
954             tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
955                                                  ENDIF
956    
957             if ((tdc(ch31b(i),hb31b(i)).lt.4095).and.
958         &             (tof31(right,i,iadc).lt.3786)) THEN
959             xhelp = tw31(right,i)/(tof31(right,i,iadc)**0.5)
960             tof31(right,i,itdc) = tof31(right,i,itdc) + xhelp
961             tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
962                                                 ENDIF
963          ENDDO
964    
965          DO I=1,3
966             if ((tdc(ch32a(i),hb32a(i)).lt.4095).and.
967         &             (tof32(left,i,iadc).lt.3786)) THEN
968             xhelp = tw32(left,i)/(tof32(left,i,iadc)**0.5)
969             tof32(left,i,itdc) = tof32(left,i,itdc) + xhelp
970             tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
971                                                  ENDIF
972    
973             if ((tdc(ch32b(i),hb32b(i)).lt.4095).and.
974         &             (tof32(right,i,iadc).lt.3786)) THEN
975             xhelp = tw32(right,i)/(tof32(right,i,iadc)**0.5)
976             tof32(right,i,itdc) = tof32(right,i,itdc) + xhelp
977             tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
978                                                 ENDIF
979          ENDDO
980    
981    
982    C-----------------------------------------------------------------------
983    C--------------------Insert Artifical TDC Value  ---------------------
984    C     For each Paddle perform check:
985    C     if left paddle=4095  and right paddle OK => create TDC value left
986    C     if right paddle=4095  and left paddle OK => create TDC value right
987    C-----------------------------------------------------------------------
988    
989    C-----------------------S11 -----------------------------------------
990    
991          IF (tof11_i.GT.none_find) THEN
992             xpos = yout(1)
993             i = tof11_i
994            if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.
995         &          (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN
996              tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)
997         &           + 2*(y_coor_lin11(tof11_i,offset)
998         &           + xpos*y_coor_lin11(tof11_i,slope))
999                tdcflag(ch11a(i),hb11a(i)) = 1
1000            ENDIF
1001    
1002            if ((tdc(ch11b(i),hb11b(i)).EQ.4095).AND.
1003         &          (tdc(ch11a(i),hb11a(i)).LT.4095)) THEN
1004                tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)
1005         &           - 2*(y_coor_lin11(tof11_i,offset)
1006         &           + xpos*y_coor_lin11(tof11_i,slope))
1007                tdcflag(ch11b(i),hb11b(i)) = 1
1008             ENDIF
1009    
1010          ENDIF
1011    
1012    C-----------------------S12 -----------------------------------------
1013    
1014          IF (tof12_i.GT.none_find) THEN
1015             xpos = xout(2)
1016             i = tof12_i
1017            if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.
1018         &          (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN
1019                tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)
1020         &           + 2*(x_coor_lin12(tof12_i,offset)
1021         &           + xpos*x_coor_lin12(tof12_i,slope))
1022                tdcflag(ch12a(i),hb12a(i)) = 1
1023             ENDIF
1024    
1025            if ((tdc(ch12b(i),hb12b(i)).EQ.4095).AND.
1026         &          (tdc(ch12a(i),hb12a(i)).LT.4095)) THEN
1027                tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)
1028         &           - 2*(x_coor_lin12(tof12_i,offset)
1029         &           + xpos*x_coor_lin12(tof12_i,slope))
1030                tdcflag(ch12b(i),hb12b(i)) = 1
1031             ENDIF
1032          ENDIF
1033    
1034    C-----------------------S21 -----------------------------------------
1035    
1036          IF (tof21_i.GT.none_find) THEN
1037             xpos = xout(3)
1038             i = tof21_i
1039            if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.
1040         &          (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN
1041                tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)
1042         &           + 2*(x_coor_lin21(tof21_i,offset)
1043         &           + xpos*x_coor_lin21(tof21_i,slope))
1044                tdcflag(ch21a(i),hb21a(i)) = 1
1045             ENDIF
1046    
1047            if ((tdc(ch21b(i),hb21b(i)).EQ.4095).AND.
1048         &          (tdc(ch21a(i),hb21a(i)).LT.4095)) THEN
1049                tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)
1050         &           - 2*(x_coor_lin21(tof21_i,offset)
1051         &           + xpos*x_coor_lin21(tof21_i,slope))
1052                tdcflag(ch21b(i),hb21b(i)) = 1
1053             ENDIF
1054          ENDIF
1055    
1056    C-----------------------S22 -----------------------------------------
1057    
1058          IF (tof22_i.GT.none_find) THEN
1059             xpos = yout(4)
1060             i = tof22_i
1061            if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.
1062         &          (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN
1063                tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)
1064         &           + 2*(y_coor_lin22(tof22_i,offset)
1065         &           + xpos*y_coor_lin22(tof22_i,slope))
1066                tdcflag(ch22a(i),hb22a(i)) = 1
1067             ENDIF
1068    
1069            if ((tdc(ch22b(i),hb22b(i)).EQ.4095).AND.
1070         &          (tdc(ch22a(i),hb22a(i)).LT.4095)) THEN
1071                tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)
1072         &           - 2*(y_coor_lin22(tof22_i,offset)
1073         &           + xpos*y_coor_lin22(tof22_i,slope))
1074                tdcflag(ch22b(i),hb22b(i)) = 1
1075             ENDIF
1076          ENDIF
1077    
1078    C-----------------------S31 -----------------------------------------
1079    
1080          IF (tof31_i.GT.none_find) THEN
1081             xpos = yout(5)
1082             i = tof31_i
1083            if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.
1084         &          (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN
1085                tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)
1086         &           + 2*(y_coor_lin31(tof31_i,offset)
1087         &           + xpos*y_coor_lin31(tof31_i,slope))
1088                tdcflag(ch31a(i),hb31a(i)) = 1
1089             ENDIF
1090    
1091            if ((tdc(ch31b(i),hb31b(i)).EQ.4095).AND.
1092         &          (tdc(ch31a(i),hb31a(i)).LT.4095)) THEN
1093                tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)
1094         &           - 2*(y_coor_lin31(tof31_i,offset)
1095         &           + xpos*y_coor_lin31(tof31_i,slope))
1096                tdcflag(ch31b(i),hb31b(i)) = 1
1097             ENDIF
1098          ENDIF
1099    
1100    C-----------------------S32 -----------------------------------------
1101    
1102          IF (tof32_i.GT.none_find) THEN
1103             xpos = xout(6)
1104             i = tof32_i
1105            if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.
1106         &          (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN
1107                tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)
1108         &           + 2*(x_coor_lin32(tof32_i,offset)
1109         &           + xpos*x_coor_lin32(tof32_i,slope))
1110                tdcflag(ch32a(i),hb32a(i)) = 1
1111             ENDIF
1112    
1113            if ((tdc(ch32b(i),hb32b(i)).EQ.4095).AND.
1114         &          (tdc(ch32a(i),hb32a(i)).LT.4095)) THEN
1115                tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)
1116         &           - 2*(x_coor_lin32(tof32_i,offset)
1117         &           + xpos*x_coor_lin32(tof32_i,slope))
1118                tdcflag(ch32b(i),hb32b(i)) = 1
1119             ENDIF
1120          ENDIF
1121    
1122    
1123  C------------------------------------------------------------------  C------------------------------------------------------------------
1124  C---  calculate track position in paddle using timing difference  C---  calculate track position in paddle using timing difference
# Line 827  C--------------------------------------- Line 1128  C---------------------------------------
1128           xtofpos(i)=100.           xtofpos(i)=100.
1129           ytofpos(i)=100.           ytofpos(i)=100.
1130        enddo        enddo
1131    
1132  C-----------------------------S1 --------------------------------  C-----------------------------S1 --------------------------------
1133    
1134        IF (tof11_i.GT.none_find) THEN        IF (tof11_i.GT.none_find) THEN
# Line 835  C-----------------------------S1 ------- Line 1137  C-----------------------------S1 -------
1137           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.
1138       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1139          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
1140          i=tof11_i
1141        endif        endif
1142        endif        endif
1143    
# Line 844  C-----------------------------S1 ------- Line 1147  C-----------------------------S1 -------
1147           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.
1148       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1149          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
1150          i=tof12_i
1151        endif        endif
1152        endif        endif
1153    
# Line 855  C-----------------------------S2 ------- Line 1159  C-----------------------------S2 -------
1159           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.
1160       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1161          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
1162          i=tof21_i
1163        endif        endif
1164        endif        endif
1165    
# Line 864  C-----------------------------S2 ------- Line 1169  C-----------------------------S2 -------
1169           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.
1170       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1171          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
1172          i=tof22_i
1173        endif        endif
1174        endif        endif
1175    
# Line 875  C-----------------------------S3 ------- Line 1181  C-----------------------------S3 -------
1181           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.
1182       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1183          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
1184          i=tof31_i
1185        endif        endif
1186        endif        endif
1187    
# Line 884  C-----------------------------S3 ------- Line 1191  C-----------------------------S3 -------
1191           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.
1192       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1193          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
1194          i=tof32_i
1195        endif        endif
1196        endif        endif
1197    
# Line 898  c      enddo Line 1206  c      enddo
1206    
1207    
1208    
   
1209  C--------------------------------------------------------------------  C--------------------------------------------------------------------
1210  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 -------------------------  
1211  C-----------------angle and ADC(x) correction -----------------------  C-----------------angle and ADC(x) correction -----------------------
1212    C----------------   moved to the new dEdx routine -------------------
1213    
1214  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-----------------------------------------------------------------------  
1215  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1216  C-----------------------------------------------------------------------  C--------------------------------------------------------------------
1217  C-------------------difference of sums  ---------------------------  C---------------------difference of sums  ---------------------------
1218  C  C
1219  C     DS = (t1+t2) - t3+t4)  C     DS = (t1+t2) - t3+t4)
1220  C     DS = c1 + c2/beta*cos(theta)  C     DS = c1 + c2/beta*cos(theta)
# Line 1209  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1247  C      IF (tof11_i.GT.none_find.AND.tof3
1247              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1248              ihelp=(tof11_i-1)*3+tof31_i              ihelp=(tof11_i-1)*3+tof31_i
1249              c1 = k_S11S31(1,ihelp)              c1 = k_S11S31(1,ihelp)
1250                if (iz.gt.2) c1 = c1 + k1corrA1
1251              c2 = k_S11S31(2,ihelp)              c2 = k_S11S31(2,ihelp)
1252              beta_a(1) = c2*F/(ds-c1)              beta_a(1) = c2*F/(ds-c1)
1253         write(*,*) 'S11-S31 ',c1,c2,F  c       write(*,*) 'S11-S31 ',c1,c2,F
1254         write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
1255  C-------ToF Mask - S11 - S31  C-------ToF Mask - S11 - S31
1256    
1257              tofmask(ch11a(tof11_i),hb11a(tof11_i)) =              tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
# Line 1250  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1289  C      IF (tof11_i.GT.none_find.AND.tof3
1289              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1290              ihelp=(tof11_i-1)*3+tof32_i              ihelp=(tof11_i-1)*3+tof32_i
1291              c1 = k_S11S32(1,ihelp)              c1 = k_S11S32(1,ihelp)
1292                if (iz.gt.2) c1 = c1 + k1corrA1
1293              c2 = k_S11S32(2,ihelp)              c2 = k_S11S32(2,ihelp)
1294              beta_a(2) = c2*F/(ds-c1)              beta_a(2) = c2*F/(ds-c1)
1295  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
# Line 1293  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1333  C      IF (tof12_i.GT.none_find.AND.tof3
1333              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1334              ihelp=(tof12_i-1)*3+tof31_i              ihelp=(tof12_i-1)*3+tof31_i
1335              c1 = k_S12S31(1,ihelp)              c1 = k_S12S31(1,ihelp)
1336                if (iz.gt.2) c1 = c1 + k1corrA1
1337              c2 = k_S12S31(2,ihelp)              c2 = k_S12S31(2,ihelp)
1338              beta_a(3) = c2*F/(ds-c1)              beta_a(3) = c2*F/(ds-c1)
1339  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
# Line 1337  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1378  C      IF (tof12_i.GT.none_find.AND.tof3
1378              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1379              ihelp=(tof12_i-1)*3+tof32_i              ihelp=(tof12_i-1)*3+tof32_i
1380              c1 = k_S12S32(1,ihelp)              c1 = k_S12S32(1,ihelp)
1381                if (iz.gt.2) c1 = c1 + k1corrA1
1382              c2 = k_S12S32(2,ihelp)              c2 = k_S12S32(2,ihelp)
1383              beta_a(4) = c2*F/(ds-c1)              beta_a(4) = c2*F/(ds-c1)
1384  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
# Line 1381  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1423  C      IF (tof21_i.GT.none_find.AND.tof3
1423              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1424              ihelp=(tof21_i-1)*3+tof31_i              ihelp=(tof21_i-1)*3+tof31_i
1425              c1 = k_S21S31(1,ihelp)              c1 = k_S21S31(1,ihelp)
1426                if (iz.gt.2) c1 = c1 + k1corrB1
1427              c2 = k_S21S31(2,ihelp)              c2 = k_S21S31(2,ihelp)
1428              beta_a(5) = c2*F/(ds-c1)              beta_a(5) = c2*F/(ds-c1)
1429    
# Line 1424  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1467  C      IF (tof21_i.GT.none_find.AND.tof3
1467              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1468              ihelp=(tof21_i-1)*3+tof32_i              ihelp=(tof21_i-1)*3+tof32_i
1469              c1 = k_S21S32(1,ihelp)              c1 = k_S21S32(1,ihelp)
1470                if (iz.gt.2) c1 = c1 + k1corrB1
1471              c2 = k_S21S32(2,ihelp)              c2 = k_S21S32(2,ihelp)
1472              beta_a(6) = c2*F/(ds-c1)              beta_a(6) = c2*F/(ds-c1)
1473    
# Line 1452  C     S22 - S31 Line 1496  C     S22 - S31
1496           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1497        ENDDO        ENDDO
1498        F = dl/dist        F = dl/dist
1499          
1500    C WM workaround
1501          dl = dl - 0.06*F
1502          F = dl/dist
1503    
1504  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
1505         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.
# Line 1467  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1515  C      IF (tof22_i.GT.none_find.AND.tof3
1515              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1516              ihelp=(tof22_i-1)*3+tof31_i              ihelp=(tof22_i-1)*3+tof31_i
1517              c1 = k_S22S31(1,ihelp)              c1 = k_S22S31(1,ihelp)
1518                if (iz.gt.2) c1 = c1 + k1corrB1
1519              c2 = k_S22S31(2,ihelp)              c2 = k_S22S31(2,ihelp)
1520              beta_a(7) = c2*F/(ds-c1)              beta_a(7) = c2*F/(ds-c1)
1521    
# Line 1495  C     S22 - S32 Line 1544  C     S22 - S32
1544           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1545        ENDDO        ENDDO
1546        F = dl/dist        F = dl/dist
1547          
1548    C WM workaround      
1549          dl = dl - 0.06*F
1550          F = dl/dist
1551    
1552    
1553  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
1554         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 1510  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1564  C      IF (tof22_i.GT.none_find.AND.tof3
1564              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1565              ihelp=(tof22_i-1)*3+tof32_i              ihelp=(tof22_i-1)*3+tof32_i
1566              c1 = k_S22S32(1,ihelp)              c1 = k_S22S32(1,ihelp)
1567                if (iz.gt.2) c1 = c1 + k1corrB1
1568              c2 = k_S22S32(2,ihelp)              c2 = k_S22S32(2,ihelp)
1569              beta_a(8) = c2*F/(ds-c1)              beta_a(8) = c2*F/(ds-c1)
1570    
# Line 1539  C     S11 - S21 Line 1594  C     S11 - S21
1594        ENDDO        ENDDO
1595        F = dl/dist        F = dl/dist
1596    
1597    C WM workaround      
1598          dl = dl - 0.442*F
1599          F = dl/dist
1600    
1601  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
1602         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.
1603       &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
# Line 1553  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1612  C      IF (tof11_i.GT.none_find.AND.tof2
1612              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1613              ihelp=(tof11_i-1)*2+tof21_i              ihelp=(tof11_i-1)*2+tof21_i
1614              c1 = k_S11S21(1,ihelp)              c1 = k_S11S21(1,ihelp)
1615                if (iz.gt.2) c1 = c1 + k1corrC1
1616              c2 = k_S11S21(2,ihelp)              c2 = k_S11S21(2,ihelp)
1617              beta_a(9) = c2*F/(ds-c1)              beta_a(9) = c2*F/(ds-c1)
1618    
# Line 1596  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1656  C      IF (tof11_i.GT.none_find.AND.tof2
1656              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1657              ihelp=(tof11_i-1)*2+tof22_i              ihelp=(tof11_i-1)*2+tof22_i
1658              c1 = k_S11S22(1,ihelp)              c1 = k_S11S22(1,ihelp)
1659                if (iz.gt.2) c1 = c1 + k1corrC1
1660              c2 = k_S11S22(2,ihelp)              c2 = k_S11S22(2,ihelp)
1661              beta_a(10) = c2*F/(ds-c1)              beta_a(10) = c2*F/(ds-c1)
1662    
# Line 1625  C     S12 - S21 Line 1686  C     S12 - S21
1686        ENDDO        ENDDO
1687        F = dl/dist        F = dl/dist
1688    
1689    C  WM workaround
1690          dl = dl - 0.442*F
1691          F = dl/dist
1692    
1693  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
1694         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.
1695       &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
# Line 1639  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1704  C      IF (tof12_i.GT.none_find.AND.tof2
1704              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1705              ihelp=(tof12_i-1)*2+tof21_i              ihelp=(tof12_i-1)*2+tof21_i
1706              c1 = k_S12S21(1,ihelp)              c1 = k_S12S21(1,ihelp)
1707                if (iz.gt.2) c1 = c1 + k1corrC1
1708              c2 = k_S12S21(2,ihelp)              c2 = k_S12S21(2,ihelp)
1709              beta_a(11) = c2*F/(ds-c1)              beta_a(11) = c2*F/(ds-c1)
1710    
# Line 1682  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1748  C      IF (tof12_i.GT.none_find.AND.tof2
1748              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1749              ihelp=(tof12_i-1)*2+tof22_i              ihelp=(tof12_i-1)*2+tof22_i
1750              c1 = k_S12S22(1,ihelp)              c1 = k_S12S22(1,ihelp)
1751                if (iz.gt.2) c1 = c1 + k1corrC1
1752              c2 = k_S12S22(2,ihelp)              c2 = k_S12S22(2,ihelp)
1753              beta_a(12) = c2*F/(ds-c1)              beta_a(12) = c2*F/(ds-c1)
1754    
# Line 1703  C------- Line 1770  C-------
1770        ENDIF        ENDIF
1771    
1772  C-------  C-------
1773    C
1774    C      icount=0
1775    C      sw=0.
1776    C      sxw=0.
1777    C      beta_mean=100.
1778    C
1779    C      do i=1,12
1780    C         if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
1781    C            icount= icount+1
1782    C            if (i.le.4) w_i=1./(0.13**2.)
1783    C            if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1784    C            if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1785    C            sxw=sxw + beta_a(i)*w_i
1786    C            sw =sw + w_i
1787    C         endif
1788    C      enddo
1789    C
1790    C      if (icount.gt.0) beta_mean=sxw/sw
1791    C      beta_a(13) = beta_mean
1792    C
1793    
1794        icount=0  C-------  New mean beta  calculation
       sw=0.  
       sxw=0.  
       beta_mean=100.  
1795    
1796        do i=1,12         do i=1,12
1797           if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then           btemp(i) =  beta_a(i)
1798              icount= icount+1         enddo
1799              if (i.le.4) w_i=1./(0.13**2.)  
1800              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  
1801    
1802        if (icount.gt.0) beta_mean=sxw/sw  C-------
       beta_a(13) = beta_mean  
1803    
1804    
1805  c       IF (tof11_i.GT.none_find)  c       IF (tof11_i.GT.none_find)
# Line 1750  c      write(*,*) ytofpos Line 1828  c      write(*,*) ytofpos
1828  c      write(*,*) xtr_tof  c      write(*,*) xtr_tof
1829  c      write(*,*) ytr_tof  c      write(*,*) ytr_tof
1830    
1831    c       write(*,*) '---------  end toftrk ----------'
1832    
1833        RETURN        RETURN
1834        END        END
# Line 1760  c      write(*,*) ytr_tof Line 1838  c      write(*,*) ytr_tof
1838    
1839  C------------------------------------------------------------------  C------------------------------------------------------------------
1840    
1841    

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

  ViewVC Help
Powered by ViewVC 1.1.23