/[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.19 by mocchiut, Mon Nov 23 09:50:51 2009 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  nov-09 WM: the dEdx part ("adc_c") moved to the new dEdx routine from Napoli
56    C
57  C****************************************************************************  C****************************************************************************
58        IMPLICIT NONE        IMPLICIT NONE
59  C  C
# Line 105  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 110  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
110        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
111    
112    
113    C--- new
114          REAL xtofpre(3),ytofpre(3)
115    
116          REAL y_coor_lin11c(8,2),x_coor_lin12c(6,2)
117          REAL x_coor_lin21c(2,2),y_coor_lin22c(2,2)
118          REAL y_coor_lin31c(3,2),x_coor_lin32c(3,2)
119    
120          DATA y_coor_lin11c(1,1),y_coor_lin11c(1,2) /-20.66,-2.497/
121          DATA y_coor_lin11c(2,1),y_coor_lin11c(2,2) /-9.10, -2.52/
122          DATA y_coor_lin11c(3,1),y_coor_lin11c(3,2) /-24.07,-2.12/
123          DATA y_coor_lin11c(4,1),y_coor_lin11c(4,2) /-13.40,-2.47/
124          DATA y_coor_lin11c(5,1),y_coor_lin11c(5,2) /-31.07,-2.32/
125          DATA y_coor_lin11c(6,1),y_coor_lin11c(6,2) /-21.69,-2.63/
126          DATA y_coor_lin11c(7,1),y_coor_lin11c(7,2) /-12.37,-2.65/
127          DATA y_coor_lin11c(8,1),y_coor_lin11c(8,2) /-10.81,-3.15/
128    
129          DATA x_coor_lin12c(1,1),x_coor_lin12c(1,2) /12.96, -2.65/
130          DATA x_coor_lin12c(2,1),x_coor_lin12c(2,2) /17.12,-2.44/
131          DATA x_coor_lin12c(3,1),x_coor_lin12c(3,2) /7.26, -1.98/
132          DATA x_coor_lin12c(4,1),x_coor_lin12c(4,2) /-22.52,-2.27/
133          DATA x_coor_lin12c(5,1),x_coor_lin12c(5,2) /-18.54,-2.28/
134          DATA x_coor_lin12c(6,1),x_coor_lin12c(6,2) /-7.67,-2.15/
135    
136          DATA x_coor_lin21c(1,1),x_coor_lin21c(1,2) /22.56,-1.56/
137          DATA x_coor_lin21c(2,1),x_coor_lin21c(2,2) /13.94,-1.56/
138    
139          DATA y_coor_lin22c(1,1),y_coor_lin22c(1,2) /-24.24,-2.23/
140          DATA y_coor_lin22c(2,1),y_coor_lin22c(2,2) /-45.99,-1.68/
141    
142          DATA y_coor_lin31c(1,1),y_coor_lin31c(1,2) /-22.99,-3.54/
143          DATA y_coor_lin31c(2,1),y_coor_lin31c(2,2) /-42.28,-4.10/
144          DATA y_coor_lin31c(3,1),y_coor_lin31c(3,2) /-41.29,-3.69/
145    
146          DATA x_coor_lin32c(1,1),x_coor_lin32c(1,2) /0.961, -3.22/
147          DATA x_coor_lin32c(2,1),x_coor_lin32c(2,2) /4.98,-3.48/
148          DATA x_coor_lin32c(3,1),x_coor_lin32c(3,2) /-22.08,-3.37/
149    
150    C---
151    
152        INTEGER ihelp        INTEGER ihelp
153        REAL xkorr,xpos        REAL xkorr,xpos
154    
# Line 232  c     put the adc and tdc values from nt Line 276  c     put the adc and tdc values from nt
276           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
277           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
278        enddo        enddo
279    
280        do j=1,2        do j=1,2
281           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
282           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 359  C     COPY THE ALFA VECTOR FROM AL_PP TO
359        enddo        enddo
360    
361  c      write(*,*) AL_P  c      write(*,*) AL_P
362    c      write(*,*) 'Rigidity ',(1./AL_P(5))
363    
364        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
365  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 384  C---  Fill xtr_tof  and ytr_tof: positio
384        do j=1,6        do j=1,6
385        xtr_tof(j) = XOUT(j)        xtr_tof(j) = XOUT(j)
386        ytr_tof(j) = YOUT(j)        ytr_tof(j) = YOUT(j)
387    c      write(*,*) XOUT(j),YOUT(j)
388        enddo        enddo
389    
390    
# Line 429  c     S22 2 paddles  15.0 x 9.0 cm Line 475  c     S22 2 paddles  15.0 x 9.0 cm
475  c     S31 3 paddles  15.0 x 6.0 cm  c     S31 3 paddles  15.0 x 6.0 cm
476  c     S32 3 paddles  18.0 x 5.0 cm  c     S32 3 paddles  18.0 x 5.0 cm
477    
 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)  
478    
479  C--------------S11 --------------------------------------  C--------------S11 --------------------------------------
480    
# Line 535  C--------------S32 --------------------- Line 579  C--------------S32 ---------------------
579        endif        endif
580    
581    
 C     write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i  
582    
583         hitvec(1)=tof11_i         hitvec(1)=tof11_i
584         hitvec(2)=tof12_i         hitvec(2)=tof12_i
# Line 544  C     write(*,*) tof11_i,tof12_i,tof21_i Line 587  C     write(*,*) tof11_i,tof12_i,tof21_i
587         hitvec(5)=tof31_i         hitvec(5)=tof31_i
588         hitvec(6)=tof32_i         hitvec(6)=tof32_i
589    
 c       write(*,*) 'toftrk ',  
 c     &  tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i  
590    
591  C----------------------------------------------------------------------  C----------------------------------------------------------------------
592  C--- check charge:  C--- check charge:
# Line 567  C--------------------------------------- Line 608  C---------------------------------------
608         iz = int(check_charge(theta,hitvec))         iz = int(check_charge(theta,hitvec))
609  c       write(*,*) 'in toftrk',iz  c       write(*,*) 'in toftrk',iz
610    
611    
612    C-------------------------------  new  ---------------------------
613    C--  calculate track position in paddle using timing difference
614    C--  this calculation is preliminary and uses some standard
615    C--  calibration values, but we need to find a rough position to
616    C--  be able to calculate artificial ADC values (needed for the
617    C--  timewalk...
618    C------------------------------------------------------------------
619    
620           do i=1,3
621             xtofpre(i)=100.
622             ytofpre(i)=100.
623           enddo
624    
625    C-----------------------------S1 --------------------------------
626    
627          IF (tof11_i.GT.none_find) THEN
628          IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
629         +                             (tof11(2,tof11_i,itdc).LT.2000))
630         +    ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
631         +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
632          endif
633    
634          IF (tof12_i.GT.none_find) THEN
635          IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
636         +                             (tof12(2,tof12_i,itdc).LT.2000))
637         +    xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
638         +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
639          endif
640    
641    
642    C-----------------------------S2 --------------------------------
643    
644          IF (tof21_i.GT.none_find) THEN
645          IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
646         +                             (tof21(2,tof21_i,itdc).LT.2000))
647         +    xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
648         +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
649          endif
650    
651          IF (tof22_i.GT.none_find) THEN
652          IF ((tof22(1,tof22_i,itdc).LT.2000).AND.
653         +                             (tof22(2,tof22_i,itdc).LT.2000))
654         +    ytofpre(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
655         +    -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
656          endif
657    
658    
659    C-----------------------------S3 --------------------------------
660    
661          IF (tof31_i.GT.none_find) THEN
662          IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
663         +                             (tof31(2,tof31_i,itdc).LT.2000))
664         +    ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
665         +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
666          endif
667    
668          IF (tof32_i.GT.none_find) THEN
669          IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
670         +                             (tof32(2,tof32_i,itdc).LT.2000))
671         +    xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
672         +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
673          endif
674    
675    
676    C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
677    
678            if (abs(xtofpre(1)).gt.31.)  xtofpre(1)=100.
679            if (abs(xtofpre(2)).gt.19.)  xtofpre(2)=100.
680            if (abs(xtofpre(3)).gt.19.)  xtofpre(3)=100.
681    
682            if (abs(ytofpre(1)).gt.26.)  ytofpre(1)=100.
683            if (abs(ytofpre(2)).gt.18.)  ytofpre(2)=100.
684            if (abs(ytofpre(3)).gt.18.)  ytofpre(3)=100.
685    
686  C--------------------------------------------------------------------  C--------------------------------------------------------------------
687  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
688    C---- use the "pre" position if possible, since this gives better time
689    C---- resolution ... october 2008
690  C--------------------------------------------------------------------  C--------------------------------------------------------------------
691  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
692  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 698  c     DATA tof32_y/ -5.0,0.0,5.0/
698    
699  C----------------------------S1 -------------------------------------  C----------------------------S1 -------------------------------------
700    
701        yhelp=yout(1)  c     yhelp=yout(1)
702        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        yhelp = ytofpre(1)
703          if (yhelp.eq.100) yhelp=yout(1)
704    
705          IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
706           i = tof11_i           i = tof11_i
707           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.           if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
708       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then       &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
# Line 603  C----------------------------S1 -------- Line 724  C----------------------------S1 --------
724           endif           endif
725        ENDIF        ENDIF
726    
727        xhelp=xout(2)  c      xhelp=xout(2)
728        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        xhelp = xtofpre(1)
729          if (xhelp.eq.100) xhelp=xout(2)
730    
731          IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
732           i = tof12_i           i = tof12_i
733           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.           if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
734       &       (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 754  c            xkorr=adcx12(right,i,1)*exp
754    
755  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
756    
757        xhelp=xout(3)  c      xhelp=xout(3)
758        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN        xhelp = xtofpre(2)
759          if (xhelp.eq.100) xhelp=xout(3)
760    
761          IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
762           i = tof21_i           i = tof21_i
763           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.           if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
764       &       (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 783  c            xkorr=adcx21(right,i,1)*exp
783        ENDIF        ENDIF
784    
785    
786        yhelp=yout(4)  c      yhelp=yout(4)
787        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        yhelp = ytofpre(2)
788          if (yhelp.eq.100) yhelp=yout(4)
789    
790          IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
791           i = tof22_i           i = tof22_i
792           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.           if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
793       &       (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 813  c            xkorr=adcx22(right,i,1)*exp
813    
814  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
815    
816        yhelp=yout(5)  c      yhelp=yout(5)
817        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN        yhelp = ytofpre(3)
818          if (yhelp.eq.100) yhelp=yout(5)
819    
820          IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
821           i = tof31_i           i = tof31_i
822           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.           if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
823       &       (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 842  c            xkorr=adcx31(right,i,1)*exp
842        ENDIF        ENDIF
843    
844    
845        xhelp=xout(6)  c      xhelp=xout(6)
846          xhelp = xtofpre(3)
847          if (xhelp.eq.100) xhelp=xout(6)
848    
849        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
850           i = tof32_i           i = tof32_i
851           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.           if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
# Line 1001  C-----------------------------S1 ------- Line 1137  C-----------------------------S1 -------
1137           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.
1138       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)       +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1139          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.          if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
1140          i=tof11_i
1141        endif        endif
1142        endif        endif
1143    
# Line 1010  C-----------------------------S1 ------- Line 1147  C-----------------------------S1 -------
1147           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.
1148       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)       +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1149          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.          if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
1150          i=tof12_i
1151        endif        endif
1152        endif        endif
1153    
# Line 1021  C-----------------------------S2 ------- Line 1159  C-----------------------------S2 -------
1159           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.
1160       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)       +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1161          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.          if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
1162          i=tof21_i
1163        endif        endif
1164        endif        endif
1165    
# Line 1030  C-----------------------------S2 ------- Line 1169  C-----------------------------S2 -------
1169           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.
1170       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)       +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1171          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.          if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
1172          i=tof22_i
1173        endif        endif
1174        endif        endif
1175    
# Line 1041  C-----------------------------S3 ------- Line 1181  C-----------------------------S3 -------
1181           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.
1182       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)       +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1183          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.          if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
1184          i=tof31_i
1185        endif        endif
1186        endif        endif
1187    
# Line 1050  C-----------------------------S3 ------- Line 1191  C-----------------------------S3 -------
1191           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.
1192       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)       +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1193          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.          if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
1194          i=tof32_i
1195        endif        endif
1196        endif        endif
1197    
# Line 1064  c      enddo Line 1206  c      enddo
1206    
1207    
1208    
1209  C---------------------------------------------------------------------  C--------------------------------------------------------------------
1210  C--------------------Corrections on ADC-data -------------------------  C-------------------Corrections on ADC-data -------------------------
1211  C-----------------angle and ADC(x) correction -----------------------  C-----------------angle and ADC(x) correction -----------------------
1212    C----------------   moved to the new dEdx routine -------------------
1213    
1214  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-----------------------------------------------------------------------  
1215  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1216  C-----------------------------------------------------------------------  C--------------------------------------------------------------------
1217  C-------------------difference of sums  ---------------------------  C---------------------difference of sums  ---------------------------
1218  C  C
1219  C     DS = (t1+t2) - t3+t4)  C     DS = (t1+t2) - t3+t4)
1220  C     DS = c1 + c2/beta*cos(theta)  C     DS = c1 + c2/beta*cos(theta)
# Line 1824  c      write(*,*) ytofpos Line 1828  c      write(*,*) ytofpos
1828  c      write(*,*) xtr_tof  c      write(*,*) xtr_tof
1829  c      write(*,*) ytr_tof  c      write(*,*) ytr_tof
1830    
1831    c       write(*,*) '---------  end toftrk ----------'
1832    
1833        RETURN        RETURN
1834        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.23