/[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.1.1 by mocchiut, Sat Jun 17 12:14:56 2006 UTC revision 1.18 by pamelats, Thu Nov 27 13:49:13 2008 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     08-12-06 WM:
12    C     adc_c-bug :  The raw ADC value was multiplied with cos(theta)
13    C     and AFTER that there was an if statement "if tof32(right,i,iadc) < 4095"
14    C
15    C  jan-07 GF: ADC/TDCflags(4,12) inserted to flag artificial ADC/TDC
16    C             values
17    C  jan-07 WM: artificial ADC values created using attenuation calibration
18    C  jan-07 WM: artificial TDC values created using xy_coor calibration
19    C  jan-07 WM: modified xtofpos flag "101". xtofpos must be inside physical
20    C             dimension of the paddle +/- 10 cm
21    C  jan-07 WM: if xtofpos=101 then this paddle is not used for beta
22    C             calculation
23    C  jan-07 WM: in the xtofpos calculation a check for TDC.ne.4095 was
24    C             inserted. In the old code one would still calculate a
25    C             xtofpos-value even if the TDC information was missing
26    C  jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift
27    C  jan-05 WM: bug fixed: calculation of zenith angles using DOTRACK2
28    C             was incorrect
29    C  jan-07 WM: bug fixed: in some cases tdc_tw was calculated due to a
30    C             leftover "xhelp" value
31    C  apr-07 WM: attenuation fit curve is now a double exponential fit
32    C             conversion from raw ADC to pC using calibration function
33    C             new variables xtr_tof(6) and ytr_tof(6) give track position
34    C             at ToF layers
35    C  aug-07 WM: artificial ADC creation revised: Now an ADC value is created
36    C             only if there is a TDC value (before ADC was created in ANY
37    C             case)
38    C  jan-08 WM: Major Update: Time Walk correction introduced
39    C             Additionally we use the information from the "check_charge"
40    C             function to fill artificial ADC values and make small corrections
41    C             to the k1-parameter (for Z>2)
42    C  feb-08 WM: Calculation of beta(13) changed: First a mean beta is calculated,
43    C             then in a second step we check the residuals of the single
44    C             measurements, reject if > 10 sigma, calculate chi2 and "quality"
45    C             beta is taken as good if chi2<20 and quality>10
46    C             The function "newbeta" is located in "tofl2com.for"
47    C  mar-08 WM: Call to "newbeta" changed, now a flag tells the function if the
48    C             call comes from "tofl2com" or form "toftrack"
49    C  mar-08 WM: Bug found in dEdx if check_charge>1
50    C  apr-08 WM: Bug found in S22 artificial ADC, mismatch found between the track
51    C             length  from DOTRACK2 and "GetLength" method for 4 combinations
52    C  oct-08 WM: New method to create artificial ADC values. Do NOT take the position
53    C             from the tracking, but the position from timing. This method gives a
54    C             better time resolution
55    C****************************************************************************
56        IMPLICIT NONE        IMPLICIT NONE
57  C      C
58        include  'input_tof.txt'        include  'input_tof.txt'
59        include  'output_tof.txt'        include  'output_tof.txt'
60        include  'tofcomm.txt'        include  'tofcomm.txt'
61  C      C
62          
63  c     =======================================  c     =======================================
64  c     variables for tracking routine  c     variables for tracking routine
65  c     =======================================  c     =======================================
# Line 20  c     define TOF Z-coordinates Line 72  c     define TOF Z-coordinates
72        DOUBLE PRECISION ZTOF(NPTOF)        DOUBLE PRECISION ZTOF(NPTOF)
73        DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006        DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
74    
75        integer itof        integer itof,pmt_id
76    
77        DOUBLE PRECISION al_p(5),        DOUBLE PRECISION al_p(5),
78       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF)       &     xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
79         &     THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
80    
81    
82        INTEGER IFAIL        INTEGER IFAIL
83        REAL dx,dy,dr,ds  c      REAL dx,dy,dr
84        REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2        REAL ds
85        REAL c1,c2,sw,sxw,w_i        REAL t1,t2,t3,t4
86        INTEGER icount        REAL yhelp,xhelp,xhelp1,xhelp2
87          REAL c1,c2
88    C     REAL sw,sxw,w_i
89          REAL dist,dl,F
90          INTEGER ievent
91    C      INTEGER icount
92    C      REAL beta_mean
93          REAL btemp(12)
94          REAL hepratio
95    
96          INTEGER j,hitvec(6)
97    
98        REAL beta_mean        real atten,pc_adc,check_charge,newbeta
99    
100    
101        REAL theta12,theta13,theta23        REAL theta,phi
102  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
103        REAL tofarm12        REAL tofarm12
104        PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69        PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
105        REAL tofarm23                REAL tofarm23
106        PARAMETER (tofarm23 = 47.61)  ! from 23.69 to -23.92        PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
107        REAL tofarm13        REAL tofarm13
108        PARAMETER (tofarm13 = 77.31)  ! from 53.39 to -23.92        PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
109    
110    
111    C--- new
112          REAL xtofpre(3),ytofpre(3)
113    
114          REAL y_coor_lin11c(8,2),x_coor_lin12c(6,2)
115          REAL x_coor_lin21c(2,2),y_coor_lin22c(2,2)
116          REAL y_coor_lin31c(3,2),x_coor_lin32c(3,2)
117    
118          DATA y_coor_lin11c(1,1),y_coor_lin11c(1,2) /-20.66,-2.497/
119          DATA y_coor_lin11c(2,1),y_coor_lin11c(2,2) /-9.10, -2.52/
120          DATA y_coor_lin11c(3,1),y_coor_lin11c(3,2) /-24.07,-2.12/
121          DATA y_coor_lin11c(4,1),y_coor_lin11c(4,2) /-13.40,-2.47/
122          DATA y_coor_lin11c(5,1),y_coor_lin11c(5,2) /-31.07,-2.32/
123          DATA y_coor_lin11c(6,1),y_coor_lin11c(6,2) /-21.69,-2.63/
124          DATA y_coor_lin11c(7,1),y_coor_lin11c(7,2) /-12.37,-2.65/
125          DATA y_coor_lin11c(8,1),y_coor_lin11c(8,2) /-10.81,-3.15/
126    
127          DATA x_coor_lin12c(1,1),x_coor_lin12c(1,2) /12.96, -2.65/
128          DATA x_coor_lin12c(2,1),x_coor_lin12c(2,2) /17.12,-2.44/
129          DATA x_coor_lin12c(3,1),x_coor_lin12c(3,2) /7.26, -1.98/
130          DATA x_coor_lin12c(4,1),x_coor_lin12c(4,2) /-22.52,-2.27/
131          DATA x_coor_lin12c(5,1),x_coor_lin12c(5,2) /-18.54,-2.28/
132          DATA x_coor_lin12c(6,1),x_coor_lin12c(6,2) /-7.67,-2.15/
133    
134          DATA x_coor_lin21c(1,1),x_coor_lin21c(1,2) /22.56,-1.56/
135          DATA x_coor_lin21c(2,1),x_coor_lin21c(2,2) /13.94,-1.56/
136    
137          DATA y_coor_lin22c(1,1),y_coor_lin22c(1,2) /-24.24,-2.23/
138          DATA y_coor_lin22c(2,1),y_coor_lin22c(2,2) /-45.99,-1.68/
139    
140          DATA y_coor_lin31c(1,1),y_coor_lin31c(1,2) /-22.99,-3.54/
141          DATA y_coor_lin31c(2,1),y_coor_lin31c(2,2) /-42.28,-4.10/
142          DATA y_coor_lin31c(3,1),y_coor_lin31c(3,2) /-41.29,-3.69/
143    
144          DATA x_coor_lin32c(1,1),x_coor_lin32c(1,2) /0.961, -3.22/
145          DATA x_coor_lin32c(2,1),x_coor_lin32c(2,2) /4.98,-3.48/
146          DATA x_coor_lin32c(3,1),x_coor_lin32c(3,2) /-22.08,-3.37/
147    
148    C---
149    
         
         
         
150        INTEGER ihelp        INTEGER ihelp
151        REAL xkorr        REAL xkorr,xpos
152    
153          INTEGER IZ
154          REAL k1corrA1,k1corrB1,k1corrC1
155    
156        REAL yl,yh,xl,xh        REAL yl,yh,xl,xh
157  C      C
158        REAL hmemor(9000000)        REAL hmemor(9000000)
159        INTEGER Iquest(100)        INTEGER Iquest(100)
160  C      C
161          DATA ievent / 0 /
162    
163          INTEGER ifst
164          DATA ifst /0/
165    
166        COMMON / pawcd / hmemor        COMMON / pawcd / hmemor
167        save / pawcd /        save / pawcd /
168  C      C
169        Common / QUESTd / Iquest        Common / QUESTd / Iquest
170        save / questd /        save / questd /
171  C      C
172  C     Begin !  C     Begin !
173  C      C
174        TOFTRK = 0        TOFTRK = 0
175    
176  *******************************************************************  *******************************************************************
177    
178           if (ifst.eq.0) then
179           ifst=1
180    
181    C  ratio helium to proton ca. 4
182          hepratio = 4.
183    
184        offset = 1        offset = 1
185        slope = 2        slope = 2
186        left = 1        left = 1
# Line 77  C     Line 192  C    
192        itdc = 1        itdc = 1
193        iadc = 2        iadc = 2
194    
195    
196          k1corrA1 = 0.
197          k1corrB1 = -5.0
198          k1corrC1=  8.0
199    
200          ENDIF   ! ifst
201    
202    *******************************************************************
203    
204          ievent = ievent +1
205    
206        do i=1,13        do i=1,13
207           beta_a(i) = 100.           beta_a(i) = 100.
208        enddo        enddo
209    
210  C------ read  tracking routine        do i=1,4
211             do j=1,12
212                adc_c(i,j) = 1000.
213             enddo
214          enddo
215    
216          do i=1,12
217             do j=1,4
218                tofmask(j,i) = 0
219             enddo
220          enddo
221    
222          do i=1,4
223             do j=1,12
224                adcflag(i,j) = 0
225             enddo
226          enddo
227    
228          do i=1,4
229             do j=1,12
230                tdcflag(i,j) = 0
231             enddo
232          enddo
233    
234          pmt_id=0
235    
236          do j=1,6
237          THXOUT(j) = 0.
238          THYOUT(j) = 0.
239          enddo
240    
241          do j=1,6
242          xtr_tof(j) = 100.
243          ytr_tof(j) = 100.
244          enddo
245    
246    
247    C----------------------------------------------------------------------
248    C-------------------------get ToF data --------------------------------
249    C     we cannot use the tofxx(x,x,x)  data  from tofl2com since it is
250    C     manipulated (Time-walk, artificila ADc and TDC values using ToF
251    C     standalone information
252    C----------------------------------------------------------------------
253    
254    c     put the adc and tdc values from ntuple into tofxx(i,j,k) variables
255    
256          do j=1,8
257             tof11(1,j,2) = pc_adc(adc(ch11a(j),hb11a(j)))
258             tof11(2,j,2) = pc_adc(adc(ch11b(j),hb11b(j)))
259             tof11(1,j,1) = (tdc(ch11a(j),hb11a(j)))
260             tof11(2,j,1) = (tdc(ch11b(j),hb11b(j)))
261          enddo
262    
263    
264          do j=1,6
265             tof12(1,j,2) = pc_adc(adc(ch12a(j),hb12a(j)))
266             tof12(2,j,2) = pc_adc(adc(ch12b(j),hb12b(j)))
267             tof12(1,j,1) = (tdc(ch12a(j),hb12a(j)))
268             tof12(2,j,1) = (tdc(ch12b(j),hb12b(j)))
269          enddo
270    
271          do j=1,2
272             tof21(1,j,2) = pc_adc(adc(ch21a(j),hb21a(j)))
273             tof21(2,j,2) = pc_adc(adc(ch21b(j),hb21b(j)))
274             tof21(1,j,1) = (tdc(ch21a(j),hb21a(j)))
275             tof21(2,j,1) = (tdc(ch21b(j),hb21b(j)))
276          enddo
277    
278          do j=1,2
279             tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j)))
280             tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j)))
281             tof22(1,j,1) = (tdc(ch22a(j),hb22a(j)))
282             tof22(2,j,1) = (tdc(ch22b(j),hb22b(j)))
283          enddo
284    
285          do j=1,3
286             tof31(1,j,2) = pc_adc(adc(ch31a(j),hb31a(j)))
287             tof31(2,j,2) = pc_adc(adc(ch31b(j),hb31b(j)))
288             tof31(1,j,1) = (tdc(ch31a(j),hb31a(j)))
289             tof31(2,j,1) = (tdc(ch31b(j),hb31b(j)))
290          enddo
291    
292          do j=1,3
293             tof32(1,j,2) = pc_adc(adc(ch32a(j),hb32a(j)))
294             tof32(2,j,2) = pc_adc(adc(ch32b(j),hb32b(j)))
295             tof32(1,j,1) = (tdc(ch32a(j),hb32a(j)))
296             tof32(2,j,1) = (tdc(ch32b(j),hb32b(j)))
297          enddo
298    
299    C----------------------------------------------------------------------
300    
301          DO i = 1,8
302             if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000.
303             if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000.
304             if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000.
305             if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000.
306          ENDDO
307    
308          DO i = 1,6
309             if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000.
310             if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000.
311             if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000.
312             if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000.
313          ENDDO
314    
315    
316          DO i = 1,2
317             if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000.
318             if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000.
319             if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000.
320             if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000.
321          ENDDO
322    
323          DO i = 1,2
324             if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000.
325             if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000.
326             if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000.
327             if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000.
328          ENDDO
329    
330          DO i = 1,3
331             if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000.
332             if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000.
333             if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000.
334             if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000.
335          ENDDO
336    
337          DO i = 1,3
338             if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000.
339             if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000.
340             if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000.
341             if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
342          ENDDO
343    
344    C----------------------------------------------------------------------
345    
346    C------read  tracking routine
347  *     igoodevent = igoodevent+1  *     igoodevent = igoodevent+1
348  *     assigned input  parameters for track routine  *     assigned input  parameters for track routine
349  *     1) Z-coordinates where the trajectory is evaluated  *     1) Z-coordinates where the trajectory is evaluated
# Line 93  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 355  C     COPY THE ALFA VECTOR FROM AL_PP TO
355        do i=1,5        do i=1,5
356           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
357        enddo        enddo
358    
359    c      write(*,*) AL_P
360    c      write(*,*) 'Rigidity ',(1./AL_P(5))
361    
362        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
363           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'  c         PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
364           GOTO 969           GOTO 969
365        ENDIF        ENDIF
366  *     -------- *** tracking routine *** --------  *     -------- *** tracking routine *** --------
367        IFAIL = 0        IFAIL = 0
368        call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)  C     call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
369          call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
370    
371    C     write(*,*) (TLOUT(i),i=1,6)
372    
373        if(IFAIL.ne.0)then        if(IFAIL.ne.0)then
374           print *,' TOF - WARNING F77: tracking failed '  c         print *,' TOF - WARNING F77: tracking failed '
375           goto 969           goto 969
376        endif        endif
377  *     ------------------------------------------  *     ------------------------------------------
378    
379  969   continue   969  continue
380    
381    C---  Fill xtr_tof  and ytr_tof: positions from tracker at ToF layers
382          do j=1,6
383          xtr_tof(j) = XOUT(j)
384          ytr_tof(j) = YOUT(j)
385    c      write(*,*) XOUT(j),YOUT(j)
386          enddo
387    
388    
389    C---  convert  angles to radian
390          do j=1,6
391          THXOUT(j) = 3.1415927*THXOUT(j)/180.
392          THYOUT(j) = 3.1415927*THYOUT(j)/180.
393          enddo
394    
395          do j=1,6
396    c      write (*,*) j,THXOUT(j),THYOUT(j)
397          enddo
398    
399    
400    C----------------------------------------------------------------------
401    C------------------  set ADC & TDC flag = 0    ------------------------
402    C----------------------------------------------------------------------
403    
404          do j=1,8
405          if (adc(ch11a(j),hb11a(j)).LT.4096)adcflagtof(ch11a(j),hb11a(j))=0
406          if (adc(ch11b(j),hb11b(j)).LT.4096)adcflagtof(ch11b(j),hb11b(j))=0
407          if (tdc(ch11a(j),hb11a(j)).LT.4096)tdcflagtof(ch11a(j),hb11a(j))=0
408          if (tdc(ch11b(j),hb11b(j)).LT.4096)tdcflagtof(ch11b(j),hb11b(j))=0
409          enddo
410          do j=1,6
411          if (adc(ch12a(j),hb12a(j)).LT.4096)adcflagtof(ch12a(j),hb12a(j))=0
412          if (adc(ch12b(j),hb12b(j)).LT.4096)adcflagtof(ch12b(j),hb12b(j))=0
413          if (tdc(ch12a(j),hb12a(j)).LT.4096)tdcflagtof(ch12a(j),hb12a(j))=0
414          if (tdc(ch12b(j),hb12b(j)).LT.4096)tdcflagtof(ch12b(j),hb12b(j))=0
415          enddo
416          do j=1,2
417          if (adc(ch21a(j),hb21a(j)).LT.4096)adcflagtof(ch21a(j),hb21a(j))=0
418          if (adc(ch21b(j),hb21b(j)).LT.4096)adcflagtof(ch21b(j),hb21b(j))=0
419          if (tdc(ch21a(j),hb21a(j)).LT.4096)tdcflagtof(ch21a(j),hb21a(j))=0
420          if (tdc(ch21b(j),hb21b(j)).LT.4096)tdcflagtof(ch21b(j),hb21b(j))=0
421          enddo
422          do j=1,2
423          if (adc(ch22a(j),hb22a(j)).LT.4096)adcflagtof(ch22a(j),hb22a(j))=0
424          if (adc(ch22b(j),hb22b(j)).LT.4096)adcflagtof(ch22b(j),hb22b(j))=0
425          if (tdc(ch22a(j),hb22a(j)).LT.4096)tdcflagtof(ch22a(j),hb22a(j))=0
426          if (tdc(ch22b(j),hb22b(j)).LT.4096)tdcflagtof(ch22b(j),hb22b(j))=0
427          enddo
428          do j=1,3
429          if (adc(ch31a(j),hb31a(j)).LT.4096)adcflagtof(ch31a(j),hb31a(j))=0
430          if (adc(ch31b(j),hb31b(j)).LT.4096)adcflagtof(ch31b(j),hb31b(j))=0
431          if (tdc(ch31a(j),hb31a(j)).LT.4096)tdcflagtof(ch31a(j),hb31a(j))=0
432          if (tdc(ch31b(j),hb31b(j)).LT.4096)tdcflagtof(ch31b(j),hb31b(j))=0
433          enddo
434          do j=1,3
435          if (adc(ch32a(j),hb32a(j)).LT.4096)adcflagtof(ch32a(j),hb32a(j))=0
436          if (adc(ch32b(j),hb32b(j)).LT.4096)adcflagtof(ch32b(j),hb32b(j))=0
437          if (tdc(ch32a(j),hb32a(j)).LT.4096)tdcflagtof(ch32a(j),hb32a(j))=0
438          if (tdc(ch32b(j),hb32b(j)).LT.4096)tdcflagtof(ch32b(j),hb32b(j))=0
439          enddo
440    
441    
442    C----------------------------------------------------------------
443    C---------- Check PMTs 10 and 35 for strange TDC values----------
444    C----------------------------------------------------------------
445    
446    C---- S116A TDC=819
447           if (tof11(1,6,1).EQ.819) then
448                 tof11(1,6,1) = 4095
449                 tdcflagtof(ch11a(6),hb11a(6))=2
450           endif
451    
452    C---- S222B TDC=819
453           if (tof22(2,2,1).EQ.819) then
454                 tof22(2,2,1) = 4095
455                 tdcflagtof(ch22b(2),hb22b(2))=2
456           endif
457    
458  C-------------------------------------------------------------  C-------------------------------------------------------------
459  C-------  check which paddle penetrated the track  -----------  C-------check which paddle penetrated the track  -----------
460  C-------------------------------------------------------------  C-------------------------------------------------------------
461  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
462  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/
463  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/
464  c       DATA tof21_y/ -3.75,3.75/  c     DATA tof21_y/  3.75,-3.75/  ! paddles in different order
465  c       DATA tof22_x/ -4.5,4.5/  c     DATA tof22_x/ -4.5,4.5/
466  c       DATA tof31_x/ -6.0,0.,6.0/  c     DATA tof31_x/ -6.0,0.,6.0/
467  c       DATA tof32_y/ -5.0,0.0,5.0/  c     DATA tof32_y/ -5.0,0.0,5.0/
468  c  c
469  c  S11 8 paddles  33.0 x 5.1 cm  c     S11 8 paddles  33.0 x 5.1 cm
470  c  S12 6 paddles  40.8 x 5.5 cm  c     S12 6 paddles  40.8 x 5.5 cm
471  c  S21 2 paddles  18.0 x 7.5 cm  c     S21 2 paddles  18.0 x 7.5 cm
472  c  S22 2 paddles  15.0 x 9.0 cm  c     S22 2 paddles  15.0 x 9.0 cm
473  c  S31 3 paddles  15.0 x 6.0 cm  c     S31 3 paddles  15.0 x 6.0 cm
474  c  S32 3 paddles  18.0 x 5.0 cm  c     S32 3 paddles  18.0 x 5.0 cm
475    
476    
477  C--------------     S11 --------------------------------------  C--------------S11 --------------------------------------
478    
479        tof11_i = none_find        tof11_i = none_find
480    
# Line 135  C--------------     S11 ---------------- Line 482  C--------------     S11 ----------------
482        yh =  33.0/2.        yh =  33.0/2.
483    
484        if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then        if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then
485        do i=1,8           do i=1,8
486        xl = tof11_x(i) - 5.1/2.              xl = tof11_x(i) - 5.1/2.
487        xh = tof11_x(i) + 5.1/2.              xh = tof11_x(i) + 5.1/2.
488        if ((xout(1).gt.xl).and.(xout(1).le.xh)) then              if ((xout(1).gt.xl).and.(xout(1).le.xh)) then
489        tof11_i=i                 tof11_i=i
490        endif              endif
491        enddo           enddo
492        endif        endif
493    
494  C--------------     S12 --------------------------------------  C--------------S12 --------------------------------------
495    
496        tof12_i = none_find        tof12_i = none_find
497    
498        xl = -40.8/2.        xl = -40.8/2.
499        xh =  40.8/2.        xh =  40.8/2.
500    
501        if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then        if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then
502        do i=1,6           do i=1,6
503        yl = tof12_y(i) - 5.5/2.              yl = tof12_y(i) - 5.5/2.
504        yh = tof12_y(i) + 5.5/2.              yh = tof12_y(i) + 5.5/2.
505        if ((yout(2).gt.yl).and.(yout(2).le.yh)) then              if ((yout(2).gt.yl).and.(yout(2).le.yh)) then
506        tof12_i=i                 tof12_i=i
507        endif              endif
508        enddo           enddo
509        endif        endif
510    
511  C--------------     S21 --------------------------------------  C--------------S21 --------------------------------------
512    
513        tof21_i = none_find        tof21_i = none_find
514    
515        xl = -18./2.        xl = -18./2.
516        xh =  18./2.        xh =  18./2.
517    
518        if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then        if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then
519        do i=1,2           do i=1,2
520        yl = tof21_y(i) - 7.5/2.              yl = tof21_y(i) - 7.5/2.
521        yh = tof21_y(i) + 7.5/2.              yh = tof21_y(i) + 7.5/2.
522        if ((yout(3).gt.yl).and.(yout(3).le.yh)) then              if ((yout(3).gt.yl).and.(yout(3).le.yh)) then
523        tof21_i=i                 tof21_i=i
524        endif              endif
525        enddo           enddo
526        endif        endif
527    
528  C--------------     S22 --------------------------------------  C--------------S22 --------------------------------------
529    
530        tof22_i = none_find        tof22_i = none_find
531    
532        yl = -15./2.        yl = -15./2.
533        yh =  15./2.        yh =  15./2.
534    
535        if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then        if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then
536        do i=1,2           do i=1,2
537        xl = tof22_x(i) - 9.0/2.              xl = tof22_x(i) - 9.0/2.
538        xh = tof22_x(i) + 9.0/2.              xh = tof22_x(i) + 9.0/2.
539        if ((xout(4).gt.xl).and.(xout(4).le.xh)) then              if ((xout(4).gt.xl).and.(xout(4).le.xh)) then
540        tof22_i=i                 tof22_i=i
541        endif              endif
542        enddo           enddo
543        endif        endif
544    
545  C--------------     S31 --------------------------------------  C--------------S31 --------------------------------------
546    
547        tof31_i = none_find        tof31_i = none_find
548    
549        yl = -15.0/2.        yl = -15.0/2.
550        yh =  15.0/2.        yh =  15.0/2.
551    
552        if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then        if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then
553        do i=1,3           do i=1,3
554        xl = tof31_x(i) - 6.0/2.              xl = tof31_x(i) - 6.0/2.
555        xh = tof31_x(i) + 6.0/2.              xh = tof31_x(i) + 6.0/2.
556        if ((xout(5).gt.xl).and.(xout(5).le.xh)) then              if ((xout(5).gt.xl).and.(xout(5).le.xh)) then
557        tof31_i=i                 tof31_i=i
558        endif              endif
559        enddo           enddo
560        endif        endif
561    
562  C--------------     S32 --------------------------------------  C--------------S32 --------------------------------------
563    
564        tof32_i = none_find        tof32_i = none_find
565    
566        xl = -18.0/2.        xl = -18.0/2.
567        xh =  18.0/2.        xh =  18.0/2.
568    
569        if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then        if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then
570        do i=1,3           do i=1,3
571        yl = tof32_y(i) - 5.0/2.              yl = tof32_y(i) - 5.0/2.
572        yh = tof32_y(i) + 5.0/2.              yh = tof32_y(i) + 5.0/2.
573        if ((yout(6).gt.yl).and.(yout(6).le.yh)) then              if ((yout(6).gt.yl).and.(yout(6).le.yh)) then
574        tof32_i=i                 tof32_i=i
575        endif              endif
576        enddo           enddo
577        endif        endif
578    
579    
580    
581           hitvec(1)=tof11_i
582           hitvec(2)=tof12_i
583           hitvec(3)=tof21_i
584           hitvec(4)=tof22_i
585           hitvec(5)=tof31_i
586           hitvec(6)=tof32_i
587    
588    
589  C----------------------------------------------------------------------  C----------------------------------------------------------------------
590  C--------------------Corrections on ADC-data -------------------------  C--- check charge:
591  C---------------------zenith angle theta  ---------------------------  C--- if Z=2 we should use the attenuation curve for helium to
592    C--- fill the artificail ADC values and NOT divide by "hepratio"
593    C--- if Z>2 we should do a correction to
594    C--- the k1 constants in the beta calculation
595  C----------------------------------------------------------------------  C----------------------------------------------------------------------
596    
597           theta=0.  
598           dist = ZTOF(1) - ZTOF(5)
599           dl = 0.
600           DO I=1,5
601             dl = dl + TLOUT(i)
602           ENDDO
603           F = dl/dist
604           theta = acos(1/F)
605    
606           iz = int(check_charge(theta,hitvec))
607    c       write(*,*) 'in toftrk',iz
608    
609    
610    C-------------------------------  new  ---------------------------
611    C--  calculate track position in paddle using timing difference
612    C--  this calculation is preliminary and uses some standard
613    C--  calibration values, but we need to find a rough position to
614    C--  be able to calculate artificial ADC values (needed for the
615    C--  timewalk...
616    C------------------------------------------------------------------
617    
618           do i=1,3
619             xtofpre(i)=100.
620             ytofpre(i)=100.
621           enddo
622    
623    C-----------------------------S1 --------------------------------
624    
625        dx=0.        IF (tof11_i.GT.none_find) THEN
626        dy=0.        IF ((tof11(1,tof11_i,itdc).LT.2000).AND.
627        dr=0.       +                             (tof11(2,tof11_i,itdc).LT.2000))
628        theta13 = 0.       +    ytofpre(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
629         +   -y_coor_lin11c(tof11_i,offset))/y_coor_lin11c(tof11_i,slope)
       if (xout(1).lt.100.) then  
          dx = xout(1)-xout(6)  
          dy = yout(1)-yout(6)  
          dr = sqrt(dx*dx+dy*dy)  
          theta13 = atan(dr/tofarm13)  
630        endif        endif
631    
632          IF (tof12_i.GT.none_find) THEN
633          IF ((tof12(1,tof12_i,itdc).LT.2000).AND.
634         +                             (tof12(2,tof12_i,itdc).LT.2000))
635         +    xtofpre(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
636         +   -x_coor_lin12c(tof12_i,offset))/x_coor_lin12c(tof12_i,slope)
637          endif
638    
639    
640    C-----------------------------S2 --------------------------------
641    
642          IF (tof21_i.GT.none_find) THEN
643          IF ((tof21(1,tof21_i,itdc).LT.2000).AND.
644         +                             (tof21(2,tof21_i,itdc).LT.2000))
645         +    xtofpre(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
646         +    -x_coor_lin21c(tof21_i,offset))/x_coor_lin21c(tof21_i,slope)
647          endif
648    
649          IF (tof22_i.GT.none_find) THEN
650          IF ((tof22(1,tof22_i,itdc).LT.2000).AND.
651         +                             (tof22(2,tof22_i,itdc).LT.2000))
652         +    ytofpre(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
653         +    -y_coor_lin22c(tof22_i,offset))/y_coor_lin22c(tof22_i,slope)
654          endif
655    
656    
657    C-----------------------------S3 --------------------------------
658    
659          IF (tof31_i.GT.none_find) THEN
660          IF ((tof31(1,tof31_i,itdc).LT.2000).AND.
661         +                             (tof31(2,tof31_i,itdc).LT.2000))
662         +    ytofpre(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
663         +    -y_coor_lin31c(tof31_i,offset))/y_coor_lin31c(tof31_i,slope)
664          endif
665    
666          IF (tof32_i.GT.none_find) THEN
667          IF ((tof32(1,tof32_i,itdc).LT.2000).AND.
668         +                             (tof32(2,tof32_i,itdc).LT.2000))
669         +    xtofpre(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
670         +    -x_coor_lin32c(tof32_i,offset))/x_coor_lin32c(tof32_i,slope)
671          endif
672    
673    
674    C--  restrict TDC measurements to physical paddle dimensions +/- 10 cm
675    
676            if (abs(xtofpre(1)).gt.31.)  xtofpre(1)=100.
677            if (abs(xtofpre(2)).gt.19.)  xtofpre(2)=100.
678            if (abs(xtofpre(3)).gt.19.)  xtofpre(3)=100.
679    
680            if (abs(ytofpre(1)).gt.26.)  ytofpre(1)=100.
681            if (abs(ytofpre(2)).gt.18.)  ytofpre(2)=100.
682            if (abs(ytofpre(3)).gt.18.)  ytofpre(3)=100.
683    
684    C--------------------------------------------------------------------
685    C---- if paddle hit: if we have TDC value but no ADC, create ADC value
686    C---- use the "pre" position if possible, since this gives better time
687    C---- resolution ... october 2008
688    C--------------------------------------------------------------------
689    c     middle y (or x) position of the upper and middle ToF-Paddle
690    c     DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
691    c     DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
692    c     DATA tof21_y/  3.75,-3.75/  ! paddles in different order
693    c     DATA tof22_x/ -4.5,4.5/
694    c     DATA tof31_x/ -6.0,0.,6.0/
695    c     DATA tof32_y/ -5.0,0.0,5.0/
696    
697    C----------------------------S1 -------------------------------------
698    
699    c     yhelp=yout(1)
700          yhelp = ytofpre(1)
701          if (yhelp.eq.100) yhelp=yout(1)
702    
703          IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
704             i = tof11_i
705             if ((tdc(ch11a(i),hb11a(i)).lt.4095).AND.
706         &       (adc(ch11a(i),hb11a(i)).eq.4095)) then
707                phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
708                theta = atan(tan(THXOUT(1))/cos(phi))
709                xkorr = atten(left,11,i,yhelp)
710                if (iz.le.1) xkorr=xkorr/hepratio
711                tof11(left,i,iadc)=xkorr/cos(theta)
712                adcflag(ch11a(i),hb11a(i)) = 1
713             endif
714             if ((tdc(ch11b(i),hb11b(i)).lt.4095).AND.
715         &       (adc(ch11b(i),hb11b(i)).eq.4095)) then
716                phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
717                theta = atan(tan(THXOUT(1))/cos(phi))
718                xkorr = atten(right,11,i,yhelp)
719                if (iz.le.1) xkorr=xkorr/hepratio
720                tof11(right,i,iadc)=xkorr/cos(theta)
721                adcflag(ch11b(i),hb11b(i)) = 1
722             endif
723          ENDIF
724    
725    c      xhelp=xout(2)
726          xhelp = xtofpre(1)
727          if (xhelp.eq.100) xhelp=xout(2)
728    
729          IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
730             i = tof12_i
731             if ((tdc(ch12a(i),hb12a(i)).lt.4095).AND.
732         &       (adc(ch12a(i),hb12a(i)).eq.4095)) then
733                phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
734                theta = atan(tan(THXOUT(2))/cos(phi))
735    c            xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
736                xkorr = atten(left,12,i,xhelp)
737                if (iz.le.1) xkorr=xkorr/hepratio
738                tof12(left,i,iadc) = xkorr/cos(theta)
739                adcflag(ch12a(i),hb12a(i)) = 1
740             endif
741             if ((tdc(ch12b(i),hb12b(i)).lt.4095).AND.
742         &       (adc(ch12b(i),hb12b(i)).eq.4095)) then
743                phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
744                theta = atan(tan(THXOUT(2))/cos(phi))
745    c            xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
746                xkorr = atten(right,12,i,xhelp)
747                if (iz.le.1) xkorr=xkorr/hepratio
748                tof12(right,i,iadc) = xkorr/cos(theta)
749                adcflag(ch12b(i),hb12b(i)) = 1
750             endif
751          ENDIF
752    
753    C-----------------------------S2 --------------------------------
754    
755    c      xhelp=xout(3)
756          xhelp = xtofpre(2)
757          if (xhelp.eq.100) xhelp=xout(3)
758    
759          IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
760             i = tof21_i
761             if ((tdc(ch21a(i),hb21a(i)).lt.4095).AND.
762         &       (adc(ch21a(i),hb21a(i)).eq.4095)) then
763                phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
764                theta = atan(tan(THXOUT(3))/cos(phi))
765    c            xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
766                xkorr = atten(left,21,i,xhelp)
767                if (iz.le.1) xkorr=xkorr/hepratio
768                tof21(left,i,iadc) = xkorr/cos(theta)
769                adcflag(ch21a(i),hb21a(i)) = 1
770             endif
771             if ((tdc(ch21b(i),hb21b(i)).lt.4095).AND.
772         &       (adc(ch21b(i),hb21b(i)).eq.4095)) then
773                phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
774                theta = atan(tan(THXOUT(3))/cos(phi))
775    c            xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
776                xkorr = atten(right,21,i,xhelp)
777                if (iz.le.1) xkorr=xkorr/hepratio
778                tof21(right,i,iadc) = xkorr/cos(theta)
779                adcflag(ch21b(i),hb21b(i)) = 1
780             endif
781          ENDIF
782    
783    
784    c      yhelp=yout(4)
785          yhelp = ytofpre(2)
786          if (yhelp.eq.100) yhelp=yout(4)
787    
788          IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
789             i = tof22_i
790             if ((tdc(ch22a(i),hb22a(i)).lt.4095).AND.
791         &       (adc(ch22a(i),hb22a(i)).eq.4095)) then
792                phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
793                theta = atan(tan(THXOUT(4))/cos(phi))
794    c            xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
795                xkorr = atten(left,22,i,yhelp)
796                if (iz.le.1) xkorr=xkorr/hepratio
797                tof22(left,i,iadc) = xkorr/cos(theta)
798                adcflag(ch22a(i),hb22a(i)) = 1
799             endif
800             if ((tdc(ch22b(i),hb22b(i)).lt.4095).AND.
801         &       (adc(ch22b(i),hb22b(i)).eq.4095)) then
802                phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
803                theta = atan(tan(THXOUT(4))/cos(phi))
804    c            xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
805                xkorr = atten(right,22,i,yhelp)
806                if (iz.le.1) xkorr=xkorr/hepratio
807                tof22(right,i,iadc) = xkorr/cos(theta)
808                adcflag(ch22b(i),hb22b(i)) = 1
809             endif
810          ENDIF
811    
812    C-----------------------------S3 --------------------------------
813    
814    c      yhelp=yout(5)
815          yhelp = ytofpre(3)
816          if (yhelp.eq.100) yhelp=yout(5)
817    
818          IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
819             i = tof31_i
820             if ((tdc(ch31a(i),hb31a(i)).lt.4095).AND.
821         &       (adc(ch31a(i),hb31a(i)).eq.4095)) then
822                phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
823                theta = atan(tan(THXOUT(5))/cos(phi))
824    c            xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
825                xkorr = atten(left,31,i,yhelp)
826                if (iz.le.1) xkorr=xkorr/hepratio
827                tof31(left,i,iadc) = xkorr/cos(theta)
828                adcflag(ch31a(i),hb31a(i)) = 1
829             endif
830             if ((tdc(ch31b(i),hb31b(i)).lt.4095).AND.
831         &       (adc(ch31b(i),hb31b(i)).eq.4095)) then
832                phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
833                theta = atan(tan(THXOUT(5))/cos(phi))
834    c            xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
835                xkorr = atten(right,31,i,yhelp)
836                if (iz.le.1) xkorr=xkorr/hepratio
837                tof31(right,i,iadc) = xkorr/cos(theta)
838                adcflag(ch31b(i),hb31b(i)) = 1
839             endif
840          ENDIF
841    
842    
843    c      xhelp=xout(6)
844          xhelp = xtofpre(3)
845          if (xhelp.eq.100) xhelp=xout(6)
846    
847          IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
848             i = tof32_i
849             if ((tdc(ch32a(i),hb32a(i)).lt.4095).AND.
850         &       (adc(ch32a(i),hb32a(i)).eq.4095)) then
851                phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
852                theta = atan(tan(THXOUT(6))/cos(phi))
853    c            xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
854                xkorr = atten(left,32,i,xhelp)
855                if (iz.le.1) xkorr=xkorr/hepratio
856                tof32(left,i,iadc) = xkorr/cos(theta)
857                adcflag(ch32a(i),hb32a(i)) = 1
858             endif
859             if ((tdc(ch32b(i),hb32b(i)).lt.4095).AND.
860         &       (adc(ch32b(i),hb32b(i)).eq.4095)) then
861                phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
862                theta = atan(tan(THXOUT(6))/cos(phi))
863    c            xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
864                xkorr = atten(right,32,i,xhelp)
865                if (iz.le.1) xkorr=xkorr/hepratio
866                tof32(right,i,iadc) = xkorr/cos(theta)
867                adcflag(ch32b(i),hb32b(i)) = 1
868             endif
869          ENDIF
870    
871    C-------------------------------------------------------------------
872    C Now there is for each hitted paddle a TDC and ADC value, if the
873    C TDC was < 4095.
874    C There might be also TDC-ADC pairs in paddles not hitted
875    C Let's correct the raw TDC value with the time walk
876    C-------------------------------------------------------------------
877    C--------------------Time walk correction  -------------------------
878    C-------------------------------------------------------------------
879    
880          DO i=1,8
881             if ((tdc(ch11a(i),hb11a(i)).lt.4095).and.
882         &             (tof11(left,i,iadc).lt.3786)) THEN
883             xhelp = tw11(left,i)/(tof11(left,i,iadc)**0.5)
884             tof11(left,i,itdc) = tof11(left,i,itdc) + xhelp
885             tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
886                                                  ENDIF
887    
888             if ((tdc(ch11b(i),hb11b(i)).lt.4095).and.
889         &             (tof11(right,i,iadc).lt.3786)) THEN
890             xhelp = tw11(right,i)/(tof11(right,i,iadc)**0.5)
891             tof11(right,i,itdc) = tof11(right,i,itdc) + xhelp
892             tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
893                                                 ENDIF
894          ENDDO
895    
896    
897          DO i=1,6
898             if ((tdc(ch12a(i),hb12a(i)).lt.4095).and.
899         &             (tof12(left,i,iadc).lt.3786)) THEN
900             xhelp = tw12(left,i)/(tof12(left,i,iadc)**0.5)
901             tof12(left,i,itdc) = tof12(left,i,itdc) + xhelp
902             tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
903                                                  ENDIF
904    
905             if ((tdc(ch12b(i),hb12b(i)).lt.4095).and.
906         &             (tof12(right,i,iadc).lt.3786)) THEN
907             xhelp = tw12(right,i)/(tof12(right,i,iadc)**0.5)
908             tof12(right,i,itdc) = tof12(right,i,itdc) + xhelp
909             tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
910                                                 ENDIF
911          ENDDO
912    
913    C----
914          DO I=1,2
915             if ((tdc(ch21a(i),hb21a(i)).lt.4095).and.
916         &             (tof21(left,i,iadc).lt.3786)) THEN
917             xhelp = tw21(left,i)/(tof21(left,i,iadc)**0.5)
918             tof21(left,i,itdc) = tof21(left,i,itdc) + xhelp
919             tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
920                                                  ENDIF
921    
922             if ((tdc(ch21b(i),hb21b(i)).lt.4095).and.
923         &             (tof21(right,i,iadc).lt.3786)) THEN
924             xhelp = tw21(right,i)/(tof21(right,i,iadc)**0.5)
925             tof21(right,i,itdc) = tof21(right,i,itdc) + xhelp
926             tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
927                                                 ENDIF
928          ENDDO
929    
930          DO I=1,2
931             if ((tdc(ch22a(i),hb22a(i)).lt.4095).and.
932         &             (tof22(left,i,iadc).lt.3786)) THEN
933             xhelp = tw22(left,i)/(tof22(left,i,iadc)**0.5)
934             tof22(left,i,itdc) = tof22(left,i,itdc) + xhelp
935             tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
936                                                  ENDIF
937    
938             if ((tdc(ch22b(i),hb22b(i)).lt.4095).and.
939         &             (tof22(right,i,iadc).lt.3786)) THEN
940             xhelp = tw22(right,i)/(tof22(right,i,iadc)**0.5)
941             tof22(right,i,itdc) = tof22(right,i,itdc) + xhelp
942             tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
943                                                 ENDIF
944          ENDDO
945    
946    C----
947          DO I=1,3
948             if ((tdc(ch31a(i),hb31a(i)).lt.4095).and.
949         &             (tof31(left,i,iadc).lt.3786)) THEN
950             xhelp = tw31(left,i)/(tof31(left,i,iadc)**0.5)
951             tof31(left,i,itdc) = tof31(left,i,itdc) + xhelp
952             tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
953                                                  ENDIF
954    
955             if ((tdc(ch31b(i),hb31b(i)).lt.4095).and.
956         &             (tof31(right,i,iadc).lt.3786)) THEN
957             xhelp = tw31(right,i)/(tof31(right,i,iadc)**0.5)
958             tof31(right,i,itdc) = tof31(right,i,itdc) + xhelp
959             tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
960                                                 ENDIF
961          ENDDO
962    
963          DO I=1,3
964             if ((tdc(ch32a(i),hb32a(i)).lt.4095).and.
965         &             (tof32(left,i,iadc).lt.3786)) THEN
966             xhelp = tw32(left,i)/(tof32(left,i,iadc)**0.5)
967             tof32(left,i,itdc) = tof32(left,i,itdc) + xhelp
968             tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
969                                                  ENDIF
970    
971             if ((tdc(ch32b(i),hb32b(i)).lt.4095).and.
972         &             (tof32(right,i,iadc).lt.3786)) THEN
973             xhelp = tw32(right,i)/(tof32(right,i,iadc)**0.5)
974             tof32(right,i,itdc) = tof32(right,i,itdc) + xhelp
975             tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
976                                                 ENDIF
977          ENDDO
978    
979    
980    C-----------------------------------------------------------------------
981    C--------------------Insert Artifical TDC Value  ---------------------
982    C     For each Paddle perform check:
983    C     if left paddle=4095  and right paddle OK => create TDC value left
984    C     if right paddle=4095  and left paddle OK => create TDC value right
985    C-----------------------------------------------------------------------
986    
987    C-----------------------S11 -----------------------------------------
988    
989          IF (tof11_i.GT.none_find) THEN
990             xpos = yout(1)
991             i = tof11_i
992            if ((tdc(ch11a(i),hb11a(i)).EQ.4095).AND.
993         &          (tdc(ch11b(i),hb11b(i)).LT.4095)) THEN
994              tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)
995         &           + 2*(y_coor_lin11(tof11_i,offset)
996         &           + xpos*y_coor_lin11(tof11_i,slope))
997                tdcflag(ch11a(i),hb11a(i)) = 1
998            ENDIF
999    
1000            if ((tdc(ch11b(i),hb11b(i)).EQ.4095).AND.
1001         &          (tdc(ch11a(i),hb11a(i)).LT.4095)) THEN
1002                tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)
1003         &           - 2*(y_coor_lin11(tof11_i,offset)
1004         &           + xpos*y_coor_lin11(tof11_i,slope))
1005                tdcflag(ch11b(i),hb11b(i)) = 1
1006             ENDIF
1007    
1008          ENDIF
1009    
1010    C-----------------------S12 -----------------------------------------
1011    
1012          IF (tof12_i.GT.none_find) THEN
1013             xpos = xout(2)
1014             i = tof12_i
1015            if ((tdc(ch12a(i),hb12a(i)).EQ.4095).AND.
1016         &          (tdc(ch12b(i),hb12b(i)).LT.4095)) THEN
1017                tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)
1018         &           + 2*(x_coor_lin12(tof12_i,offset)
1019         &           + xpos*x_coor_lin12(tof12_i,slope))
1020                tdcflag(ch12a(i),hb12a(i)) = 1
1021             ENDIF
1022    
1023            if ((tdc(ch12b(i),hb12b(i)).EQ.4095).AND.
1024         &          (tdc(ch12a(i),hb12a(i)).LT.4095)) THEN
1025                tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)
1026         &           - 2*(x_coor_lin12(tof12_i,offset)
1027         &           + xpos*x_coor_lin12(tof12_i,slope))
1028                tdcflag(ch12b(i),hb12b(i)) = 1
1029             ENDIF
1030          ENDIF
1031    
1032    C-----------------------S21 -----------------------------------------
1033    
1034          IF (tof21_i.GT.none_find) THEN
1035             xpos = xout(3)
1036             i = tof21_i
1037            if ((tdc(ch21a(i),hb21a(i)).EQ.4095).AND.
1038         &          (tdc(ch21b(i),hb21b(i)).LT.4095)) THEN
1039                tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)
1040         &           + 2*(x_coor_lin21(tof21_i,offset)
1041         &           + xpos*x_coor_lin21(tof21_i,slope))
1042                tdcflag(ch21a(i),hb21a(i)) = 1
1043             ENDIF
1044    
1045            if ((tdc(ch21b(i),hb21b(i)).EQ.4095).AND.
1046         &          (tdc(ch21a(i),hb21a(i)).LT.4095)) THEN
1047                tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)
1048         &           - 2*(x_coor_lin21(tof21_i,offset)
1049         &           + xpos*x_coor_lin21(tof21_i,slope))
1050                tdcflag(ch21b(i),hb21b(i)) = 1
1051             ENDIF
1052          ENDIF
1053    
1054    C-----------------------S22 -----------------------------------------
1055    
1056          IF (tof22_i.GT.none_find) THEN
1057             xpos = yout(4)
1058             i = tof22_i
1059            if ((tdc(ch22a(i),hb22a(i)).EQ.4095).AND.
1060         &          (tdc(ch22b(i),hb22b(i)).LT.4095)) THEN
1061                tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)
1062         &           + 2*(y_coor_lin22(tof22_i,offset)
1063         &           + xpos*y_coor_lin22(tof22_i,slope))
1064                tdcflag(ch22a(i),hb22a(i)) = 1
1065             ENDIF
1066    
1067            if ((tdc(ch22b(i),hb22b(i)).EQ.4095).AND.
1068         &          (tdc(ch22a(i),hb22a(i)).LT.4095)) THEN
1069                tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)
1070         &           - 2*(y_coor_lin22(tof22_i,offset)
1071         &           + xpos*y_coor_lin22(tof22_i,slope))
1072                tdcflag(ch22b(i),hb22b(i)) = 1
1073             ENDIF
1074          ENDIF
1075    
1076    C-----------------------S31 -----------------------------------------
1077    
1078          IF (tof31_i.GT.none_find) THEN
1079             xpos = yout(5)
1080             i = tof31_i
1081            if ((tdc(ch31a(i),hb31a(i)).EQ.4095).AND.
1082         &          (tdc(ch31b(i),hb31b(i)).LT.4095)) THEN
1083                tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)
1084         &           + 2*(y_coor_lin31(tof31_i,offset)
1085         &           + xpos*y_coor_lin31(tof31_i,slope))
1086                tdcflag(ch31a(i),hb31a(i)) = 1
1087             ENDIF
1088    
1089            if ((tdc(ch31b(i),hb31b(i)).EQ.4095).AND.
1090         &          (tdc(ch31a(i),hb31a(i)).LT.4095)) THEN
1091                tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)
1092         &           - 2*(y_coor_lin31(tof31_i,offset)
1093         &           + xpos*y_coor_lin31(tof31_i,slope))
1094                tdcflag(ch31b(i),hb31b(i)) = 1
1095             ENDIF
1096          ENDIF
1097    
1098    C-----------------------S32 -----------------------------------------
1099    
1100          IF (tof32_i.GT.none_find) THEN
1101             xpos = xout(6)
1102             i = tof32_i
1103            if ((tdc(ch32a(i),hb32a(i)).EQ.4095).AND.
1104         &          (tdc(ch32b(i),hb32b(i)).LT.4095)) THEN
1105                tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)
1106         &           + 2*(x_coor_lin32(tof32_i,offset)
1107         &           + xpos*x_coor_lin32(tof32_i,slope))
1108                tdcflag(ch32a(i),hb32a(i)) = 1
1109             ENDIF
1110    
1111            if ((tdc(ch32b(i),hb32b(i)).EQ.4095).AND.
1112         &          (tdc(ch32a(i),hb32a(i)).LT.4095)) THEN
1113                tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)
1114         &           - 2*(x_coor_lin32(tof32_i,offset)
1115         &           + xpos*x_coor_lin32(tof32_i,slope))
1116                tdcflag(ch32b(i),hb32b(i)) = 1
1117             ENDIF
1118          ENDIF
1119    
1120    
1121    C------------------------------------------------------------------
1122    C---  calculate track position in paddle using timing difference
1123    C------------------------------------------------------------------
1124    
1125          do i=1,3
1126             xtofpos(i)=100.
1127             ytofpos(i)=100.
1128          enddo
1129    
 C----------------------------------------------------------------------  
 C------------------angle and ADC(x) correction  
 C----------------------------------------------------------------------  
1130  C-----------------------------S1 --------------------------------  C-----------------------------S1 --------------------------------
1131    
1132          IF (tof11_i.GT.none_find) THEN
1133             IF ((tof11(1,tof11_i,itdc).NE.4095).AND.
1134         &       (tof11(2,tof11_i,itdc).NE.4095)) THEN
1135             ytofpos(1)  = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
1136         +        -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
1137            if (abs(ytofpos(1)).gt.26.)  ytofpos(1)=101.
1138          i=tof11_i
1139          endif
1140          endif
1141    
1142          IF (tof12_i.GT.none_find) THEN
1143             IF ((tof12(1,tof12_i,itdc).NE.4095).AND.
1144         &       (tof12(2,tof12_i,itdc).NE.4095)) THEN
1145             xtofpos(1)  = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
1146         +        -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
1147            if (abs(xtofpos(1)).gt.31.)  xtofpos(1)=101.
1148          i=tof12_i
1149          endif
1150          endif
1151    
1152    C-----------------------------S2 --------------------------------
1153    
1154          IF (tof21_i.GT.none_find) THEN
1155             IF ((tof21(1,tof21_i,itdc).NE.4095).AND.
1156         &       (tof21(2,tof21_i,itdc).NE.4095)) THEN
1157             xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
1158         +        -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
1159            if (abs(xtofpos(2)).gt.19.)  xtofpos(2)=101.
1160          i=tof21_i
1161          endif
1162          endif
1163    
1164          IF (tof22_i.GT.none_find) THEN
1165             IF ((tof22(1,tof22_i,itdc).NE.4095).AND.
1166         &       (tof22(2,tof22_i,itdc).NE.4095)) THEN
1167             ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
1168         +        -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
1169            if (abs(ytofpos(2)).gt.18.)  ytofpos(2)=101.
1170          i=tof22_i
1171          endif
1172          endif
1173    
1174    C-----------------------------S3 --------------------------------
1175    
1176          IF (tof31_i.GT.none_find) THEN
1177             IF ((tof31(1,tof31_i,itdc).NE.4095).AND.
1178         &       (tof31(2,tof31_i,itdc).NE.4095)) THEN
1179             ytofpos(3)  = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
1180         +        -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
1181            if (abs(ytofpos(3)).gt.18.)  ytofpos(3)=101.
1182          i=tof31_i
1183          endif
1184          endif
1185    
1186          IF (tof32_i.GT.none_find) THEN
1187             IF ((tof32(1,tof32_i,itdc).NE.4095).AND.
1188         &       (tof32(2,tof32_i,itdc).NE.4095)) THEN
1189             xtofpos(3)  = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
1190         +        -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
1191            if (abs(xtofpos(3)).gt.19.)  xtofpos(3)=101.
1192          i=tof32_i
1193          endif
1194          endif
1195    
1196    c      do i=1,3
1197    c         if (abs(xtofpos(i)).gt.100.) then
1198    c            xtofpos(i)=101.
1199    c         endif
1200    c         if (abs(ytofpos(i)).gt.100.) then
1201    c            ytofpos(i)=101.
1202    c         endif
1203    c      enddo
1204    
1205    
1206    
1207    C---------------------------------------------------------------------
1208    C--------------------Corrections on ADC-data -------------------------
1209    C-----------------angle and ADC(x) correction -----------------------
1210    
1211    C-----------------------------S1 -------------------------------------
1212    
1213        yhelp=yout(1)        yhelp=yout(1)
1214    
1215          phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
1216          theta = atan(tan(THXOUT(1))/cos(phi))
1217    
1218        IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
1219    
1220           i = tof11_i           i = tof11_i
1221           xdummy=tof11(left,i,iadc)  
1222           tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)           if (tof11(left,i,iadc).lt.3786) then
1223           if (tof11(left,i,iadc).lt.1000) then              tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)
1224              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))              xkorr = atten(left,11,i,yhelp)
1225              xkorr0=adcx11(left,i,1)              xkorr=xkorr/hepratio
1226              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr              adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
1227           endif           endif
1228    
1229           tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)  
1230           if (tof11(right,i,iadc).lt.1000) then           if (tof11(right,i,iadc).lt.3786) then
1231              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))              tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)
1232              xkorr0=adcx11(right,i,1)              xkorr = atten(right,11,i,yhelp)
1233                xkorr=xkorr/hepratio
1234              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr              adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
1235           endif           endif
1236        ENDIF        ENDIF
1237    
1238    
1239        xhelp=xout(2)        xhelp=xout(2)
1240        IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN        phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
1241          theta = atan(tan(THXOUT(2))/cos(phi))
1242    
1243          IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
1244           i = tof12_i           i = tof12_i
1245           tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)           if (tof12(left,i,iadc).lt.3786) then
1246           if (tof12(left,i,iadc).lt.1000) then              tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)
1247              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))              xkorr = atten(left,12,i,xhelp)
1248              xkorr0=adcx12(left,i,1)              xkorr=xkorr/hepratio
1249              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr              adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
1250           endif           endif
1251    
1252           tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)           if (tof12(right,i,iadc).lt.3786) then
1253           if (tof12(right,i,iadc).lt.1000) then              tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)
1254              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))              xkorr = atten(right,12,i,xhelp)
1255              xkorr0=adcx12(right,i,1)              xkorr=xkorr/hepratio
1256              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr              adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
1257           endif           endif
1258        ENDIF        ENDIF
# Line 297  C-----------------------------S1 ------- Line 1260  C-----------------------------S1 -------
1260  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
1261    
1262        xhelp=xout(3)        xhelp=xout(3)
1263        IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN        phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
1264          theta = atan(tan(THXOUT(3))/cos(phi))
1265    
1266          IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
1267           i = tof21_i           i = tof21_i
1268           tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)           if (tof21(left,i,iadc).lt.3786) then
1269           if (tof21(left,i,iadc).lt.1000) then              tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)
1270              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))              xkorr = atten(left,21,i,xhelp)
1271              xkorr0=adcx21(left,i,1)              xkorr=xkorr/hepratio
1272              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr              adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
1273           endif           endif
1274    
1275           tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)           if (tof21(right,i,iadc).lt.3786) then
1276           if (tof21(right,i,iadc).lt.1000) then              tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)
1277              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))              xkorr = atten(right,21,i,xhelp)
1278              xkorr0=adcx21(right,i,1)              xkorr=xkorr/hepratio
1279              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr              adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
1280           endif           endif
1281        ENDIF        ENDIF
1282    
1283        yhelp=yout(4)        yhelp=yout(4)
1284        IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN        phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
1285          theta = atan(tan(THXOUT(4))/cos(phi))
1286    
1287          IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
1288           i = tof22_i           i = tof22_i
1289           tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)           if (tof22(left,i,iadc).lt.3786) then
1290           if (tof22(left,i,iadc).lt.1000) then              tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)
1291              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))              xkorr = atten(left,22,i,yhelp)
1292              xkorr0=adcx22(left,i,1)              xkorr=xkorr/hepratio
1293              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr              adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
1294           endif           endif
1295    
1296           tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)           if (tof22(right,i,iadc).lt.3786) then
1297           if (tof22(right,i,iadc).lt.1000) then              tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)
1298              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))              xkorr = atten(right,22,i,yhelp)
1299              xkorr0=adcx22(right,i,1)              xkorr=xkorr/hepratio
1300              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr              adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
1301           endif           endif
1302        ENDIF        ENDIF
# Line 337  C-----------------------------S2 ------- Line 1304  C-----------------------------S2 -------
1304  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
1305    
1306        yhelp=yout(5)        yhelp=yout(5)
1307          phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
1308          theta = atan(tan(THXOUT(5))/cos(phi))
1309    
1310        IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
1311    
1312           i = tof31_i           i = tof31_i
1313           tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)           if (tof31(left,i,iadc).lt.3786) then
1314           if (tof31(left,i,iadc).lt.1000) then              tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)
1315              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))              xkorr = atten(left,31,i,yhelp)
1316              xkorr0=adcx31(left,i,1)              xkorr=xkorr/hepratio
1317              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr              adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1318           endif           endif
1319    
1320           tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)           if (tof31(right,i,iadc).lt.3786) then
1321           if (tof31(right,i,iadc).lt.1000) then              tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)
1322              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))              xkorr = atten(right,31,i,yhelp)
1323              xkorr0=adcx31(right,i,1)              xkorr=xkorr/hepratio
1324              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr              adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1325           endif           endif
1326        ENDIF        ENDIF
1327    
1328        xhelp=xout(6)        xhelp=xout(6)
1329        IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN        phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
1330          theta = atan(tan(THXOUT(6))/cos(phi))
1331    
1332          IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
1333           i = tof32_i           i = tof32_i
1334           tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)           if (tof32(left,i,iadc).lt.3786) then
1335           if (tof32(left,i,iadc).lt.1000) then              tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)
1336              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))              xkorr = atten(left,32,i,xhelp)
1337              xkorr0=adcx32(left,i,1)              xkorr=xkorr/hepratio
1338              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr              adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1339           endif           endif
1340    
1341           tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)           if (tof32(right,i,iadc).lt.3786) then
1342           if (tof32(right,i,iadc).lt.1000) then              tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)
1343              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))              xkorr = atten(right,32,i,xhelp)
1344              xkorr0=adcx32(right,i,1)              xkorr=xkorr/hepratio
1345              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr              adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1346           endif           endif
1347        ENDIF        ENDIF
1348    
1349    
1350  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
1351  C----------------------calculate Beta  ------------------------------  C----------------------calculate Beta  ------------------------------
1352  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
# Line 384  C     DS = c1 + c2/beta*cos(theta) Line 1357  C     DS = c1 + c2/beta*cos(theta)
1357  C     c2 = 2d/c   gives c2 = 2d/(c*TDCresolution)  TDC=50ps/channel  C     c2 = 2d/c   gives c2 = 2d/(c*TDCresolution)  TDC=50ps/channel
1358  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
1359  C     since TDC resolution varies slightly c2 has to be calibrated  C     since TDC resolution varies slightly c2 has to be calibrated
1360    C     instead of cos(theta) use factor F:
1361    C     F =  pathlength/d
1362    C     => beta = c2*F/(DS-c1))
1363    
1364          dist = ZTOF(1) - ZTOF(5)
1365          dl = 0.
1366          DO I=1,5
1367             dl = dl + TLOUT(i)
1368          ENDDO
1369          F = dl/dist
1370    
1371  C     S11 - S31  C     S11 - S31
1372        IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1373           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)        IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1374           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)       &    (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1375           ds = xhelp1-xhelp2           t1 = tof11(1,tof11_i,itdc)
1376           ihelp=(tof11_i-1)*3+tof31_i           t2 = tof11(2,tof11_i,itdc)
1377           c1 = k_S11S31(1,ihelp)           t3 = tof31(1,tof31_i,itdc)
1378           c2 = k_S11S31(2,ihelp)                   t4 = tof31(2,tof31_i,itdc)
1379           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           IF ((t1.lt.4095).and.(t2.lt.4095).and.
1380       &   beta_a(1) = c2/(cos(theta13)*(ds-c1))       &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1381                xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1382                xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1383                ds = xhelp1-xhelp2
1384                ihelp=(tof11_i-1)*3+tof31_i
1385                c1 = k_S11S31(1,ihelp)
1386                if (iz.gt.2) c1 = c1 + k1corrA1
1387                c2 = k_S11S31(2,ihelp)
1388                beta_a(1) = c2*F/(ds-c1)
1389    c       write(*,*) 'S11-S31 ',c1,c2,F
1390    c       write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
1391    C-------ToF Mask - S11 - S31
1392    
1393                tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1394         $           tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1395                tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1396         $           tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1397    
1398                tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1399         $           tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1400                tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1401         $           tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1402    
1403             ENDIF
1404        ENDIF        ENDIF
1405          
1406          dist = ZTOF(1) - ZTOF(6)
1407          dl = 0.
1408          DO I=1,6
1409             dl = dl + TLOUT(i)
1410          ENDDO
1411          F = dl/dist
1412    
1413  C     S11 - S32  C     S11 - S32
1414        IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  C      IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1415           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)         IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1416           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)       &    (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1417           ds = xhelp1-xhelp2           t1 = tof11(1,tof11_i,itdc)
1418           ihelp=(tof11_i-1)*3+tof32_i           t2 = tof11(2,tof11_i,itdc)
1419           c1 = k_S11S32(1,ihelp)           t3 = tof32(1,tof32_i,itdc)
1420           c2 = k_S11S32(2,ihelp)                   t4 = tof32(2,tof32_i,itdc)
1421           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))           IF ((t1.lt.4095).and.(t2.lt.4095).and.
1422       &   beta_a(2) = c2/(cos(theta13)*(ds-c1))       &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1423                xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1424                xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1425                ds = xhelp1-xhelp2
1426                ihelp=(tof11_i-1)*3+tof32_i
1427                c1 = k_S11S32(1,ihelp)
1428                if (iz.gt.2) c1 = c1 + k1corrA1
1429                c2 = k_S11S32(2,ihelp)
1430                beta_a(2) = c2*F/(ds-c1)
1431    C     write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1432    
1433    C-------ToF Mask - S11 - S32
1434    
1435                tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1436         $           tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1437                tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1438         $           tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1439    
1440                tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1441         $           tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1442                tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1443         $           tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1444    
1445    C-------
1446    
1447             ENDIF
1448        ENDIF        ENDIF
1449    
1450  C     S12 - S31  C     S12 - S31
1451        IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN        dist = ZTOF(2) - ZTOF(5)
1452           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)        dl = 0.
1453           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)        DO I=2,5
1454           ds = xhelp1-xhelp2           dl = dl + TLOUT(i)
1455           ihelp=(tof12_i-1)*3+tof31_i        ENDDO
1456           c1 = k_S12S31(1,ihelp)        F = dl/dist
1457           c2 = k_S12S31(2,ihelp)  
1458           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  C      IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1459       &   beta_a(3) = c2/(cos(theta13)*(ds-c1))         IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1460         &    (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1461             t1 = tof12(1,tof12_i,itdc)
1462             t2 = tof12(2,tof12_i,itdc)
1463             t3 = tof31(1,tof31_i,itdc)
1464             t4 = tof31(2,tof31_i,itdc)
1465             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1466         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1467                xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1468                xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1469                ds = xhelp1-xhelp2
1470                ihelp=(tof12_i-1)*3+tof31_i
1471                c1 = k_S12S31(1,ihelp)
1472                if (iz.gt.2) c1 = c1 + k1corrA1
1473                c2 = k_S12S31(2,ihelp)
1474                beta_a(3) = c2*F/(ds-c1)
1475    C     write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1476    
1477    C-------ToF Mask - S12 - S31
1478    
1479                tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1480         $           tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1481                tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1482         $           tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1483    
1484                tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1485         $           tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1486                tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1487         $           tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1488    
1489    C-------
1490    
1491             ENDIF
1492        ENDIF        ENDIF
1493    
1494  C     S12 - S32  C     S12 - S32
1495        IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1496           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)        dist = ZTOF(2) - ZTOF(6)
1497           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)        dl = 0.
1498           ds = xhelp1-xhelp2        DO I=2,6
1499           ihelp=(tof12_i-1)*3+tof32_i           dl = dl + TLOUT(i)
1500           c1 = k_S12S32(1,ihelp)        ENDDO
1501           c2 = k_S12S32(2,ihelp)        F = dl/dist
1502           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1503       &   beta_a(4) = c2/(cos(theta13)*(ds-c1))  C      IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1504           IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1505         &    (xtofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1506             t1 = tof12(1,tof12_i,itdc)
1507             t2 = tof12(2,tof12_i,itdc)
1508             t3 = tof32(1,tof32_i,itdc)
1509             t4 = tof32(2,tof32_i,itdc)
1510             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1511         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1512                xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1513                xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1514                ds = xhelp1-xhelp2
1515                ihelp=(tof12_i-1)*3+tof32_i
1516                c1 = k_S12S32(1,ihelp)
1517                if (iz.gt.2) c1 = c1 + k1corrA1
1518                c2 = k_S12S32(2,ihelp)
1519                beta_a(4) = c2*F/(ds-c1)
1520    C     write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1521    
1522    C-------ToF Mask - S12 - S32
1523    
1524                tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1525         $           tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1526                tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1527         $           tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1528    
1529                tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1530         $           tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1531                tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1532         $           tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1533    
1534    C-------
1535    
1536             ENDIF
1537        ENDIF        ENDIF
1538    
1539  C     S21 - S31  C     S21 - S31
1540        IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  
1541           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)        dist = ZTOF(3) - ZTOF(5)
1542           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)        dl = 0.
1543           ds = xhelp1-xhelp2        DO I=3,5
1544           ihelp=(tof21_i-1)*3+tof31_i           dl = dl + TLOUT(i)
1545           c1 = k_S21S31(1,ihelp)        ENDDO
1546           c2 = k_S21S31(2,ihelp)        F = dl/dist
1547           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1548       &   beta_a(5) = c2/(cos(theta23)*(ds-c1))  C      IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1549           IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1550         &    (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1551             t1 = tof21(1,tof21_i,itdc)
1552             t2 = tof21(2,tof21_i,itdc)
1553             t3 = tof31(1,tof31_i,itdc)
1554             t4 = tof31(2,tof31_i,itdc)
1555             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1556         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1557                xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1558                xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1559                ds = xhelp1-xhelp2
1560                ihelp=(tof21_i-1)*3+tof31_i
1561                c1 = k_S21S31(1,ihelp)
1562                if (iz.gt.2) c1 = c1 + k1corrB1
1563                c2 = k_S21S31(2,ihelp)
1564                beta_a(5) = c2*F/(ds-c1)
1565    
1566    C-------ToF Mask - S21 - S31
1567    
1568                tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1569         $           tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1570                tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1571         $           tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1572    
1573                tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1574         $           tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1575                tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1576         $           tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1577    
1578    C-------
1579    
1580             ENDIF
1581        ENDIF        ENDIF
1582    
1583  C     S21 - S32  C     S21 - S32
1584        IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1585           xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)        dist = ZTOF(3) - ZTOF(6)
1586           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)        dl = 0.
1587           ds = xhelp1-xhelp2        DO I=3,6
1588           ihelp=(tof21_i-1)*3+tof32_i           dl = dl + TLOUT(i)
1589           c1 = k_S21S32(1,ihelp)        ENDDO
1590           c2 = k_S21S32(2,ihelp)        F = dl/dist
1591           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1592       &   beta_a(6) = c2/(cos(theta23)*(ds-c1))  C      IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1593           IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1594         &    (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1595             t1 = tof21(1,tof21_i,itdc)
1596             t2 = tof21(2,tof21_i,itdc)
1597             t3 = tof32(1,tof32_i,itdc)
1598             t4 = tof32(2,tof32_i,itdc)
1599             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1600         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1601                xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1602                xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1603                ds = xhelp1-xhelp2
1604                ihelp=(tof21_i-1)*3+tof32_i
1605                c1 = k_S21S32(1,ihelp)
1606                if (iz.gt.2) c1 = c1 + k1corrB1
1607                c2 = k_S21S32(2,ihelp)
1608                beta_a(6) = c2*F/(ds-c1)
1609    
1610    C-------ToF Mask - S21 - S32
1611    
1612                tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1613         $           tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1614                tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1615         $           tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1616    
1617                tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1618         $           tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1619                tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1620         $           tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1621    
1622    C-------
1623    
1624             ENDIF
1625        ENDIF        ENDIF
1626    
1627  C     S22 - S31  C     S22 - S31
1628        IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN  
1629           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)        dist = ZTOF(4) - ZTOF(5)
1630           xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)        dl = 0.
1631           ds = xhelp1-xhelp2        DO I=4,5
1632           ihelp=(tof22_i-1)*3+tof31_i           dl = dl + TLOUT(i)
1633           c1 = k_S22S31(1,ihelp)        ENDDO
1634           c2 = k_S22S31(2,ihelp)        F = dl/dist
          if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
      &   beta_a(7) = c2/(cos(theta13)*(ds-c1))  
       ENDIF  
1635                
1636    C WM workaround
1637          dl = dl - 0.06*F
1638          F = dl/dist
1639    
1640    C      IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1641           IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1642         &    (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1643             t1 = tof22(1,tof22_i,itdc)
1644             t2 = tof22(2,tof22_i,itdc)
1645             t3 = tof31(1,tof31_i,itdc)
1646             t4 = tof31(2,tof31_i,itdc)
1647             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1648         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1649                xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1650                xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1651                ds = xhelp1-xhelp2
1652                ihelp=(tof22_i-1)*3+tof31_i
1653                c1 = k_S22S31(1,ihelp)
1654                if (iz.gt.2) c1 = c1 + k1corrB1
1655                c2 = k_S22S31(2,ihelp)
1656                beta_a(7) = c2*F/(ds-c1)
1657    
1658    C-------ToF Mask - S22 - S31
1659    
1660                tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1661         $           tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1662                tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1663         $           tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1664    
1665                tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1666         $           tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1667                tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1668         $           tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1669    
1670    C-------
1671    
1672             ENDIF
1673          ENDIF
1674    
1675  C     S22 - S32  C     S22 - S32
1676        IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN  
1677           xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)        dist = ZTOF(4) - ZTOF(6)
1678           xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)        dl = 0.
1679           ds = xhelp1-xhelp2        DO I=4,6
1680           ihelp=(tof22_i-1)*3+tof32_i           dl = dl + TLOUT(i)
1681           c1 = k_S22S32(1,ihelp)        ENDDO
1682           c2 = k_S22S32(2,ihelp)        F = dl/dist
1683           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))        
1684       &   beta_a(8) = c2/(cos(theta13)*(ds-c1))  C WM workaround      
1685          dl = dl - 0.06*F
1686          F = dl/dist
1687    
1688    
1689    C      IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1690           IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1691         &    (ytofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1692             t1 = tof22(1,tof22_i,itdc)
1693             t2 = tof22(2,tof22_i,itdc)
1694             t3 = tof32(1,tof32_i,itdc)
1695             t4 = tof32(2,tof32_i,itdc)
1696             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1697         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1698                xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1699                xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1700                ds = xhelp1-xhelp2
1701                ihelp=(tof22_i-1)*3+tof32_i
1702                c1 = k_S22S32(1,ihelp)
1703                if (iz.gt.2) c1 = c1 + k1corrB1
1704                c2 = k_S22S32(2,ihelp)
1705                beta_a(8) = c2*F/(ds-c1)
1706    
1707    C-------ToF Mask - S22 - S32
1708    
1709                tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1710         $           tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1711                tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1712         $           tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1713    
1714                tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1715         $           tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1716                tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1717         $           tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1718    
1719    C-------
1720    
1721             ENDIF
1722        ENDIF        ENDIF
1723    
1724  C     S11 - S21  C     S11 - S21
1725        IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN  
1726           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)        dist = ZTOF(1) - ZTOF(3)
1727           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)        dl = 0.
1728           ds = xhelp1-xhelp2        DO I=1,3
1729           ihelp=(tof11_i-1)*2+tof21_i           dl = dl + TLOUT(i)
1730           c1 = k_S11S21(1,ihelp)        ENDDO
1731           c2 = k_S11S21(2,ihelp)        F = dl/dist
1732           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1733       &   beta_a(9) = c2/(cos(theta12)*(ds-c1))  C WM workaround      
1734          dl = dl - 0.442*F
1735          F = dl/dist
1736    
1737    C      IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1738           IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1739         &    (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1740             t1 = tof11(1,tof11_i,itdc)
1741             t2 = tof11(2,tof11_i,itdc)
1742             t3 = tof21(1,tof21_i,itdc)
1743             t4 = tof21(2,tof21_i,itdc)
1744             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1745         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1746                xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1747                xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1748                ds = xhelp1-xhelp2
1749                ihelp=(tof11_i-1)*2+tof21_i
1750                c1 = k_S11S21(1,ihelp)
1751                if (iz.gt.2) c1 = c1 + k1corrC1
1752                c2 = k_S11S21(2,ihelp)
1753                beta_a(9) = c2*F/(ds-c1)
1754    
1755    C-------ToF Mask - S11 - S21
1756    
1757                tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1758         $           tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1759                tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1760         $           tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1761    
1762                tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1763         $           tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1764                tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1765         $           tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1766    
1767    C-------
1768    
1769             ENDIF
1770        ENDIF        ENDIF
1771          
1772  C     S11 - S22  C     S11 - S22
1773        IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  
1774           xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)        dist = ZTOF(1) - ZTOF(4)
1775           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)        dl = 0.
1776           ds = xhelp1-xhelp2        DO I=1,4
1777           ihelp=(tof11_i-1)*2+tof22_i           dl = dl + TLOUT(i)
1778           c1 = k_S11S22(1,ihelp)        ENDDO
1779           c2 = k_S11S22(2,ihelp)        F = dl/dist
1780           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1781       &   beta_a(10) = c2/(cos(theta12)*(ds-c1))  C      IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1782           IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1783         &    (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1784             t1 = tof11(1,tof11_i,itdc)
1785             t2 = tof11(2,tof11_i,itdc)
1786             t3 = tof22(1,tof22_i,itdc)
1787             t4 = tof22(2,tof22_i,itdc)
1788             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1789         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1790                xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1791                xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1792                ds = xhelp1-xhelp2
1793                ihelp=(tof11_i-1)*2+tof22_i
1794                c1 = k_S11S22(1,ihelp)
1795                if (iz.gt.2) c1 = c1 + k1corrC1
1796                c2 = k_S11S22(2,ihelp)
1797                beta_a(10) = c2*F/(ds-c1)
1798    
1799    C-------ToF Mask - S11 - S22
1800    
1801                tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1802         $           tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1803                tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1804         $           tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1805    
1806                tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1807         $           tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1808                tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1809         $           tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1810    
1811    C-------
1812    
1813             ENDIF
1814        ENDIF        ENDIF
1815    
1816  C     S12 - S21  C     S12 - S21
1817        IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN  
1818           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)        dist = ZTOF(2) - ZTOF(3)
1819           xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)        dl = 0.
1820           ds = xhelp1-xhelp2        DO I=2,3
1821           ihelp=(tof12_i-1)*2+tof21_i           dl = dl + TLOUT(i)
1822           c1 = k_S12S21(1,ihelp)        ENDDO
1823           c2 = k_S12S21(2,ihelp)        F = dl/dist
1824           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1825       &   beta_a(11) = c2/(cos(theta12)*(ds-c1))  C  WM workaround
1826          dl = dl - 0.442*F
1827          F = dl/dist
1828    
1829    C      IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1830           IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1831         &    (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1832             t1 = tof12(1,tof12_i,itdc)
1833             t2 = tof12(2,tof12_i,itdc)
1834             t3 = tof21(1,tof21_i,itdc)
1835             t4 = tof21(2,tof21_i,itdc)
1836             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1837         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1838                xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1839                xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1840                ds = xhelp1-xhelp2
1841                ihelp=(tof12_i-1)*2+tof21_i
1842                c1 = k_S12S21(1,ihelp)
1843                if (iz.gt.2) c1 = c1 + k1corrC1
1844                c2 = k_S12S21(2,ihelp)
1845                beta_a(11) = c2*F/(ds-c1)
1846    
1847    C-------ToF Mask - S12 - S21
1848    
1849                tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1850         $           tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1851                tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1852         $           tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1853    
1854                tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1855         $           tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1856                tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1857         $           tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1858    
1859    C-------
1860    
1861             ENDIF
1862        ENDIF        ENDIF
1863    
1864  C     S12 - S22  C     S12 - S22
1865        IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN  
1866           xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)        dist = ZTOF(2) - ZTOF(4)
1867           xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)        dl = 0.
1868           ds = xhelp1-xhelp2        DO I=2,4
1869           ihelp=(tof12_i-1)*2+tof22_i           dl = dl + TLOUT(i)
1870           c1 = k_S12S22(1,ihelp)        ENDDO
1871           c2 = k_S12S22(2,ihelp)        F = dl/dist
1872           if ((xhelp1.lt.8000.).and.(xhelp2.lt.8000))  
1873       &   beta_a(12) = c2/(cos(theta12)*(ds-c1))  C      IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1874           IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1875         &    (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1876             t1 = tof12(1,tof12_i,itdc)
1877             t2 = tof12(2,tof12_i,itdc)
1878             t3 = tof22(1,tof22_i,itdc)
1879             t4 = tof22(2,tof22_i,itdc)
1880             IF ((t1.lt.4095).and.(t2.lt.4095).and.
1881         &        (t3.lt.4095).and.(t4.lt.4095)) THEN
1882                xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1883                xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1884                ds = xhelp1-xhelp2
1885                ihelp=(tof12_i-1)*2+tof22_i
1886                c1 = k_S12S22(1,ihelp)
1887                if (iz.gt.2) c1 = c1 + k1corrC1
1888                c2 = k_S12S22(2,ihelp)
1889                beta_a(12) = c2*F/(ds-c1)
1890    
1891    C-------ToF Mask - S12 - S22
1892    
1893                tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1894         $           tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1895                tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1896         $           tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1897    
1898                tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1899         $           tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1900                tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1901         $           tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1902    
1903    C-------
1904    
1905             ENDIF
1906        ENDIF        ENDIF
1907          
1908  C-------  C-------
1909    C
1910    C      icount=0
1911    C      sw=0.
1912    C      sxw=0.
1913    C      beta_mean=100.
1914    C
1915    C      do i=1,12
1916    C         if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
1917    C            icount= icount+1
1918    C            if (i.le.4) w_i=1./(0.13**2.)
1919    C            if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1920    C            if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1921    C            sxw=sxw + beta_a(i)*w_i
1922    C            sw =sw + w_i
1923    C         endif
1924    C      enddo
1925    C
1926    C      if (icount.gt.0) beta_mean=sxw/sw
1927    C      beta_a(13) = beta_mean
1928    C
1929    
1930        icount=0  C-------  New mean beta  calculation
       sw=0.  
       sxw=0.  
       beta_mean=100.  
1931    
1932        do i=1,12         do i=1,12
1933           if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then           btemp(i) =  beta_a(i)
1934              icount= icount+1         enddo
1935              if (i.le.4) w_i=1./(0.13**2.)  
1936              if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)         beta_a(13)=newbeta(2,btemp,hitvec,10.,10.,20.)
1937              if (i.ge.9) w_i=1./(0.25**2.)     ! to be checked  
1938              sxw=sxw + beta_a(i)*w_i  C-------
1939              sw =sw + w_i  
1940           endif  
1941        enddo  c       IF (tof11_i.GT.none_find)
1942          c     &  write(*,*) '11 ',tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
1943        if (icount.gt.0) beta_mean=sxw/sw  c       IF (tof12_i.GT.none_find)
1944        beta_a(13) = beta_mean  c     &  write(*,*) '12 ',tof12(1,tof12_i,itdc),tof12(2,tof12_i,itdc)
1945    
1946    c       IF (tof21_i.GT.none_find)
1947    c     &  write(*,*) '21 ',tof21(1,tof21_i,itdc),tof21(2,tof21_i,itdc)
1948    c       IF (tof22_i.GT.none_find)
1949    c     &  write(*,*) '22 ',tof22(1,tof22_i,itdc),tof22(2,tof22_i,itdc)
1950    
1951    c       IF (tof31_i.GT.none_find)
1952    c     &  write(*,*) '31 ',tof31(1,tof31_i,itdc),tof31(2,tof31_i,itdc)
1953    c       IF (tof32_i.GT.none_find)
1954    c     &  write(*,*) '32 ',tof32(1,tof32_i,itdc),tof32(2,tof32_i,itdc)
1955    
1956    c      write(*,*) xtofpos
1957    c      write(*,*) ytofpos
1958    C      write(*,*)'toftrk beta', beta_a
1959    C      write(*,*) adcflagtof
1960    C     write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4)
1961    c      write(*,*) 'toftrk'
1962    c      write(*,*) xtofpos
1963    c      write(*,*) ytofpos
1964    c      write(*,*) xtr_tof
1965    c      write(*,*) ytr_tof
1966    
1967    c       write(*,*) '---------  end toftrk ----------'
1968    
1969        RETURN        RETURN
1970        END        END
1971    
1972    
1973    
1974    
1975    C------------------------------------------------------------------
1976    
1977    

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

  ViewVC Help
Powered by ViewVC 1.1.23