/[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.18 by pamelats, Thu Nov 27 13:49:13 2008 UTC revision 1.20 by mocchiut, Wed Feb 17 11:50:54 2010 UTC
# Line 52  C             length  from DOTRACK2 and Line 52  C             length  from DOTRACK2 and
52  C  oct-08 WM: New method to create artificial ADC values. Do NOT take the position  C  oct-08 WM: New method to create artificial ADC values. Do NOT take the position
53  C             from the tracking, but the position from timing. This method gives a  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
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
59  C****************************************************************************  C****************************************************************************
60        IMPLICIT NONE        IMPLICIT NONE
61  C  C
# Line 78  c     define TOF Z-coordinates Line 82  c     define TOF Z-coordinates
82       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
83       &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)       &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
84    
85          DOUBLE PRECISION dedxtrk
86          DOUBLE PRECISION deflection
87    
88        INTEGER IFAIL        INTEGER IFAIL
89  c      REAL dx,dy,dr  c      REAL dx,dy,dr
90        REAL ds        REAL ds
91        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
92        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
93          REAL yhelp1,yhelp2
94        REAL c1,c2        REAL c1,c2
95  C     REAL sw,sxw,w_i  C     REAL sw,sxw,w_i
96        REAL dist,dl,F        REAL dist,dl,F
# Line 95  C      REAL beta_mean Line 102  C      REAL beta_mean
102    
103        INTEGER j,hitvec(6)        INTEGER j,hitvec(6)
104    
105        real atten,pc_adc,check_charge,newbeta        real atten,pc_adc,newbeta
106    C      real check_charge
107    
108    
109        REAL theta,phi        REAL theta,phi
# Line 151  C--- Line 159  C---
159        REAL xkorr,xpos        REAL xkorr,xpos
160    
161        INTEGER IZ        INTEGER IZ
       REAL k1corrA1,k1corrB1,k1corrC1  
162    
163        REAL yl,yh,xl,xh        REAL yl,yh,xl,xh
164  C  C
# Line 192  C  ratio helium to proton ca. 4 Line 199  C  ratio helium to proton ca. 4
199        itdc = 1        itdc = 1
200        iadc = 2        iadc = 2
201    
   
       k1corrA1 = 0.  
       k1corrB1 = -5.0  
       k1corrC1=  8.0  
   
202        ENDIF   ! ifst        ENDIF   ! ifst
203    
204  *******************************************************************  *******************************************************************
# Line 355  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 357  C     COPY THE ALFA VECTOR FROM AL_PP TO
357        do i=1,5        do i=1,5
358           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
359        enddo        enddo
360          deflection = AL_P(5)
361    *     3) tracker dEdx
362          dedxtrk = trkmip
363        
364  c      write(*,*) AL_P  c      write(*,*) AL_P
365  c      write(*,*) 'Rigidity ',(1./AL_P(5))  c      write(*,*) 'Rig, Def, dEdx ',(1./AL_P(5)),AL_P(5),dedxtrk
366    
367    
368    C--  charge selection with tracker using dedx vs. deflection^2  ----
369    
370           yhelp1 = 3.5 + 4.5*deflection*deflection
371           yhelp2 = 9. + 20.*deflection*deflection
372    c       write(*,*) yhelp1,yhelp2
373    
374           iz = 0
375           if  (dedxtrk.lt.yhelp1) iz=1
376           if ((dedxtrk.gt.yhelp1).and.(dedxtrk.lt.yhelp2)) iz=2
377           if  (dedxtrk.gt.yhelp2) iz=3
378    c       write(*,*) 'tracker charge ',iz
379    
380    C--------------------------------------------------------------------
381    
382        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
383  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
# Line 603  C--------------------------------------- Line 623  C---------------------------------------
623         F = dl/dist         F = dl/dist
624         theta = acos(1/F)         theta = acos(1/F)
625    
626         iz = int(check_charge(theta,hitvec))  c       iz = int(check_charge(theta,hitvec))
627  c       write(*,*) 'in toftrk',iz  c       write(*,*) 'in toftrk',iz
628    
629    
# Line 1204  c      enddo Line 1224  c      enddo
1224    
1225    
1226    
1227  C---------------------------------------------------------------------  C--------------------------------------------------------------------
1228  C--------------------Corrections on ADC-data -------------------------  C-------------------Corrections on ADC-data -------------------------
1229  C-----------------angle and ADC(x) correction -----------------------  C-----------------angle and ADC(x) correction -----------------------
1230    C----------------   moved to the new dEdx routine -------------------
1231    
1232  C-----------------------------S1 -------------------------------------  C--------------------------------------------------------------------
   
       yhelp=yout(1)  
   
       phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))  
       theta = atan(tan(THXOUT(1))/cos(phi))  
   
       IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN  
   
          i = tof11_i  
   
          if (tof11(left,i,iadc).lt.3786) then  
             tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)  
             xkorr = atten(left,11,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr  
          endif  
   
   
          if (tof11(right,i,iadc).lt.3786) then  
             tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)  
             xkorr = atten(right,11,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
   
       xhelp=xout(2)  
       phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))  
       theta = atan(tan(THXOUT(2))/cos(phi))  
   
       IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN  
          i = tof12_i  
          if (tof12(left,i,iadc).lt.3786) then  
             tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)  
             xkorr = atten(left,12,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr  
          endif  
   
          if (tof12(right,i,iadc).lt.3786) then  
             tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)  
             xkorr = atten(right,12,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
 C-----------------------------S2 --------------------------------  
   
       xhelp=xout(3)  
       phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))  
       theta = atan(tan(THXOUT(3))/cos(phi))  
   
       IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN  
          i = tof21_i  
          if (tof21(left,i,iadc).lt.3786) then  
             tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)  
             xkorr = atten(left,21,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr  
          endif  
   
          if (tof21(right,i,iadc).lt.3786) then  
             tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)  
             xkorr = atten(right,21,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
       yhelp=yout(4)  
       phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))  
       theta = atan(tan(THXOUT(4))/cos(phi))  
   
       IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN  
          i = tof22_i  
          if (tof22(left,i,iadc).lt.3786) then  
             tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)  
             xkorr = atten(left,22,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr  
          endif  
   
          if (tof22(right,i,iadc).lt.3786) then  
             tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)  
             xkorr = atten(right,22,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
 C-----------------------------S3 --------------------------------  
   
       yhelp=yout(5)  
       phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))  
       theta = atan(tan(THXOUT(5))/cos(phi))  
   
       IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN  
   
          i = tof31_i  
          if (tof31(left,i,iadc).lt.3786) then  
             tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)  
             xkorr = atten(left,31,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr  
          endif  
   
          if (tof31(right,i,iadc).lt.3786) then  
             tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)  
             xkorr = atten(right,31,i,yhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
       xhelp=xout(6)  
       phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))  
       theta = atan(tan(THXOUT(6))/cos(phi))  
   
       IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN  
          i = tof32_i  
          if (tof32(left,i,iadc).lt.3786) then  
             tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)  
             xkorr = atten(left,32,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr  
          endif  
   
          if (tof32(right,i,iadc).lt.3786) then  
             tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)  
             xkorr = atten(right,32,i,xhelp)  
             xkorr=xkorr/hepratio  
             adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr  
          endif  
       ENDIF  
   
   
 C-----------------------------------------------------------------------  
1233  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1234  C-----------------------------------------------------------------------  C--------------------------------------------------------------------
1235  C-------------------difference of sums  ---------------------------  C---------------------difference of sums  ---------------------------
1236  C  C
1237  C     DS = (t1+t2) - t3+t4)  C     DS = (t1+t2) - t3+t4)
1238  C     DS = c1 + c2/beta*cos(theta)  C     DS = c1 + c2/beta*cos(theta)
# Line 1361  C     instead of cos(theta) use factor F Line 1243  C     instead of cos(theta) use factor F
1243  C     F =  pathlength/d  C     F =  pathlength/d
1244  C     => beta = c2*F/(DS-c1))  C     => beta = c2*F/(DS-c1))
1245    
1246    C---------------------     S11 - S31  ------------------------
1247    
1248        dist = ZTOF(1) - ZTOF(5)        dist = ZTOF(1) - ZTOF(5)
1249        dl = 0.        dl = 0.
1250        DO I=1,5        DO I=1,5
# Line 1368  C     => beta = c2*F/(DS-c1)) Line 1252  C     => beta = c2*F/(DS-c1))
1252        ENDDO        ENDDO
1253        F = dl/dist        F = dl/dist
1254    
1255  C     S11 - S31        c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1256    
1257  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1258        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1259       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1382  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1267  C      IF (tof11_i.GT.none_find.AND.tof3
1267              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1268              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1269              ihelp=(tof11_i-1)*3+tof31_i              ihelp=(tof11_i-1)*3+tof31_i
1270              c1 = k_S11S31(1,ihelp)              if (iz.le.1) c1 = k_S11S31(1,ihelp)
1271              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S11S31(2,ihelp)
1272              c2 = k_S11S31(2,ihelp)              if (iz.gt.2) c1 = k_S11S31(3,ihelp)
1273    c        write(*,*)k_S11S31(1,ihelp),k_S11S31(2,ihelp),k_S11S31(3,ihelp)
1274    c        write(*,*)iz,c1,c2
1275              beta_a(1) = c2*F/(ds-c1)              beta_a(1) = c2*F/(ds-c1)
1276  c       write(*,*) 'S11-S31 ',c1,c2,F  c       write(*,*) 'S11-S31 ',c1,c2,F
1277  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)  c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
# Line 1403  C-------ToF Mask - S11 - S31 Line 1290  C-------ToF Mask - S11 - S31
1290           ENDIF           ENDIF
1291        ENDIF        ENDIF
1292    
1293    C---------------------     S11 - S32  ------------------------
1294    
1295        dist = ZTOF(1) - ZTOF(6)        dist = ZTOF(1) - ZTOF(6)
1296        dl = 0.        dl = 0.
1297        DO I=1,6        DO I=1,6
# Line 1410  C-------ToF Mask - S11 - S31 Line 1299  C-------ToF Mask - S11 - S31
1299        ENDDO        ENDDO
1300        F = dl/dist        F = dl/dist
1301    
1302  C     S11 - S32        c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1303    
1304  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1305         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1306       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
# Line 1424  C      IF (tof11_i.GT.none_find.AND.tof3 Line 1314  C      IF (tof11_i.GT.none_find.AND.tof3
1314              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1315              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1316              ihelp=(tof11_i-1)*3+tof32_i              ihelp=(tof11_i-1)*3+tof32_i
1317              c1 = k_S11S32(1,ihelp)              if (iz.le.1) c1 = k_S11S32(1,ihelp)
1318              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S11S32(2,ihelp)
1319              c2 = k_S11S32(2,ihelp)              if (iz.gt.2) c1 = k_S11S32(3,ihelp)
1320              beta_a(2) = c2*F/(ds-c1)              beta_a(2) = c2*F/(ds-c1)
1321  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)  C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1322    
# Line 1447  C------- Line 1337  C-------
1337           ENDIF           ENDIF
1338        ENDIF        ENDIF
1339    
1340  C     S12 - S31  C---------------------     S12 - S31  ------------------------
1341    
1342        dist = ZTOF(2) - ZTOF(5)        dist = ZTOF(2) - ZTOF(5)
1343        dl = 0.        dl = 0.
1344        DO I=2,5        DO I=2,5
# Line 1455  C     S12 - S31 Line 1346  C     S12 - S31
1346        ENDDO        ENDDO
1347        F = dl/dist        F = dl/dist
1348    
1349          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1350    
1351  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1352         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1353       &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1468  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1361  C      IF (tof12_i.GT.none_find.AND.tof3
1361              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1362              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1363              ihelp=(tof12_i-1)*3+tof31_i              ihelp=(tof12_i-1)*3+tof31_i
1364              c1 = k_S12S31(1,ihelp)              if (iz.le.1) c1 = k_S12S31(1,ihelp)
1365              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S12S31(2,ihelp)
1366              c2 = k_S12S31(2,ihelp)              if (iz.gt.2) c1 = k_S12S31(3,ihelp)
1367              beta_a(3) = c2*F/(ds-c1)              beta_a(3) = c2*F/(ds-c1)
1368  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)  C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1369    
# Line 1491  C------- Line 1384  C-------
1384           ENDIF           ENDIF
1385        ENDIF        ENDIF
1386    
1387  C     S12 - S32  C---------------------     S12 - S32  ------------------------
1388    
1389        dist = ZTOF(2) - ZTOF(6)        dist = ZTOF(2) - ZTOF(6)
1390        dl = 0.        dl = 0.
# Line 1499  C     S12 - S32 Line 1392  C     S12 - S32
1392           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1393        ENDDO        ENDDO
1394        F = dl/dist        F = dl/dist
1395          
1396          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1397    
1398  C      IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1399         IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
# Line 1513  C      IF (tof12_i.GT.none_find.AND.tof3 Line 1408  C      IF (tof12_i.GT.none_find.AND.tof3
1408              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1409              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1410              ihelp=(tof12_i-1)*3+tof32_i              ihelp=(tof12_i-1)*3+tof32_i
1411              c1 = k_S12S32(1,ihelp)              if (iz.le.1) c1 = k_S12S32(1,ihelp)
1412              if (iz.gt.2) c1 = c1 + k1corrA1              if (iz.eq.2) c1 = k_S12S32(2,ihelp)
1413              c2 = k_S12S32(2,ihelp)              if (iz.gt.2) c1 = k_S12S32(3,ihelp)
1414              beta_a(4) = c2*F/(ds-c1)              beta_a(4) = c2*F/(ds-c1)
1415  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)  C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1416    
# Line 1536  C------- Line 1431  C-------
1431           ENDIF           ENDIF
1432        ENDIF        ENDIF
1433    
1434  C     S21 - S31  C---------------------     S21 - S31  ------------------------
1435    
1436        dist = ZTOF(3) - ZTOF(5)        dist = ZTOF(3) - ZTOF(5)
1437        dl = 0.        dl = 0.
# Line 1545  C     S21 - S31 Line 1440  C     S21 - S31
1440        ENDDO        ENDDO
1441        F = dl/dist        F = dl/dist
1442    
1443          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1444    
1445  C      IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1446         IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1447       &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN       &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
# Line 1558  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1455  C      IF (tof21_i.GT.none_find.AND.tof3
1455              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1456              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1457              ihelp=(tof21_i-1)*3+tof31_i              ihelp=(tof21_i-1)*3+tof31_i
1458              c1 = k_S21S31(1,ihelp)              if (iz.le.1) c1 = k_S21S31(1,ihelp)
1459              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S21S31(2,ihelp)
1460              c2 = k_S21S31(2,ihelp)              if (iz.gt.2) c1 = k_S21S31(3,ihelp)
1461              beta_a(5) = c2*F/(ds-c1)              beta_a(5) = c2*F/(ds-c1)
1462    
1463  C-------ToF Mask - S21 - S31  C-------ToF Mask - S21 - S31
# Line 1580  C------- Line 1477  C-------
1477           ENDIF           ENDIF
1478        ENDIF        ENDIF
1479    
1480  C     S21 - S32  C---------------------     S21 - S32  ------------------------
1481    
1482        dist = ZTOF(3) - ZTOF(6)        dist = ZTOF(3) - ZTOF(6)
1483        dl = 0.        dl = 0.
# Line 1589  C     S21 - S32 Line 1486  C     S21 - S32
1486        ENDDO        ENDDO
1487        F = dl/dist        F = dl/dist
1488    
1489          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1490    
1491  C      IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1492         IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1493       &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN       &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
# Line 1602  C      IF (tof21_i.GT.none_find.AND.tof3 Line 1501  C      IF (tof21_i.GT.none_find.AND.tof3
1501              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1502              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1503              ihelp=(tof21_i-1)*3+tof32_i              ihelp=(tof21_i-1)*3+tof32_i
1504              c1 = k_S21S32(1,ihelp)              if (iz.le.1) c1 = k_S21S32(1,ihelp)
1505              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S21S32(2,ihelp)
1506              c2 = k_S21S32(2,ihelp)              if (iz.gt.2) c1 = k_S21S32(3,ihelp)
1507              beta_a(6) = c2*F/(ds-c1)              beta_a(6) = c2*F/(ds-c1)
1508    
1509  C-------ToF Mask - S21 - S32  C-------ToF Mask - S21 - S32
# Line 1624  C------- Line 1523  C-------
1523           ENDIF           ENDIF
1524        ENDIF        ENDIF
1525    
1526  C     S22 - S31  C---------------------     S22 - S31  ------------------------
1527    
1528        dist = ZTOF(4) - ZTOF(5)        dist = ZTOF(4) - ZTOF(5)
1529        dl = 0.        dl = 0.
# Line 1632  C     S22 - S31 Line 1531  C     S22 - S31
1531           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1532        ENDDO        ENDDO
1533        F = dl/dist        F = dl/dist
1534          
1535          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1536    
1537  C WM workaround  C WM workaround
1538        dl = dl - 0.06*F        dl = dl - 0.06*F
1539        F = dl/dist        F = dl/dist
# Line 1650  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1551  C      IF (tof22_i.GT.none_find.AND.tof3
1551              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)              xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1552              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1553              ihelp=(tof22_i-1)*3+tof31_i              ihelp=(tof22_i-1)*3+tof31_i
1554              c1 = k_S22S31(1,ihelp)              if (iz.le.1) c1 = k_S22S31(1,ihelp)
1555              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S22S31(2,ihelp)
1556              c2 = k_S22S31(2,ihelp)              if (iz.gt.2) c1 = k_S22S31(3,ihelp)
1557              beta_a(7) = c2*F/(ds-c1)              beta_a(7) = c2*F/(ds-c1)
1558    
1559  C-------ToF Mask - S22 - S31  C-------ToF Mask - S22 - S31
# Line 1672  C------- Line 1573  C-------
1573           ENDIF           ENDIF
1574        ENDIF        ENDIF
1575    
1576  C     S22 - S32  C---------------------     S22 - S32  ------------------------
1577    
1578    
1579        dist = ZTOF(4) - ZTOF(6)        dist = ZTOF(4) - ZTOF(6)
1580        dl = 0.        dl = 0.
# Line 1681  C     S22 - S32 Line 1583  C     S22 - S32
1583        ENDDO        ENDDO
1584        F = dl/dist        F = dl/dist
1585                
1586          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1587    
1588  C WM workaround        C WM workaround      
1589        dl = dl - 0.06*F        dl = dl - 0.06*F
1590        F = dl/dist        F = dl/dist
# Line 1699  C      IF (tof22_i.GT.none_find.AND.tof3 Line 1603  C      IF (tof22_i.GT.none_find.AND.tof3
1603              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)              xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1604              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1605              ihelp=(tof22_i-1)*3+tof32_i              ihelp=(tof22_i-1)*3+tof32_i
1606              c1 = k_S22S32(1,ihelp)              if (iz.le.1) c1 = k_S22S32(1,ihelp)
1607              if (iz.gt.2) c1 = c1 + k1corrB1              if (iz.eq.2) c1 = k_S22S32(2,ihelp)
1608              c2 = k_S22S32(2,ihelp)              if (iz.gt.2) c1 = k_S22S32(3,ihelp)
1609              beta_a(8) = c2*F/(ds-c1)              beta_a(8) = c2*F/(ds-c1)
1610    
1611  C-------ToF Mask - S22 - S32  C-------ToF Mask - S22 - S32
# Line 1721  C------- Line 1625  C-------
1625           ENDIF           ENDIF
1626        ENDIF        ENDIF
1627    
1628  C     S11 - S21  C---------------------     S11 - S21  ------------------------
1629    
1630        dist = ZTOF(1) - ZTOF(3)        dist = ZTOF(1) - ZTOF(3)
1631        dl = 0.        dl = 0.
# Line 1730  C     S11 - S21 Line 1634  C     S11 - S21
1634        ENDDO        ENDDO
1635        F = dl/dist        F = dl/dist
1636    
1637          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1638    
1639  C WM workaround        C WM workaround      
1640        dl = dl - 0.442*F        dl = dl - 0.442*F
1641        F = dl/dist        F = dl/dist
# Line 1747  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1653  C      IF (tof11_i.GT.none_find.AND.tof2
1653              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1654              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1655              ihelp=(tof11_i-1)*2+tof21_i              ihelp=(tof11_i-1)*2+tof21_i
1656              c1 = k_S11S21(1,ihelp)              if (iz.le.1) c1 = k_S11S21(1,ihelp)
1657              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S11S21(2,ihelp)
1658              c2 = k_S11S21(2,ihelp)              if (iz.gt.2) c1 = k_S11S21(3,ihelp)
1659              beta_a(9) = c2*F/(ds-c1)              beta_a(9) = c2*F/(ds-c1)
1660    
1661  C-------ToF Mask - S11 - S21  C-------ToF Mask - S11 - S21
# Line 1769  C------- Line 1675  C-------
1675           ENDIF           ENDIF
1676        ENDIF        ENDIF
1677    
1678  C     S11 - S22  C---------------------     S11 - S22  ------------------------
1679    
1680        dist = ZTOF(1) - ZTOF(4)        dist = ZTOF(1) - ZTOF(4)
1681        dl = 0.        dl = 0.
# Line 1778  C     S11 - S22 Line 1684  C     S11 - S22
1684        ENDDO        ENDDO
1685        F = dl/dist        F = dl/dist
1686    
1687          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1688    
1689  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1690         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1691       &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
# Line 1791  C      IF (tof11_i.GT.none_find.AND.tof2 Line 1699  C      IF (tof11_i.GT.none_find.AND.tof2
1699              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1700              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1701              ihelp=(tof11_i-1)*2+tof22_i              ihelp=(tof11_i-1)*2+tof22_i
1702              c1 = k_S11S22(1,ihelp)              if (iz.le.1) c1 = k_S11S22(1,ihelp)
1703              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S11S22(2,ihelp)
1704              c2 = k_S11S22(2,ihelp)              if (iz.gt.2) c1 = k_S11S22(3,ihelp)
1705              beta_a(10) = c2*F/(ds-c1)              beta_a(10) = c2*F/(ds-c1)
1706    
1707  C-------ToF Mask - S11 - S22  C-------ToF Mask - S11 - S22
# Line 1813  C------- Line 1721  C-------
1721           ENDIF           ENDIF
1722        ENDIF        ENDIF
1723    
1724  C     S12 - S21  C---------------------     S12 - S21  ------------------------
1725    
1726        dist = ZTOF(2) - ZTOF(3)        dist = ZTOF(2) - ZTOF(3)
1727        dl = 0.        dl = 0.
# Line 1822  C     S12 - S21 Line 1730  C     S12 - S21
1730        ENDDO        ENDDO
1731        F = dl/dist        F = dl/dist
1732    
1733          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1734    
1735  C  WM workaround  C  WM workaround
1736        dl = dl - 0.442*F        dl = dl - 0.442*F
1737        F = dl/dist        F = dl/dist
# Line 1839  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1749  C      IF (tof12_i.GT.none_find.AND.tof2
1749              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)              xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1750              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1751              ihelp=(tof12_i-1)*2+tof21_i              ihelp=(tof12_i-1)*2+tof21_i
1752              c1 = k_S12S21(1,ihelp)              if (iz.le.1) c1 = k_S12S21(1,ihelp)
1753              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S12S21(2,ihelp)
1754              c2 = k_S12S21(2,ihelp)              if (iz.gt.2) c1 = k_S12S21(3,ihelp)
1755              beta_a(11) = c2*F/(ds-c1)              beta_a(11) = c2*F/(ds-c1)
1756    
1757  C-------ToF Mask - S12 - S21  C-------ToF Mask - S12 - S21
# Line 1861  C------- Line 1771  C-------
1771           ENDIF           ENDIF
1772        ENDIF        ENDIF
1773    
1774  C     S12 - S22  C---------------------     S12 - S22  ------------------------
1775    
1776        dist = ZTOF(2) - ZTOF(4)        dist = ZTOF(2) - ZTOF(4)
1777        dl = 0.        dl = 0.
# Line 1870  C     S12 - S22 Line 1780  C     S12 - S22
1780        ENDDO        ENDDO
1781        F = dl/dist        F = dl/dist
1782    
1783          c2 = (2.*0.01*dist)/(3.E08*50.E-12  )
1784    
1785  C      IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1786         IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1787       &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
# Line 1882  C      IF (tof12_i.GT.none_find.AND.tof2 Line 1794  C      IF (tof12_i.GT.none_find.AND.tof2
1794              xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)              xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1795              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)              xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1796              ds = xhelp1-xhelp2              ds = xhelp1-xhelp2
1797              ihelp=(tof12_i-1)*2+tof22_i              ihelp=(tof12_i-1)*2+tof22_i          
1798              c1 = k_S12S22(1,ihelp)              if (iz.le.1) c1 = k_S12S22(1,ihelp)
1799              if (iz.gt.2) c1 = c1 + k1corrC1              if (iz.eq.2) c1 = k_S12S22(2,ihelp)
1800              c2 = k_S12S22(2,ihelp)              if (iz.gt.2) c1 = k_S12S22(3,ihelp)
1801              beta_a(12) = c2*F/(ds-c1)              beta_a(12) = c2*F/(ds-c1)
1802    
1803  C-------ToF Mask - S12 - S22  C-------ToF Mask - S12 - S22

Legend:
Removed from v.1.18  
changed lines
  Added in v.1.20

  ViewVC Help
Powered by ViewVC 1.1.23