/[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.17 by mocchiut, Fri Apr 18 18:55:55 2008 UTC revision 1.18 by pamelats, Thu Nov 27 13:49:13 2008 UTC
# Line 49  C             call comes from "tofl2com" Line 49  C             call comes from "tofl2com"
49  C  mar-08 WM: Bug found in dEdx if check_charge>1  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  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  C             length  from DOTRACK2 and "GetLength" method for 4 combinations
52    C  oct-08 WM: New method to create artificial ADC values. Do NOT take the position
53    C             from the tracking, but the position from timing. This method gives a
54    C             better time resolution
55  C****************************************************************************  C****************************************************************************
56        IMPLICIT NONE        IMPLICIT NONE
57  C  C
# Line 105  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 108  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
108        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
109    
110    
111    C--- new
112          REAL xtofpre(3),ytofpre(3)
113    
114          REAL y_coor_lin11c(8,2),x_coor_lin12c(6,2)
115          REAL x_coor_lin21c(2,2),y_coor_lin22c(2,2)
116          REAL y_coor_lin31c(3,2),x_coor_lin32c(3,2)
117    
118          DATA y_coor_lin11c(1,1),y_coor_lin11c(1,2) /-20.66,-2.497/
119          DATA y_coor_lin11c(2,1),y_coor_lin11c(2,2) /-9.10, -2.52/
120          DATA y_coor_lin11c(3,1),y_coor_lin11c(3,2) /-24.07,-2.12/
121          DATA y_coor_lin11c(4,1),y_coor_lin11c(4,2) /-13.40,-2.47/
122          DATA y_coor_lin11c(5,1),y_coor_lin11c(5,2) /-31.07,-2.32/
123          DATA y_coor_lin11c(6,1),y_coor_lin11c(6,2) /-21.69,-2.63/
124          DATA y_coor_lin11c(7,1),y_coor_lin11c(7,2) /-12.37,-2.65/
125          DATA y_coor_lin11c(8,1),y_coor_lin11c(8,2) /-10.81,-3.15/
126    
127          DATA x_coor_lin12c(1,1),x_coor_lin12c(1,2) /12.96, -2.65/
128          DATA x_coor_lin12c(2,1),x_coor_lin12c(2,2) /17.12,-2.44/
129          DATA x_coor_lin12c(3,1),x_coor_lin12c(3,2) /7.26, -1.98/
130          DATA x_coor_lin12c(4,1),x_coor_lin12c(4,2) /-22.52,-2.27/
131          DATA x_coor_lin12c(5,1),x_coor_lin12c(5,2) /-18.54,-2.28/
132          DATA x_coor_lin12c(6,1),x_coor_lin12c(6,2) /-7.67,-2.15/
133    
134          DATA x_coor_lin21c(1,1),x_coor_lin21c(1,2) /22.56,-1.56/
135          DATA x_coor_lin21c(2,1),x_coor_lin21c(2,2) /13.94,-1.56/
136    
137          DATA y_coor_lin22c(1,1),y_coor_lin22c(1,2) /-24.24,-2.23/
138          DATA y_coor_lin22c(2,1),y_coor_lin22c(2,2) /-45.99,-1.68/
139    
140          DATA y_coor_lin31c(1,1),y_coor_lin31c(1,2) /-22.99,-3.54/
141          DATA y_coor_lin31c(2,1),y_coor_lin31c(2,2) /-42.28,-4.10/
142          DATA y_coor_lin31c(3,1),y_coor_lin31c(3,2) /-41.29,-3.69/
143    
144          DATA x_coor_lin32c(1,1),x_coor_lin32c(1,2) /0.961, -3.22/
145          DATA x_coor_lin32c(2,1),x_coor_lin32c(2,2) /4.98,-3.48/
146          DATA x_coor_lin32c(3,1),x_coor_lin32c(3,2) /-22.08,-3.37/
147    
148    C---
149    
150        INTEGER ihelp        INTEGER ihelp
151        REAL xkorr,xpos        REAL xkorr,xpos
152    
# Line 232  c     put the adc and tdc values from nt Line 274  c     put the adc and tdc values from nt
274           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
275           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
276        enddo        enddo
277    
278        do j=1,2        do j=1,2
279           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
280           tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))           tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))
# Line 315  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 357  C     COPY THE ALFA VECTOR FROM AL_PP TO
357        enddo        enddo
358    
359  c      write(*,*) AL_P  c      write(*,*) AL_P
360    c      write(*,*) 'Rigidity ',(1./AL_P(5))
361    
362        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
363  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
# Line 339  C---  Fill xtr_tof  and ytr_tof: positio Line 382  C---  Fill xtr_tof  and ytr_tof: positio
382        do j=1,6        do j=1,6
383        xtr_tof(j) = XOUT(j)        xtr_tof(j) = XOUT(j)
384        ytr_tof(j) = YOUT(j)        ytr_tof(j) = YOUT(j)
385    c      write(*,*) XOUT(j),YOUT(j)
386        enddo        enddo
387    
388    
# Line 429  c     S22 2 paddles  15.0 x 9.0 cm Line 473  c     S22 2 paddles  15.0 x 9.0 cm
473  c     S31 3 paddles  15.0 x 6.0 cm  c     S31 3 paddles  15.0 x 6.0 cm
474  c     S32 3 paddles  18.0 x 5.0 cm  c     S32 3 paddles  18.0 x 5.0 cm
475    
 c     write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)  
 c     write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)  
476    
477  C--------------S11 --------------------------------------  C--------------S11 --------------------------------------
478    
# Line 535  C--------------S32 --------------------- Line 577  C--------------S32 ---------------------
577        endif        endif
578    
579    
 C     write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i  
580    
581         hitvec(1)=tof11_i         hitvec(1)=tof11_i
582         hitvec(2)=tof12_i         hitvec(2)=tof12_i
# Line 544  C     write(*,*) tof11_i,tof12_i,tof21_i Line 585  C     write(*,*) tof11_i,tof12_i,tof21_i
585         hitvec(5)=tof31_i         hitvec(5)=tof31_i
586         hitvec(6)=tof32_i         hitvec(6)=tof32_i
587    
 c       write(*,*) 'toftrk ',  
 c     &  tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i  
588    
589  C----------------------------------------------------------------------  C----------------------------------------------------------------------
590  C--- check charge:  C--- check charge:
# Line 567  C--------------------------------------- Line 606  C---------------------------------------
606         iz = int(check_charge(theta,hitvec))         iz = int(check_charge(theta,hitvec))
607  c       write(*,*) 'in toftrk',iz  c       write(*,*) 'in toftrk',iz
608    
609    
610    C-------------------------------  new  ---------------------------
611    C--  calculate track position in paddle using timing difference
612    C--  this calculation is preliminary and uses some standard
613    C--  calibration values, but we need to find a rough position to
614    C--  be able to calculate artificial ADC values (needed for the
615    C--  timewalk...
616    C------------------------------------------------------------------
617    
618           do i=1,3
619             xtofpre(i)=100.
620             ytofpre(i)=100.
621           enddo
622    
623    C-----------------------------S1 --------------------------------
624    
625          IF (tof11_i.GT.none_find) THEN
626          IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
627         +                             (tof11(2,tof11_i,itdc).LT.2000))
628         +    ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
629         +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
630          endif
631    
632          IF (tof12_i.GT.none_find) THEN
633          IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
634         +                             (tof12(2,tof12_i,itdc).LT.2000))
635         +    xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
636         +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
637          endif
638    
639    
640    C-----------------------------S2 --------------------------------
641    
642          IF (tof21_i.GT.none_find) THEN
643          IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
644         +                             (tof21(2,tof21_i,itdc).LT.2000))
645         +    xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
646         +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
647          endif
648    
649          IF (tof22_i.GT.none_find) THEN
650          IF ((tof22(1,tof22_i,itdc).LT.2000).AND.
651         +                             (tof22(2,tof22_i,itdc).LT.2000))
652         +    ytofpre(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
653         +    -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
654          endif
655    
656    
657    C-----------------------------S3 --------------------------------
658    
659          IF (tof31_i.GT.none_find) THEN
660          IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
661         +                             (tof31(2,tof31_i,itdc).LT.2000))
662         +    ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
663         +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
664          endif
665    
666          IF (tof32_i.GT.none_find) THEN
667          IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
668         +                             (tof32(2,tof32_i,itdc).LT.2000))
669         +    xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
670         +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
671          endif
672    
673    
674    C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
675    
676            if (abs(xtofpre(1)).gt.31.)  xtofpre(1)=100.
677            if (abs(xtofpre(2)).gt.19.)  xtofpre(2)=100.
678            if (abs(xtofpre(3)).gt.19.)  xtofpre(3)=100.
679    
680            if (abs(ytofpre(1)).gt.26.)  ytofpre(1)=100.
681            if (abs(ytofpre(2)).gt.18.)  ytofpre(2)=100.
682            if (abs(ytofpre(3)).gt.18.)  ytofpre(3)=100.
683    
684  C--------------------------------------------------------------------  C--------------------------------------------------------------------
685  C---- if paddle hit: if we have TDC value but no ADC, create ADC value  C---- if paddle hit: if we have TDC value but no ADC, create ADC value
686    C---- use the "pre" position if possible, since this gives better time
687    C---- resolution ... october 2008
688  C--------------------------------------------------------------------  C--------------------------------------------------------------------
689  c     middle y (or x) position of the upper and middle ToF-Paddle  c     middle y (or x) position of the upper and middle ToF-Paddle
690  c     DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/  c     DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
# Line 580  c     DATA tof32_y/ -5.0,0.0,5.0/ Line 696  c     DATA tof32_y/ -5.0,0.0,5.0/
696    
697  C----------------------------S1 -------------------------------------  C----------------------------S1 -------------------------------------
698    
699        yhelp=yout(1)  c     yhelp=yout(1)
700        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        yhelp = ytofpre(1)
701          if (yhelp.eq.100) yhelp=yout(1)
702    
703          IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
704           i = tof11_i           i = tof11_i
705           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
706       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
# Line 603  C----------------------------S1 -------- Line 722  C----------------------------S1 --------
722           endif           endif
723        ENDIF        ENDIF
724    
725        xhelp=xout(2)  c      xhelp=xout(2)
726        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        xhelp = xtofpre(1)
727          if (xhelp.eq.100) xhelp=xout(2)
728    
729          IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
730           i = tof12_i           i = tof12_i
731           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
732       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then       &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
# Line 630  c            xkorr=adcx12(right,i,1)*exp Line 752  c            xkorr=adcx12(right,i,1)*exp
752    
753  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
754    
755        xhelp=xout(3)  c      xhelp=xout(3)
756        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN        xhelp = xtofpre(2)
757          if (xhelp.eq.100) xhelp=xout(3)
758    
759          IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
760           i = tof21_i           i = tof21_i
761           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
762       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then       &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
# Line 656  c            xkorr=adcx21(right,i,1)*exp Line 781  c            xkorr=adcx21(right,i,1)*exp
781        ENDIF        ENDIF
782    
783    
784        yhelp=yout(4)  c      yhelp=yout(4)
785        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        yhelp = ytofpre(2)
786          if (yhelp.eq.100) yhelp=yout(4)
787    
788          IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
789           i = tof22_i           i = tof22_i
790           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
791       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then       &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
# Line 683  c            xkorr=adcx22(right,i,1)*exp Line 811  c            xkorr=adcx22(right,i,1)*exp
811    
812  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
813    
814        yhelp=yout(5)  c      yhelp=yout(5)
815        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN        yhelp = ytofpre(3)
816          if (yhelp.eq.100) yhelp=yout(5)
817    
818          IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
819           i = tof31_i           i = tof31_i
820           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
821       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then       &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
# Line 709  c            xkorr=adcx31(right,i,1)*exp Line 840  c            xkorr=adcx31(right,i,1)*exp
840        ENDIF        ENDIF
841    
842    
843        xhelp=xout(6)  c      xhelp=xout(6)
844          xhelp = xtofpre(3)
845          if (xhelp.eq.100) xhelp=xout(6)
846    
847        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
848           i = tof32_i           i = tof32_i
849           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
# Line 1001  C-----------------------------S1 ------- Line 1135  C-----------------------------S1 -------
1135           ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.           ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
1136       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1137          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
1138          i=tof11_i
1139        endif        endif
1140        endif        endif
1141    
# Line 1010  C-----------------------------S1 ------- Line 1145  C-----------------------------S1 -------
1145           xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.           xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
1146       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1147          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
1148          i=tof12_i
1149        endif        endif
1150        endif        endif
1151    
# Line 1021  C-----------------------------S2 ------- Line 1157  C-----------------------------S2 -------
1157           xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.           xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
1158       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1159          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
1160          i=tof21_i
1161        endif        endif
1162        endif        endif
1163    
# Line 1030  C-----------------------------S2 ------- Line 1167  C-----------------------------S2 -------
1167           ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.           ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
1168       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1169          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
1170          i=tof22_i
1171        endif        endif
1172        endif        endif
1173    
# Line 1041  C-----------------------------S3 ------- Line 1179  C-----------------------------S3 -------
1179           ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.           ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
1180       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1181          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
1182          i=tof31_i
1183        endif        endif
1184        endif        endif
1185    
# Line 1050  C-----------------------------S3 ------- Line 1189  C-----------------------------S3 -------
1189           xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.           xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
1190       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1191          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
1192          i=tof32_i
1193        endif        endif
1194        endif        endif
1195    
# Line 1824  c      write(*,*) ytofpos Line 1964  c      write(*,*) ytofpos
1964  c      write(*,*) xtr_tof  c      write(*,*) xtr_tof
1965  c      write(*,*) ytr_tof  c      write(*,*) ytr_tof
1966    
1967    c       write(*,*) '---------  end toftrk ----------'
1968    
1969        RETURN        RETURN
1970        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.23