/[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.19 by mocchiut, Mon Nov 23 09:50:51 2009 UTC revision 1.22 by mocchiut, Thu Jan 16 15:29:37 2014 UTC
# Line 53  C  oct-08 WM: New method to create artif Line 53  C  oct-08 WM: New method to create artif
53  C             from the tracking, but the position from timing. This method gives a  C             from the tracking, but the position from timing. This method gives a
54  C             better time resolution  C             better time resolution
55  C  nov-09 WM: the dEdx part ("adc_c") moved to the new dEdx routine from Napoli  C  nov-09 WM: the dEdx part ("adc_c") moved to the new dEdx routine from Napoli
56    C  feb-10 WM: k1 values now for Z=1, Z=2, Z>2, k2 values are fix
57    C  feb-10 WM: charge calculation with tracker dEdx vs. deflection^2
58  C  C
59  C****************************************************************************  C****************************************************************************
60        IMPLICIT NONE        IMPLICIT NONE
# Line 71  c     ================================== Line 73  c     ==================================
73  c     define TOF Z-coordinates  c     define TOF Z-coordinates
74        integer NPTOF        integer NPTOF
75        parameter (NPTOF=6)        parameter (NPTOF=6)
76        DOUBLE PRECISION ZTOF(NPTOF)  c      DOUBLE PRECISION ZTOF(NPTOF)
77          REAL ZTOF(NPTOF) !EM GCC4.7
78        DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006        DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
79    
80        integer itof,pmt_id        integer itof,pmt_id
# Line 80  c     define TOF Z-coordinates Line 83  c     define TOF Z-coordinates
83       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
84       &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)       &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
85    
86          DOUBLE PRECISION dedxtrk
87          DOUBLE PRECISION deflection
88    
89        INTEGER IFAIL        INTEGER IFAIL
90  c      REAL dx,dy,dr  c      REAL dx,dy,dr
91        REAL ds        REAL ds
92        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
93        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
94          REAL(8) yhelp1,yhelp2
95        REAL c1,c2        REAL c1,c2
96  C     REAL sw,sxw,w_i  C     REAL sw,sxw,w_i
97        REAL dist,dl,F        REAL dist,dl,F
# Line 97  C      REAL beta_mean Line 103  C      REAL beta_mean
103    
104        INTEGER j,hitvec(6)        INTEGER j,hitvec(6)
105    
106        real atten,pc_adc,check_charge,newbeta        real atten,pc_adc,newbeta
107    C      real check_charge
108    
109    
110        REAL theta,phi        REAL theta,phi
# Line 153  C--- Line 160  C---
160        REAL xkorr,xpos        REAL xkorr,xpos
161    
162        INTEGER IZ        INTEGER IZ
       REAL k1corrA1,k1corrB1,k1corrC1  
163    
164        REAL yl,yh,xl,xh        REAL yl,yh,xl,xh
165  C  C
# Line 194  C  ratio helium to proton ca. 4 Line 200  C  ratio helium to proton ca. 4
200        itdc = 1        itdc = 1
201        iadc = 2        iadc = 2
202    
   
       k1corrA1 = 0.  
       k1corrB1 = -5.0  
       k1corrC1=  8.0  
   
203        ENDIF   ! ifst        ENDIF   ! ifst
204    
205  *******************************************************************  *******************************************************************
# Line 357  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 358  C     COPY THE ALFA VECTOR FROM AL_PP TO
358        do i=1,5        do i=1,5
359           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
360        enddo        enddo
361          deflection = AL_P(5)
362    *     3) tracker dEdx
363          dedxtrk = trkmip
364        
365  c      write(*,*) AL_P  c      write(*,*) AL_P
366  c      write(*,*) 'Rigidity ',(1./AL_P(5))  c      write(*,*) 'Rig, Def, dEdx ',(1./AL_P(5)),AL_P(5),dedxtrk
367    
368    
369    C--  charge selection with tracker using dedx vs. deflection^2  ----
370    
371           yhelp1 = 3.5 + 4.5*deflection*deflection
372           yhelp2 = 9. + 20.*deflection*deflection
373    c       write(*,*) yhelp1,yhelp2
374    
375           iz = 0
376           if  (dedxtrk.lt.yhelp1) iz=1
377           if ((dedxtrk.gt.yhelp1).and.(dedxtrk.lt.yhelp2)) iz=2
378           if  (dedxtrk.gt.yhelp2) iz=3
379    c       write(*,*) 'tracker charge ',iz
380    
381    C--------------------------------------------------------------------
382    
383        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
384  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
# Line 382  c         print *,' TOF - WARNING F77: t Line 401  c         print *,' TOF - WARNING F77: t
401    
402  C---  Fill xtr_tof  and ytr_tof: positions from tracker at ToF layers  C---  Fill xtr_tof  and ytr_tof: positions from tracker at ToF layers
403        do j=1,6        do j=1,6
404        xtr_tof(j) = XOUT(j)        xtr_tof(j) = REAL(XOUT(j)) !EM GCC4.7
405        ytr_tof(j) = YOUT(j)        ytr_tof(j) = REAL(YOUT(j)) !EM GCC4.7
406  c      write(*,*) XOUT(j),YOUT(j)  c      write(*,*) XOUT(j),YOUT(j)
407        enddo        enddo
408    
# Line 394  C---  convert  angles to radian Line 413  C---  convert  angles to radian
413        THYOUT(j) = 3.1415927*THYOUT(j)/180.        THYOUT(j) = 3.1415927*THYOUT(j)/180.
414        enddo        enddo
415    
416        do j=1,6  c      do j=1,6 !EM GCC 4.7
417  c      write (*,*) j,THXOUT(j),THYOUT(j)  c      write (*,*) j,THXOUT(j),THYOUT(j)
418        enddo  c      enddo !EM GCC4.7
419    
420    
421  C----------------------------------------------------------------------  C----------------------------------------------------------------------
# Line 600  C--------------------------------------- Line 619  C---------------------------------------
619         dist = ZTOF(1) - ZTOF(5)         dist = ZTOF(1) - ZTOF(5)
620         dl = 0.         dl = 0.
621         DO I=1,5         DO I=1,5
622           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC4.7
623         ENDDO         ENDDO
624         F = dl/dist         F = dl/dist
625         theta = acos(1/F)         theta = acos(1/F)
626    
627         iz = int(check_charge(theta,hitvec))  c       iz = int(check_charge(theta,hitvec))
628  c       write(*,*) 'in toftrk',iz  c       write(*,*) 'in toftrk',iz
629    
630    
# Line 627  C-----------------------------S1 ------- Line 646  C-----------------------------S1 -------
646        IF (tof11_i.GT.none_find) THEN        IF (tof11_i.GT.none_find) THEN
647        IF ((tof11(1,tof11_i,itdc).LT.2000).AND.        IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
648       +                             (tof11(2,tof11_i,itdc).LT.2000))       +                             (tof11(2,tof11_i,itdc).LT.2000))
649       +    ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.       +   ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
650       +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)       +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
651        endif        endif
652    
653        IF (tof12_i.GT.none_find) THEN        IF (tof12_i.GT.none_find) THEN
654        IF ((tof12(1,tof12_i,itdc).LT.2000).AND.        IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
655       +                             (tof12(2,tof12_i,itdc).LT.2000))       +                             (tof12(2,tof12_i,itdc).LT.2000))
656       +    xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.       +   xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
657       +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)       +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
658        endif        endif
659    
# Line 644  C-----------------------------S2 ------- Line 663  C-----------------------------S2 -------
663        IF (tof21_i.GT.none_find) THEN        IF (tof21_i.GT.none_find) THEN
664        IF ((tof21(1,tof21_i,itdc).LT.2000).AND.        IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
665       +                             (tof21(2,tof21_i,itdc).LT.2000))       +                             (tof21(2,tof21_i,itdc).LT.2000))
666       +    xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.       +   xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
667       +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)       +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
668        endif        endif
669    
# Line 661  C-----------------------------S3 ------- Line 680  C-----------------------------S3 -------
680        IF (tof31_i.GT.none_find) THEN        IF (tof31_i.GT.none_find) THEN
681        IF ((tof31(1,tof31_i,itdc).LT.2000).AND.        IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
682       +                             (tof31(2,tof31_i,itdc).LT.2000))       +                             (tof31(2,tof31_i,itdc).LT.2000))
683       +    ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.       +   ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
684       +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)       +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
685        endif        endif
686    
687        IF (tof32_i.GT.none_find) THEN        IF (tof32_i.GT.none_find) THEN
688        IF ((tof32(1,tof32_i,itdc).LT.2000).AND.        IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
689       +                             (tof32(2,tof32_i,itdc).LT.2000))       +                             (tof32(2,tof32_i,itdc).LT.2000))
690       +    xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.       +   xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
691       +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)       +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
692        endif        endif
693    
# Line 700  C----------------------------S1 -------- Line 719  C----------------------------S1 --------
719    
720  c     yhelp=yout(1)  c     yhelp=yout(1)
721        yhelp = ytofpre(1)        yhelp = ytofpre(1)
722        if (yhelp.eq.100) yhelp=yout(1)        if (yhelp.eq.100) yhelp=REAL(yout(1)) !EM GCC4.7
723    
724        IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN        IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
725           i = tof11_i           i = tof11_i
726           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
727       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
728              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(REAL(THYOUT(1)))/tan(REAL(THXOUT(1))))
729              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(REAL(THXOUT(1)))/cos(phi))
730              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
731              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
732              tof11(left,i,iadc)=xkorr/cos(theta)              tof11(left,i,iadc)=xkorr/cos(theta)
# Line 715  c     yhelp=yout(1) Line 734  c     yhelp=yout(1)
734           endif           endif
735           if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.           if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
736       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then       &       (adc(ch11b(i),hb11b(i)).eq.4095)) then
737              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))              phi   = atan(tan(REAL(THYOUT(1)))/tan(REAL(THXOUT(1))))
738              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(REAL(THXOUT(1)))/cos(phi))
739              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
740              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
741              tof11(right,i,iadc)=xkorr/cos(theta)              tof11(right,i,iadc)=xkorr/cos(theta)
# Line 726  c     yhelp=yout(1) Line 745  c     yhelp=yout(1)
745    
746  c      xhelp=xout(2)  c      xhelp=xout(2)
747        xhelp = xtofpre(1)        xhelp = xtofpre(1)
748        if (xhelp.eq.100) xhelp=xout(2)        if (xhelp.eq.100) xhelp=REAL(xout(2))
749    
750        IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN        IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
751           i = tof12_i           i = tof12_i
752           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
753       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
754              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(REAL(THYOUT(2)))/tan(REAL(THXOUT(2))))
755              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(REAL(THXOUT(2)))/cos(phi))
756  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))  c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
757              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
758              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 742  c            xkorr=adcx12(left,i,1)*exp( Line 761  c            xkorr=adcx12(left,i,1)*exp(
761           endif           endif
762           if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.           if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
763       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then       &       (adc(ch12b(i),hb12b(i)).eq.4095)) then
764              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))              phi   = atan(tan(REAL(THYOUT(2)))/tan(REAL(THXOUT(2))))
765              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(REAL(THXOUT(2)))/cos(phi))
766  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))  c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
767              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
768              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 756  C-----------------------------S2 ------- Line 775  C-----------------------------S2 -------
775    
776  c      xhelp=xout(3)  c      xhelp=xout(3)
777        xhelp = xtofpre(2)        xhelp = xtofpre(2)
778        if (xhelp.eq.100) xhelp=xout(3)        if (xhelp.eq.100) xhelp=REAL(xout(3))
779    
780        IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN        IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
781           i = tof21_i           i = tof21_i
782           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
783       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
784              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(REAL(THYOUT(3)))/tan(REAL(THXOUT(3))))
785              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(REAL(THXOUT(3)))/cos(phi))
786  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))  c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
787              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
788              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 772  c            xkorr=adcx21(left,i,1)*exp( Line 791  c            xkorr=adcx21(left,i,1)*exp(
791           endif           endif
792           if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.           if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
793       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then       &       (adc(ch21b(i),hb21b(i)).eq.4095)) then
794              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))              phi   = atan(tan(REAL(THYOUT(3)))/tan(REAL(THXOUT(3))))
795              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(REAL(THXOUT(3)))/cos(phi))
796  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))  c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
797              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
798              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 785  c            xkorr=adcx21(right,i,1)*exp Line 804  c            xkorr=adcx21(right,i,1)*exp
804    
805  c      yhelp=yout(4)  c      yhelp=yout(4)
806        yhelp = ytofpre(2)        yhelp = ytofpre(2)
807        if (yhelp.eq.100) yhelp=yout(4)        if (yhelp.eq.100) yhelp=REAL(yout(4))
808    
809        IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN        IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
810           i = tof22_i           i = tof22_i
811           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
812       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
813              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(REAL(THYOUT(4)))/tan(REAL(THXOUT(4))))
814              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(REAL(THXOUT(4)))/cos(phi))
815  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))  c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
816              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
817              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 801  c            xkorr=adcx22(left,i,1)*exp( Line 820  c            xkorr=adcx22(left,i,1)*exp(
820           endif           endif
821           if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.           if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
822       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
823              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(REAL(THYOUT(4)))/tan(REAL(THXOUT(4))))
824              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(REAL(THXOUT(4)))/cos(phi))
825  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))  c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
826              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
827              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 815  C-----------------------------S3 ------- Line 834  C-----------------------------S3 -------
834    
835  c      yhelp=yout(5)  c      yhelp=yout(5)
836        yhelp = ytofpre(3)        yhelp = ytofpre(3)
837        if (yhelp.eq.100) yhelp=yout(5)        if (yhelp.eq.100) yhelp=REAL(yout(5))
838    
839        IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN        IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
840           i = tof31_i           i = tof31_i
841           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
842       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
843              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(REAL(THYOUT(5)))/tan(REAL(THXOUT(5))))
844              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(REAL(THXOUT(5)))/cos(phi))
845  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))  c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
846              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
847              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 831  c            xkorr=adcx31(left,i,1)*exp( Line 850  c            xkorr=adcx31(left,i,1)*exp(
850           endif           endif
851           if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.           if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
852       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then       &       (adc(ch31b(i),hb31b(i)).eq.4095)) then
853              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))              phi   = atan(tan(REAL(THYOUT(5)))/tan(REAL(THXOUT(5))))
854              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(REAL(THXOUT(5)))/cos(phi))
855  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))  c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
856              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
857              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 844  c            xkorr=adcx31(right,i,1)*exp Line 863  c            xkorr=adcx31(right,i,1)*exp
863    
864  c      xhelp=xout(6)  c      xhelp=xout(6)
865        xhelp = xtofpre(3)        xhelp = xtofpre(3)
866        if (xhelp.eq.100) xhelp=xout(6)        if (xhelp.eq.100) xhelp=REAL(xout(6))
867    
868        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
869           i = tof32_i           i = tof32_i
870           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
871       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then       &       (adc(ch32a(i),hb32a(i)).eq.4095)) then
872              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(REAL(THYOUT(6)))/tan(REAL(THXOUT(6))))
873              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(REAL(THXOUT(6)))/cos(phi))
874  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))  c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
875              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
876              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 860  c            xkorr=adcx32(left,i,1)*exp( Line 879  c            xkorr=adcx32(left,i,1)*exp(
879           endif           endif
880           if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.           if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
881       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then       &       (adc(ch32b(i),hb32b(i)).eq.4095)) then
882              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))              phi   = atan(tan(REAL(THYOUT(6)))/tan(REAL(THXOUT(6))))
883              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(REAL(THXOUT(6)))/cos(phi))
884  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))  c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
885              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
886              if (iz.le.1) xkorr=xkorr/hepratio              if (iz.le.1) xkorr=xkorr/hepratio
# Line 989  C--------------------------------------- Line 1008  C---------------------------------------
1008  C-----------------------S11 -----------------------------------------  C-----------------------S11 -----------------------------------------
1009    
1010        IF (tof11_i.GT.none_find) THEN        IF (tof11_i.GT.none_find) THEN
1011           xpos = yout(1)           xpos = REAL(yout(1))
1012           i = tof11_i           i = tof11_i
1013          if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.          if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.
1014       &          (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN       &          (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN
# Line 1012  C-----------------------S11 ------------ Line 1031  C-----------------------S11 ------------
1031  C-----------------------S12 -----------------------------------------  C-----------------------S12 -----------------------------------------
1032    
1033        IF (tof12_i.GT.none_find) THEN        IF (tof12_i.GT.none_find) THEN
1034           xpos = xout(2)           xpos = REAL(xout(2))
1035           i = tof12_i           i = tof12_i
1036          if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.          if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.
1037       &          (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN       &          (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN
# Line 1034  C-----------------------S12 ------------ Line 1053  C-----------------------S12 ------------
1053  C-----------------------S21 -----------------------------------------  C-----------------------S21 -----------------------------------------
1054    
1055        IF (tof21_i.GT.none_find) THEN        IF (tof21_i.GT.none_find) THEN
1056           xpos = xout(3)           xpos = REAL(xout(3))
1057           i = tof21_i           i = tof21_i
1058          if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.          if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.
1059       &          (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN       &          (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN
# Line 1056  C-----------------------S21 ------------ Line 1075  C-----------------------S21 ------------
1075  C-----------------------S22 -----------------------------------------  C-----------------------S22 -----------------------------------------
1076    
1077        IF (tof22_i.GT.none_find) THEN        IF (tof22_i.GT.none_find) THEN
1078           xpos = yout(4)           xpos = REAL(yout(4))
1079           i = tof22_i           i = tof22_i
1080          if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.          if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.
1081       &          (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN       &          (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN
# Line 1078  C-----------------------S22 ------------ Line 1097  C-----------------------S22 ------------
1097  C-----------------------S31 -----------------------------------------  C-----------------------S31 -----------------------------------------
1098    
1099        IF (tof31_i.GT.none_find) THEN        IF (tof31_i.GT.none_find) THEN
1100           xpos = yout(5)           xpos = REAL(yout(5))
1101           i = tof31_i           i = tof31_i
1102          if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.          if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.
1103       &          (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN       &          (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN
# Line 1100  C-----------------------S31 ------------ Line 1119  C-----------------------S31 ------------
1119  C-----------------------S32 -----------------------------------------  C-----------------------S32 -----------------------------------------
1120    
1121        IF (tof32_i.GT.none_find) THEN        IF (tof32_i.GT.none_find) THEN
1122           xpos = xout(6)           xpos = REAL(xout(6))
1123           i = tof32_i           i = tof32_i
1124          if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.          if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.
1125       &          (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN       &          (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN
# Line 1225  C     instead of cos(theta) use factor F Line 1244  C     instead of cos(theta) use factor F
1244  C     F =  pathlength/d  C     F =  pathlength/d
1245  C     => beta = c2*F/(DS-c1))  C     => beta = c2*F/(DS-c1))
1246    
1247    C---------------------     S11 - S31  ------------------------
1248    
1249        dist = ZTOF(1) - ZTOF(5)        dist = ZTOF(1) - ZTOF(5)
1250        dl = 0.        dl = 0.
1251        DO I=1,5        DO I=1,5
1252           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1253        ENDDO        ENDDO
1254        F = dl/dist        F = dl/dist
1255    
1256  C     S11 - S31        c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1257    
1258  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1259        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1260       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1246  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1268  C      IF (tof11_i.GT.none_find.AND.tof3
1268              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1269              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1270              ihelp=(tof11_i-1)*3+tof31_i              ihelp=(tof11_i-1)*3+tof31_i
1271              c1 = k_S11S31(1,ihelp)              if (iz.le.1) c1 = k_S11S31(1,ihelp)
1272              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S11S31(2,ihelp)
1273              c2 = k_S11S31(2,ihelp)              if (iz.gt.2) c1 = k_S11S31(3,ihelp)
1274    c        write(*,*)k_S11S31(1,ihelp),k_S11S31(2,ihelp),k_S11S31(3,ihelp)
1275    c        write(*,*)iz,c1,c2
1276              beta_a(1) = c2*F/(ds-c1)              beta_a(1) = c2*F/(ds-c1)
1277  c       write(*,*) 'S11-S31 ',c1,c2,F  c       write(*,*) 'S11-S31 ',c1,c2,F
1278  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
# Line 1267  C-------ToF Mask - S11 - S31 Line 1291  C-------ToF Mask - S11 - S31
1291           ENDIF           ENDIF
1292        ENDIF        ENDIF
1293    
1294    C---------------------     S11 - S32  ------------------------
1295    
1296        dist = ZTOF(1) - ZTOF(6)        dist = ZTOF(1) - ZTOF(6)
1297        dl = 0.        dl = 0.
1298        DO I=1,6        DO I=1,6
1299           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1300        ENDDO        ENDDO
1301        F = dl/dist        F = dl/dist
1302    
1303  C     S11 - S32        c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1304    
1305  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1306         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1307       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
# Line 1288  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1315  C      IF (tof11_i.GT.none_find.AND.tof3
1315              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1316              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1317              ihelp=(tof11_i-1)*3+tof32_i              ihelp=(tof11_i-1)*3+tof32_i
1318              c1 = k_S11S32(1,ihelp)              if (iz.le.1) c1 = k_S11S32(1,ihelp)
1319              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S11S32(2,ihelp)
1320              c2 = k_S11S32(2,ihelp)              if (iz.gt.2) c1 = k_S11S32(3,ihelp)
1321              beta_a(2) = c2*F/(ds-c1)              beta_a(2) = c2*F/(ds-c1)
1322  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1323    
# Line 1311  C------- Line 1338  C-------
1338           ENDIF           ENDIF
1339        ENDIF        ENDIF
1340    
1341  C     S12 - S31  C---------------------     S12 - S31  ------------------------
1342    
1343        dist = ZTOF(2) - ZTOF(5)        dist = ZTOF(2) - ZTOF(5)
1344        dl = 0.        dl = 0.
1345        DO I=2,5        DO I=2,5
1346           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1347        ENDDO        ENDDO
1348        F = dl/dist        F = dl/dist
1349    
1350          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1351    
1352  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1353         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1354       &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1332  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1362  C      IF (tof12_i.GT.none_find.AND.tof3
1362              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1363              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1364              ihelp=(tof12_i-1)*3+tof31_i              ihelp=(tof12_i-1)*3+tof31_i
1365              c1 = k_S12S31(1,ihelp)              if (iz.le.1) c1 = k_S12S31(1,ihelp)
1366              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S12S31(2,ihelp)
1367              c2 = k_S12S31(2,ihelp)              if (iz.gt.2) c1 = k_S12S31(3,ihelp)
1368              beta_a(3) = c2*F/(ds-c1)              beta_a(3) = c2*F/(ds-c1)
1369  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1370    
# Line 1355  C------- Line 1385  C-------
1385           ENDIF           ENDIF
1386        ENDIF        ENDIF
1387    
1388  C     S12 - S32  C---------------------     S12 - S32  ------------------------
1389    
1390        dist = ZTOF(2) - ZTOF(6)        dist = ZTOF(2) - ZTOF(6)
1391        dl = 0.        dl = 0.
1392        DO I=2,6        DO I=2,6
1393           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1394        ENDDO        ENDDO
1395        F = dl/dist        F = dl/dist
1396          
1397          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1398    
1399  C      IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1400         IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
# Line 1377  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1409  C      IF (tof12_i.GT.none_find.AND.tof3
1409              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1410              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1411              ihelp=(tof12_i-1)*3+tof32_i              ihelp=(tof12_i-1)*3+tof32_i
1412              c1 = k_S12S32(1,ihelp)              if (iz.le.1) c1 = k_S12S32(1,ihelp)
1413              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S12S32(2,ihelp)
1414              c2 = k_S12S32(2,ihelp)              if (iz.gt.2) c1 = k_S12S32(3,ihelp)
1415              beta_a(4) = c2*F/(ds-c1)              beta_a(4) = c2*F/(ds-c1)
1416  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1417    
# Line 1400  C------- Line 1432  C-------
1432           ENDIF           ENDIF
1433        ENDIF        ENDIF
1434    
1435  C     S21 - S31  C---------------------     S21 - S31  ------------------------
1436    
1437        dist = ZTOF(3) - ZTOF(5)        dist = ZTOF(3) - ZTOF(5)
1438        dl = 0.        dl = 0.
1439        DO I=3,5        DO I=3,5
1440           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1441        ENDDO        ENDDO
1442        F = dl/dist        F = dl/dist
1443    
1444          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1445    
1446  C      IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1447         IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1448       &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1422  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1456  C      IF (tof21_i.GT.none_find.AND.tof3
1456              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1457              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1458              ihelp=(tof21_i-1)*3+tof31_i              ihelp=(tof21_i-1)*3+tof31_i
1459              c1 = k_S21S31(1,ihelp)              if (iz.le.1) c1 = k_S21S31(1,ihelp)
1460              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S21S31(2,ihelp)
1461              c2 = k_S21S31(2,ihelp)              if (iz.gt.2) c1 = k_S21S31(3,ihelp)
1462              beta_a(5) = c2*F/(ds-c1)              beta_a(5) = c2*F/(ds-c1)
1463    
1464  C-------ToF Mask - S21 - S31  C-------ToF Mask - S21 - S31
# Line 1444  C------- Line 1478  C-------
1478           ENDIF           ENDIF
1479        ENDIF        ENDIF
1480    
1481  C     S21 - S32  C---------------------     S21 - S32  ------------------------
1482    
1483        dist = ZTOF(3) - ZTOF(6)        dist = ZTOF(3) - ZTOF(6)
1484        dl = 0.        dl = 0.
1485        DO I=3,6        DO I=3,6
1486           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1487        ENDDO        ENDDO
1488        F = dl/dist        F = dl/dist
1489    
1490          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1491    
1492  C      IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1493         IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1494       &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN       &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
# Line 1466  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1502  C      IF (tof21_i.GT.none_find.AND.tof3
1502              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1503              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1504              ihelp=(tof21_i-1)*3+tof32_i              ihelp=(tof21_i-1)*3+tof32_i
1505              c1 = k_S21S32(1,ihelp)              if (iz.le.1) c1 = k_S21S32(1,ihelp)
1506              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S21S32(2,ihelp)
1507              c2 = k_S21S32(2,ihelp)              if (iz.gt.2) c1 = k_S21S32(3,ihelp)
1508              beta_a(6) = c2*F/(ds-c1)              beta_a(6) = c2*F/(ds-c1)
1509    
1510  C-------ToF Mask - S21 - S32  C-------ToF Mask - S21 - S32
# Line 1488  C------- Line 1524  C-------
1524           ENDIF           ENDIF
1525        ENDIF        ENDIF
1526    
1527  C     S22 - S31  C---------------------     S22 - S31  ------------------------
1528    
1529        dist = ZTOF(4) - ZTOF(5)        dist = ZTOF(4) - ZTOF(5)
1530        dl = 0.        dl = 0.
1531        DO I=4,5        DO I=4,5
1532           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1533        ENDDO        ENDDO
1534        F = dl/dist        F = dl/dist
1535          
1536          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1537    
1538  C WM workaround  C WM workaround
1539        dl = dl - 0.06*F        dl = dl - 0.06*F
1540        F = dl/dist        F = dl/dist
# Line 1514  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1552  C      IF (tof22_i.GT.none_find.AND.tof3
1552              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1553              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1554              ihelp=(tof22_i-1)*3+tof31_i              ihelp=(tof22_i-1)*3+tof31_i
1555              c1 = k_S22S31(1,ihelp)              if (iz.le.1) c1 = k_S22S31(1,ihelp)
1556              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S22S31(2,ihelp)
1557              c2 = k_S22S31(2,ihelp)              if (iz.gt.2) c1 = k_S22S31(3,ihelp)
1558              beta_a(7) = c2*F/(ds-c1)              beta_a(7) = c2*F/(ds-c1)
1559    
1560  C-------ToF Mask - S22 - S31  C-------ToF Mask - S22 - S31
# Line 1536  C------- Line 1574  C-------
1574           ENDIF           ENDIF
1575        ENDIF        ENDIF
1576    
1577  C     S22 - S32  C---------------------     S22 - S32  ------------------------
1578    
1579    
1580        dist = ZTOF(4) - ZTOF(6)        dist = ZTOF(4) - ZTOF(6)
1581        dl = 0.        dl = 0.
1582        DO I=4,6        DO I=4,6
1583           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1584        ENDDO        ENDDO
1585        F = dl/dist        F = dl/dist
1586                
1587          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1588    
1589  C WM workaround        C WM workaround      
1590        dl = dl - 0.06*F        dl = dl - 0.06*F
1591        F = dl/dist        F = dl/dist
# Line 1563  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1604  C      IF (tof22_i.GT.none_find.AND.tof3
1604              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1605              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1606              ihelp=(tof22_i-1)*3+tof32_i              ihelp=(tof22_i-1)*3+tof32_i
1607              c1 = k_S22S32(1,ihelp)              if (iz.le.1) c1 = k_S22S32(1,ihelp)
1608              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S22S32(2,ihelp)
1609              c2 = k_S22S32(2,ihelp)              if (iz.gt.2) c1 = k_S22S32(3,ihelp)
1610              beta_a(8) = c2*F/(ds-c1)              beta_a(8) = c2*F/(ds-c1)
1611    
1612  C-------ToF Mask - S22 - S32  C-------ToF Mask - S22 - S32
# Line 1585  C------- Line 1626  C-------
1626           ENDIF           ENDIF
1627        ENDIF        ENDIF
1628    
1629  C     S11 - S21  C---------------------     S11 - S21  ------------------------
1630    
1631        dist = ZTOF(1) - ZTOF(3)        dist = ZTOF(1) - ZTOF(3)
1632        dl = 0.        dl = 0.
1633        DO I=1,3        DO I=1,3
1634           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1635        ENDDO        ENDDO
1636        F = dl/dist        F = dl/dist
1637    
1638          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1639    
1640  C WM workaround        C WM workaround      
1641        dl = dl - 0.442*F        dl = dl - 0.442*F
1642        F = dl/dist        F = dl/dist
# Line 1611  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1654  C      IF (tof11_i.GT.none_find.AND.tof2
1654              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1655              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1656              ihelp=(tof11_i-1)*2+tof21_i              ihelp=(tof11_i-1)*2+tof21_i
1657              c1 = k_S11S21(1,ihelp)              if (iz.le.1) c1 = k_S11S21(1,ihelp)
1658              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S11S21(2,ihelp)
1659              c2 = k_S11S21(2,ihelp)              if (iz.gt.2) c1 = k_S11S21(3,ihelp)
1660              beta_a(9) = c2*F/(ds-c1)              beta_a(9) = c2*F/(ds-c1)
1661    
1662  C-------ToF Mask - S11 - S21  C-------ToF Mask - S11 - S21
# Line 1633  C------- Line 1676  C-------
1676           ENDIF           ENDIF
1677        ENDIF        ENDIF
1678    
1679  C     S11 - S22  C---------------------     S11 - S22  ------------------------
1680    
1681        dist = ZTOF(1) - ZTOF(4)        dist = ZTOF(1) - ZTOF(4)
1682        dl = 0.        dl = 0.
1683        DO I=1,4        DO I=1,4
1684           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1685        ENDDO        ENDDO
1686        F = dl/dist        F = dl/dist
1687    
1688          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1689    
1690  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1691         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1692       &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
# Line 1655  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1700  C      IF (tof11_i.GT.none_find.AND.tof2
1700              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1701              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1702              ihelp=(tof11_i-1)*2+tof22_i              ihelp=(tof11_i-1)*2+tof22_i
1703              c1 = k_S11S22(1,ihelp)              if (iz.le.1) c1 = k_S11S22(1,ihelp)
1704              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S11S22(2,ihelp)
1705              c2 = k_S11S22(2,ihelp)              if (iz.gt.2) c1 = k_S11S22(3,ihelp)
1706              beta_a(10) = c2*F/(ds-c1)              beta_a(10) = c2*F/(ds-c1)
1707    
1708  C-------ToF Mask - S11 - S22  C-------ToF Mask - S11 - S22
# Line 1677  C------- Line 1722  C-------
1722           ENDIF           ENDIF
1723        ENDIF        ENDIF
1724    
1725  C     S12 - S21  C---------------------     S12 - S21  ------------------------
1726    
1727        dist = ZTOF(2) - ZTOF(3)        dist = ZTOF(2) - ZTOF(3)
1728        dl = 0.        dl = 0.
1729        DO I=2,3        DO I=2,3
1730           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1731        ENDDO        ENDDO
1732        F = dl/dist        F = dl/dist
1733    
1734          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1735    
1736  C  WM workaround  C  WM workaround
1737        dl = dl - 0.442*F        dl = dl - 0.442*F
1738        F = dl/dist        F = dl/dist
# Line 1703  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1750  C      IF (tof12_i.GT.none_find.AND.tof2
1750              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1751              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1752              ihelp=(tof12_i-1)*2+tof21_i              ihelp=(tof12_i-1)*2+tof21_i
1753              c1 = k_S12S21(1,ihelp)              if (iz.le.1) c1 = k_S12S21(1,ihelp)
1754              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S12S21(2,ihelp)
1755              c2 = k_S12S21(2,ihelp)              if (iz.gt.2) c1 = k_S12S21(3,ihelp)
1756              beta_a(11) = c2*F/(ds-c1)              beta_a(11) = c2*F/(ds-c1)
1757    
1758  C-------ToF Mask - S12 - S21  C-------ToF Mask - S12 - S21
# Line 1725  C------- Line 1772  C-------
1772           ENDIF           ENDIF
1773        ENDIF        ENDIF
1774    
1775  C     S12 - S22  C---------------------     S12 - S22  ------------------------
1776    
1777        dist = ZTOF(2) - ZTOF(4)        dist = ZTOF(2) - ZTOF(4)
1778        dl = 0.        dl = 0.
1779        DO I=2,4        DO I=2,4
1780           dl = dl + TLOUT(i)           dl = dl + REAL(TLOUT(i))!EM GCC 4.7
1781        ENDDO        ENDDO
1782        F = dl/dist        F = dl/dist
1783    
1784          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1785    
1786  C      IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1787         IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1788       &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
# Line 1746  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1795  C      IF (tof12_i.GT.none_find.AND.tof2
1795              xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)              xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1796              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1797              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1798              ihelp=(tof12_i-1)*2+tof22_i              ihelp=(tof12_i-1)*2+tof22_i          
1799              c1 = k_S12S22(1,ihelp)              if (iz.le.1) c1 = k_S12S22(1,ihelp)
1800              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S12S22(2,ihelp)
1801              c2 = k_S12S22(2,ihelp)              if (iz.gt.2) c1 = k_S12S22(3,ihelp)
1802              beta_a(12) = c2*F/(ds-c1)              beta_a(12) = c2*F/(ds-c1)
1803    
1804  C-------ToF Mask - S12 - S22  C-------ToF Mask - S12 - S22

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

  ViewVC Help
Powered by ViewVC 1.1.23