/[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.4 by mocchiut, Sat Sep 9 05:17:20 2006 UTC revision 1.5 by mocchiut, Tue Sep 12 13:58:24 2006 UTC
# Line 1  Line 1 
1  *****************************************************************************  *****************************************************************************
2        INTEGER FUNCTION TOFTRK()        INTEGER FUNCTION TOFTRK()
3  c      
4    C****************************************************************************
5    C 31-08-06  WM
6    C Changed to use DOTRACK2
7    C Beta calculation: now the flightpath (instead of cos(theta)) is used
8    C Beta calculation: all 4 TDV measurements must be < 4095 (in the old
9    C routine it was (t1+t2)<8000
10    C    
11    C****************************************************************************
12        IMPLICIT NONE        IMPLICIT NONE
13  C      C    
14        include  'input_tof.txt'        include  'input_tof.txt'
# Line 23  c     define TOF Z-coordinates Line 31  c     define TOF Z-coordinates
31        integer itof        integer itof
32    
33        DOUBLE PRECISION al_p(5),        DOUBLE PRECISION al_p(5),
34       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF)       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
35         &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
36    
37    
38        INTEGER IFAIL        INTEGER IFAIL
39        REAL dx,dy,dr,ds        REAL dx,dy,dr,ds
40          REAL t1,t2,t3,t4
41        REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2        REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2
42        REAL c1,c2,sw,sxw,w_i        REAL c1,c2,sw,sxw,w_i
43        INTEGER icount        REAL dist,dl,F
44          INTEGER icount,ievent
45    
46        REAL beta_mean        REAL beta_mean
47          
48        INTEGER j        INTEGER j
49    
50        REAL theta12,theta13,theta23        REAL theta12,theta13,theta23
# Line 54  C     Line 67  C    
67        REAL hmemor(9000000)        REAL hmemor(9000000)
68        INTEGER Iquest(100)        INTEGER Iquest(100)
69  C      C    
70          DATA ievent / 0 /
71    
72        COMMON / pawcd / hmemor        COMMON / pawcd / hmemor
73        save / pawcd /        save / pawcd /
74  C      C    
# Line 66  C     Line 81  C    
81    
82  *******************************************************************  *******************************************************************
83    
84          ievent = ievent +1
85    
86    
87        offset = 1        offset = 1
88        slope = 2        slope = 2
89        left = 1        left = 1
# Line 105  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 123  C     COPY THE ALFA VECTOR FROM AL_PP TO
123        do i=1,5        do i=1,5
124           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
125        enddo        enddo
126    
127    c      write(*,*) AL_P
128    
129        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
130  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
131           GOTO 969           GOTO 969
132        ENDIF        ENDIF
133  *     -------- *** tracking routine *** --------  *     -------- *** tracking routine *** --------
134        IFAIL = 0        IFAIL = 0
135        call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)  C      call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
136          call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
137    
138    
139    C      write(*,*) (TLOUT(i),i=1,6)
140    
141        if(IFAIL.ne.0)then        if(IFAIL.ne.0)then
142  c         print *,' TOF - WARNING F77: tracking failed '           print *,' TOF - WARNING F77: tracking failed '
143           goto 969           goto 969
144        endif        endif
145  *     ------------------------------------------  *     ------------------------------------------
# Line 138  c  S22 2 paddles  15.0 x 9.0 cm Line 164  c  S22 2 paddles  15.0 x 9.0 cm
164  c  S31 3 paddles  15.0 x 6.0 cm  c  S31 3 paddles  15.0 x 6.0 cm
165  c  S32 3 paddles  18.0 x 5.0 cm  c  S32 3 paddles  18.0 x 5.0 cm
166    
167    c       write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)
168    c       write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)
169    
170  C--------------     S11 --------------------------------------  C--------------     S11 --------------------------------------
171    
# Line 241  C--------------     S32 ---------------- Line 269  C--------------     S32 ----------------
269        enddo        enddo
270        endif        endif
271    
272    
273    C      write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
274    
275  C------------------------------------------------------------------  C------------------------------------------------------------------
276  C---  calculate track position in paddle using timing difference  C---  calculate track position in paddle using timing difference
277  C------------------------------------------------------------------  C------------------------------------------------------------------
# Line 328  C-----------------------------S1 ------- Line 359  C-----------------------------S1 -------
359           i = tof11_i           i = tof11_i
360           xdummy=tof11(left,i,iadc)           xdummy=tof11(left,i,iadc)
361           tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)           tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
362           if (tof11(left,i,iadc).lt.4095) then           if (tof11(left,i,iadc).lt.1000) then
363              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
364              xkorr0=adcx11(left,i,1)              xkorr0=adcx11(left,i,1)
365              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
366           endif           endif
367    
368           tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)           tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
369           if (tof11(right,i,iadc).lt.4095) then           if (tof11(right,i,iadc).lt.1000) then
370              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
371              xkorr0=adcx11(right,i,1)              xkorr0=adcx11(right,i,1)
372              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
# Line 348  C-----------------------------S1 ------- Line 379  C-----------------------------S1 -------
379    
380           i = tof12_i           i = tof12_i
381           tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)           tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
382           if (tof12(left,i,iadc).lt.4095) then           if (tof12(left,i,iadc).lt.1000) then
383              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
384              xkorr0=adcx12(left,i,1)              xkorr0=adcx12(left,i,1)
385              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
386           endif           endif
387    
388           tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)           tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
389           if (tof12(right,i,iadc).lt.4095) then           if (tof12(right,i,iadc).lt.1000) then
390              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
391              xkorr0=adcx12(right,i,1)              xkorr0=adcx12(right,i,1)
392              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
# Line 369  C-----------------------------S2 ------- Line 400  C-----------------------------S2 -------
400    
401           i = tof21_i           i = tof21_i
402           tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)           tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
403           if (tof21(left,i,iadc).lt.4095) then           if (tof21(left,i,iadc).lt.1000) then
404              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
405              xkorr0=adcx21(left,i,1)              xkorr0=adcx21(left,i,1)
406              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
407           endif           endif
408    
409           tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)           tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
410           if (tof21(right,i,iadc).lt.4095) then           if (tof21(right,i,iadc).lt.1000) then
411              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
412              xkorr0=adcx21(right,i,1)              xkorr0=adcx21(right,i,1)
413              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
# Line 388  C-----------------------------S2 ------- Line 419  C-----------------------------S2 -------
419    
420           i = tof22_i           i = tof22_i
421           tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)           tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
422           if (tof22(left,i,iadc).lt.4095) then           if (tof22(left,i,iadc).lt.1000) then
423              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
424              xkorr0=adcx22(left,i,1)              xkorr0=adcx22(left,i,1)
425              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
426           endif           endif
427    
428           tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)           tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
429           if (tof22(right,i,iadc).lt.4095) then           if (tof22(right,i,iadc).lt.1000) then
430              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
431              xkorr0=adcx22(right,i,1)              xkorr0=adcx22(right,i,1)
432              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
# Line 409  C-----------------------------S3 ------- Line 440  C-----------------------------S3 -------
440    
441           i = tof31_i           i = tof31_i
442           tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)           tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
443           if (tof31(left,i,iadc).lt.4095) then           if (tof31(left,i,iadc).lt.1000) then
444              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
445              xkorr0=adcx31(left,i,1)              xkorr0=adcx31(left,i,1)
446              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
447           endif           endif
448    
449           tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)           tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
450           if (tof31(right,i,iadc).lt.4095) then           if (tof31(right,i,iadc).lt.1000) then
451              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
452              xkorr0=adcx31(right,i,1)              xkorr0=adcx31(right,i,1)
453              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
# Line 428  C-----------------------------S3 ------- Line 459  C-----------------------------S3 -------
459    
460           i = tof32_i           i = tof32_i
461           tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)           tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
462           if (tof32(left,i,iadc).lt.4095) then           if (tof32(left,i,iadc).lt.1000) then
463              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
464              xkorr0=adcx32(left,i,1)              xkorr0=adcx32(left,i,1)
465              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
466           endif           endif
467    
468           tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)           tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
469           if (tof32(right,i,iadc).lt.4095) then           if (tof32(right,i,iadc).lt.1000) then
470              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
471              xkorr0=adcx32(right,i,1)              xkorr0=adcx32(right,i,1)
472              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
# Line 452  C     DS = c1 + c2/beta*cos(theta) Line 483  C     DS = c1 + c2/beta*cos(theta)
483  C     c2 = 2d/c   gives c2 = 2d/(c*TDCresolution)  TDC=50ps/channel  C     c2 = 2d/c   gives c2 = 2d/(c*TDCresolution)  TDC=50ps/channel
484  C     =>  c2 =  ca.60 for  0.45 m    c2 = ca.109  for 0.81 m  C     =>  c2 =  ca.60 for  0.45 m    c2 = ca.109  for 0.81 m
485  C     since TDC resolution varies slightly c2 has to be calibrated  C     since TDC resolution varies slightly c2 has to be calibrated
486    C     instead of cos(theta) use factor F:
487    C     F =  pathlength/d
488    C     => beta = c2*F/(DS-c1))
489    
490           dist = ZTOF(1) - ZTOF(5)
491           dl = 0.
492           DO I=1,5
493           dl = dl + TLOUT(i)
494           ENDDO
495           F = dl/dist
496    
497  C     S11 - S31  C     S11 - S31
498        IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN        IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
499             t1 = tof11(1,tof11_i,itdc)
500             t2 = tof11(2,tof11_i,itdc)
501             t3 = tof31(1,tof31_i,itdc)
502             t4 = tof31(2,tof31_i,itdc)
503             IF ((t1.lt.4095).and.(t2.lt.4095).and.
504         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
505           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
506           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
507           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
508           ihelp=(tof11_i-1)*3+tof31_i           ihelp=(tof11_i-1)*3+tof31_i
509           c1 = k_S11S31(1,ihelp)           c1 = k_S11S31(1,ihelp)
510           c2 = k_S11S31(2,ihelp)                   c2 = k_S11S31(2,ihelp)        
511           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(1) = c2*F/(ds-c1)
512       &   beta_a(1) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
   
513  C------- ToF Mask - S11 - S31  C------- ToF Mask - S11 - S31
514    
515           tofmask(ch11a(tof11_i),hb11a(tof11_i)) =           tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
# Line 476  C------- ToF Mask - S11 - S31 Line 522  C------- ToF Mask - S11 - S31
522           tofmask(ch31b(tof31_i),hb31b(tof31_i)) =           tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
523       $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1       $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
524    
 C-------            
   
525        ENDIF        ENDIF
526          ENDIF
527    
528           dist = ZTOF(1) - ZTOF(6)
529           dl = 0.
530           DO I=1,6
531           dl = dl + TLOUT(i)
532           ENDDO
533           F = dl/dist
534                
535  C     S11 - S32  C     S11 - S32
536        IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN        IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
537             t1 = tof11(1,tof11_i,itdc)
538             t2 = tof11(2,tof11_i,itdc)
539             t3 = tof32(1,tof32_i,itdc)
540             t4 = tof32(2,tof32_i,itdc)
541             IF ((t1.lt.4095).and.(t2.lt.4095).and.
542         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
543           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
544           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
545           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
546           ihelp=(tof11_i-1)*3+tof32_i           ihelp=(tof11_i-1)*3+tof32_i
547           c1 = k_S11S32(1,ihelp)           c1 = k_S11S32(1,ihelp)
548           c2 = k_S11S32(2,ihelp)                   c2 = k_S11S32(2,ihelp)        
549           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(2) = c2*F/(ds-c1)
550       &   beta_a(2) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
551    
552  C------- ToF Mask - S11 - S32  C------- ToF Mask - S11 - S32
553    
# Line 506  C------- ToF Mask - S11 - S32 Line 564  C------- ToF Mask - S11 - S32
564  C-------            C-------          
565    
566        ENDIF        ENDIF
567          ENDIF
568    
569  C     S12 - S31  C     S12 - S31
570           dist = ZTOF(2) - ZTOF(5)
571           dl = 0.
572           DO I=2,5
573           dl = dl + TLOUT(i)
574           ENDDO
575           F = dl/dist
576    
577        IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN        IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
578             t1 = tof12(1,tof12_i,itdc)
579             t2 = tof12(2,tof12_i,itdc)
580             t3 = tof31(1,tof31_i,itdc)
581             t4 = tof31(2,tof31_i,itdc)
582             IF ((t1.lt.4095).and.(t2.lt.4095).and.
583         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
584           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
585           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
586           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
587           ihelp=(tof12_i-1)*3+tof31_i           ihelp=(tof12_i-1)*3+tof31_i
588           c1 = k_S12S31(1,ihelp)           c1 = k_S12S31(1,ihelp)
589           c2 = k_S12S31(2,ihelp)           c2 = k_S12S31(2,ihelp)
590           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(3) = c2*F/(ds-c1)
591       &   beta_a(3) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
592    
593  C------- ToF Mask - S12 - S31  C------- ToF Mask - S12 - S31
594    
# Line 533  C------- ToF Mask - S12 - S31 Line 605  C------- ToF Mask - S12 - S31
605  C-------  C-------
606    
607        ENDIF        ENDIF
608          ENDIF
609    
610  C     S12 - S32  C     S12 - S32
611    
612           dist = ZTOF(2) - ZTOF(6)
613           dl = 0.
614           DO I=2,6
615           dl = dl + TLOUT(i)
616           ENDDO
617           F = dl/dist
618    
619        IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN        IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
620             t1 = tof12(1,tof12_i,itdc)
621             t2 = tof12(2,tof12_i,itdc)
622             t3 = tof32(1,tof32_i,itdc)
623             t4 = tof32(2,tof32_i,itdc)
624             IF ((t1.lt.4095).and.(t2.lt.4095).and.
625         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
626           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
627           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
628           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
629           ihelp=(tof12_i-1)*3+tof32_i           ihelp=(tof12_i-1)*3+tof32_i
630           c1 = k_S12S32(1,ihelp)           c1 = k_S12S32(1,ihelp)
631           c2 = k_S12S32(2,ihelp)           c2 = k_S12S32(2,ihelp)
632           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(4) = c2*F/(ds-c1)
633       &   beta_a(4) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
634    
635  C------- ToF Mask - S12 - S32  C------- ToF Mask - S12 - S32
636    
# Line 560  C------- ToF Mask - S12 - S32 Line 647  C------- ToF Mask - S12 - S32
647  C-------  C-------
648    
649        ENDIF        ENDIF
650          ENDIF
651    
652  C     S21 - S31  C     S21 - S31
653    
654           dist = ZTOF(3) - ZTOF(5)
655           dl = 0.
656           DO I=3,5
657           dl = dl + TLOUT(i)
658           ENDDO
659           F = dl/dist
660    
661        IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN        IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
662             t1 = tof21(1,tof21_i,itdc)
663             t2 = tof21(2,tof21_i,itdc)
664             t3 = tof31(1,tof31_i,itdc)
665             t4 = tof31(2,tof31_i,itdc)
666             IF ((t1.lt.4095).and.(t2.lt.4095).and.
667         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
668           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
669           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
670           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
671           ihelp=(tof21_i-1)*3+tof31_i           ihelp=(tof21_i-1)*3+tof31_i
672           c1 = k_S21S31(1,ihelp)           c1 = k_S21S31(1,ihelp)
673           c2 = k_S21S31(2,ihelp)           c2 = k_S21S31(2,ihelp)
674           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(5) = c2*F/(ds-c1)
      &   beta_a(5) = c2/(cos(theta23)*(ds-c1))  
675    
676  C------- ToF Mask - S21 - S31  C------- ToF Mask - S21 - S31
677    
# Line 587  C------- ToF Mask - S21 - S31 Line 688  C------- ToF Mask - S21 - S31
688  C-------  C-------
689    
690        ENDIF        ENDIF
691          ENDIF
692    
693  C     S21 - S32  C     S21 - S32
694    
695           dist = ZTOF(3) - ZTOF(6)
696           dl = 0.
697           DO I=3,6
698           dl = dl + TLOUT(i)
699           ENDDO
700           F = dl/dist
701    
702        IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN        IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
703             t1 = tof21(1,tof21_i,itdc)
704             t2 = tof21(2,tof21_i,itdc)
705             t3 = tof32(1,tof32_i,itdc)
706             t4 = tof32(2,tof32_i,itdc)
707             IF ((t1.lt.4095).and.(t2.lt.4095).and.
708         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
709           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
710           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
711           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
712           ihelp=(tof21_i-1)*3+tof32_i           ihelp=(tof21_i-1)*3+tof32_i
713           c1 = k_S21S32(1,ihelp)           c1 = k_S21S32(1,ihelp)
714           c2 = k_S21S32(2,ihelp)           c2 = k_S21S32(2,ihelp)
715           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(6) = c2*F/(ds-c1)
      &   beta_a(6) = c2/(cos(theta23)*(ds-c1))  
716    
717  C------- ToF Mask - S21 - S32  C------- ToF Mask - S21 - S32
718    
# Line 614  C------- ToF Mask - S21 - S32 Line 729  C------- ToF Mask - S21 - S32
729  C-------  C-------
730    
731        ENDIF        ENDIF
732          ENDIF
733    
734  C     S22 - S31  C     S22 - S31
735    
736           dist = ZTOF(4) - ZTOF(5)
737           dl = 0.
738           DO I=4,5
739           dl = dl + TLOUT(i)
740           ENDDO
741           F = dl/dist
742    
743        IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN        IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
744             t1 = tof22(1,tof22_i,itdc)
745             t2 = tof22(2,tof22_i,itdc)
746             t3 = tof31(1,tof31_i,itdc)
747             t4 = tof31(2,tof31_i,itdc)
748             IF ((t1.lt.4095).and.(t2.lt.4095).and.
749         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
750           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
751           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
752           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
753           ihelp=(tof22_i-1)*3+tof31_i           ihelp=(tof22_i-1)*3+tof31_i
754           c1 = k_S22S31(1,ihelp)           c1 = k_S22S31(1,ihelp)
755           c2 = k_S22S31(2,ihelp)           c2 = k_S22S31(2,ihelp)
756           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(7) = c2*F/(ds-c1)
      &   beta_a(7) = c2/(cos(theta13)*(ds-c1))  
757    
758  C------- ToF Mask - S22 - S31  C------- ToF Mask - S22 - S31
759    
# Line 641  C------- ToF Mask - S22 - S31 Line 770  C------- ToF Mask - S22 - S31
770  C-------    C-------  
771    
772        ENDIF        ENDIF
773          ENDIF
774                
775  C     S22 - S32  C     S22 - S32
776    
777           dist = ZTOF(4) - ZTOF(6)
778           dl = 0.
779           DO I=4,6
780           dl = dl + TLOUT(i)
781           ENDDO
782           F = dl/dist
783    
784        IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN        IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
785             t1 = tof22(1,tof22_i,itdc)
786             t2 = tof22(2,tof22_i,itdc)
787             t3 = tof32(1,tof32_i,itdc)
788             t4 = tof32(2,tof32_i,itdc)
789             IF ((t1.lt.4095).and.(t2.lt.4095).and.
790         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
791           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
792           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
793           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
794           ihelp=(tof22_i-1)*3+tof32_i           ihelp=(tof22_i-1)*3+tof32_i
795           c1 = k_S22S32(1,ihelp)           c1 = k_S22S32(1,ihelp)
796           c2 = k_S22S32(2,ihelp)           c2 = k_S22S32(2,ihelp)
797           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(8) = c2*F/(ds-c1)
      &   beta_a(8) = c2/(cos(theta13)*(ds-c1))  
798    
799  C------- ToF Mask - S22 - S32  C------- ToF Mask - S22 - S32
800    
# Line 668  C------- ToF Mask - S22 - S32 Line 811  C------- ToF Mask - S22 - S32
811  C-------    C-------  
812    
813        ENDIF        ENDIF
814          ENDIF
815    
816  C     S11 - S21  C     S11 - S21
817    
818           dist = ZTOF(1) - ZTOF(3)
819           dl = 0.
820           DO I=1,3
821           dl = dl + TLOUT(i)
822           ENDDO
823           F = dl/dist
824    
825        IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN        IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
826             t1 = tof11(1,tof11_i,itdc)
827             t2 = tof11(2,tof11_i,itdc)
828             t3 = tof21(1,tof21_i,itdc)
829             t4 = tof21(2,tof21_i,itdc)
830             IF ((t1.lt.4095).and.(t2.lt.4095).and.
831         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
832           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
833           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
834           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
835           ihelp=(tof11_i-1)*2+tof21_i           ihelp=(tof11_i-1)*2+tof21_i
836           c1 = k_S11S21(1,ihelp)           c1 = k_S11S21(1,ihelp)
837           c2 = k_S11S21(2,ihelp)           c2 = k_S11S21(2,ihelp)
838           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(9) = c2*F/(ds-c1)
      &   beta_a(9) = c2/(cos(theta12)*(ds-c1))  
839    
840  C------- ToF Mask - S11 - S21  C------- ToF Mask - S11 - S21
841    
# Line 695  C------- ToF Mask - S11 - S21 Line 852  C------- ToF Mask - S11 - S21
852  C-------    C-------  
853    
854        ENDIF        ENDIF
855          ENDIF
856                
857  C     S11 - S22  C     S11 - S22
858    
859           dist = ZTOF(1) - ZTOF(4)
860           dl = 0.
861           DO I=1,4
862           dl = dl + TLOUT(i)
863           ENDDO
864           F = dl/dist
865    
866        IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN        IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
867             t1 = tof11(1,tof11_i,itdc)
868             t2 = tof11(2,tof11_i,itdc)
869             t3 = tof22(1,tof22_i,itdc)
870             t4 = tof22(2,tof22_i,itdc)
871             IF ((t1.lt.4095).and.(t2.lt.4095).and.
872         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
873           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
874           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
875           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
876           ihelp=(tof11_i-1)*2+tof22_i           ihelp=(tof11_i-1)*2+tof22_i
877           c1 = k_S11S22(1,ihelp)           c1 = k_S11S22(1,ihelp)
878           c2 = k_S11S22(2,ihelp)           c2 = k_S11S22(2,ihelp)
879           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(10) = c2*F/(ds-c1)
      &   beta_a(10) = c2/(cos(theta12)*(ds-c1))  
880    
881  C------- ToF Mask - S11 - S22  C------- ToF Mask - S11 - S22
882    
# Line 722  C------- ToF Mask - S11 - S22 Line 893  C------- ToF Mask - S11 - S22
893  C-------  C-------
894    
895        ENDIF        ENDIF
896          ENDIF
897    
898  C     S12 - S21  C     S12 - S21
899    
900           dist = ZTOF(2) - ZTOF(3)
901           dl = 0.
902           DO I=2,3
903           dl = dl + TLOUT(i)
904           ENDDO
905           F = dl/dist
906    
907        IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN        IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
908             t1 = tof12(1,tof12_i,itdc)
909             t2 = tof12(2,tof12_i,itdc)
910             t3 = tof21(1,tof21_i,itdc)
911             t4 = tof21(2,tof21_i,itdc)
912             IF ((t1.lt.4095).and.(t2.lt.4095).and.
913         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
914           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
915           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
916           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
917           ihelp=(tof12_i-1)*2+tof21_i           ihelp=(tof12_i-1)*2+tof21_i
918           c1 = k_S12S21(1,ihelp)           c1 = k_S12S21(1,ihelp)
919           c2 = k_S12S21(2,ihelp)           c2 = k_S12S21(2,ihelp)
920           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(11) = c2*F/(ds-c1)
      &   beta_a(11) = c2/(cos(theta12)*(ds-c1))  
921    
922  C------- ToF Mask - S12 - S21  C------- ToF Mask - S12 - S21
923    
# Line 749  C------- ToF Mask - S12 - S21 Line 934  C------- ToF Mask - S12 - S21
934  C-------    C-------  
935    
936        ENDIF        ENDIF
937          ENDIF
938    
939  C     S12 - S22  C     S12 - S22
940    
941           dist = ZTOF(2) - ZTOF(4)
942           dl = 0.
943           DO I=2,4
944           dl = dl + TLOUT(i)
945           ENDDO
946           F = dl/dist
947    
948        IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN        IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
949             t1 = tof12(1,tof12_i,itdc)
950             t2 = tof12(2,tof12_i,itdc)
951             t3 = tof22(1,tof22_i,itdc)
952             t4 = tof22(2,tof22_i,itdc)
953             IF ((t1.lt.4095).and.(t2.lt.4095).and.
954         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
955           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
956           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
957           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
958           ihelp=(tof12_i-1)*2+tof22_i           ihelp=(tof12_i-1)*2+tof22_i
959           c1 = k_S12S22(1,ihelp)           c1 = k_S12S22(1,ihelp)
960           c2 = k_S12S22(2,ihelp)           c2 = k_S12S22(2,ihelp)
961           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(12) = c2*F/(ds-c1)
      &   beta_a(12) = c2/(cos(theta12)*(ds-c1))  
962    
963  C------- ToF Mask - S12 - S22  C------- ToF Mask - S12 - S22
964    
# Line 776  C------- ToF Mask - S12 - S22 Line 975  C------- ToF Mask - S12 - S22
975  C-------    C-------  
976    
977        ENDIF        ENDIF
978          ENDIF
979                
980  C-------  C-------
981    
# Line 798  C------- Line 998  C-------
998        if (icount.gt.0) beta_mean=sxw/sw        if (icount.gt.0) beta_mean=sxw/sw
999        beta_a(13) = beta_mean        beta_a(13) = beta_mean
1000    
1001    C      write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4)
1002    
1003        RETURN        RETURN
1004        END        END
1005    

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.23