/[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.15 by mocchiut, Mon Mar 3 09:51:04 2008 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  C
48  C****************************************************************************  C****************************************************************************
49        IMPLICIT NONE        IMPLICIT NONE
# Line 68  c      REAL dx,dy,dr Line 77  c      REAL dx,dy,dr
77        REAL ds        REAL ds
78        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
79        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
80        REAL c1,c2,sw,sxw,w_i        REAL c1,c2
81    C     REAL sw,sxw,w_i
82        REAL dist,dl,F        REAL dist,dl,F
83        INTEGER icount,ievent        INTEGER ievent
84        REAL xhelp_a,xhelp_t  C      INTEGER icount
85    C      REAL beta_mean
86        REAL beta_mean        REAL btemp(12)
87        REAL hepratio        REAL hepratio
88    
89        INTEGER j        INTEGER j,hitvec(6)
90    
91        real atten,pc_adc        real atten,pc_adc,check_charge,newbeta
92    
93    
94        REAL theta,phi        REAL theta,phi
# Line 94  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 104  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
104        INTEGER ihelp        INTEGER ihelp
105        REAL xkorr,xpos        REAL xkorr,xpos
106    
107          INTEGER IZ
108          REAL k1corrA1,k1corrB1,k1corrC1
109    
110        REAL yl,yh,xl,xh        REAL yl,yh,xl,xh
111  C  C
112        REAL hmemor(9000000)        REAL hmemor(9000000)
# Line 101  C Line 114  C
114  C  C
115        DATA ievent / 0 /        DATA ievent / 0 /
116    
117          INTEGER ifst
118          DATA ifst /0/
119    
120        COMMON / pawcd / hmemor        COMMON / pawcd / hmemor
121        save / pawcd /        save / pawcd /
122  C  C
# Line 113  C Line 129  C
129    
130  *******************************************************************  *******************************************************************
131    
132        ievent = ievent +1         if (ifst.eq.0) then
133           ifst=1
134    
135  C  ratio helium to proton ca. 4  C  ratio helium to proton ca. 4
136        hepratio = 4.        hepratio = 4.
# Line 129  C  ratio helium to proton ca. 4 Line 146  C  ratio helium to proton ca. 4
146        itdc = 1        itdc = 1
147        iadc = 2        iadc = 2
148    
149    
150          k1corrA1 = 0.
151          k1corrB1 = -5.0
152          k1corrC1=  8.0
153    
154          ENDIF   ! ifst
155    
156    *******************************************************************
157    
158          ievent = ievent +1
159    
160        do i=1,13        do i=1,13
161           beta_a(i) = 100.           beta_a(i) = 100.
162        enddo        enddo
# Line 169  C  ratio helium to proton ca. 4 Line 197  C  ratio helium to proton ca. 4
197        ytr_tof(j) = 100.        ytr_tof(j) = 100.
198        enddo        enddo
199    
200    
201  C----------------------------------------------------------------------  C----------------------------------------------------------------------
202  C-------------------------get ToF data --------------------------------  C-------------------------get ToF data --------------------------------
203  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 284  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 313  C     COPY THE ALFA VECTOR FROM AL_PP TO
313  c      write(*,*) AL_P  c      write(*,*) AL_P
314    
315        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
316           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
317           GOTO 969           GOTO 969
318        ENDIF        ENDIF
319  *     -------- *** tracking routine *** --------  *     -------- *** tracking routine *** --------
# Line 295  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,A Line 324  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,A
324  C     write(*,*) (TLOUT(i),i=1,6)  C     write(*,*) (TLOUT(i),i=1,6)
325    
326        if(IFAIL.ne.0)then        if(IFAIL.ne.0)then
327           print *,' TOF - WARNING F77: tracking failed '  c         print *,' TOF - WARNING F77: tracking failed '
328           goto 969           goto 969
329        endif        endif
330  *     ------------------------------------------  *     ------------------------------------------
# Line 504  C--------------S32 --------------------- Line 533  C--------------S32 ---------------------
533    
534  C     write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i  C     write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
535    
536  C-----------------------------------------------------------------------         hitvec(1)=tof11_i
537  C--------------------Insert Artifical TDC Value  ---------------------         hitvec(2)=tof12_i
538  C     For each Paddle perform check:         hitvec(3)=tof21_i
539  C     if left paddle=4095  and right paddle OK => create TDC value left         hitvec(4)=tof22_i
540  C     if right paddle=4095  and left paddle OK => create TDC value right         hitvec(5)=tof31_i
541  C-----------------------------------------------------------------------         hitvec(6)=tof32_i
   
 C-----------------------S11 -----------------------------------------  
   
       IF (tof11_i.GT.none_find) THEN  
          xpos = yout(1)  
          i = tof11_i  
          if ((tof11(1,tof11_i,itdc).EQ.4095).AND.  
      &        (tof11(2,tof11_i,itdc).LT.4095)) THEN  
   
 c       write(*,*)'11lb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  
   
             tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)  
      &           + 2*(y_coor_lin11(tof11_i,offset)  
      &           + xpos*y_coor_lin11(tof11_i,slope))  
   
 c       write(*,*)'11laf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  
   
             tdcflag(ch11a(i),hb11a(i)) = 1  
   
         ENDIF  
          if ((tof11(2,tof11_i,itdc).EQ.4095).AND.  
      &        (tof11(1,tof11_i,itdc).LT.4095)) THEN  
   
 c       write(*,*)'11rb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  
   
             tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)  
      &           - 2*(y_coor_lin11(tof11_i,offset)  
      &           + xpos*y_coor_lin11(tof11_i,slope))  
 c       write(*,*)'11raf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)  
   
             tdcflag(ch11b(i),hb11b(i)) = 1  
          ENDIF  
       ENDIF  
   
 C-----------------------S12 -----------------------------------------  
   
       IF (tof12_i.GT.none_find) THEN  
          xpos = xout(2)  
          i = tof12_i  
          if ((tof12(1,tof12_i,itdc).EQ.4095).AND.  
      &        (tof12(2,tof12_i,itdc).LT.4095)) THEN  
             tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)  
      &           + 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  
   
 C-----------------------S21 -----------------------------------------  
   
       IF (tof21_i.GT.none_find) THEN  
          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  
   
 C-----------------------S22 -----------------------------------------  
   
       IF (tof22_i.GT.none_find) THEN  
          xpos = yout(4)  
          i = tof22_i  
          if ((tof22(1,tof22_i,itdc).EQ.4095).AND.  
      &        (tof22(2,tof22_i,itdc).LT.4095)) THEN  
             tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)  
      &           + 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  
542    
543  C-----------------------S31 -----------------------------------------  c       write(*,*) 'toftrk ',
544    c     &  tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
545    
546        IF (tof31_i.GT.none_find) THEN  C----------------------------------------------------------------------
547           xpos = yout(5)  C--- check charge:
548           i = tof31_i  C--- if Z=2 we should use the attenuation curve for helium to
549           if ((tof31(1,tof31_i,itdc).EQ.4095).AND.  C--- fill the artificail ADC values and NOT divide by "hepratio"
550       &        (tof31(2,tof31_i,itdc).LT.4095)) THEN  C--- if Z>2 we should do a correction to
551              tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)  C--- the k1 constants in the beta calculation
552       &           + 2*(y_coor_lin31(tof31_i,offset)  C----------------------------------------------------------------------
      &           + 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  
553    
554  C-----------------------S32 -----------------------------------------         theta=0.  
555           dist = ZTOF(1) - ZTOF(5)
556           dl = 0.
557           DO I=1,5
558             dl = dl + TLOUT(i)
559           ENDDO
560           F = dl/dist
561           theta = acos(1/F)
562    
563        IF (tof32_i.GT.none_find) THEN         iz = int(check_charge(theta,hitvec))
564           xpos = xout(6)  c       write(*,*) 'in toftrk',iz
          i = tof32_i  
          if ((tof32(1,tof32_i,itdc).EQ.4095).AND.  
      &        (tof32(2,tof32_i,itdc).LT.4095)) THEN  
             tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)  
      &           + 2*(x_coor_lin32(tof32_i,offset)  
      &           + xpos*x_coor_lin32(tof32_i,slope))  
             tdcflag(ch32a(i),hb32a(i)) = 1  
          ENDIF  
          if ((tof32(2,tof32_i,itdc).EQ.4095).AND.  
      &        (tof32(1,tof32_i,itdc).LT.4095)) THEN  
             tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)  
      &           - 2*(x_coor_lin32(tof32_i,offset)  
      &           + xpos*x_coor_lin32(tof32_i,slope))  
             tdcflag(ch32b(i),hb32b(i)) = 1  
          ENDIF  
       ENDIF  
565    
566  C--------------------------------------------------------------------  C--------------------------------------------------------------------
567  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
# Line 665  C----------------------------S1 -------- Line 579  C----------------------------S1 --------
579        yhelp=yout(1)        yhelp=yout(1)
580        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN
581           i = tof11_i           i = tof11_i
582           if ((tof11(left,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
583       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
584              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
585              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))  
586              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
587              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
588              tof11(left,i,iadc)=xkorr/cos(theta)              tof11(left,i,iadc)=xkorr/cos(theta)
589              adcflag(ch11a(i),hb11a(i)) = 1              adcflag(ch11a(i),hb11a(i)) = 1
590           endif           endif
591           if ((tof11(right,tof11_i,itdc).LT.4095).AND.           if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
592       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then
593              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
594              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))  
595              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
596              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
597              tof11(right,i,iadc)=xkorr/cos(theta)              tof11(right,i,iadc)=xkorr/cos(theta)
598              adcflag(ch11b(i),hb11b(i)) = 1              adcflag(ch11b(i),hb11b(i)) = 1
599           endif           endif
# Line 690  c            xkorr=adcx11(right,i,1)*exp Line 602  c            xkorr=adcx11(right,i,1)*exp
602        xhelp=xout(2)        xhelp=xout(2)
603        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN
604           i = tof12_i           i = tof12_i
605           if ((tof12(left,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
606       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
607              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
608              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
609  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
610              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
611              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
612              tof12(left,i,iadc) = xkorr/cos(theta)              tof12(left,i,iadc) = xkorr/cos(theta)
613              adcflag(ch12a(i),hb12a(i)) = 1              adcflag(ch12a(i),hb12a(i)) = 1
614           endif           endif
615           if ((tof12(right,tof12_i,itdc).LT.4095).AND.           if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
616       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then
617              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
618              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
619  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
620              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
621              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
622              tof12(right,i,iadc) = xkorr/cos(theta)              tof12(right,i,iadc) = xkorr/cos(theta)
623              adcflag(ch12b(i),hb12b(i)) = 1              adcflag(ch12b(i),hb12b(i)) = 1
624           endif           endif
# Line 717  C-----------------------------S2 ------- Line 629  C-----------------------------S2 -------
629        xhelp=xout(3)        xhelp=xout(3)
630        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN
631           i = tof21_i           i = tof21_i
632           if ((tof21(left,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
633       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
634              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
635              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
636  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
637              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
638              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
639              tof21(left,i,iadc) = xkorr/cos(theta)              tof21(left,i,iadc) = xkorr/cos(theta)
640              adcflag(ch21a(i),hb21a(i)) = 1              adcflag(ch21a(i),hb21a(i)) = 1
641           endif           endif
642           if ((tof21(right,tof21_i,itdc).LT.4095).AND.           if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
643       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then
644              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
645              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
646  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
647              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
648              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
649              tof21(right,i,iadc) = xkorr/cos(theta)              tof21(right,i,iadc) = xkorr/cos(theta)
650              adcflag(ch21b(i),hb21b(i)) = 1              adcflag(ch21b(i),hb21b(i)) = 1
651           endif           endif
# Line 743  c            xkorr=adcx21(right,i,1)*exp Line 655  c            xkorr=adcx21(right,i,1)*exp
655        yhelp=yout(4)        yhelp=yout(4)
656        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN
657           i = tof22_i           i = tof22_i
658           if ((tof22(left,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
659       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
660              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
661              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
662  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
663              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
664              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
665              tof22(left,i,iadc) = xkorr/cos(theta)              tof22(left,i,iadc) = xkorr/cos(theta)
666              adcflag(ch22a(i),hb22a(i)) = 1              adcflag(ch22a(i),hb22a(i)) = 1
667           endif           endif
668           if ((tof22(right,tof22_i,itdc).LT.4095).AND.           if ((tdc(ch22a(i),hb22b(i)).lt.4095).AND.
669       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
670              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
671              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
672  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
673              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
674              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
675              tof22(right,i,iadc) = xkorr/cos(theta)              tof22(right,i,iadc) = xkorr/cos(theta)
676              adcflag(ch22b(i),hb22b(i)) = 1              adcflag(ch22b(i),hb22b(i)) = 1
677           endif           endif
# Line 770  C-----------------------------S3 ------- Line 682  C-----------------------------S3 -------
682        yhelp=yout(5)        yhelp=yout(5)
683        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN
684           i = tof31_i           i = tof31_i
685           if ((tof31(left,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
686       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
687              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
688              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
689  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
690              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
691              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
692              tof31(left,i,iadc) = xkorr/cos(theta)              tof31(left,i,iadc) = xkorr/cos(theta)
693              adcflag(ch31a(i),hb31a(i)) = 1              adcflag(ch31a(i),hb31a(i)) = 1
694           endif           endif
695           if ((tof31(right,tof31_i,itdc).LT.4095).AND.           if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
696       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then
697              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
698              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
699  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
700              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
701              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
702              tof31(right,i,iadc) = xkorr/cos(theta)              tof31(right,i,iadc) = xkorr/cos(theta)
703              adcflag(ch31b(i),hb31b(i)) = 1              adcflag(ch31b(i),hb31b(i)) = 1
704           endif           endif
# Line 796  c            xkorr=adcx31(right,i,1)*exp Line 708  c            xkorr=adcx31(right,i,1)*exp
708        xhelp=xout(6)        xhelp=xout(6)
709        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
710           i = tof32_i           i = tof32_i
711           if ((tof32(left,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
712       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then
713              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
714              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
715  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
716              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
717              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
718              tof32(left,i,iadc) = xkorr/cos(theta)              tof32(left,i,iadc) = xkorr/cos(theta)
719              adcflag(ch32a(i),hb32a(i)) = 1              adcflag(ch32a(i),hb32a(i)) = 1
720           endif           endif
721           if ((tof32(right,tof32_i,itdc).LT.4095).AND.           if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
722       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then
723              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
724              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
725  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
726              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
727              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
728              tof32(right,i,iadc) = xkorr/cos(theta)              tof32(right,i,iadc) = xkorr/cos(theta)
729              adcflag(ch32b(i),hb32b(i)) = 1              adcflag(ch32b(i),hb32b(i)) = 1
730           endif           endif
731        ENDIF        ENDIF
732    
733    C-------------------------------------------------------------------
734    C Now there is for each hitted paddle a TDC and ADC value, if the
735    C TDC was < 4095.
736    C There might be also TDC-ADC pairs in paddles not hitted
737    C Let's correct the raw TDC value with the time walk
738    C-------------------------------------------------------------------
739    C--------------------Time walk correction  -------------------------
740    C-------------------------------------------------------------------
741    
742          DO i=1,8
743             if ((tdc(ch11a(i),hb11a(i)).lt.4095).and.
744         &             (tof11(left,i,iadc).lt.3786)) THEN
745             xhelp = tw11(left,i)/(tof11(left,i,iadc)**0.5)
746             tof11(left,i,itdc) = tof11(left,i,itdc) + xhelp
747             tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
748                                                  ENDIF
749    
750             if ((tdc(ch11b(i),hb11b(i)).lt.4095).and.
751         &             (tof11(right,i,iadc).lt.3786)) THEN
752             xhelp = tw11(right,i)/(tof11(right,i,iadc)**0.5)
753             tof11(right,i,itdc) = tof11(right,i,itdc) + xhelp
754             tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
755                                                 ENDIF
756          ENDDO
757    
758    
759          DO i=1,6
760             if ((tdc(ch12a(i),hb12a(i)).lt.4095).and.
761         &             (tof12(left,i,iadc).lt.3786)) THEN
762             xhelp = tw12(left,i)/(tof12(left,i,iadc)**0.5)
763             tof12(left,i,itdc) = tof12(left,i,itdc) + xhelp
764             tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
765                                                  ENDIF
766    
767             if ((tdc(ch12b(i),hb12b(i)).lt.4095).and.
768         &             (tof12(right,i,iadc).lt.3786)) THEN
769             xhelp = tw12(right,i)/(tof12(right,i,iadc)**0.5)
770             tof12(right,i,itdc) = tof12(right,i,itdc) + xhelp
771             tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
772                                                 ENDIF
773          ENDDO
774    
775    C----
776          DO I=1,2
777             if ((tdc(ch21a(i),hb21a(i)).lt.4095).and.
778         &             (tof21(left,i,iadc).lt.3786)) THEN
779             xhelp = tw21(left,i)/(tof21(left,i,iadc)**0.5)
780             tof21(left,i,itdc) = tof21(left,i,itdc) + xhelp
781             tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
782                                                  ENDIF
783    
784             if ((tdc(ch21b(i),hb21b(i)).lt.4095).and.
785         &             (tof21(right,i,iadc).lt.3786)) THEN
786             xhelp = tw21(right,i)/(tof21(right,i,iadc)**0.5)
787             tof21(right,i,itdc) = tof21(right,i,itdc) + xhelp
788             tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
789                                                 ENDIF
790          ENDDO
791    
792          DO I=1,2
793             if ((tdc(ch22a(i),hb22a(i)).lt.4095).and.
794         &             (tof22(left,i,iadc).lt.3786)) THEN
795             xhelp = tw22(left,i)/(tof22(left,i,iadc)**0.5)
796             tof22(left,i,itdc) = tof22(left,i,itdc) + xhelp
797             tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
798                                                  ENDIF
799    
800             if ((tdc(ch22b(i),hb22b(i)).lt.4095).and.
801         &             (tof22(right,i,iadc).lt.3786)) THEN
802             xhelp = tw22(right,i)/(tof22(right,i,iadc)**0.5)
803             tof22(right,i,itdc) = tof22(right,i,itdc) + xhelp
804             tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
805                                                 ENDIF
806          ENDDO
807    
808    C----
809          DO I=1,3
810             if ((tdc(ch31a(i),hb31a(i)).lt.4095).and.
811         &             (tof31(left,i,iadc).lt.3786)) THEN
812             xhelp = tw31(left,i)/(tof31(left,i,iadc)**0.5)
813             tof31(left,i,itdc) = tof31(left,i,itdc) + xhelp
814             tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
815                                                  ENDIF
816    
817             if ((tdc(ch31b(i),hb31b(i)).lt.4095).and.
818         &             (tof31(right,i,iadc).lt.3786)) THEN
819             xhelp = tw31(right,i)/(tof31(right,i,iadc)**0.5)
820             tof31(right,i,itdc) = tof31(right,i,itdc) + xhelp
821             tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
822                                                 ENDIF
823          ENDDO
824    
825          DO I=1,3
826             if ((tdc(ch32a(i),hb32a(i)).lt.4095).and.
827         &             (tof32(left,i,iadc).lt.3786)) THEN
828             xhelp = tw32(left,i)/(tof32(left,i,iadc)**0.5)
829             tof32(left,i,itdc) = tof32(left,i,itdc) + xhelp
830             tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
831                                                  ENDIF
832    
833             if ((tdc(ch32b(i),hb32b(i)).lt.4095).and.
834         &             (tof32(right,i,iadc).lt.3786)) THEN
835             xhelp = tw32(right,i)/(tof32(right,i,iadc)**0.5)
836             tof32(right,i,itdc) = tof32(right,i,itdc) + xhelp
837             tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
838                                                 ENDIF
839          ENDDO
840    
841    
842    C-----------------------------------------------------------------------
843    C--------------------Insert Artifical TDC Value  ---------------------
844    C     For each Paddle perform check:
845    C     if left paddle=4095  and right paddle OK => create TDC value left
846    C     if right paddle=4095  and left paddle OK => create TDC value right
847    C-----------------------------------------------------------------------
848    
849    C-----------------------S11 -----------------------------------------
850    
851          IF (tof11_i.GT.none_find) THEN
852             xpos = yout(1)
853             i = tof11_i
854            if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.
855         &          (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN
856              tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)
857         &           + 2*(y_coor_lin11(tof11_i,offset)
858         &           + xpos*y_coor_lin11(tof11_i,slope))
859                tdcflag(ch11a(i),hb11a(i)) = 1
860            ENDIF
861    
862            if ((tdc(ch11b(i),hb11b(i)).EQ.4095).AND.
863         &          (tdc(ch11a(i),hb11a(i)).LT.4095)) THEN
864                tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)
865         &           - 2*(y_coor_lin11(tof11_i,offset)
866         &           + xpos*y_coor_lin11(tof11_i,slope))
867                tdcflag(ch11b(i),hb11b(i)) = 1
868             ENDIF
869    
870          ENDIF
871    
872    C-----------------------S12 -----------------------------------------
873    
874          IF (tof12_i.GT.none_find) THEN
875             xpos = xout(2)
876             i = tof12_i
877            if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.
878         &          (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN
879                tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)
880         &           + 2*(x_coor_lin12(tof12_i,offset)
881         &           + xpos*x_coor_lin12(tof12_i,slope))
882                tdcflag(ch12a(i),hb12a(i)) = 1
883             ENDIF
884    
885            if ((tdc(ch12b(i),hb12b(i)).EQ.4095).AND.
886         &          (tdc(ch12a(i),hb12a(i)).LT.4095)) THEN
887                tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)
888         &           - 2*(x_coor_lin12(tof12_i,offset)
889         &           + xpos*x_coor_lin12(tof12_i,slope))
890                tdcflag(ch12b(i),hb12b(i)) = 1
891             ENDIF
892          ENDIF
893    
894    C-----------------------S21 -----------------------------------------
895    
896          IF (tof21_i.GT.none_find) THEN
897             xpos = xout(3)
898             i = tof21_i
899            if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.
900         &          (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN
901                tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)
902         &           + 2*(x_coor_lin21(tof21_i,offset)
903         &           + xpos*x_coor_lin21(tof21_i,slope))
904                tdcflag(ch21a(i),hb21a(i)) = 1
905             ENDIF
906    
907            if ((tdc(ch21b(i),hb21b(i)).EQ.4095).AND.
908         &          (tdc(ch21a(i),hb21a(i)).LT.4095)) THEN
909                tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)
910         &           - 2*(x_coor_lin21(tof21_i,offset)
911         &           + xpos*x_coor_lin21(tof21_i,slope))
912                tdcflag(ch21b(i),hb21b(i)) = 1
913             ENDIF
914          ENDIF
915    
916    C-----------------------S22 -----------------------------------------
917    
918          IF (tof22_i.GT.none_find) THEN
919             xpos = yout(4)
920             i = tof22_i
921            if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.
922         &          (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN
923                tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)
924         &           + 2*(y_coor_lin22(tof22_i,offset)
925         &           + xpos*y_coor_lin22(tof22_i,slope))
926                tdcflag(ch22a(i),hb22a(i)) = 1
927             ENDIF
928    
929            if ((tdc(ch22b(i),hb22b(i)).EQ.4095).AND.
930         &          (tdc(ch22a(i),hb22a(i)).LT.4095)) THEN
931                tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)
932         &           - 2*(y_coor_lin22(tof22_i,offset)
933         &           + xpos*y_coor_lin22(tof22_i,slope))
934                tdcflag(ch22b(i),hb22b(i)) = 1
935             ENDIF
936          ENDIF
937    
938    C-----------------------S31 -----------------------------------------
939    
940          IF (tof31_i.GT.none_find) THEN
941             xpos = yout(5)
942             i = tof31_i
943            if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.
944         &          (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN
945                tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)
946         &           + 2*(y_coor_lin31(tof31_i,offset)
947         &           + xpos*y_coor_lin31(tof31_i,slope))
948                tdcflag(ch31a(i),hb31a(i)) = 1
949             ENDIF
950    
951            if ((tdc(ch31b(i),hb31b(i)).EQ.4095).AND.
952         &          (tdc(ch31a(i),hb31a(i)).LT.4095)) THEN
953                tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)
954         &           - 2*(y_coor_lin31(tof31_i,offset)
955         &           + xpos*y_coor_lin31(tof31_i,slope))
956                tdcflag(ch31b(i),hb31b(i)) = 1
957             ENDIF
958          ENDIF
959    
960    C-----------------------S32 -----------------------------------------
961    
962          IF (tof32_i.GT.none_find) THEN
963             xpos = xout(6)
964             i = tof32_i
965            if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.
966         &          (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN
967                tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)
968         &           + 2*(x_coor_lin32(tof32_i,offset)
969         &           + xpos*x_coor_lin32(tof32_i,slope))
970                tdcflag(ch32a(i),hb32a(i)) = 1
971             ENDIF
972    
973            if ((tdc(ch32b(i),hb32b(i)).EQ.4095).AND.
974         &          (tdc(ch32a(i),hb32a(i)).LT.4095)) THEN
975                tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)
976         &           - 2*(x_coor_lin32(tof32_i,offset)
977         &           + xpos*x_coor_lin32(tof32_i,slope))
978                tdcflag(ch32b(i),hb32b(i)) = 1
979             ENDIF
980          ENDIF
981    
982    
983  C------------------------------------------------------------------  C------------------------------------------------------------------
984  C---  calculate track position in paddle using timing difference  C---  calculate track position in paddle using timing difference
# Line 827  C--------------------------------------- Line 988  C---------------------------------------
988           xtofpos(i)=100.           xtofpos(i)=100.
989           ytofpos(i)=100.           ytofpos(i)=100.
990        enddo        enddo
991    
992  C-----------------------------S1 --------------------------------  C-----------------------------S1 --------------------------------
993    
994        IF (tof11_i.GT.none_find) THEN        IF (tof11_i.GT.none_find) THEN
# Line 898  c      enddo Line 1060  c      enddo
1060    
1061    
1062    
   
 C--------------------------------------------------------------------  
 C--------------------Time walk correction  -------------------------  
 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  
   
   
1063  C---------------------------------------------------------------------  C---------------------------------------------------------------------
1064  C--------------------Corrections on ADC-data -------------------------  C--------------------Corrections on ADC-data -------------------------
1065  C-----------------angle and ADC(x) correction -----------------------  C-----------------angle and ADC(x) correction -----------------------
# Line 1016  C-----------------------------S1 ------- Line 1076  C-----------------------------S1 -------
1076           i = tof11_i           i = tof11_i
1077    
1078           if (tof11(left,i,iadc).lt.3786) then           if (tof11(left,i,iadc).lt.3786) then
 c         if (adc(ch11a(i),hb11a(i)).lt.4095) then  
1079              tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)              tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)
 c            xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))  
1080              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
1081              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1082              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
1083           endif           endif
1084    
1085    
1086           if (tof11(right,i,iadc).lt.3786) then           if (tof11(right,i,iadc).lt.3786) then
 c         if (adc(ch11b(i),hb11b(i)).lt.4095) then  
1087              tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)              tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)
 c            xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))  
1088              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
1089              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1090              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
1091           endif           endif
1092        ENDIF        ENDIF
# Line 1039  c            xkorr=adcx11(right,i,1)*exp Line 1095  c            xkorr=adcx11(right,i,1)*exp
1095        xhelp=xout(2)        xhelp=xout(2)
1096        phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))        phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
1097        theta = atan(tan(THXOUT(2))/cos(phi))        theta = atan(tan(THXOUT(2))/cos(phi))
 c      write(*,*) 'theta12 ',theta  
       IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN  
1098    
1099          IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
1100           i = tof12_i           i = tof12_i
1101           if (tof12(left,i,iadc).lt.3786) then           if (tof12(left,i,iadc).lt.3786) then
 c         if (adc(ch12a(i),hb12a(i)).lt.4095) then  
1102              tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)              tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)
 c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  
1103              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
1104              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1105              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
1106           endif           endif
1107    
1108           if (tof12(right,i,iadc).lt.3786) then           if (tof12(right,i,iadc).lt.3786) then
 c         if (adc(ch12b(i),hb12b(i)).lt.4095) then  
1109              tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)              tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)
 c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  
1110              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
1111              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1112              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
1113           endif           endif
1114        ENDIF        ENDIF
# Line 1067  C-----------------------------S2 ------- Line 1118  C-----------------------------S2 -------
1118        xhelp=xout(3)        xhelp=xout(3)
1119        phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))        phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
1120        theta = atan(tan(THXOUT(3))/cos(phi))        theta = atan(tan(THXOUT(3))/cos(phi))
 c      write(*,*) 'theta21 ',theta  
       IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN  
1121    
1122          IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
1123           i = tof21_i           i = tof21_i
1124           if (tof21(left,i,iadc).lt.3786) then           if (tof21(left,i,iadc).lt.3786) then
 c         if (adc(ch21a(i),hb21a(i)).lt.4095) then  
1125              tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)              tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)
 c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  
1126              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
1127              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1128              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
1129           endif           endif
1130    
1131           if (tof21(right,i,iadc).lt.3786) then           if (tof21(right,i,iadc).lt.3786) then
 c         if (adc(ch21b(i),hb21b(i)).lt.4095) then  
1132              tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)              tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)
 c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  
1133              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
1134              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1135              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
1136           endif           endif
1137        ENDIF        ENDIF
# Line 1093  c            xkorr=adcx21(right,i,1)*exp Line 1139  c            xkorr=adcx21(right,i,1)*exp
1139        yhelp=yout(4)        yhelp=yout(4)
1140        phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))        phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
1141        theta = atan(tan(THXOUT(4))/cos(phi))        theta = atan(tan(THXOUT(4))/cos(phi))
 c      write(*,*) 'theta22 ',theta  
1142    
1143        IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
   
1144           i = tof22_i           i = tof22_i
1145           if (tof22(left,i,iadc).lt.3786) then           if (tof22(left,i,iadc).lt.3786) then
 c         if (adc(ch22a(i),hb22a(i)).lt.4095) then  
1146              tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)              tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)
 c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  
1147              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
1148              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1149              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
1150           endif           endif
1151    
1152           if (tof22(right,i,iadc).lt.3786) then           if (tof22(right,i,iadc).lt.3786) then
 c         if (adc(ch22b(i),hb22b(i)).lt.4095) then  
1153              tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)              tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)
 c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  
1154              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
1155              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1156              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
1157           endif           endif
1158        ENDIF        ENDIF
# Line 1122  C-----------------------------S3 ------- Line 1162  C-----------------------------S3 -------
1162        yhelp=yout(5)        yhelp=yout(5)
1163        phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))        phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
1164        theta = atan(tan(THXOUT(5))/cos(phi))        theta = atan(tan(THXOUT(5))/cos(phi))
 c      write(*,*) 'theta31 ',theta  
1165    
1166        IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
1167    
1168           i = tof31_i           i = tof31_i
1169           if (tof31(left,i,iadc).lt.3786) then           if (tof31(left,i,iadc).lt.3786) then
 c         if (adc(ch31a(i),hb31a(i)).lt.4095) then  
1170              tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)              tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)
 c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  
1171              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
1172              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1173              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1174           endif           endif
1175    
1176           if (tof31(right,i,iadc).lt.3786) then           if (tof31(right,i,iadc).lt.3786) then
 c         if (adc(ch31b(i),hb31b(i)).lt.4095) then  
1177              tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)              tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)
 c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  
1178              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
1179              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1180              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1181           endif           endif
1182        ENDIF        ENDIF
# Line 1149  c            xkorr=adcx31(right,i,1)*exp Line 1184  c            xkorr=adcx31(right,i,1)*exp
1184        xhelp=xout(6)        xhelp=xout(6)
1185        phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))        phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
1186        theta = atan(tan(THXOUT(6))/cos(phi))        theta = atan(tan(THXOUT(6))/cos(phi))
 c      write(*,*) 'theta32 ',theta  
1187    
1188        IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN        IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
   
1189           i = tof32_i           i = tof32_i
1190           if (tof32(left,i,iadc).lt.3786) then           if (tof32(left,i,iadc).lt.3786) then
 c         if (adc(ch32a(i),hb32a(i)).lt.4095) then  
1191              tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)              tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)
 c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  
1192              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
1193              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1194              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1195           endif           endif
1196    
1197           if (tof32(right,i,iadc).lt.3786) then           if (tof32(right,i,iadc).lt.3786) then
 c         if (adc(ch32b(i),hb32b(i)).lt.4095) then  
1198              tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)              tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)
 c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  
1199              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
1200              xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
1201              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1202           endif           endif
1203        ENDIF        ENDIF
1204    
1205    
1206  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
1207  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1208  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
# Line 1209  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1239  C      IF (tof11_i.GT.none_find.AND.tof3
1239              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1240              ihelp=(tof11_i-1)*3+tof31_i              ihelp=(tof11_i-1)*3+tof31_i
1241              c1 = k_S11S31(1,ihelp)              c1 = k_S11S31(1,ihelp)
1242                if (iz.gt.2) c1 = c1 + k1corrA1
1243              c2 = k_S11S31(2,ihelp)              c2 = k_S11S31(2,ihelp)
1244              beta_a(1) = c2*F/(ds-c1)              beta_a(1) = c2*F/(ds-c1)
1245         write(*,*) 'S11-S31 ',c1,c2,F  c       write(*,*) 'S11-S31 ',c1,c2,F
1246         write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
1247  C-------ToF Mask - S11 - S31  C-------ToF Mask - S11 - S31
1248    
1249              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 1281  C      IF (tof11_i.GT.none_find.AND.tof3
1281              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1282              ihelp=(tof11_i-1)*3+tof32_i              ihelp=(tof11_i-1)*3+tof32_i
1283              c1 = k_S11S32(1,ihelp)              c1 = k_S11S32(1,ihelp)
1284                if (iz.gt.2) c1 = c1 + k1corrA1
1285              c2 = k_S11S32(2,ihelp)              c2 = k_S11S32(2,ihelp)
1286              beta_a(2) = c2*F/(ds-c1)              beta_a(2) = c2*F/(ds-c1)
1287  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 1325  C      IF (tof12_i.GT.none_find.AND.tof3
1325              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1326              ihelp=(tof12_i-1)*3+tof31_i              ihelp=(tof12_i-1)*3+tof31_i
1327              c1 = k_S12S31(1,ihelp)              c1 = k_S12S31(1,ihelp)
1328                if (iz.gt.2) c1 = c1 + k1corrA1
1329              c2 = k_S12S31(2,ihelp)              c2 = k_S12S31(2,ihelp)
1330              beta_a(3) = c2*F/(ds-c1)              beta_a(3) = c2*F/(ds-c1)
1331  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 1370  C      IF (tof12_i.GT.none_find.AND.tof3
1370              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1371              ihelp=(tof12_i-1)*3+tof32_i              ihelp=(tof12_i-1)*3+tof32_i
1372              c1 = k_S12S32(1,ihelp)              c1 = k_S12S32(1,ihelp)
1373                if (iz.gt.2) c1 = c1 + k1corrA1
1374              c2 = k_S12S32(2,ihelp)              c2 = k_S12S32(2,ihelp)
1375              beta_a(4) = c2*F/(ds-c1)              beta_a(4) = c2*F/(ds-c1)
1376  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 1415  C      IF (tof21_i.GT.none_find.AND.tof3
1415              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1416              ihelp=(tof21_i-1)*3+tof31_i              ihelp=(tof21_i-1)*3+tof31_i
1417              c1 = k_S21S31(1,ihelp)              c1 = k_S21S31(1,ihelp)
1418                if (iz.gt.2) c1 = c1 + k1corrB1
1419              c2 = k_S21S31(2,ihelp)              c2 = k_S21S31(2,ihelp)
1420              beta_a(5) = c2*F/(ds-c1)              beta_a(5) = c2*F/(ds-c1)
1421    
# Line 1424  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1459  C      IF (tof21_i.GT.none_find.AND.tof3
1459              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1460              ihelp=(tof21_i-1)*3+tof32_i              ihelp=(tof21_i-1)*3+tof32_i
1461              c1 = k_S21S32(1,ihelp)              c1 = k_S21S32(1,ihelp)
1462                if (iz.gt.2) c1 = c1 + k1corrB1
1463              c2 = k_S21S32(2,ihelp)              c2 = k_S21S32(2,ihelp)
1464              beta_a(6) = c2*F/(ds-c1)              beta_a(6) = c2*F/(ds-c1)
1465    
# Line 1467  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1503  C      IF (tof22_i.GT.none_find.AND.tof3
1503              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1504              ihelp=(tof22_i-1)*3+tof31_i              ihelp=(tof22_i-1)*3+tof31_i
1505              c1 = k_S22S31(1,ihelp)              c1 = k_S22S31(1,ihelp)
1506                if (iz.gt.2) c1 = c1 + k1corrB1
1507              c2 = k_S22S31(2,ihelp)              c2 = k_S22S31(2,ihelp)
1508              beta_a(7) = c2*F/(ds-c1)              beta_a(7) = c2*F/(ds-c1)
1509    
# Line 1510  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1547  C      IF (tof22_i.GT.none_find.AND.tof3
1547              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1548              ihelp=(tof22_i-1)*3+tof32_i              ihelp=(tof22_i-1)*3+tof32_i
1549              c1 = k_S22S32(1,ihelp)              c1 = k_S22S32(1,ihelp)
1550                if (iz.gt.2) c1 = c1 + k1corrB1
1551              c2 = k_S22S32(2,ihelp)              c2 = k_S22S32(2,ihelp)
1552              beta_a(8) = c2*F/(ds-c1)              beta_a(8) = c2*F/(ds-c1)
1553    
# Line 1553  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1591  C      IF (tof11_i.GT.none_find.AND.tof2
1591              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1592              ihelp=(tof11_i-1)*2+tof21_i              ihelp=(tof11_i-1)*2+tof21_i
1593              c1 = k_S11S21(1,ihelp)              c1 = k_S11S21(1,ihelp)
1594                if (iz.gt.2) c1 = c1 + k1corrC1
1595              c2 = k_S11S21(2,ihelp)              c2 = k_S11S21(2,ihelp)
1596              beta_a(9) = c2*F/(ds-c1)              beta_a(9) = c2*F/(ds-c1)
1597    
# Line 1596  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1635  C      IF (tof11_i.GT.none_find.AND.tof2
1635              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1636              ihelp=(tof11_i-1)*2+tof22_i              ihelp=(tof11_i-1)*2+tof22_i
1637              c1 = k_S11S22(1,ihelp)              c1 = k_S11S22(1,ihelp)
1638                if (iz.gt.2) c1 = c1 + k1corrC1
1639              c2 = k_S11S22(2,ihelp)              c2 = k_S11S22(2,ihelp)
1640              beta_a(10) = c2*F/(ds-c1)              beta_a(10) = c2*F/(ds-c1)
1641    
# Line 1639  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1679  C      IF (tof12_i.GT.none_find.AND.tof2
1679              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1680              ihelp=(tof12_i-1)*2+tof21_i              ihelp=(tof12_i-1)*2+tof21_i
1681              c1 = k_S12S21(1,ihelp)              c1 = k_S12S21(1,ihelp)
1682                if (iz.gt.2) c1 = c1 + k1corrC1
1683              c2 = k_S12S21(2,ihelp)              c2 = k_S12S21(2,ihelp)
1684              beta_a(11) = c2*F/(ds-c1)              beta_a(11) = c2*F/(ds-c1)
1685    
# Line 1682  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1723  C      IF (tof12_i.GT.none_find.AND.tof2
1723              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1724              ihelp=(tof12_i-1)*2+tof22_i              ihelp=(tof12_i-1)*2+tof22_i
1725              c1 = k_S12S22(1,ihelp)              c1 = k_S12S22(1,ihelp)
1726                if (iz.gt.2) c1 = c1 + k1corrC1
1727              c2 = k_S12S22(2,ihelp)              c2 = k_S12S22(2,ihelp)
1728              beta_a(12) = c2*F/(ds-c1)              beta_a(12) = c2*F/(ds-c1)
1729    
# Line 1703  C------- Line 1745  C-------
1745        ENDIF        ENDIF
1746    
1747  C-------  C-------
1748    C
1749    C      icount=0
1750    C      sw=0.
1751    C      sxw=0.
1752    C      beta_mean=100.
1753    C
1754    C      do i=1,12
1755    C         if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
1756    C            icount= icount+1
1757    C            if (i.le.4) w_i=1./(0.13**2.)
1758    C            if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1759    C            if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1760    C            sxw=sxw + beta_a(i)*w_i
1761    C            sw =sw + w_i
1762    C         endif
1763    C      enddo
1764    C
1765    C      if (icount.gt.0) beta_mean=sxw/sw
1766    C      beta_a(13) = beta_mean
1767    C
1768    C-------  New mean beta  calculation
1769    
1770        icount=0         do i=1,12
1771        sw=0.           btemp(i) =  beta_a(i)
1772        sxw=0.         enddo
       beta_mean=100.  
1773    
1774        do i=1,12         beta_a(13)=newbeta(btemp,hitvec,10.,10.,20.)
          if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then  
             icount= icount+1  
             if (i.le.4) w_i=1./(0.13**2.)  
             if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)  
             if (i.ge.9) w_i=1./(0.25**2.) ! to be checked  
             sxw=sxw + beta_a(i)*w_i  
             sw =sw + w_i  
          endif  
       enddo  
1775    
1776        if (icount.gt.0) beta_mean=sxw/sw  C-------
       beta_a(13) = beta_mean  
1777    
1778    
1779  c       IF (tof11_i.GT.none_find)  c       IF (tof11_i.GT.none_find)

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

  ViewVC Help
Powered by ViewVC 1.1.23