/[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.1 by mocchiut, Sat Jun 17 12:14:56 2006 UTC revision 1.7 by pam-de, Wed Dec 6 07:21:32 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
49    
50    c      REAL theta12,theta13,theta23
51        REAL theta12,theta13,theta23        REAL theta13
52  C--   DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006  C--   DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
53        REAL tofarm12        REAL tofarm12
54        PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69        PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
# Line 54  C     Line 68  C    
68        REAL hmemor(9000000)        REAL hmemor(9000000)
69        INTEGER Iquest(100)        INTEGER Iquest(100)
70  C      C    
71          DATA ievent / 0 /
72    
73        COMMON / pawcd / hmemor        COMMON / pawcd / hmemor
74        save / pawcd /        save / pawcd /
75  C      C    
# Line 66  C     Line 82  C    
82    
83  *******************************************************************  *******************************************************************
84    
85          ievent = ievent +1
86    
87    
88        offset = 1        offset = 1
89        slope = 2        slope = 2
90        left = 1        left = 1
# Line 81  C     Line 100  C    
100           beta_a(i) = 100.           beta_a(i) = 100.
101        enddo        enddo
102    
103          do i=1,4
104             do j=1,12
105                adc_c(i,j) = 1000.
106             enddo
107          enddo
108    
109          do i=1,12
110             do j=1,4
111                tofmask(j,i) = 0
112             enddo
113          enddo
114    
115  C------ read  tracking routine  C------ read  tracking routine
116  *     igoodevent = igoodevent+1  *     igoodevent = igoodevent+1
117  *     assigned input  parameters for track routine  *     assigned input  parameters for track routine
# Line 93  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 124  C     COPY THE ALFA VECTOR FROM AL_PP TO
124        do i=1,5        do i=1,5
125           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
126        enddo        enddo
127    
128    c      write(*,*) AL_P
129    
130        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
131           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
132           GOTO 969           GOTO 969
133        ENDIF        ENDIF
134  *     -------- *** tracking routine *** --------  *     -------- *** tracking routine *** --------
135        IFAIL = 0        IFAIL = 0
136        call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)  C      call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
137          call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
138    
139    
140    C      write(*,*) (TLOUT(i),i=1,6)
141    
142        if(IFAIL.ne.0)then        if(IFAIL.ne.0)then
143           print *,' TOF - WARNING F77: tracking failed '           print *,' TOF - WARNING F77: tracking failed '
144           goto 969           goto 969
# Line 126  c  S22 2 paddles  15.0 x 9.0 cm Line 165  c  S22 2 paddles  15.0 x 9.0 cm
165  c  S31 3 paddles  15.0 x 6.0 cm  c  S31 3 paddles  15.0 x 6.0 cm
166  c  S32 3 paddles  18.0 x 5.0 cm  c  S32 3 paddles  18.0 x 5.0 cm
167    
168    c       write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)
169    c       write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)
170    
171  C--------------     S11 --------------------------------------  C--------------     S11 --------------------------------------
172    
# Line 229  C--------------     S32 ---------------- Line 270  C--------------     S32 ----------------
270        enddo        enddo
271        endif        endif
272    
273    
274    C      write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
275    
276    C------------------------------------------------------------------
277    C---  calculate track position in paddle using timing difference
278    C------------------------------------------------------------------
279    
280          do i=1,3
281             xtofpos(i)=100.
282             ytofpos(i)=100.
283          enddo
284    C-----------------------------S1 --------------------------------
285          
286          IF (tof11_i.GT.none_find) THEN
287             ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
288         +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
289          endif
290    
291          IF (tof12_i.GT.none_find) THEN
292             xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
293         +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
294          endif
295          
296          
297    C-----------------------------S2 --------------------------------
298          
299          IF (tof21_i.GT.none_find) THEN
300             xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
301         +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
302          endif
303          
304          IF (tof22_i.GT.none_find) THEN
305             ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
306         +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
307          endif
308          
309          
310    C-----------------------------S3 --------------------------------
311          
312          IF (tof31_i.GT.none_find) THEN
313             ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
314         +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
315          endif
316          
317          IF (tof32_i.GT.none_find) THEN
318             xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
319         +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
320          endif
321          
322          
323          do i=1,3
324             if (abs(xtofpos(i)).gt.100.) then
325                xtofpos(i)=101.
326             endif
327             if (abs(ytofpos(i)).gt.100.) then
328                ytofpos(i)=101.
329             endif
330          enddo
331          
332  C----------------------------------------------------------------------  C----------------------------------------------------------------------
333  C--------------------Corrections on ADC-data -------------------------  C--------------------Corrections on ADC-data -------------------------
334  C---------------------zenith angle theta  ---------------------------  C---------------------zenith angle theta  ---------------------------
# Line 260  C-----------------------------S1 ------- Line 360  C-----------------------------S1 -------
360           i = tof11_i           i = tof11_i
361           xdummy=tof11(left,i,iadc)           xdummy=tof11(left,i,iadc)
362           tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)           tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
363           if (tof11(left,i,iadc).lt.1000) then           if (tof11(left,i,iadc).lt.4095) then
364              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
365              xkorr0=adcx11(left,i,1)              xkorr0=adcx11(left,i,1)
366              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
367           endif           endif
368    
369           tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)           tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
370           if (tof11(right,i,iadc).lt.1000) then           if (tof11(right,i,iadc).lt.4095) then
371              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
372              xkorr0=adcx11(right,i,1)              xkorr0=adcx11(right,i,1)
373              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
# Line 280  C-----------------------------S1 ------- Line 380  C-----------------------------S1 -------
380    
381           i = tof12_i           i = tof12_i
382           tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)           tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
383           if (tof12(left,i,iadc).lt.1000) then           if (tof12(left,i,iadc).lt.4095) then
384              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
385              xkorr0=adcx12(left,i,1)              xkorr0=adcx12(left,i,1)
386              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
387           endif           endif
388    
389           tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)           tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
390           if (tof12(right,i,iadc).lt.1000) then           if (tof12(right,i,iadc).lt.4095) then
391              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
392              xkorr0=adcx12(right,i,1)              xkorr0=adcx12(right,i,1)
393              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
# Line 301  C-----------------------------S2 ------- Line 401  C-----------------------------S2 -------
401    
402           i = tof21_i           i = tof21_i
403           tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)           tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
404           if (tof21(left,i,iadc).lt.1000) then           if (tof21(left,i,iadc).lt.4095) then
405              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
406              xkorr0=adcx21(left,i,1)              xkorr0=adcx21(left,i,1)
407              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
408           endif           endif
409    
410           tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)           tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
411           if (tof21(right,i,iadc).lt.1000) then           if (tof21(right,i,iadc).lt.4095) then
412              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
413              xkorr0=adcx21(right,i,1)              xkorr0=adcx21(right,i,1)
414              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
# Line 320  C-----------------------------S2 ------- Line 420  C-----------------------------S2 -------
420    
421           i = tof22_i           i = tof22_i
422           tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)           tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
423           if (tof22(left,i,iadc).lt.1000) then           if (tof22(left,i,iadc).lt.4095) then
424              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
425              xkorr0=adcx22(left,i,1)              xkorr0=adcx22(left,i,1)
426              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
427           endif           endif
428    
429           tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)           tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
430           if (tof22(right,i,iadc).lt.1000) then           if (tof22(right,i,iadc).lt.4095) then
431              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
432              xkorr0=adcx22(right,i,1)              xkorr0=adcx22(right,i,1)
433              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
# Line 341  C-----------------------------S3 ------- Line 441  C-----------------------------S3 -------
441    
442           i = tof31_i           i = tof31_i
443           tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)           tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
444           if (tof31(left,i,iadc).lt.1000) then           if (tof31(left,i,iadc).lt.4095) then
445              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
446              xkorr0=adcx31(left,i,1)              xkorr0=adcx31(left,i,1)
447              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
448           endif           endif
449    
450           tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)           tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
451           if (tof31(right,i,iadc).lt.1000) then           if (tof31(right,i,iadc).lt.4095) then
452              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
453              xkorr0=adcx31(right,i,1)              xkorr0=adcx31(right,i,1)
454              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
# Line 360  C-----------------------------S3 ------- Line 460  C-----------------------------S3 -------
460    
461           i = tof32_i           i = tof32_i
462           tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)           tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
463           if (tof32(left,i,iadc).lt.1000) then           if (tof32(left,i,iadc).lt.4095) then
464              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
465              xkorr0=adcx32(left,i,1)              xkorr0=adcx32(left,i,1)
466              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
467           endif           endif
468    
469           tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)           tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
470           if (tof32(right,i,iadc).lt.1000) then           if (tof32(right,i,iadc).lt.4095) then
471              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
472              xkorr0=adcx32(right,i,1)              xkorr0=adcx32(right,i,1)
473              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
# Line 384  C     DS = c1 + c2/beta*cos(theta) Line 484  C     DS = c1 + c2/beta*cos(theta)
484  C     c2 = 2d/c   gives c2 = 2d/(c*TDCresolution)  TDC=50ps/channel  C     c2 = 2d/c   gives c2 = 2d/(c*TDCresolution)  TDC=50ps/channel
485  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
486  C     since TDC resolution varies slightly c2 has to be calibrated  C     since TDC resolution varies slightly c2 has to be calibrated
487    C     instead of cos(theta) use factor F:
488    C     F =  pathlength/d
489    C     => beta = c2*F/(DS-c1))
490    
491           dist = ZTOF(1) - ZTOF(5)
492           dl = 0.
493           DO I=1,5
494           dl = dl + TLOUT(i)
495           ENDDO
496           F = dl/dist
497    
498  C     S11 - S31  C     S11 - S31
499        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
500             t1 = tof11(1,tof11_i,itdc)
501             t2 = tof11(2,tof11_i,itdc)
502             t3 = tof31(1,tof31_i,itdc)
503             t4 = tof31(2,tof31_i,itdc)
504             IF ((t1.lt.4095).and.(t2.lt.4095).and.
505         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
506           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
507           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
508           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
509           ihelp=(tof11_i-1)*3+tof31_i           ihelp=(tof11_i-1)*3+tof31_i
510           c1 = k_S11S31(1,ihelp)           c1 = k_S11S31(1,ihelp)
511           c2 = k_S11S31(2,ihelp)                   c2 = k_S11S31(2,ihelp)        
512           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(1) = c2*F/(ds-c1)
513       &   beta_a(1) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
514    C------- ToF Mask - S11 - S31
515    
516             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
517         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
518             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
519         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
520    
521             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
522         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
523             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
524         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
525    
526          ENDIF
527        ENDIF        ENDIF
528    
529           dist = ZTOF(1) - ZTOF(6)
530           dl = 0.
531           DO I=1,6
532           dl = dl + TLOUT(i)
533           ENDDO
534           F = dl/dist
535                
536  C     S11 - S32  C     S11 - S32
537        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
538             t1 = tof11(1,tof11_i,itdc)
539             t2 = tof11(2,tof11_i,itdc)
540             t3 = tof32(1,tof32_i,itdc)
541             t4 = tof32(2,tof32_i,itdc)
542             IF ((t1.lt.4095).and.(t2.lt.4095).and.
543         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
544           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
545           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
546           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
547           ihelp=(tof11_i-1)*3+tof32_i           ihelp=(tof11_i-1)*3+tof32_i
548           c1 = k_S11S32(1,ihelp)           c1 = k_S11S32(1,ihelp)
549           c2 = k_S11S32(2,ihelp)                   c2 = k_S11S32(2,ihelp)        
550           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(2) = c2*F/(ds-c1)
551       &   beta_a(2) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
552    
553    C------- ToF Mask - S11 - S32
554    
555             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
556         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
557             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
558         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
559    
560             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
561         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
562             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
563         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
564    
565    C-------          
566    
567          ENDIF
568        ENDIF        ENDIF
569    
570  C     S12 - S31  C     S12 - S31
571           dist = ZTOF(2) - ZTOF(5)
572           dl = 0.
573           DO I=2,5
574           dl = dl + TLOUT(i)
575           ENDDO
576           F = dl/dist
577    
578        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
579             t1 = tof12(1,tof12_i,itdc)
580             t2 = tof12(2,tof12_i,itdc)
581             t3 = tof31(1,tof31_i,itdc)
582             t4 = tof31(2,tof31_i,itdc)
583             IF ((t1.lt.4095).and.(t2.lt.4095).and.
584         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
585           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
586           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
587           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
588           ihelp=(tof12_i-1)*3+tof31_i           ihelp=(tof12_i-1)*3+tof31_i
589           c1 = k_S12S31(1,ihelp)           c1 = k_S12S31(1,ihelp)
590           c2 = k_S12S31(2,ihelp)           c2 = k_S12S31(2,ihelp)
591           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(3) = c2*F/(ds-c1)
592       &   beta_a(3) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
593    
594    C------- ToF Mask - S12 - S31
595    
596             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
597         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
598             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
599         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
600    
601             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
602         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
603             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
604         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
605    
606    C-------
607    
608          ENDIF
609        ENDIF        ENDIF
610    
611  C     S12 - S32  C     S12 - S32
612    
613           dist = ZTOF(2) - ZTOF(6)
614           dl = 0.
615           DO I=2,6
616           dl = dl + TLOUT(i)
617           ENDDO
618           F = dl/dist
619    
620        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
621             t1 = tof12(1,tof12_i,itdc)
622             t2 = tof12(2,tof12_i,itdc)
623             t3 = tof32(1,tof32_i,itdc)
624             t4 = tof32(2,tof32_i,itdc)
625             IF ((t1.lt.4095).and.(t2.lt.4095).and.
626         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
627           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
628           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
629           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
630           ihelp=(tof12_i-1)*3+tof32_i           ihelp=(tof12_i-1)*3+tof32_i
631           c1 = k_S12S32(1,ihelp)           c1 = k_S12S32(1,ihelp)
632           c2 = k_S12S32(2,ihelp)           c2 = k_S12S32(2,ihelp)
633           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(4) = c2*F/(ds-c1)
634       &   beta_a(4) = c2/(cos(theta13)*(ds-c1))  C         write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
635    
636    C------- ToF Mask - S12 - S32
637    
638             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
639         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
640             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
641         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
642    
643             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
644         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
645             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
646         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
647    
648    C-------
649    
650          ENDIF
651        ENDIF        ENDIF
652    
653  C     S21 - S31  C     S21 - S31
654    
655           dist = ZTOF(3) - ZTOF(5)
656           dl = 0.
657           DO I=3,5
658           dl = dl + TLOUT(i)
659           ENDDO
660           F = dl/dist
661    
662        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
663             t1 = tof21(1,tof21_i,itdc)
664             t2 = tof21(2,tof21_i,itdc)
665             t3 = tof31(1,tof31_i,itdc)
666             t4 = tof31(2,tof31_i,itdc)
667             IF ((t1.lt.4095).and.(t2.lt.4095).and.
668         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
669           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
670           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
671           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
672           ihelp=(tof21_i-1)*3+tof31_i           ihelp=(tof21_i-1)*3+tof31_i
673           c1 = k_S21S31(1,ihelp)           c1 = k_S21S31(1,ihelp)
674           c2 = k_S21S31(2,ihelp)           c2 = k_S21S31(2,ihelp)
675           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(5) = c2*F/(ds-c1)
676       &   beta_a(5) = c2/(cos(theta23)*(ds-c1))  
677    C------- ToF Mask - S21 - S31
678    
679             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
680         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
681             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
682         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
683    
684             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
685         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
686             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
687         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
688    
689    C-------
690    
691          ENDIF
692        ENDIF        ENDIF
693    
694  C     S21 - S32  C     S21 - S32
695    
696           dist = ZTOF(3) - ZTOF(6)
697           dl = 0.
698           DO I=3,6
699           dl = dl + TLOUT(i)
700           ENDDO
701           F = dl/dist
702    
703        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
704             t1 = tof21(1,tof21_i,itdc)
705             t2 = tof21(2,tof21_i,itdc)
706             t3 = tof32(1,tof32_i,itdc)
707             t4 = tof32(2,tof32_i,itdc)
708             IF ((t1.lt.4095).and.(t2.lt.4095).and.
709         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
710           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
711           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
712           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
713           ihelp=(tof21_i-1)*3+tof32_i           ihelp=(tof21_i-1)*3+tof32_i
714           c1 = k_S21S32(1,ihelp)           c1 = k_S21S32(1,ihelp)
715           c2 = k_S21S32(2,ihelp)           c2 = k_S21S32(2,ihelp)
716           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(6) = c2*F/(ds-c1)
717       &   beta_a(6) = c2/(cos(theta23)*(ds-c1))  
718    C------- ToF Mask - S21 - S32
719    
720             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
721         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
722             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
723         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
724    
725             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
726         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
727             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
728         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
729    
730    C-------
731    
732          ENDIF
733        ENDIF        ENDIF
734    
735  C     S22 - S31  C     S22 - S31
736    
737           dist = ZTOF(4) - ZTOF(5)
738           dl = 0.
739           DO I=4,5
740           dl = dl + TLOUT(i)
741           ENDDO
742           F = dl/dist
743    
744        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
745             t1 = tof22(1,tof22_i,itdc)
746             t2 = tof22(2,tof22_i,itdc)
747             t3 = tof31(1,tof31_i,itdc)
748             t4 = tof31(2,tof31_i,itdc)
749             IF ((t1.lt.4095).and.(t2.lt.4095).and.
750         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
751           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
752           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
753           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
754           ihelp=(tof22_i-1)*3+tof31_i           ihelp=(tof22_i-1)*3+tof31_i
755           c1 = k_S22S31(1,ihelp)           c1 = k_S22S31(1,ihelp)
756           c2 = k_S22S31(2,ihelp)           c2 = k_S22S31(2,ihelp)
757           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(7) = c2*F/(ds-c1)
758       &   beta_a(7) = c2/(cos(theta13)*(ds-c1))  
759    C------- ToF Mask - S22 - S31
760    
761             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
762         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
763             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
764         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
765    
766             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
767         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
768             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
769         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
770    
771    C-------  
772    
773          ENDIF
774        ENDIF        ENDIF
775                
776  C     S22 - S32  C     S22 - S32
777    
778           dist = ZTOF(4) - ZTOF(6)
779           dl = 0.
780           DO I=4,6
781           dl = dl + TLOUT(i)
782           ENDDO
783           F = dl/dist
784    
785        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
786             t1 = tof22(1,tof22_i,itdc)
787             t2 = tof22(2,tof22_i,itdc)
788             t3 = tof32(1,tof32_i,itdc)
789             t4 = tof32(2,tof32_i,itdc)
790             IF ((t1.lt.4095).and.(t2.lt.4095).and.
791         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
792           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
793           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
794           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
795           ihelp=(tof22_i-1)*3+tof32_i           ihelp=(tof22_i-1)*3+tof32_i
796           c1 = k_S22S32(1,ihelp)           c1 = k_S22S32(1,ihelp)
797           c2 = k_S22S32(2,ihelp)           c2 = k_S22S32(2,ihelp)
798           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(8) = c2*F/(ds-c1)
799       &   beta_a(8) = c2/(cos(theta13)*(ds-c1))  
800    C------- ToF Mask - S22 - S32
801    
802             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
803         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
804             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
805         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
806    
807             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
808         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
809             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
810         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
811    
812    C-------  
813    
814          ENDIF
815        ENDIF        ENDIF
816    
817  C     S11 - S21  C     S11 - S21
818    
819           dist = ZTOF(1) - ZTOF(3)
820           dl = 0.
821           DO I=1,3
822           dl = dl + TLOUT(i)
823           ENDDO
824           F = dl/dist
825    
826        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
827             t1 = tof11(1,tof11_i,itdc)
828             t2 = tof11(2,tof11_i,itdc)
829             t3 = tof21(1,tof21_i,itdc)
830             t4 = tof21(2,tof21_i,itdc)
831             IF ((t1.lt.4095).and.(t2.lt.4095).and.
832         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
833           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
834           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
835           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
836           ihelp=(tof11_i-1)*2+tof21_i           ihelp=(tof11_i-1)*2+tof21_i
837           c1 = k_S11S21(1,ihelp)           c1 = k_S11S21(1,ihelp)
838           c2 = k_S11S21(2,ihelp)           c2 = k_S11S21(2,ihelp)
839           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(9) = c2*F/(ds-c1)
840       &   beta_a(9) = c2/(cos(theta12)*(ds-c1))  
841    C------- ToF Mask - S11 - S21
842    
843             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
844         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
845             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
846         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
847    
848             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
849         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
850             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
851         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
852    
853    C-------  
854    
855          ENDIF
856        ENDIF        ENDIF
857                
858  C     S11 - S22  C     S11 - S22
859    
860           dist = ZTOF(1) - ZTOF(4)
861           dl = 0.
862           DO I=1,4
863           dl = dl + TLOUT(i)
864           ENDDO
865           F = dl/dist
866    
867        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
868             t1 = tof11(1,tof11_i,itdc)
869             t2 = tof11(2,tof11_i,itdc)
870             t3 = tof22(1,tof22_i,itdc)
871             t4 = tof22(2,tof22_i,itdc)
872             IF ((t1.lt.4095).and.(t2.lt.4095).and.
873         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
874           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
875           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
876           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
877           ihelp=(tof11_i-1)*2+tof22_i           ihelp=(tof11_i-1)*2+tof22_i
878           c1 = k_S11S22(1,ihelp)           c1 = k_S11S22(1,ihelp)
879           c2 = k_S11S22(2,ihelp)           c2 = k_S11S22(2,ihelp)
880           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(10) = c2*F/(ds-c1)
881       &   beta_a(10) = c2/(cos(theta12)*(ds-c1))  
882    C------- ToF Mask - S11 - S22
883    
884             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
885         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
886             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
887         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
888    
889             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
890         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
891             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
892         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
893    
894    C-------
895    
896          ENDIF
897        ENDIF        ENDIF
898    
899  C     S12 - S21  C     S12 - S21
900    
901           dist = ZTOF(2) - ZTOF(3)
902           dl = 0.
903           DO I=2,3
904           dl = dl + TLOUT(i)
905           ENDDO
906           F = dl/dist
907    
908        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
909             t1 = tof12(1,tof12_i,itdc)
910             t2 = tof12(2,tof12_i,itdc)
911             t3 = tof21(1,tof21_i,itdc)
912             t4 = tof21(2,tof21_i,itdc)
913             IF ((t1.lt.4095).and.(t2.lt.4095).and.
914         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
915           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
916           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
917           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
918           ihelp=(tof12_i-1)*2+tof21_i           ihelp=(tof12_i-1)*2+tof21_i
919           c1 = k_S12S21(1,ihelp)           c1 = k_S12S21(1,ihelp)
920           c2 = k_S12S21(2,ihelp)           c2 = k_S12S21(2,ihelp)
921           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(11) = c2*F/(ds-c1)
922       &   beta_a(11) = c2/(cos(theta12)*(ds-c1))  
923    C------- ToF Mask - S12 - S21
924    
925             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
926         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
927             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
928         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
929    
930             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
931         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
932             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
933         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
934    
935    C-------  
936    
937          ENDIF
938        ENDIF        ENDIF
939    
940  C     S12 - S22  C     S12 - S22
941    
942           dist = ZTOF(2) - ZTOF(4)
943           dl = 0.
944           DO I=2,4
945           dl = dl + TLOUT(i)
946           ENDDO
947           F = dl/dist
948    
949        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
950             t1 = tof12(1,tof12_i,itdc)
951             t2 = tof12(2,tof12_i,itdc)
952             t3 = tof22(1,tof22_i,itdc)
953             t4 = tof22(2,tof22_i,itdc)
954             IF ((t1.lt.4095).and.(t2.lt.4095).and.
955         &                    (t3.lt.4095).and.(t4.lt.4095)) THEN
956           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
957           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
958           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
959           ihelp=(tof12_i-1)*2+tof22_i           ihelp=(tof12_i-1)*2+tof22_i
960           c1 = k_S12S22(1,ihelp)           c1 = k_S12S22(1,ihelp)
961           c2 = k_S12S22(2,ihelp)           c2 = k_S12S22(2,ihelp)
962           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           beta_a(12) = c2*F/(ds-c1)
963       &   beta_a(12) = c2/(cos(theta12)*(ds-c1))  
964    C------- ToF Mask - S12 - S22
965    
966             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
967         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
968             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
969         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
970    
971             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
972         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
973             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
974         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
975    
976    C-------  
977    
978          ENDIF
979        ENDIF        ENDIF
980                
981  C-------  C-------
# Line 550  C------- Line 999  C-------
999        if (icount.gt.0) beta_mean=sxw/sw        if (icount.gt.0) beta_mean=sxw/sw
1000        beta_a(13) = beta_mean        beta_a(13) = beta_mean
1001    
1002    C      write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4)
1003    
1004        RETURN        RETURN
1005        END        END
1006    

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.7

  ViewVC Help
Powered by ViewVC 1.1.23