/[PAMELA software]/DarthVader/ToFLevel2/src/tofl2com.for
ViewVC logotype

Diff of /DarthVader/ToFLevel2/src/tofl2com.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.6 by mocchiut, Mon Apr 30 15:46:30 2007 UTC
# Line 1  Line 1 
1  *****************************************************************************  
2    ******************************************************************************
3    *
4    *  08-12-06 WM: adc_c-bug :  The raw ADc value was multiplied with cos(theta)
5    *  and AFTER that there was an if statement "if tof32(right,i,iadc) < 4095"
6    *
7    *  jan-07 GF: ADCflags(4,12) inserted to flag artificial ADC values
8    *  jan-07 WM: artificial ADC values created using attenuation calibration
9    *  jan-07 WM: modified xtofpos flag "101". xtofpos must be inside physical
10    *             dimension of the paddle +/- 10 cm
11    *  jan-07 WM: if xtofpos=101 then this paddle is not used for beta
12    *             calculation
13    *  jan-07 WM: the definition for a "hit" is changed: Now we must have a
14    *             valid TDC signal on both sides
15    *  jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift
16    *  jan-07 WM: bug removed: in some cases tdc_tw was calculated due to a
17    *             leftover "xhelp" value
18    *  apr-07 WM: attenuation fit curve is now a double exponential fit
19    *             conversion from raw ADC to pC using calibration function
20    *             variables xtr_tof and ytr_tof inserted (filled with default)
21    ******************************************************************************
22    
23        INTEGER FUNCTION TOFL2COM()        INTEGER FUNCTION TOFL2COM()
24  c      c    
25        IMPLICIT NONE        IMPLICIT NONE
# Line 17  C     Line 38  C    
38        REAL xhelp_a,xhelp_t        REAL xhelp_a,xhelp_t
39    
40        REAL dx,dy,dr,ds        REAL dx,dy,dr,ds
41        REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
42        REAL c1,c2,sw,sxw,w_i        REAL c1,c2,sw,sxw,w_i
43        INTEGER icount        INTEGER icount
44    
45    c      REAL xdummy
46    
47        INTEGER tof11_j,tof21_j,tof31_j        INTEGER tof11_j,tof21_j,tof31_j
48        INTEGER tof12_j,tof22_j,tof32_j        INTEGER tof12_j,tof22_j,tof32_j
49    
# Line 35  c     second index : 1... number of padd Line 58  c     second index : 1... number of padd
58        INTEGER tof31_event(2,3),tof32_event(2,3)        INTEGER tof31_event(2,3),tof32_event(2,3)
59    
60                
61        REAL theta12,theta13,theta23        REAL theta13
62  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
63        REAL tofarm12        REAL tofarm12
64        PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69        PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
# Line 43  C--   DATA ZTOF/53.74,53.04,23.94,23.44, Line 66  C--   DATA ZTOF/53.74,53.04,23.94,23.44,
66        PARAMETER (tofarm23 = 47.61)  ! from 23.69 to -23.92        PARAMETER (tofarm23 = 47.61)  ! from 23.69 to -23.92
67        REAL tofarm13        REAL tofarm13
68        PARAMETER (tofarm13 = 77.31)  ! from 53.39 to -23.92        PARAMETER (tofarm13 = 77.31)  ! from 53.39 to -23.92
69          
70          REAL hepratio      
71    
72        INTEGER ihelp        INTEGER ihelp
73        REAL xkorr        REAL xkorr
74    
75          real atten,pc_adc
76    
77  C---------------------------------------  C---------------------------------------
78  C      C    
79  C     Begin !  C     Begin !
# Line 63  C     Line 89  C    
89  *     amplitude has to be 'secure' higher than pedestal for an adc event  *     amplitude has to be 'secure' higher than pedestal for an adc event
90        secure = 2.        secure = 2.
91    
92    C     ratio between helium and proton ca. 4
93          hepratio = 4.  !
94        offset = 1        offset = 1
95        slope = 2        slope = 2
96        left = 1        left = 1
# Line 92  C     Line 120  C    
120        enddo        enddo
121    
122    
123          do i=1,12
124             do j=1,4
125                tofmask(j,i) = 0
126             enddo
127          enddo
128    
129    
130    c gf adc falg:
131          do i=1,4
132             do j=1,12
133                adcflagtof(i,j) = 0
134             enddo
135          enddo
136    
137    c gf tdc falg:
138          do i=1,4
139             do j=1,12
140                tdcflagtof(i,j) = 0
141             enddo
142          enddo
143    
144    
145    C---  Fill xtr_tof and ytr_tof: positions from tracker at ToF layers
146    C---  since this is standalone ToF fill with default values
147          do j=1,6
148          xtr_tof(j) = 101.
149          ytr_tof(j) = 101.
150          enddo
151    
152  c the calibration files are read in the main program from xxx_tofcalib.rz  c the calibration files are read in the main program from xxx_tofcalib.rz
153    
154    
155  c-------------------------get ToF data --------------------------------  c-------------------------get ToF data --------------------------------
156    
157  c     put the adc and tdc values from ntuple into tofxx(i,j,k) variables  c     put the adc and tdc values from ntuple into tofxx(i,j,k) variables
158    c     adc valueas are then pC
159    
160        do j=1,8        do j=1,8
161           tof11(1,j,2) = adc(ch11a(j),hb11a(j))           tof11(1,j,2) = pc_adc(adc(ch11a(j),hb11a(j)))
162           tof11(2,j,2) = adc(ch11b(j),hb11b(j))           tof11(2,j,2) = pc_adc(adc(ch11b(j),hb11b(j)))
163           tof11(1,j,1) = tdc(ch11a(j),hb11a(j))           tof11(1,j,1) = (tdc(ch11a(j),hb11a(j)))
164           tof11(2,j,1) = tdc(ch11b(j),hb11b(j))           tof11(2,j,1) = (tdc(ch11b(j),hb11b(j)))
165        enddo        enddo
166    
167    
168        do j=1,6        do j=1,6
169           tof12(1,j,2) = adc(ch12a(j),hb12a(j))           tof12(1,j,2) = pc_adc(adc(ch12a(j),hb12a(j)))
170           tof12(2,j,2) = adc(ch12b(j),hb12b(j))           tof12(2,j,2) = pc_adc(adc(ch12b(j),hb12b(j)))
171           tof12(1,j,1) = tdc(ch12a(j),hb12a(j))           tof12(1,j,1) = (tdc(ch12a(j),hb12a(j)))
172           tof12(2,j,1) = tdc(ch12b(j),hb12b(j))           tof12(2,j,1) = (tdc(ch12b(j),hb12b(j)))
173        enddo        enddo
174    
175        do j=1,2        do j=1,2
176           tof21(1,j,2) = adc(ch21a(j),hb21a(j))           tof21(1,j,2) = pc_adc(adc(ch21a(j),hb21a(j)))
177           tof21(2,j,2) = adc(ch21b(j),hb21b(j))           tof21(2,j,2) = pc_adc(adc(ch21b(j),hb21b(j)))
178           tof21(1,j,1) = tdc(ch21a(j),hb21a(j))           tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
179           tof21(2,j,1) = tdc(ch21b(j),hb21b(j))           tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
180        enddo        enddo
181    
182        do j=1,2        do j=1,2
183           tof22(1,j,2) = adc(ch22a(j),hb22a(j))           tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
184           tof22(2,j,2) = adc(ch22b(j),hb22b(j))           tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))
185           tof22(1,j,1) = tdc(ch22a(j),hb22a(j))           tof22(1,j,1) = (tdc(ch22a(j),hb22a(j)))
186           tof22(2,j,1) = tdc(ch22b(j),hb22b(j))           tof22(2,j,1) = (tdc(ch22b(j),hb22b(j)))
187        enddo        enddo
188    
189        do j=1,3        do j=1,3
190           tof31(1,j,2) = adc(ch31a(j),hb31a(j))           tof31(1,j,2) = pc_adc(adc(ch31a(j),hb31a(j)))
191           tof31(2,j,2) = adc(ch31b(j),hb31b(j))           tof31(2,j,2) = pc_adc(adc(ch31b(j),hb31b(j)))
192           tof31(1,j,1) = tdc(ch31a(j),hb31a(j))           tof31(1,j,1) = (tdc(ch31a(j),hb31a(j)))
193           tof31(2,j,1) = tdc(ch31b(j),hb31b(j))           tof31(2,j,1) = (tdc(ch31b(j),hb31b(j)))
194        enddo        enddo
195    
196        do j=1,3        do j=1,3
197           tof32(1,j,2) = adc(ch32a(j),hb32a(j))           tof32(1,j,2) = pc_adc(adc(ch32a(j),hb32a(j)))
198           tof32(2,j,2) = adc(ch32b(j),hb32b(j))           tof32(2,j,2) = pc_adc(adc(ch32b(j),hb32b(j)))
199           tof32(1,j,1) = tdc(ch32a(j),hb32a(j))           tof32(1,j,1) = (tdc(ch32a(j),hb32a(j)))
200           tof32(2,j,1) = tdc(ch32b(j),hb32b(j))           tof32(2,j,1) = (tdc(ch32b(j),hb32b(j)))
201        enddo        enddo
202    
203  C----------------------------------------------------------------------  C----------------------------------------------------------------------
# Line 188  C--------------------------------------- Line 245  C---------------------------------------
245           if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.           if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
246        ENDDO        ENDDO
247    
248    C----------------------------------------------------------------------
249    C------------------  set ADC & TDC flag = 0    ------------------------
250    C----------------------------------------------------------------------
251    
252          do j=1,8
253          if (adc(ch11a(j),hb11a(j)).LT.4096)adcflagtof(ch11a(j),hb11a(j))=0
254          if (adc(ch11b(j),hb11b(j)).LT.4096)adcflagtof(ch11b(j),hb11b(j))=0
255          if (tdc(ch11a(j),hb11a(j)).LT.4096)tdcflagtof(ch11a(j),hb11a(j))=0
256          if (tdc(ch11b(j),hb11b(j)).LT.4096)tdcflagtof(ch11b(j),hb11b(j))=0
257          enddo
258          do j=1,6
259          if (adc(ch12a(j),hb12a(j)).LT.4096)adcflagtof(ch12a(j),hb12a(j))=0
260          if (adc(ch12b(j),hb12b(j)).LT.4096)adcflagtof(ch12b(j),hb12b(j))=0
261          if (tdc(ch12a(j),hb12a(j)).LT.4096)tdcflagtof(ch12a(j),hb12a(j))=0
262          if (tdc(ch12b(j),hb12b(j)).LT.4096)tdcflagtof(ch12b(j),hb12b(j))=0
263          enddo
264          do j=1,2
265          if (adc(ch21a(j),hb21a(j)).LT.4096)adcflagtof(ch21a(j),hb21a(j))=0
266          if (adc(ch21b(j),hb21b(j)).LT.4096)adcflagtof(ch21b(j),hb21b(j))=0
267          if (tdc(ch21a(j),hb21a(j)).LT.4096)tdcflagtof(ch21a(j),hb21a(j))=0
268          if (tdc(ch21b(j),hb21b(j)).LT.4096)tdcflagtof(ch21b(j),hb21b(j))=0
269          enddo
270          do j=1,2
271          if (adc(ch22a(j),hb22a(j)).LT.4096)adcflagtof(ch22a(j),hb22a(j))=0
272          if (adc(ch22b(j),hb22b(j)).LT.4096)adcflagtof(ch22b(j),hb22b(j))=0
273          if (tdc(ch22a(j),hb22a(j)).LT.4096)tdcflagtof(ch22a(j),hb22a(j))=0
274          if (tdc(ch22b(j),hb22b(j)).LT.4096)tdcflagtof(ch22b(j),hb22b(j))=0
275          enddo
276          do j=1,3
277          if (adc(ch31a(j),hb31a(j)).LT.4096)adcflagtof(ch31a(j),hb31a(j))=0
278          if (adc(ch31b(j),hb31b(j)).LT.4096)adcflagtof(ch31b(j),hb31b(j))=0
279          if (tdc(ch31a(j),hb31a(j)).LT.4096)tdcflagtof(ch31a(j),hb31a(j))=0
280          if (tdc(ch31b(j),hb31b(j)).LT.4096)tdcflagtof(ch31b(j),hb31b(j))=0
281          enddo
282          do j=1,3
283          if (adc(ch32a(j),hb32a(j)).LT.4096)adcflagtof(ch32a(j),hb32a(j))=0
284          if (adc(ch32b(j),hb32b(j)).LT.4096)adcflagtof(ch32b(j),hb32b(j))=0
285          if (tdc(ch32a(j),hb32a(j)).LT.4096)tdcflagtof(ch32a(j),hb32a(j))=0
286          if (tdc(ch32b(j),hb32b(j)).LT.4096)tdcflagtof(ch32b(j),hb32b(j))=0
287          enddo
288    
289    C----------------------------------------------------------------
290    C---------- Check PMTs 10 and 35 for strange TDC values----------
291    C----------------------------------------------------------------
292    
293    C---- S116A TDC=819
294           if (tof11(1,6,1).EQ.819) then
295                 tof11(1,6,1) = 4095
296                 tdcflagtof(ch11a(6),hb11a(6))=2
297           endif
298      
299    C---- S222B TDC=819
300           if (tof22(2,2,1).EQ.819) then
301                 tof22(2,2,1) = 4095
302                 tdcflagtof(ch22b(2),hb22b(2))=2
303           endif
304    
305  C----------------------------------------------------------------  C----------------------------------------------------------------
306  C------------Check Paddles for hits  -----------------------  C------------   Check Paddles for hits    -----------------------
307    C------  a "hit" means TDC values<4095 on both sides ------------
308  C----------------------------------------------------------------  C----------------------------------------------------------------
309    
310  C     upper tof  S11  C     upper tof  S11
# Line 199  C     upper tof  S11 Line 314  C     upper tof  S11
314              tof11_event(j,i) = none_ev              tof11_event(j,i) = none_ev
315              IF ((tof11(j,i,itdc).LT.2000).AND.(tof11(j,i,itdc).GT.100))              IF ((tof11(j,i,itdc).LT.2000).AND.(tof11(j,i,itdc).GT.100))
316       +           tof11_event(j,i) = tof11_event(j,i) + tdc_ev       +           tof11_event(j,i) = tof11_event(j,i) + tdc_ev
             IF ((tof11(j,i,iadc).GT.secure).AND.  
      +           (tof11(j,i,iadc).LT.4095))  
      +           tof11_event(j,i) = tof11_event(j,i) + adc_ev  
317           ENDDO           ENDDO
318        ENDDO        ENDDO
319    
# Line 232  C     upper tof  S12 Line 344  C     upper tof  S12
344              tof12_event(j,i) = none_ev              tof12_event(j,i) = none_ev
345              IF ((tof12(j,i,itdc).LT.2000).AND.(tof12(j,i,itdc).GT.100))              IF ((tof12(j,i,itdc).LT.2000).AND.(tof12(j,i,itdc).GT.100))
346       +           tof12_event(j,i) = tof12_event(j,i) + tdc_ev       +           tof12_event(j,i) = tof12_event(j,i) + tdc_ev
             IF ((tof12(j,i,iadc).GT.secure).AND.  
      +           (tof12(j,i,iadc).LT.4095))  
      +           tof12_event(j,i) = tof12_event(j,i) + adc_ev  
347           ENDDO           ENDDO
348        ENDDO        ENDDO
349    
# Line 265  C     middle tof  S21 Line 374  C     middle tof  S21
374              tof21_event(j,i) = none_ev              tof21_event(j,i) = none_ev
375              IF ((tof21(j,i,itdc).LT.2000).AND.(tof21(j,i,itdc).GT.100))              IF ((tof21(j,i,itdc).LT.2000).AND.(tof21(j,i,itdc).GT.100))
376       +           tof21_event(j,i) = tof21_event(j,i) + tdc_ev       +           tof21_event(j,i) = tof21_event(j,i) + tdc_ev
             IF ((tof21(j,i,iadc).GT.secure).AND.  
      +           (tof21(j,i,iadc).LT.4095))  
      +           tof21_event(j,i) = tof21_event(j,i) + adc_ev  
377           ENDDO           ENDDO
378        ENDDO        ENDDO
379    
# Line 297  C     middle tof  S22 Line 403  C     middle tof  S22
403              tof22_event(j,i) = none_ev              tof22_event(j,i) = none_ev
404              IF ((tof22(j,i,itdc).LT.2000).AND.(tof22(j,i,itdc).GT.100))              IF ((tof22(j,i,itdc).LT.2000).AND.(tof22(j,i,itdc).GT.100))
405       +           tof22_event(j,i) = tof22_event(j,i) + tdc_ev       +           tof22_event(j,i) = tof22_event(j,i) + tdc_ev
             IF ((tof22(j,i,iadc).GT.secure).AND.  
      +           (tof22(j,i,iadc).LT.4095))  
      +           tof22_event(j,i) = tof22_event(j,i) + adc_ev  
406           ENDDO           ENDDO
407        ENDDO        ENDDO
408    
# Line 330  C     bottom tof  S31 Line 433  C     bottom tof  S31
433              tof31_event(j,i) = none_ev              tof31_event(j,i) = none_ev
434              IF ((tof31(j,i,itdc).LT.2000).AND.(tof31(j,i,itdc).GT.100))              IF ((tof31(j,i,itdc).LT.2000).AND.(tof31(j,i,itdc).GT.100))
435       +           tof31_event(j,i) = tof31_event(j,i) + tdc_ev       +           tof31_event(j,i) = tof31_event(j,i) + tdc_ev
             IF ((tof31(j,i,iadc).GT.secure).AND.  
      +           (tof31(j,i,iadc).LT.4095))  
      +           tof31_event(j,i) = tof31_event(j,i) + adc_ev  
436           ENDDO           ENDDO
437        ENDDO        ENDDO
438    
# Line 362  C     bottom tof  S32 Line 462  C     bottom tof  S32
462              tof32_event(j,i) = none_ev              tof32_event(j,i) = none_ev
463              IF ((tof32(j,i,itdc).LT.2000).AND.(tof32(j,i,itdc).GT.100))              IF ((tof32(j,i,itdc).LT.2000).AND.(tof32(j,i,itdc).GT.100))
464       +           tof32_event(j,i) = tof32_event(j,i) + tdc_ev       +           tof32_event(j,i) = tof32_event(j,i) + tdc_ev
             IF ((tof32(j,i,iadc).GT.secure).AND.  
      +           (tof32(j,i,iadc).LT.4095))  
      +           tof32_event(j,i) = tof32_event(j,i) + adc_ev  
465           ENDDO           ENDDO
466        ENDDO        ENDDO
467    
# Line 407  c     check if an other paddle has also Line 504  c     check if an other paddle has also
504        tof_j_flag(5)=tof31_j        tof_j_flag(5)=tof31_j
505        tof_j_flag(6)=tof32_j        tof_j_flag(6)=tof32_j
506    
507            
508    C------------------------------------------------------------------
509    C---  calculate track position in paddle using timing difference
510    C------------------------------------------------------------------
511    
512          do i=1,3
513             xtofpos(i)=100.
514             ytofpos(i)=100.
515          enddo
516    C-----------------------------S1 --------------------------------
517    
518          IF (tof11_i.GT.none_find) THEN
519             ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
520         +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
521          endif
522    
523          IF (tof12_i.GT.none_find) THEN
524             xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
525         +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
526          endif
527    
528    
529    C-----------------------------S2 --------------------------------
530    
531          IF (tof21_i.GT.none_find) THEN
532             xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
533         +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
534          endif
535    
536          IF (tof22_i.GT.none_find) THEN
537             ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
538         +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
539          endif
540          
541    
542    C-----------------------------S3 --------------------------------
543    
544          IF (tof31_i.GT.none_find) THEN
545             ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
546         +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
547          endif
548    
549          IF (tof32_i.GT.none_find) THEN
550             xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
551         +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
552          endif
553    
554    
555    c      do i=1,3
556    c         if (abs(xtofpos(i)).gt.100.) then
557    c            xtofpos(i)=101.
558    c         endif
559    c         if (abs(ytofpos(i)).gt.100.) then
560    c            ytofpos(i)=101.
561    c         endif
562    c      enddo
563    
564    C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
565    C--  this cut is now stronger than in the old versions
566    
567            if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
568            if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
569            if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
570    
571            if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
572            if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
573            if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
574    
575    
576    C----------------------------------------------------------------------
577    C---------------------  zenith angle theta  ---------------------------
578    C----------------------------------------------------------------------
579    
580          dx=0.
581          dy=0.
582          dr=0.
583          theta13 = 0.
584    
585             IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find))
586         &        dx  = xtofpos(1) - xtofpos(3)
587             IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find))
588         &        dy  = ytofpos(1) - ytofpos(3)
589             dr = sqrt(dx*dx+dy*dy)
590             theta13 = atan(dr/tofarm13)
591    
592    C------------------------------------------------------------------
593    c      dx=0.
594    c      dy=0.
595    c      dr=0.
596    c      theta12 = 0.
597    c
598    c         IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find))
599    c     &        dx  = xtofpos(1) - xtofpos(2)
600    c         IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find))
601    c     &        dy  = ytofpos(1) - ytofpos(2)
602    c         dr = sqrt(dx*dx+dy*dy)
603    c         theta12 = atan(dr/tofarm12)
604    c        
605    c      dx=0.
606    c      dy=0.
607    c      dr=0.
608    c      theta23 = 0.
609    c
610    c         IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find))
611    c     &        dx  = xtofpos(2) - xtofpos(3)
612    c         IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find))
613    c     &        dy  = ytofpos(2) - ytofpos(3)
614    c         dr = sqrt(dx*dx+dy*dy)
615    c         theta23 = atan(dr/tofarm23)
616    c        
617    C---------------------------------------------------------------------
618    
619    
620    C--------------------------------------------------------------------
621    C---- if TDCleft.and.TDCright and NO ADC insert artificial ADC
622    C---- values
623    C--------------------------------------------------------------------
624    c middle y (or x) position of the upper and middle ToF-Paddle
625    c       DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
626    c       DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
627    c       DATA tof21_y/  3.75,-3.75/     ! paddles in different order
628    c       DATA tof22_x/ -4.5,4.5/
629    c       DATA tof31_x/ -6.0,0.,6.0/
630    c       DATA tof32_y/ -5.0,0.0,5.0/
631    
632    
633    C----------------------------  S1 -------------------------------------
634    
635           yhelp=0.
636           if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i)
637           if (ytofpos(1).lt.100)  yhelp=ytofpos(1)
638    
639           IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
640             i = tof11_i
641    c         if (tof11(left,i,iadc).eq.4095) then
642             if (adc(ch11a(i),hb11a(i)).eq.4095) then
643                xkorr = atten(left,11,i,yhelp)
644                xkorr=xkorr/hepratio
645                tof11(left,i,iadc)=xkorr/cos(theta13)
646    c            write(*,*) 'tofl2 left ',i, tof11(left,i,iadc)
647                adcflagtof(ch11a(i),hb11a(i)) = 1
648             endif
649    c         if (tof11(right,i,iadc).eq.4095) then
650             if (adc(ch11b(i),hb11b(i)).eq.4095) then
651                xkorr = atten(right,11,i,yhelp)
652                xkorr=xkorr/hepratio
653                tof11(right,i,iadc)=xkorr/cos(theta13)
654    c            write(*,*) 'tofl2 right ',i, tof11(right,i,iadc)
655                adcflagtof(ch11b(i),hb11b(i)) = 1
656             endif
657           ENDIF
658    
659           xhelp=0.
660           if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i)
661           if (xtofpos(1).lt.100)  xhelp=xtofpos(1)
662    
663           IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
664             i = tof12_i
665    c         if (tof12(left,i,iadc).eq.4095) then
666             if (adc(ch12a(i),hb12a(i)).eq.4095) then
667                xkorr = atten(left,12,i,xhelp)
668                xkorr=xkorr/hepratio
669                tof12(left,i,iadc) = xkorr/cos(theta13)
670                adcflagtof(ch12a(i),hb12a(i)) = 1
671             endif
672    c         if (tof12(right,i,iadc).eq.4095) then
673             if (adc(ch12b(i),hb12b(i)).eq.4095) then
674                xkorr = atten(right,12,i,xhelp)
675                xkorr=xkorr/hepratio
676                tof12(right,i,iadc) = xkorr/cos(theta13)
677                adcflagtof(ch12b(i),hb12b(i)) = 1
678             endif
679           ENDIF
680    
681    C-----------------------------S2 --------------------------------
682    
683           xhelp=0.
684           if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i)
685           if (xtofpos(2).lt.100)  xhelp=xtofpos(2)
686    
687           IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
688             i = tof21_i
689    c         if (tof21(left,i,iadc).eq.4095) then
690             if (adc(ch21a(i),hb21a(i)).eq.4095) then
691                xkorr = atten(left,21,i,xhelp)
692                xkorr=xkorr/hepratio
693                tof21(left,i,iadc) = xkorr/cos(theta13)
694                adcflagtof(ch21a(i),hb21a(i)) = 1
695             endif
696    c         if (tof21(right,i,iadc).eq.4095) then
697             if (adc(ch21b(i),hb21b(i)).eq.4095) then
698                xkorr = atten(right,21,i,xhelp)
699                xkorr=xkorr/hepratio
700                tof21(right,i,iadc) = xkorr/cos(theta13)
701                adcflagtof(ch21b(i),hb21b(i)) = 1
702             endif
703           ENDIF
704    
705    
706           yhelp=0.
707           if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i)
708           if (ytofpos(2).lt.100)  yhelp=ytofpos(2)
709    
710           IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
711             i = tof22_i
712    c         if (tof22(left,i,iadc).eq.4095) then
713             if (adc(ch22a(i),hb22a(i)).eq.4095) then
714                xkorr = atten(left,22,i,yhelp)
715                xkorr=xkorr/hepratio
716                tof22(left,i,iadc) = xkorr/cos(theta13)
717                adcflagtof(ch22a(i),hb22a(i)) = 1
718             endif
719    c         if (tof22(right,i,iadc).eq.4095) then
720             if (adc(ch22b(i),hb22b(i)).eq.4095) then
721                xkorr = atten(right,22,i,yhelp)
722                xkorr=xkorr/hepratio
723                tof22(right,i,iadc) = xkorr/cos(theta13)
724                adcflagtof(ch22b(i),hb22b(i)) = 1
725             endif
726           ENDIF
727    
728    C-----------------------------S3 --------------------------------
729    
730           yhelp=0.
731           if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i)
732           if (ytofpos(3).lt.100)  yhelp=ytofpos(3)
733    
734           IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
735             i = tof31_i
736    c         if (tof31(left,i,iadc).eq.4095) then
737             if (adc(ch31a(i),hb31a(i)).eq.4095) then
738                xkorr = atten(left,31,i,yhelp)
739                xkorr=xkorr/hepratio
740                tof31(left,i,iadc) = xkorr/cos(theta13)
741                adcflagtof(ch31a(i),hb31a(i)) = 1
742             endif
743    c         if (tof31(right,i,iadc).eq.4095) then
744             if (adc(ch31b(i),hb31b(i)).eq.4095) then
745                xkorr = atten(right,31,i,yhelp)
746                xkorr=xkorr/hepratio
747                tof31(right,i,iadc) = xkorr/cos(theta13)
748                adcflagtof(ch31b(i),hb31b(i)) = 1
749             endif
750           ENDIF
751    
752           xhelp=0.
753           if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i)
754           if (xtofpos(3).lt.100)  xhelp=xtofpos(3)
755    
756           IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
757             i = tof32_i
758    c         if (tof32(left,i,iadc).eq.4095) then
759             if (adc(ch32a(i),hb32a(i)).eq.4095) then
760                xkorr = atten(left,32,i,xhelp)
761                xkorr=xkorr/hepratio
762                tof32(left,i,iadc) = xkorr/cos(theta13)
763                adcflagtof(ch32a(i),hb32a(i)) = 1
764             endif
765    c         if (tof32(right,i,iadc).eq.4095) then
766             if (adc(ch32b(i),hb32b(i)).eq.4095) then
767                xkorr = atten(right,32,i,xhelp)
768                xkorr=xkorr/hepratio
769                tof32(right,i,iadc) = xkorr/cos(theta13)
770                adcflagtof(ch32b(i),hb32b(i)) = 1
771             endif
772           ENDIF
773    
774    
775  C--------------------------------------------------------------------  C--------------------------------------------------------------------
776  C--------------------Time walk correction  -------------------------  C--------------------Time walk correction  -------------------------
777  C--------------------------------------------------------------------  C--------------------------------------------------------------------
778    
779        DO i=1,8        DO i=1,8
780           xhelp= 0.
781         xhelp_a = tof11(left,i,iadc)         xhelp_a = tof11(left,i,iadc)
782         xhelp_t = tof11(left,i,itdc)         xhelp_t = tof11(left,i,itdc)
783         if(xhelp_a>0) xhelp = tw11(left,i)/sqrt(xhelp_a)  c       if (xhelp_a .eq.0) write (*,*) '11 ',i,xhelp_a
784           if(xhelp_a<3786) xhelp = tw11(left,i)/sqrt(xhelp_a)
785         tof11(left,i,itdc) = xhelp_t  + xhelp         tof11(left,i,itdc) = xhelp_t  + xhelp
786         tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)         tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
787         xhelp_a = tof11(right,i,iadc)         xhelp_a = tof11(right,i,iadc)
788         xhelp_t = tof11(right,i,itdc)         xhelp_t = tof11(right,i,itdc)
789         if(xhelp_a>0) xhelp = tw11(right,i)/sqrt(xhelp_a)         if(xhelp_a<3786) xhelp = tw11(right,i)/sqrt(xhelp_a)
790         tof11(right,i,itdc) = xhelp_t  + xhelp         tof11(right,i,itdc) = xhelp_t  + xhelp
791         tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)         tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
792        ENDDO        ENDDO
793    
794        DO i=1,6        DO i=1,6
795           xhelp= 0.
796         xhelp_a = tof12(left,i,iadc)         xhelp_a = tof12(left,i,iadc)
797         xhelp_t = tof12(left,i,itdc)         xhelp_t = tof12(left,i,itdc)
798         if(xhelp_a>0) xhelp = tw12(left,i)/sqrt(xhelp_a)  c       if (xhelp_a .eq.0) write (*,*) '12 ',i,xhelp_a
799           if(xhelp_a<3786) xhelp = tw12(left,i)/sqrt(xhelp_a)
800         tof12(left,i,itdc) = xhelp_t  + xhelp         tof12(left,i,itdc) = xhelp_t  + xhelp
801         tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)         tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
802         xhelp_a = tof12(right,i,iadc)         xhelp_a = tof12(right,i,iadc)
803         xhelp_t = tof12(right,i,itdc)         xhelp_t = tof12(right,i,itdc)
804         if(xhelp_a>0) xhelp = tw12(right,i)/sqrt(xhelp_a)         if(xhelp_a<3786) xhelp = tw12(right,i)/sqrt(xhelp_a)
805         tof12(right,i,itdc) = xhelp_t  + xhelp         tof12(right,i,itdc) = xhelp_t  + xhelp
806         tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)         tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
807        ENDDO        ENDDO
808  C----  C----
809        DO i=1,2        DO i=1,2
810           xhelp= 0.
811         xhelp_a = tof21(left,i,iadc)         xhelp_a = tof21(left,i,iadc)
812         xhelp_t = tof21(left,i,itdc)         xhelp_t = tof21(left,i,itdc)
813         if(xhelp_a>0) xhelp = tw21(left,i)/sqrt(xhelp_a)  c       if (xhelp_a .eq.0) write (*,*) '21 ',i,xhelp_a
814           if(xhelp_a<3786) xhelp = tw21(left,i)/sqrt(xhelp_a)
815         tof21(left,i,itdc) = xhelp_t  + xhelp         tof21(left,i,itdc) = xhelp_t  + xhelp
816         tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)         tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
817         xhelp_a = tof21(right,i,iadc)         xhelp_a = tof21(right,i,iadc)
818         xhelp_t = tof21(right,i,itdc)         xhelp_t = tof21(right,i,itdc)
819         if(xhelp_a>0) xhelp = tw21(right,i)/sqrt(xhelp_a)         if(xhelp_a<3786) xhelp = tw21(right,i)/sqrt(xhelp_a)
820         tof21(right,i,itdc) = xhelp_t  + xhelp         tof21(right,i,itdc) = xhelp_t  + xhelp
821         tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)         tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
822        ENDDO        ENDDO
823    
824        DO i=1,2        DO i=1,2
825           xhelp= 0.
826         xhelp_a = tof22(left,i,iadc)         xhelp_a = tof22(left,i,iadc)
827         xhelp_t = tof22(left,i,itdc)         xhelp_t = tof22(left,i,itdc)
828         if(xhelp_a>0) xhelp = tw22(left,i)/sqrt(xhelp_a)  c       if (xhelp_a .eq.0) write (*,*) '22 ',i,xhelp_a
829    
830           if(xhelp_a<3786) xhelp = tw22(left,i)/sqrt(xhelp_a)
831         tof22(left,i,itdc) = xhelp_t  + xhelp         tof22(left,i,itdc) = xhelp_t  + xhelp
832         tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)         tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
833         xhelp_a = tof22(right,i,iadc)         xhelp_a = tof22(right,i,iadc)
834         xhelp_t = tof22(right,i,itdc)         xhelp_t = tof22(right,i,itdc)
835         if(xhelp_a>0) xhelp = tw22(right,i)/sqrt(xhelp_a)         if(xhelp_a<3786) xhelp = tw22(right,i)/sqrt(xhelp_a)
836         tof22(right,i,itdc) = xhelp_t  + xhelp         tof22(right,i,itdc) = xhelp_t  + xhelp
837         tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)         tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
838        ENDDO        ENDDO
839  C----  C----
840    
841        DO i=1,3        DO i=1,3
842           xhelp= 0.
843         xhelp_a = tof31(left,i,iadc)         xhelp_a = tof31(left,i,iadc)
844         xhelp_t = tof31(left,i,itdc)         xhelp_t = tof31(left,i,itdc)
845         if(xhelp_a>0) xhelp = tw31(left,i)/sqrt(xhelp_a)  c       if (xhelp_a .eq.0) write (*,*) '31 ',i,xhelp_a
846    
847           if(xhelp_a<3786) xhelp = tw31(left,i)/sqrt(xhelp_a)
848         tof31(left,i,itdc) = xhelp_t  + xhelp         tof31(left,i,itdc) = xhelp_t  + xhelp
849         tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)         tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
850         xhelp_a = tof31(right,i,iadc)         xhelp_a = tof31(right,i,iadc)
851         xhelp_t = tof31(right,i,itdc)         xhelp_t = tof31(right,i,itdc)
852         if(xhelp_a>0) xhelp = tw31(right,i)/sqrt(xhelp_a)         if(xhelp_a<3786) xhelp = tw31(right,i)/sqrt(xhelp_a)
853         tof31(right,i,itdc) = xhelp_t  + xhelp         tof31(right,i,itdc) = xhelp_t  + xhelp
854         tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)         tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
855        ENDDO        ENDDO
856    
857        DO i=1,3        DO i=1,3
858           xhelp= 0.
859         xhelp_a = tof32(left,i,iadc)         xhelp_a = tof32(left,i,iadc)
860         xhelp_t = tof32(left,i,itdc)         xhelp_t = tof32(left,i,itdc)
861         if(xhelp_a>0) xhelp = tw32(left,i)/sqrt(xhelp_a)  c       if (xhelp_a .eq.0) write (*,*) '32 ',i,xhelp_a
862    
863           if(xhelp_a<3786) xhelp = tw32(left,i)/sqrt(xhelp_a)
864         tof32(left,i,itdc) = xhelp_t  + xhelp         tof32(left,i,itdc) = xhelp_t  + xhelp
865         tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)         tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
866         xhelp_a = tof32(right,i,iadc)         xhelp_a = tof32(right,i,iadc)
867         xhelp_t = tof32(right,i,itdc)         xhelp_t = tof32(right,i,itdc)
868         if(xhelp_a>0) xhelp = tw32(right,i)/sqrt(xhelp_a)         if(xhelp_a<3786) xhelp = tw32(right,i)/sqrt(xhelp_a)
869         tof32(right,i,itdc) = xhelp_t  + xhelp         tof32(right,i,itdc) = xhelp_t  + xhelp
870         tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)         tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
871        ENDDO        ENDDO
 C----  
872    
 C------------------------------------------------------------------  
 C---  calculate track position in paddle using timing difference  
 C------------------------------------------------------------------  
   
       do i=1,3  
          xtofpos(i)=100.  
          ytofpos(i)=100.  
       enddo  
 C-----------------------------S1 --------------------------------  
   
       IF (tof11_i.GT.none_find) THEN  
          ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.  
      +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)  
       endif  
   
       IF (tof12_i.GT.none_find) THEN  
          xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.  
      +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)  
       endif  
   
   
 C-----------------------------S2 --------------------------------  
   
       IF (tof21_i.GT.none_find) THEN  
          xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.  
      +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)  
       endif  
   
       IF (tof22_i.GT.none_find) THEN  
          ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.  
      +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)  
       endif  
         
   
 C-----------------------------S3 --------------------------------  
   
       IF (tof31_i.GT.none_find) THEN  
          ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.  
      +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)  
       endif  
   
       IF (tof32_i.GT.none_find) THEN  
          xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.  
      +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)  
       endif  
   
   
       do i=1,3  
          if (abs(xtofpos(i)).gt.100.) then  
             xtofpos(i)=101.  
          endif  
          if (abs(ytofpos(i)).gt.100.) then  
             ytofpos(i)=101.  
          endif  
       enddo  
   
 C----------------------------------------------------------------------  
 C--------------------Corrections on ADC-data -------------------------  
 C---------------------zenith angle theta  ---------------------------  
 C----------------------------------------------------------------------  
   
       dx=0.  
       dy=0.  
       dr=0.  
       theta13 = 0.  
   
          IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find))  
      &        dx  = xtofpos(1) - xtofpos(3)  
          IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find))  
      &        dy  = ytofpos(1) - ytofpos(3)  
          dr = sqrt(dx*dx+dy*dy)  
          theta13 = atan(dr/tofarm13)  
   
       dx=0.  
       dy=0.  
       dr=0.  
       theta12 = 0.  
   
          IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find))  
      &        dx  = xtofpos(1) - xtofpos(2)  
          IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find))  
      &        dy  = ytofpos(1) - ytofpos(2)  
          dr = sqrt(dx*dx+dy*dy)  
          theta12 = atan(dr/tofarm12)  
           
       dx=0.  
       dy=0.  
       dr=0.  
       theta23 = 0.  
   
          IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find))  
      &        dx  = xtofpos(2) - xtofpos(3)  
          IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find))  
      &        dy  = ytofpos(2) - ytofpos(3)  
          dr = sqrt(dx*dx+dy*dy)  
          theta23 = atan(dr/tofarm23)  
           
           
873  C----------------------------------------------------------------------  C----------------------------------------------------------------------
874  C------------------angle and ADC(x) correction  C------------------angle and ADC(x) correction
875  C----------------------------------------------------------------------  C----------------------------------------------------------------------
# Line 597  C-----------------------------S1 ------- Line 877  C-----------------------------S1 -------
877  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
878  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/
879  c       DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/  c       DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
880  c       DATA tof21_y/ -3.75,3.75/  c       DATA tof21_y/  3.75,-3.75/     ! paddles in different order
881  c       DATA tof22_x/ -4.5,4.5/  c       DATA tof22_x/ -4.5,4.5/
882  c       DATA tof31_x/ -6.0,0.,6.0/  c       DATA tof31_x/ -6.0,0.,6.0/
883  c       DATA tof32_y/ -5.0,0.0,5.0/  c       DATA tof32_y/ -5.0,0.0,5.0/
# Line 609  c       DATA tof32_y/ -5.0,0.0,5.0/ Line 889  c       DATA tof32_y/ -5.0,0.0,5.0/
889        IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN        IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
890    
891           i = tof11_i           i = tof11_i
892           xdummy=tof11(left,i,iadc)           if (tof11(left,i,iadc).lt.3786) then
893           tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)  c          if (adc(ch11a(i),hb11a(i)).lt.4095) then
894           if (tof11(left,i,iadc).lt.1000) then              tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
895              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))              xkorr = atten(left,11,i,yhelp)
896              xkorr0=adcx11(left,i,1)  c            write(40+i,*) yhelp,xkorr
897                xkorr=xkorr/hepratio
898              adctof_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr              adctof_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
899           endif           endif
900    
901           tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)           if (tof11(right,i,iadc).lt.3786) then
902           if (tof11(right,i,iadc).lt.1000) then  c          if (adc(ch11b(i),hb11b(i)).lt.4095) then
903              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))              tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
904              xkorr0=adcx11(right,i,1)              xkorr = atten(right,11,i,yhelp)
905    c            write(40+i,*) yhelp,xkorr
906                xkorr=xkorr/hepratio
907              adctof_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr              adctof_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
908           endif           endif
909        ENDIF        ENDIF
# Line 632  c       DATA tof32_y/ -5.0,0.0,5.0/ Line 915  c       DATA tof32_y/ -5.0,0.0,5.0/
915        IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN        IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
916    
917           i = tof12_i           i = tof12_i
918           tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)           if (tof12(left,i,iadc).lt.3786) then
919           if (tof12(left,i,iadc).lt.1000) then  c          if (adc(ch12a(i),hb12a(i)).lt.4095) then
920              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))              tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
921              xkorr0=adcx12(left,i,1)              xkorr = atten(left,12,i,xhelp)
922    c            write(50+i,*) xhelp,xkorr
923                xkorr=xkorr/hepratio
924              adctof_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr              adctof_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
925           endif           endif
926    
927           tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)           if (tof12(right,i,iadc).lt.3786) then
928           if (tof12(right,i,iadc).lt.1000) then  c          if (adc(ch12b(i),hb12b(i)).lt.4095) then
929              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))              tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
930              xkorr0=adcx12(right,i,1)              xkorr = atten(right,12,i,xhelp)
931    c            write(50+i,*) xhelp,xkorr
932                xkorr=xkorr/hepratio
933              adctof_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr              adctof_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
934           endif           endif
935        ENDIF        ENDIF
# Line 656  C-----------------------------S2 ------- Line 943  C-----------------------------S2 -------
943        IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN        IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
944    
945           i = tof21_i           i = tof21_i
946           tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)           if (tof21(left,i,iadc).lt.3786) then
947           if (tof21(left,i,iadc).lt.1000) then  c          if (adc(ch21a(i),hb21a(i)).lt.4095) then
948              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))              tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
949              xkorr0=adcx21(left,i,1)              xkorr = atten(left,21,i,xhelp)
950    c            write(60+i,*) xhelp,xkorr
951                xkorr=xkorr/hepratio
952              adctof_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr              adctof_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
953           endif           endif
954    
955           tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)           if (tof21(right,i,iadc).lt.3786) then
956           if (tof21(right,i,iadc).lt.1000) then  c          if (adc(ch21b(i),hb21b(i)).lt.4095) then
957                tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
958              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
959              xkorr0=adcx21(right,i,1)              xkorr = atten(right,21,i,xhelp)
960    c            write(60+i,*) xhelp,xkorr
961                xkorr=xkorr/hepratio
962              adctof_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr              adctof_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
963           endif           endif
964        ENDIF        ENDIF
# Line 679  C-----------------------------S2 ------- Line 971  C-----------------------------S2 -------
971        IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN        IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
972    
973           i = tof22_i           i = tof22_i
974           tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)           if (tof22(left,i,iadc).lt.3786) then
975           if (tof22(left,i,iadc).lt.1000) then  c          if (adc(ch22a(i),hb22a(i)).lt.4095) then
976              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))              tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
977              xkorr0=adcx22(left,i,1)              xkorr = atten(left,22,i,yhelp)
978    c            write(70+i,*) yhelp,xkorr
979                xkorr=xkorr/hepratio
980              adctof_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr              adctof_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
981           endif           endif
982    
983           tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)           if (tof22(right,i,iadc).lt.3786) then
984           if (tof22(right,i,iadc).lt.1000) then  c          if (adc(ch22b(i),hb22b(i)).lt.4095) then
985              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))              tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
986              xkorr0=adcx22(right,i,1)              xkorr = atten(right,22,i,yhelp)
987    c            write(70+i,*) yhelp,xkorr
988                xkorr=xkorr/hepratio
989              adctof_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr              adctof_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
990           endif           endif
991        ENDIF        ENDIF
# Line 703  C-----------------------------S3 ------- Line 999  C-----------------------------S3 -------
999        IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN        IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
1000    
1001           i = tof31_i           i = tof31_i
1002           tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)           if (tof31(left,i,iadc).lt.3786) then
1003           if (tof31(left,i,iadc).lt.1000) then  c          if (adc(ch31a(i),hb31a(i)).lt.4095) then
1004              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))              tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
1005              xkorr0=adcx31(left,i,1)              xkorr = atten(left,31,i,yhelp)
1006    c            write(80+i,*) yhelp,xkorr
1007                xkorr=xkorr/hepratio
1008              adctof_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr              adctof_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1009           endif           endif
1010    
1011           tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)           if (tof31(right,i,iadc).lt.3786) then
1012           if (tof31(right,i,iadc).lt.1000) then  c          if (adc(ch31b(i),hb31b(i)).lt.4095) then
1013              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))              tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
1014              xkorr0=adcx31(right,i,1)              xkorr = atten(right,31,i,yhelp)
1015    c            write(80+i,*) yhelp,xkorr
1016                xkorr=xkorr/hepratio
1017              adctof_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr              adctof_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1018           endif           endif
1019        ENDIF        ENDIF
# Line 725  C-----------------------------S3 ------- Line 1025  C-----------------------------S3 -------
1025        IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN        IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
1026    
1027           i = tof32_i           i = tof32_i
1028           tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)           if (tof32(left,i,iadc).lt.3786) then
1029           if (tof32(left,i,iadc).lt.1000) then  c          if (adc(ch32a(i),hb32a(i)).lt.4095) then
1030              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))              tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
1031              xkorr0=adcx32(left,i,1)              xkorr = atten(left,32,i,xhelp)
1032    c            write(90+i,*) xhelp,xkorr
1033                xkorr=xkorr/hepratio
1034              adctof_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr              adctof_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1035           endif           endif
1036    
1037           tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)           if (tof32(right,i,iadc).lt.3786) then
1038           if (tof32(right,i,iadc).lt.1000) then  c          if (adc(ch32b(i),hb32b(i)).lt.4095) then
1039              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))              tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
1040              xkorr0=adcx32(right,i,1)              xkorr = atten(right,32,i,xhelp)
1041    c            write(90+i,*) xhelp,xkorr
1042                xkorr=xkorr/hepratio
1043              adctof_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr              adctof_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1044           endif           endif
1045        ENDIF        ENDIF
1046    
1047  C-----------------------------------------------------------------------  
1048    C--------------------------------------------------------------------
1049  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1050  C-----------------------------------------------------------------------  C--------------------------------------------------------------------
1051  C-------------------difference of sums  ---------------------------  C-------------------difference of sums  -----------------------------
1052  C  C
1053  C     DS = (t1+t2) - t3+t4)  C     DS = (t1+t2) - t3+t4)
1054  C     DS = c1 + c2/beta*cos(theta)  C     DS = c1 + c2/beta*cos(theta)
# Line 752  C     =>  c2 =  ca.60 for  0.45 m    c2 Line 1057  C     =>  c2 =  ca.60 for  0.45 m    c2
1057  C     since TDC resolution varies slightly c2 has to be calibrated  C     since TDC resolution varies slightly c2 has to be calibrated
1058    
1059  C     S11 - S31  C     S11 - S31
1060        IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  
1061           IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1062         &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1063           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1064           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1065           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 760  C     S11 - S31 Line 1067  C     S11 - S31
1067           c1 = k_S11S31(1,ihelp)           c1 = k_S11S31(1,ihelp)
1068           c2 = k_S11S31(2,ihelp)           c2 = k_S11S31(2,ihelp)
1069           betatof_a(1) = c2/(cos(theta13)*(ds-c1))           betatof_a(1) = c2/(cos(theta13)*(ds-c1))
1070    
1071    C------- ToF Mask - S11 - S31
1072    
1073             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1074         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1075             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1076         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1077    
1078             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1079         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1080             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1081         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1082    
1083    C-------
1084          
1085        ENDIF        ENDIF
1086                
1087  C     S11 - S32  C     S11 - S32
1088        IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1089           IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1090         &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1091           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1092           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1093           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 771  C     S11 - S32 Line 1095  C     S11 - S32
1095           c1 = k_S11S32(1,ihelp)           c1 = k_S11S32(1,ihelp)
1096           c2 = k_S11S32(2,ihelp)           c2 = k_S11S32(2,ihelp)
1097           betatof_a(2) = c2/(cos(theta13)*(ds-c1))           betatof_a(2) = c2/(cos(theta13)*(ds-c1))
       ENDIF  
1098    
1099    C------- ToF Mask - S11 - S32
1100    
1101             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1102         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1103             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1104         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1105    
1106             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1107         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1108             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1109         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1110    
1111    C-------
1112    
1113          ENDIF
1114          
1115  C     S12 - S31  C     S12 - S31
1116        IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  
1117           IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1118         &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1119           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1120           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1121           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 782  C     S12 - S31 Line 1123  C     S12 - S31
1123           c1 = k_S12S31(1,ihelp)           c1 = k_S12S31(1,ihelp)
1124           c2 = k_S12S31(2,ihelp)           c2 = k_S12S31(2,ihelp)
1125           betatof_a(3) = c2/(cos(theta13)*(ds-c1))           betatof_a(3) = c2/(cos(theta13)*(ds-c1))
       ENDIF  
1126    
1127    C------- ToF Mask - S12 - S31
1128    
1129             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1130         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1131             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1132         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1133    
1134             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1135         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1136             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1137         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1138    
1139    C-------
1140    
1141          ENDIF
1142                
1143  C     S12 - S32  C     S12 - S32
1144        IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1145           IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1146         &    (xtofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1147           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1148           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1149           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 793  C     S12 - S32 Line 1151  C     S12 - S32
1151           c1 = k_S12S32(1,ihelp)           c1 = k_S12S32(1,ihelp)
1152           c2 = k_S12S32(2,ihelp)           c2 = k_S12S32(2,ihelp)
1153           betatof_a(4) = c2/(cos(theta13)*(ds-c1))           betatof_a(4) = c2/(cos(theta13)*(ds-c1))
1154    
1155    C------- ToF Mask - S12 - S32
1156    
1157             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1158         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1159             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1160         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1161    
1162             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1163         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1164             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1165         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1166    
1167    C-------
1168    
1169        ENDIF        ENDIF
1170    
1171  C     S21 - S31  C     S21 - S31
1172        IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  
1173           IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1174         &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1175           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1176           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1177           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
1178           ihelp=(tof21_i-1)*3+tof31_i           ihelp=(tof21_i-1)*3+tof31_i
1179           c1 = k_S21S31(1,ihelp)           c1 = k_S21S31(1,ihelp)
1180           c2 = k_S21S31(2,ihelp)           c2 = k_S21S31(2,ihelp)
1181           betatof_a(5) = c2/(cos(theta23)*(ds-c1))           betatof_a(5) = c2/(cos(theta13)*(ds-c1))
1182    
1183    C------- ToF Mask - S21 - S31
1184    
1185             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1186         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1187             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1188         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1189    
1190             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1191         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1192             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1193         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1194    
1195    C-------
1196    
1197        ENDIF        ENDIF
1198    
1199  C     S21 - S32  C     S21 - S32
1200        IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1201           IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1202         &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1203           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1204           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1205           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
1206           ihelp=(tof21_i-1)*3+tof32_i           ihelp=(tof21_i-1)*3+tof32_i
1207           c1 = k_S21S32(1,ihelp)           c1 = k_S21S32(1,ihelp)
1208           c2 = k_S21S32(2,ihelp)           c2 = k_S21S32(2,ihelp)
1209           betatof_a(6) = c2/(cos(theta23)*(ds-c1))           betatof_a(6) = c2/(cos(theta13)*(ds-c1))
1210                      
1211    C------- ToF Mask - S21 - S32
1212    
1213             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1214         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1215             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1216         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1217    
1218             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1219         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1220             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1221         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1222    
1223    C-------
1224    
1225        ENDIF        ENDIF
1226    
1227  C     S22 - S31  C     S22 - S31
1228        IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  
1229           IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1230         &    (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1231           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1232           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1233           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 826  C     S22 - S31 Line 1235  C     S22 - S31
1235           c1 = k_S22S31(1,ihelp)           c1 = k_S22S31(1,ihelp)
1236           c2 = k_S22S31(2,ihelp)           c2 = k_S22S31(2,ihelp)
1237           betatof_a(7) = c2/(cos(theta13)*(ds-c1))           betatof_a(7) = c2/(cos(theta13)*(ds-c1))
1238    
1239    C------- ToF Mask - S22 - S31
1240    
1241             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1242         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1243             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1244         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1245    
1246             tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1247         $        tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1248             tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1249         $        tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1250    
1251    C-------          
1252    
1253        ENDIF        ENDIF
1254                
1255  C     S22 - S32  C     S22 - S32
1256        IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1257           IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1258         &    (ytofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1259           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1260           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1261           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 837  C     S22 - S32 Line 1263  C     S22 - S32
1263           c1 = k_S22S32(1,ihelp)           c1 = k_S22S32(1,ihelp)
1264           c2 = k_S22S32(2,ihelp)           c2 = k_S22S32(2,ihelp)
1265           betatof_a(8) = c2/(cos(theta13)*(ds-c1))           betatof_a(8) = c2/(cos(theta13)*(ds-c1))
1266    
1267    C------- ToF Mask - S22 - S32
1268    
1269             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1270         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1271             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1272         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1273    
1274             tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1275         $        tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1276             tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1277         $        tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1278    
1279    C-------  
1280    
1281        ENDIF        ENDIF
1282    
1283  C     S11 - S21  C     S11 - S21
1284        IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN  
1285           IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1286         &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1287           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1288           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1289           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 848  C     S11 - S21 Line 1291  C     S11 - S21
1291           c1 = k_S11S21(1,ihelp)           c1 = k_S11S21(1,ihelp)
1292           c2 = k_S11S21(2,ihelp)           c2 = k_S11S21(2,ihelp)
1293           betatof_a(9) = c2/(cos(theta13)*(ds-c1))           betatof_a(9) = c2/(cos(theta13)*(ds-c1))
1294    
1295    C------- ToF Mask - S11 - S21
1296    
1297             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1298         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1299             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1300         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1301    
1302             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1303         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1304             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1305         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1306    
1307    C-------  
1308    
1309        ENDIF        ENDIF
1310                
1311  C     S11 - S22  C     S11 - S22
1312        IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  
1313           IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1314         &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1315           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1316           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1317           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 859  C     S11 - S22 Line 1319  C     S11 - S22
1319           c1 = k_S11S22(1,ihelp)           c1 = k_S11S22(1,ihelp)
1320           c2 = k_S11S22(2,ihelp)           c2 = k_S11S22(2,ihelp)
1321           betatof_a(10) = c2/(cos(theta13)*(ds-c1))           betatof_a(10) = c2/(cos(theta13)*(ds-c1))
1322    
1323    C------- ToF Mask - S11 - S22
1324    
1325             tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1326         $        tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1327             tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1328         $        tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1329    
1330             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1331         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1332             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1333         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1334    
1335    C-------  
1336    
1337        ENDIF        ENDIF
1338    
1339  C     S12 - S21  C     S12 - S21
1340        IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN  
1341           IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1342         &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1343           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1344           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1345           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 870  C     S12 - S21 Line 1347  C     S12 - S21
1347           c1 = k_S12S21(1,ihelp)           c1 = k_S12S21(1,ihelp)
1348           c2 = k_S12S21(2,ihelp)           c2 = k_S12S21(2,ihelp)
1349           betatof_a(11) = c2/(cos(theta13)*(ds-c1))           betatof_a(11) = c2/(cos(theta13)*(ds-c1))
1350    
1351    C------- ToF Mask - S12 - S21
1352    
1353             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1354         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1355             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1356         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1357    
1358             tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1359         $        tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1360             tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1361         $        tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1362    
1363    C-------  
1364    
1365        ENDIF        ENDIF
1366    
1367  C     S12 - S22  C     S12 - S22
1368        IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  
1369           IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1370         &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1371           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1372           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1373           ds = xhelp1-xhelp2           ds = xhelp1-xhelp2
# Line 881  C     S12 - S22 Line 1375  C     S12 - S22
1375           c1 = k_S12S22(1,ihelp)           c1 = k_S12S22(1,ihelp)
1376           c2 = k_S12S22(2,ihelp)           c2 = k_S12S22(2,ihelp)
1377           betatof_a(12) = c2/(cos(theta13)*(ds-c1))           betatof_a(12) = c2/(cos(theta13)*(ds-c1))
1378    
1379    C------- ToF Mask - S12 - S22
1380    
1381             tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1382         $        tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1383             tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1384         $        tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1385    
1386             tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1387         $        tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1388             tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1389         $        tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1390    
1391    C-------  
1392    
1393        ENDIF        ENDIF
1394          
1395  C-------  C---------------------------------------------------------
1396    
1397        icount=0        icount=0
1398        sw=0.        sw=0.
# Line 903  C------- Line 1412  C-------
1412                
1413        if (icount.gt.0) beta_mean=sxw/sw        if (icount.gt.0) beta_mean=sxw/sw
1414        betatof_a(13) = beta_mean        betatof_a(13) = beta_mean
 c      write(*,*) '------------- end  tofl2com ----------'  
1415    
1416    c      write(*,*) xtofpos
1417    c      write(*,*) ytofpos
1418    c      write(*,*)'tofl2com beta', betatof_a
1419    C      write(*,*) adcflagtof
1420    c      write(*,*) 'tofl2com'
1421    c      write(*,*) xtofpos
1422    c      write(*,*) ytofpos
1423    c      write(*,*) xtr_tof
1424    c      write(*,*) ytr_tof
1425          
1426   100  continue   100  continue
1427    
1428  C  C
1429        RETURN        RETURN
1430        END        END
1431    
1432    
1433    C------------------------------------------------------------------
1434    C------------------------------------------------------------------
1435    
1436           function atten(is,ilay,ipad,x)
1437           include  'input_tof.txt'
1438           real atten
1439           real x
1440           real xmin,xmax
1441           integer  ilay,ipad
1442    
1443    *  S11 8 paddles  33.0 x 5.1 cm
1444    *  S12 6 paddles  40.8 x 5.5 cm
1445    *  S21 2 paddles  18.0 x 7.5 cm
1446    *  S22 2 paddles  15.0 x 9.0 cm
1447    *  S31 3 paddles  15.0 x 6.0 cm
1448    *  S32 3 paddles  18.0 x 5.0 cm
1449    
1450    
1451    c       if (ilay.eq.11) write(*,*) 'start ',ipad,is,adcx11(is,ipad,1),
1452    c     &  adcx11(is,ipad,2),adcx11(is,ipad,3),adcx11(is,ipad,4)
1453    c       if (ilay.eq.12) write(*,*) 'start ',ipad,is,adcx12(is,ipad,1),
1454    c     &  adcx12(is,ipad,2),adcx12(is,ipad,3),adcx12(is,ipad,4)
1455    
1456    
1457           if (ilay.eq.11)  xmin=-33.0/2.
1458           if (ilay.eq.11)  xmax= 33.0/2.
1459           if (ilay.eq.12)  xmin=-40.8/2.
1460           if (ilay.eq.12)  xmax= 40.8/2.
1461    
1462           if (ilay.eq.21)  xmin=-18.0/2.
1463           if (ilay.eq.21)  xmax= 18.0/2.
1464           if (ilay.eq.22)  xmin=-15.0/2.
1465           if (ilay.eq.22)  xmax= 15.0/2.
1466    
1467           if (ilay.eq.31)  xmin=-15.0/2.
1468           if (ilay.eq.31)  xmax= 15.0/2.
1469           if (ilay.eq.32)  xmin=-18.0/2.
1470           if (ilay.eq.32)  xmax= 18.0/2.
1471    
1472           if (x .lt. xmin) x=xmin
1473           if (x .gt. xmax) x=xmax
1474    
1475    
1476           if (ilay.eq.11) atten=
1477         &    adcx11(is,ipad,1)*exp(x*adcx11(is,ipad,2))
1478         &  + adcx11(is,ipad,3)*exp(x*adcx11(is,ipad,4))
1479    
1480           if (ilay.eq.12) atten=
1481         &    adcx12(is,ipad,1)*exp(x*adcx12(is,ipad,2))
1482         &  + adcx12(is,ipad,3)*exp(x*adcx12(is,ipad,4))
1483    
1484           if (ilay.eq.21) atten=
1485         &    adcx21(is,ipad,1)*exp(x*adcx21(is,ipad,2))
1486         &  + adcx21(is,ipad,3)*exp(x*adcx21(is,ipad,4))
1487    
1488           if (ilay.eq.22) atten=
1489         &    adcx22(is,ipad,1)*exp(x*adcx22(is,ipad,2))
1490         &  + adcx22(is,ipad,3)*exp(x*adcx22(is,ipad,4))
1491    
1492           if (ilay.eq.31) atten=
1493         &    adcx31(is,ipad,1)*exp(x*adcx31(is,ipad,2))
1494         &  + adcx31(is,ipad,3)*exp(x*adcx31(is,ipad,4))
1495    
1496           if (ilay.eq.32) atten=
1497         &    adcx32(is,ipad,1)*exp(x*adcx32(is,ipad,2))
1498         &  + adcx32(is,ipad,3)*exp(x*adcx32(is,ipad,4))
1499    
1500            if (atten.gt.10000) atten=10000.
1501    
1502           end
1503    
1504    C------------------------------------------------------------------
1505    C------------------------------------------------------------------
1506    
1507           function pc_adc(ix)
1508           include  'input_tof.txt'
1509           real pc_adc
1510           integer ix
1511    
1512           pc_adc=28.0407 + 0.628929*ix
1513         &   - 5.80901e-05*ix*ix + 3.14092e-08*ix*ix*ix
1514    c       write(*,*) ix,pc_adc
1515           end
1516    
1517    C------------------------------------------------------------------
1518    

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

  ViewVC Help
Powered by ViewVC 1.1.23