/[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.15 by mocchiut, Mon Mar 3 09:51:04 2008 UTC revision 1.17 by mocchiut, Fri Apr 18 18:55:55 2008 UTC
# Line 44  C             then in a second step we c Line 44  C             then in a second step we c
44  C             measurements, reject if > 10 sigma, calculate chi2 and "quality"  C             measurements, reject if > 10 sigma, calculate chi2 and "quality"
45  C             beta is taken as good if chi2<20 and quality>10  C             beta is taken as good if chi2<20 and quality>10
46  C             The function "newbeta" is located in "tofl2com.for"  C             The function "newbeta" is located in "tofl2com.for"
47  C  C  mar-08 WM: Call to "newbeta" changed, now a flag tells the function if the
48    C             call comes from "tofl2com" or form "toftrack"
49    C  mar-08 WM: Bug found in dEdx if check_charge>1
50    C  apr-08 WM: Bug found in S22 artificial ADC, mismatch found between the track
51    C             length  from DOTRACK2 and "GetLength" method for 4 combinations
52  C****************************************************************************  C****************************************************************************
53        IMPLICIT NONE        IMPLICIT NONE
54  C  C
# Line 665  c            xkorr=adcx22(left,i,1)*exp( Line 669  c            xkorr=adcx22(left,i,1)*exp(
669              tof22(left,i,iadc) = xkorr/cos(theta)              tof22(left,i,iadc) = xkorr/cos(theta)
670              adcflag(ch22a(i),hb22a(i)) = 1              adcflag(ch22a(i),hb22a(i)) = 1
671           endif           endif
672           if ((tdc(ch22a(i),hb22b(i)).lt.4095).AND.           if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
673       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then       &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
674              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
675              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
# Line 1078  C-----------------------------S1 ------- Line 1082  C-----------------------------S1 -------
1082           if (tof11(left,i,iadc).lt.3786) then           if (tof11(left,i,iadc).lt.3786) then
1083              tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)              tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)
1084              xkorr = atten(left,11,i,yhelp)              xkorr = atten(left,11,i,yhelp)
1085              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1086              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
1087           endif           endif
1088    
# Line 1086  C-----------------------------S1 ------- Line 1090  C-----------------------------S1 -------
1090           if (tof11(right,i,iadc).lt.3786) then           if (tof11(right,i,iadc).lt.3786) then
1091              tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)              tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)
1092              xkorr = atten(right,11,i,yhelp)              xkorr = atten(right,11,i,yhelp)
1093              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1094              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
1095           endif           endif
1096        ENDIF        ENDIF
# Line 1101  C-----------------------------S1 ------- Line 1105  C-----------------------------S1 -------
1105           if (tof12(left,i,iadc).lt.3786) then           if (tof12(left,i,iadc).lt.3786) then
1106              tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)              tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)
1107              xkorr = atten(left,12,i,xhelp)              xkorr = atten(left,12,i,xhelp)
1108              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1109              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
1110           endif           endif
1111    
1112           if (tof12(right,i,iadc).lt.3786) then           if (tof12(right,i,iadc).lt.3786) then
1113              tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)              tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)
1114              xkorr = atten(right,12,i,xhelp)              xkorr = atten(right,12,i,xhelp)
1115              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1116              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
1117           endif           endif
1118        ENDIF        ENDIF
# Line 1124  C-----------------------------S2 ------- Line 1128  C-----------------------------S2 -------
1128           if (tof21(left,i,iadc).lt.3786) then           if (tof21(left,i,iadc).lt.3786) then
1129              tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)              tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)
1130              xkorr = atten(left,21,i,xhelp)              xkorr = atten(left,21,i,xhelp)
1131              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1132              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
1133           endif           endif
1134    
1135           if (tof21(right,i,iadc).lt.3786) then           if (tof21(right,i,iadc).lt.3786) then
1136              tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)              tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)
1137              xkorr = atten(right,21,i,xhelp)              xkorr = atten(right,21,i,xhelp)
1138              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1139              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
1140           endif           endif
1141        ENDIF        ENDIF
# Line 1145  C-----------------------------S2 ------- Line 1149  C-----------------------------S2 -------
1149           if (tof22(left,i,iadc).lt.3786) then           if (tof22(left,i,iadc).lt.3786) then
1150              tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)              tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)
1151              xkorr = atten(left,22,i,yhelp)              xkorr = atten(left,22,i,yhelp)
1152              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1153              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
1154           endif           endif
1155    
1156           if (tof22(right,i,iadc).lt.3786) then           if (tof22(right,i,iadc).lt.3786) then
1157              tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)              tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)
1158              xkorr = atten(right,22,i,yhelp)              xkorr = atten(right,22,i,yhelp)
1159              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1160              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
1161           endif           endif
1162        ENDIF        ENDIF
# Line 1169  C-----------------------------S3 ------- Line 1173  C-----------------------------S3 -------
1173           if (tof31(left,i,iadc).lt.3786) then           if (tof31(left,i,iadc).lt.3786) then
1174              tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)              tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)
1175              xkorr = atten(left,31,i,yhelp)              xkorr = atten(left,31,i,yhelp)
1176              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1177              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1178           endif           endif
1179    
1180           if (tof31(right,i,iadc).lt.3786) then           if (tof31(right,i,iadc).lt.3786) then
1181              tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)              tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)
1182              xkorr = atten(right,31,i,yhelp)              xkorr = atten(right,31,i,yhelp)
1183              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1184              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1185           endif           endif
1186        ENDIF        ENDIF
# Line 1190  C-----------------------------S3 ------- Line 1194  C-----------------------------S3 -------
1194           if (tof32(left,i,iadc).lt.3786) then           if (tof32(left,i,iadc).lt.3786) then
1195              tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)              tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)
1196              xkorr = atten(left,32,i,xhelp)              xkorr = atten(left,32,i,xhelp)
1197              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1198              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1199           endif           endif
1200    
1201           if (tof32(right,i,iadc).lt.3786) then           if (tof32(right,i,iadc).lt.3786) then
1202              tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)              tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)
1203              xkorr = atten(right,32,i,xhelp)              xkorr = atten(right,32,i,xhelp)
1204              if (iz.le.1) xkorr=xkorr/hepratio              xkorr=xkorr/hepratio
1205              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1206           endif           endif
1207        ENDIF        ENDIF
# Line 1488  C     S22 - S31 Line 1492  C     S22 - S31
1492           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1493        ENDDO        ENDDO
1494        F = dl/dist        F = dl/dist
1495          
1496    C WM workaround
1497          dl = dl - 0.06*F
1498          F = dl/dist
1499    
1500  C      IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1501         IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.         IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
# Line 1532  C     S22 - S32 Line 1540  C     S22 - S32
1540           dl = dl + TLOUT(i)           dl = dl + TLOUT(i)
1541        ENDDO        ENDDO
1542        F = dl/dist        F = dl/dist
1543          
1544    C WM workaround      
1545          dl = dl - 0.06*F
1546          F = dl/dist
1547    
1548    
1549  C      IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1550         IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.         IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
# Line 1577  C     S11 - S21 Line 1590  C     S11 - S21
1590        ENDDO        ENDDO
1591        F = dl/dist        F = dl/dist
1592    
1593    C WM workaround      
1594          dl = dl - 0.442*F
1595          F = dl/dist
1596    
1597  C      IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1598         IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.         IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1599       &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN       &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
# Line 1665  C     S12 - S21 Line 1682  C     S12 - S21
1682        ENDDO        ENDDO
1683        F = dl/dist        F = dl/dist
1684    
1685    C  WM workaround
1686          dl = dl - 0.442*F
1687          F = dl/dist
1688    
1689  C      IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN  C      IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1690         IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.         IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1691       &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN       &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
# Line 1765  C Line 1786  C
1786  C      if (icount.gt.0) beta_mean=sxw/sw  C      if (icount.gt.0) beta_mean=sxw/sw
1787  C      beta_a(13) = beta_mean  C      beta_a(13) = beta_mean
1788  C  C
1789    
1790  C-------  New mean beta  calculation  C-------  New mean beta  calculation
1791    
1792         do i=1,12         do i=1,12
1793           btemp(i) =  beta_a(i)           btemp(i) =  beta_a(i)
1794         enddo         enddo
1795    
1796         beta_a(13)=newbeta(btemp,hitvec,10.,10.,20.)         beta_a(13)=newbeta(2,btemp,hitvec,10.,10.,20.)
1797    
1798  C-------  C-------
1799    
# Line 1803  c      write(*,*) xtr_tof Line 1825  c      write(*,*) xtr_tof
1825  c      write(*,*) ytr_tof  c      write(*,*) ytr_tof
1826    
1827    
   
1828        RETURN        RETURN
1829        END        END
1830    
# Line 1812  c      write(*,*) ytr_tof Line 1833  c      write(*,*) ytr_tof
1833    
1834  C------------------------------------------------------------------  C------------------------------------------------------------------
1835    
1836    

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

  ViewVC Help
Powered by ViewVC 1.1.23