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

Contents of /DarthVader/ToFLevel2/src/toftrk.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.9 - (show annotations) (download)
Mon Feb 5 15:36:44 2007 UTC (17 years, 10 months ago) by mocchiut
Branch: MAIN
Changes since 1.8: +43 -39 lines
toftrk bug fixed

1 *****************************************************************************
2 INTEGER FUNCTION TOFTRK()
3
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: claculation of zenith angles using DOTRACK2
28 C was incorrect
29 C****************************************************************************
30 IMPLICIT NONE
31 C
32 include 'input_tof.txt'
33 include 'output_tof.txt'
34 include 'tofcomm.txt'
35 C
36
37 c =======================================
38 c variables for tracking routine
39 c =======================================
40 integer NPOINT_MAX
41 parameter(NPOINT_MAX=100)
42
43 c define TOF Z-coordinates
44 integer NPTOF
45 parameter (NPTOF=6)
46 DOUBLE PRECISION ZTOF(NPTOF)
47 DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
48
49 integer itof,pmt_id
50
51 DOUBLE PRECISION al_p(5),
52 & xout(NPOINT_MAX),yout(NPOINT_MAX),zin(NPTOF),
53 & THXOUT(NPOINT_MAX),THYOUT(NPOINT_MAX),TLOUT(NPOINT_MAX)
54
55
56 INTEGER IFAIL
57 c REAL dx,dy,dr
58 REAL ds
59 REAL t1,t2,t3,t4
60 REAL yhelp,xhelp,xhelp1,xhelp2
61 REAL c1,c2,sw,sxw,w_i
62 REAL dist,dl,F
63 INTEGER icount,ievent
64 REAL xhelp_a,xhelp_t
65
66 REAL beta_mean
67 REAL hepratio
68
69 INTEGER j
70
71 REAL theta,phi
72 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
73 REAL tofarm12
74 PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
75 REAL tofarm23
76 PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
77 REAL tofarm13
78 PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
79
80
81 INTEGER ihelp
82 REAL xkorr,xpos
83
84 REAL yl,yh,xl,xh
85 C
86 REAL hmemor(9000000)
87 INTEGER Iquest(100)
88 C
89 DATA ievent / 0 /
90
91 COMMON / pawcd / hmemor
92 save / pawcd /
93 C
94 Common / QUESTd / Iquest
95 save / questd /
96 C
97 C Begin !
98 C
99 TOFTRK = 0
100
101 *******************************************************************
102
103 ievent = ievent +1
104
105 C ratio helium to proton ca. 4
106 hepratio = 4.5
107
108 offset = 1
109 slope = 2
110 left = 1
111 right = 2
112 none_ev = 0
113 none_find = 0
114 tdc_ev = 1
115 adc_ev = 1
116 itdc = 1
117 iadc = 2
118
119 do i=1,13
120 beta_a(i) = 100.
121 enddo
122
123 do i=1,4
124 do j=1,12
125 adc_c(i,j) = 1000.
126 enddo
127 enddo
128
129 do i=1,12
130 do j=1,4
131 tofmask(j,i) = 0
132 enddo
133 enddo
134
135 do i=1,4
136 do j=1,12
137 adcflag(i,j) = 0
138 enddo
139 enddo
140
141 do i=1,4
142 do j=1,12
143 tdcflag(i,j) = 0
144 enddo
145 enddo
146
147 pmt_id=0
148
149 do j=1,6
150 THXOUT(j) = 0.
151 THYOUT(j) = 0.
152 enddo
153
154 C----------------------------------------------------------------------
155 C-------------------------get ToF data --------------------------------
156 C we cannot use the tofxx(x,x,x) data from tofl2com since it is
157 C manipulated (Time-walk, artificila ADc and TDC values using ToF
158 C standalone information
159 C----------------------------------------------------------------------
160 C put the adc and tdc values from ntuple into tofxx(i,j,k) variables
161
162
163 do j=1,8
164 tof11(1,j,2) = adc(ch11a(j),hb11a(j))
165 tof11(2,j,2) = adc(ch11b(j),hb11b(j))
166 tof11(1,j,1) = tdc(ch11a(j),hb11a(j))
167 tof11(2,j,1) = tdc(ch11b(j),hb11b(j))
168 enddo
169
170
171 do j=1,6
172 tof12(1,j,2) = adc(ch12a(j),hb12a(j))
173 tof12(2,j,2) = adc(ch12b(j),hb12b(j))
174 tof12(1,j,1) = tdc(ch12a(j),hb12a(j))
175 tof12(2,j,1) = tdc(ch12b(j),hb12b(j))
176 enddo
177
178 do j=1,2
179 tof21(1,j,2) = adc(ch21a(j),hb21a(j))
180 tof21(2,j,2) = adc(ch21b(j),hb21b(j))
181 tof21(1,j,1) = tdc(ch21a(j),hb21a(j))
182 tof21(2,j,1) = tdc(ch21b(j),hb21b(j))
183 enddo
184
185 do j=1,2
186 tof22(1,j,2) = adc(ch22a(j),hb22a(j))
187 tof22(2,j,2) = adc(ch22b(j),hb22b(j))
188 tof22(1,j,1) = tdc(ch22a(j),hb22a(j))
189 tof22(2,j,1) = tdc(ch22b(j),hb22b(j))
190 enddo
191
192 do j=1,3
193 tof31(1,j,2) = adc(ch31a(j),hb31a(j))
194 tof31(2,j,2) = adc(ch31b(j),hb31b(j))
195 tof31(1,j,1) = tdc(ch31a(j),hb31a(j))
196 tof31(2,j,1) = tdc(ch31b(j),hb31b(j))
197 enddo
198
199 do j=1,3
200 tof32(1,j,2) = adc(ch32a(j),hb32a(j))
201 tof32(2,j,2) = adc(ch32b(j),hb32b(j))
202 tof32(1,j,1) = tdc(ch32a(j),hb32a(j))
203 tof32(2,j,1) = tdc(ch32b(j),hb32b(j))
204 enddo
205
206 C----------------------------------------------------------------------
207
208 DO i = 1,8
209 if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000.
210 if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000.
211 if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000.
212 if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000.
213 ENDDO
214
215 DO i = 1,6
216 if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000.
217 if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000.
218 if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000.
219 if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000.
220 ENDDO
221
222
223 DO i = 1,2
224 if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000.
225 if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000.
226 if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000.
227 if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000.
228 ENDDO
229
230 DO i = 1,2
231 if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000.
232 if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000.
233 if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000.
234 if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000.
235 ENDDO
236
237 DO i = 1,3
238 if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000.
239 if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000.
240 if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000.
241 if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000.
242 ENDDO
243
244 DO i = 1,3
245 if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000.
246 if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000.
247 if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000.
248 if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
249 ENDDO
250
251 C-------------------------------------------------------------------
252
253 C------read tracking routine
254 * igoodevent = igoodevent+1
255 * assigned input parameters for track routine
256 * 1) Z-coordinates where the trajectory is evaluated
257 do itof=1,NPTOF
258 ZIN(itof) = ZTOF(itof)
259 enddo
260 * 2) track status vector
261 C COPY THE ALFA VECTOR FROM AL_PP TO AL_P FOR THE TRACK "T"
262 do i=1,5
263 AL_P(i) = al_pp(i)
264 enddo
265
266 c write(*,*) AL_P
267
268 if (al_p(5).eq.0.) THEN
269 PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
270 GOTO 969
271 ENDIF
272 * -------- *** tracking routine *** --------
273 IFAIL = 0
274 C call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL)
275 call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL)
276
277
278 C write(*,*) (TLOUT(i),i=1,6)
279
280 if(IFAIL.ne.0)then
281 print *,' TOF - WARNING F77: tracking failed '
282 goto 969
283 endif
284 * ------------------------------------------
285
286 969 continue
287
288 C--- convert angles to radian
289 do j=1,6
290 THXOUT(j) = 3.1415927*THXOUT(j)/180.
291 THYOUT(j) = 3.1415927*THYOUT(j)/180.
292 enddo
293
294 do j=1,6
295 c write (*,*) j,THXOUT(j),THYOUT(j)
296 enddo
297
298
299 C----------------------------------------------------------------------
300 C------------------ set ADC & TDC flag = 0 ------------------------
301 C----------------------------------------------------------------------
302
303 do j=1,8
304 if (adc(ch11a(j),hb11a(j)).LT.4096)adcflagtof(ch11a(j),hb11a(j))=0
305 if (adc(ch11b(j),hb11b(j)).LT.4096)adcflagtof(ch11b(j),hb11b(j))=0
306 if (tdc(ch11a(j),hb11a(j)).LT.4096)tdcflagtof(ch11a(j),hb11a(j))=0
307 if (tdc(ch11b(j),hb11b(j)).LT.4096)tdcflagtof(ch11b(j),hb11b(j))=0
308 enddo
309 do j=1,6
310 if (adc(ch12a(j),hb12a(j)).LT.4096)adcflagtof(ch12a(j),hb12a(j))=0
311 if (adc(ch12b(j),hb12b(j)).LT.4096)adcflagtof(ch12b(j),hb12b(j))=0
312 if (tdc(ch12a(j),hb12a(j)).LT.4096)tdcflagtof(ch12a(j),hb12a(j))=0
313 if (tdc(ch12b(j),hb12b(j)).LT.4096)tdcflagtof(ch12b(j),hb12b(j))=0
314 enddo
315 do j=1,2
316 if (adc(ch21a(j),hb21a(j)).LT.4096)adcflagtof(ch21a(j),hb21a(j))=0
317 if (adc(ch21b(j),hb21b(j)).LT.4096)adcflagtof(ch21b(j),hb21b(j))=0
318 if (tdc(ch21a(j),hb21a(j)).LT.4096)tdcflagtof(ch21a(j),hb21a(j))=0
319 if (tdc(ch21b(j),hb21b(j)).LT.4096)tdcflagtof(ch21b(j),hb21b(j))=0
320 enddo
321 do j=1,2
322 if (adc(ch22a(j),hb22a(j)).LT.4096)adcflagtof(ch22a(j),hb22a(j))=0
323 if (adc(ch22b(j),hb22b(j)).LT.4096)adcflagtof(ch22b(j),hb22b(j))=0
324 if (tdc(ch22a(j),hb22a(j)).LT.4096)tdcflagtof(ch22a(j),hb22a(j))=0
325 if (tdc(ch22b(j),hb22b(j)).LT.4096)tdcflagtof(ch22b(j),hb22b(j))=0
326 enddo
327 do j=1,3
328 if (adc(ch31a(j),hb31a(j)).LT.4096)adcflagtof(ch31a(j),hb31a(j))=0
329 if (adc(ch31b(j),hb31b(j)).LT.4096)adcflagtof(ch31b(j),hb31b(j))=0
330 if (tdc(ch31a(j),hb31a(j)).LT.4096)tdcflagtof(ch31a(j),hb31a(j))=0
331 if (tdc(ch31b(j),hb31b(j)).LT.4096)tdcflagtof(ch31b(j),hb31b(j))=0
332 enddo
333 do j=1,3
334 if (adc(ch32a(j),hb32a(j)).LT.4096)adcflagtof(ch32a(j),hb32a(j))=0
335 if (adc(ch32b(j),hb32b(j)).LT.4096)adcflagtof(ch32b(j),hb32b(j))=0
336 if (tdc(ch32a(j),hb32a(j)).LT.4096)tdcflagtof(ch32a(j),hb32a(j))=0
337 if (tdc(ch32b(j),hb32b(j)).LT.4096)tdcflagtof(ch32b(j),hb32b(j))=0
338 enddo
339
340
341 C----------------------------------------------------------------
342 C---------- Check PMTs 10 and 35 for strange TDC values----------
343 C----------------------------------------------------------------
344
345 C---- S116A TDC=819
346 if (tof11(1,6,1).EQ.819) then
347 tof11(1,6,1) = 4095
348 tdcflagtof(ch11a(6),hb11a(6))=2
349 endif
350
351 C---- S222B TDC=819
352 if (tof22(2,2,1).EQ.819) then
353 tof22(2,2,1) = 4095
354 tdcflagtof(ch22b(2),hb22b(2))=2
355 endif
356
357 C-------------------------------------------------------------
358 C-------check which paddle penetrated the track -----------
359 C-------------------------------------------------------------
360 c middle y (or x) position of the upper and middle ToF-Paddle
361 c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
362 c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
363 c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
364 c DATA tof22_x/ -4.5,4.5/
365 c DATA tof31_x/ -6.0,0.,6.0/
366 c DATA tof32_y/ -5.0,0.0,5.0/
367 c
368 c S11 8 paddles 33.0 x 5.1 cm
369 c S12 6 paddles 40.8 x 5.5 cm
370 c S21 2 paddles 18.0 x 7.5 cm
371 c S22 2 paddles 15.0 x 9.0 cm
372 c S31 3 paddles 15.0 x 6.0 cm
373 c S32 3 paddles 18.0 x 5.0 cm
374
375 c write(*,*) xout(1),xout(2),xout(3),xout(4),xout(5),xout(6)
376 c write(*,*) yout(1),yout(2),yout(3),yout(4),yout(5),yout(6)
377
378 C--------------S11 --------------------------------------
379
380 tof11_i = none_find
381
382 yl = -33.0/2.
383 yh = 33.0/2.
384
385 if ((yout(1).gt.yl).and.(yout(1).lt.yh)) then
386 do i=1,8
387 xl = tof11_x(i) - 5.1/2.
388 xh = tof11_x(i) + 5.1/2.
389 if ((xout(1).gt.xl).and.(xout(1).le.xh)) then
390 tof11_i=i
391 endif
392 enddo
393 endif
394
395 C--------------S12 --------------------------------------
396
397 tof12_i = none_find
398
399 xl = -40.8/2.
400 xh = 40.8/2.
401
402 if ((xout(2).gt.xl).and.(xout(2).lt.xh)) then
403 do i=1,6
404 yl = tof12_y(i) - 5.5/2.
405 yh = tof12_y(i) + 5.5/2.
406 if ((yout(2).gt.yl).and.(yout(2).le.yh)) then
407 tof12_i=i
408 endif
409 enddo
410 endif
411
412 C--------------S21 --------------------------------------
413
414 tof21_i = none_find
415
416 xl = -18./2.
417 xh = 18./2.
418
419 if ((xout(3).gt.xl).and.(xout(3).lt.xh)) then
420 do i=1,2
421 yl = tof21_y(i) - 7.5/2.
422 yh = tof21_y(i) + 7.5/2.
423 if ((yout(3).gt.yl).and.(yout(3).le.yh)) then
424 tof21_i=i
425 endif
426 enddo
427 endif
428
429 C--------------S22 --------------------------------------
430
431 tof22_i = none_find
432
433 yl = -15./2.
434 yh = 15./2.
435
436 if ((yout(4).gt.yl).and.(yout(4).lt.yh)) then
437 do i=1,2
438 xl = tof22_x(i) - 9.0/2.
439 xh = tof22_x(i) + 9.0/2.
440 if ((xout(4).gt.xl).and.(xout(4).le.xh)) then
441 tof22_i=i
442 endif
443 enddo
444 endif
445
446 C--------------S31 --------------------------------------
447
448 tof31_i = none_find
449
450 yl = -15.0/2.
451 yh = 15.0/2.
452
453 if ((yout(5).gt.yl).and.(yout(5).lt.yh)) then
454 do i=1,3
455 xl = tof31_x(i) - 6.0/2.
456 xh = tof31_x(i) + 6.0/2.
457 if ((xout(5).gt.xl).and.(xout(5).le.xh)) then
458 tof31_i=i
459 endif
460 enddo
461 endif
462
463 C--------------S32 --------------------------------------
464
465 tof32_i = none_find
466
467 xl = -18.0/2.
468 xh = 18.0/2.
469
470 if ((xout(6).gt.xl).and.(xout(6).lt.xh)) then
471 do i=1,3
472 yl = tof32_y(i) - 5.0/2.
473 yh = tof32_y(i) + 5.0/2.
474 if ((yout(6).gt.yl).and.(yout(6).le.yh)) then
475 tof32_i=i
476 endif
477 enddo
478 endif
479
480
481 C write(*,*) tof11_i,tof12_i,tof21_i,tof22_i,tof31_i,tof32_i
482
483 C-----------------------------------------------------------------------
484 C--------------------Insert Artifical TDC Value ---------------------
485 C For each Paddle perform check:
486 C if left paddle=4095 and right paddle OK => create TDC value left
487 C if right paddle=4095 and left paddle OK => create TDC value right
488 C-----------------------------------------------------------------------
489
490 C-----------------------S11 -----------------------------------------
491
492 IF (tof11_i.GT.none_find) THEN
493 xpos = yout(1)
494 i = tof11_i
495 if ((tof11(1,tof11_i,itdc).EQ.4095).AND.
496 & (tof11(2,tof11_i,itdc).LT.4095)) THEN
497
498 c write(*,*)'11lb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
499
500 tof11(1,tof11_i,itdc) = tof11(2,tof11_i,itdc)
501 & + 2*(y_coor_lin11(tof11_i,offset)
502 & + xpos*y_coor_lin11(tof11_i,slope))
503
504 c write(*,*)'11laf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
505
506 tdcflag(ch11a(i),hb11a(i)) = 1
507
508 ENDIF
509 if ((tof11(2,tof11_i,itdc).EQ.4095).AND.
510 & (tof11(1,tof11_i,itdc).LT.4095)) THEN
511
512 c write(*,*)'11rb4 ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
513
514 tof11(2,tof11_i,itdc) = tof11(1,tof11_i,itdc)
515 & - 2*(y_coor_lin11(tof11_i,offset)
516 & + xpos*y_coor_lin11(tof11_i,slope))
517 c write(*,*)'11raf ',i,tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
518
519 tdcflag(ch11b(i),hb11b(i)) = 1
520 ENDIF
521 ENDIF
522
523 C-----------------------S12 -----------------------------------------
524
525 IF (tof12_i.GT.none_find) THEN
526 xpos = xout(2)
527 i = tof12_i
528 if ((tof12(1,tof12_i,itdc).EQ.4095).AND.
529 & (tof12(2,tof12_i,itdc).LT.4095)) THEN
530 tof12(1,tof12_i,itdc) = tof12(2,tof12_i,itdc)
531 & + 2*(x_coor_lin12(tof12_i,offset)
532 & + xpos*x_coor_lin12(tof12_i,slope))
533 tdcflag(ch12a(i),hb12a(i)) = 1
534 ENDIF
535 if ((tof12(2,tof12_i,itdc).EQ.4095).AND.
536 & (tof12(1,tof12_i,itdc).LT.4095)) THEN
537 tof12(2,tof12_i,itdc) = tof12(1,tof12_i,itdc)
538 & - 2*(x_coor_lin12(tof12_i,offset)
539 & + xpos*x_coor_lin12(tof12_i,slope))
540 tdcflag(ch12b(i),hb12b(i)) = 1
541 ENDIF
542 ENDIF
543
544 C-----------------------S21 -----------------------------------------
545
546 IF (tof21_i.GT.none_find) THEN
547 xpos = xout(3)
548 i = tof21_i
549 if ((tof21(1,tof21_i,itdc).EQ.4095).AND.
550 & (tof21(2,tof21_i,itdc).LT.4095)) THEN
551 tof21(1,tof21_i,itdc) = tof21(2,tof21_i,itdc)
552 & + 2*(x_coor_lin21(tof21_i,offset)
553 & + xpos*x_coor_lin21(tof21_i,slope))
554 tdcflag(ch21a(i),hb21a(i)) = 1
555 ENDIF
556 if ((tof21(2,tof21_i,itdc).EQ.4095).AND.
557 & (tof21(1,tof21_i,itdc).LT.4095)) THEN
558 tof21(2,tof21_i,itdc) = tof21(1,tof21_i,itdc)
559 & - 2*(x_coor_lin21(tof21_i,offset)
560 & + xpos*x_coor_lin21(tof21_i,slope))
561 tdcflag(ch21b(i),hb21b(i)) = 1
562 ENDIF
563 ENDIF
564
565 C-----------------------S22 -----------------------------------------
566
567 IF (tof22_i.GT.none_find) THEN
568 xpos = yout(4)
569 i = tof22_i
570 if ((tof22(1,tof22_i,itdc).EQ.4095).AND.
571 & (tof22(2,tof22_i,itdc).LT.4095)) THEN
572 tof22(1,tof22_i,itdc) = tof22(2,tof22_i,itdc)
573 & + 2*(y_coor_lin22(tof22_i,offset)
574 & + xpos*y_coor_lin22(tof22_i,slope))
575 tdcflag(ch22a(i),hb22a(i)) = 1
576 ENDIF
577 if ((tof22(2,tof22_i,itdc).EQ.4095).AND.
578 & (tof22(1,tof22_i,itdc).LT.4095)) THEN
579 tof22(2,tof22_i,itdc) = tof22(1,tof22_i,itdc)
580 & - 2*(y_coor_lin22(tof22_i,offset)
581 & + xpos*y_coor_lin22(tof22_i,slope))
582 tdcflag(ch22b(i),hb22b(i)) = 1
583 ENDIF
584 ENDIF
585
586 C-----------------------S31 -----------------------------------------
587
588 IF (tof31_i.GT.none_find) THEN
589 xpos = yout(5)
590 i = tof31_i
591 if ((tof31(1,tof31_i,itdc).EQ.4095).AND.
592 & (tof31(2,tof31_i,itdc).LT.4095)) THEN
593 tof31(1,tof31_i,itdc) = tof31(2,tof31_i,itdc)
594 & + 2*(y_coor_lin31(tof31_i,offset)
595 & + xpos*y_coor_lin31(tof31_i,slope))
596 tdcflag(ch31a(i),hb31a(i)) = 1
597 ENDIF
598 if ((tof31(2,tof31_i,itdc).EQ.4095).AND.
599 & (tof31(1,tof31_i,itdc).LT.4095)) THEN
600 tof31(2,tof31_i,itdc) = tof31(1,tof31_i,itdc)
601 & - 2*(y_coor_lin31(tof31_i,offset)
602 & + xpos*y_coor_lin31(tof31_i,slope))
603 tdcflag(ch31b(i),hb31b(i)) = 1
604 ENDIF
605 ENDIF
606
607 C-----------------------S32 -----------------------------------------
608
609 IF (tof32_i.GT.none_find) THEN
610 xpos = xout(6)
611 i = tof32_i
612 if ((tof32(1,tof32_i,itdc).EQ.4095).AND.
613 & (tof32(2,tof32_i,itdc).LT.4095)) THEN
614 tof32(1,tof32_i,itdc) = tof32(2,tof32_i,itdc)
615 & + 2*(x_coor_lin32(tof32_i,offset)
616 & + xpos*x_coor_lin32(tof32_i,slope))
617 tdcflag(ch32a(i),hb32a(i)) = 1
618 ENDIF
619 if ((tof32(2,tof32_i,itdc).EQ.4095).AND.
620 & (tof32(1,tof32_i,itdc).LT.4095)) THEN
621 tof32(2,tof32_i,itdc) = tof32(1,tof32_i,itdc)
622 & - 2*(x_coor_lin32(tof32_i,offset)
623 & + xpos*x_coor_lin32(tof32_i,slope))
624 tdcflag(ch32b(i),hb32b(i)) = 1
625 ENDIF
626 ENDIF
627
628 C--------------------------------------------------------------------
629 C---- if TDCleft.and.TDCright and NO ADC insert artificial ADC
630 C---- values
631 C--------------------------------------------------------------------
632 c middle y (or x) position of the upper and middle ToF-Paddle
633 c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
634 c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
635 c DATA tof21_y/ 3.75,-3.75/ ! paddles in different order
636 c DATA tof22_x/ -4.5,4.5/
637 c DATA tof31_x/ -6.0,0.,6.0/
638 c DATA tof32_y/ -5.0,0.0,5.0/
639
640 C----------------------------S1 -------------------------------------
641
642 yhelp=yout(1)
643 IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN
644 i = tof11_i
645 if (tof11(left,i,iadc).eq.4095) then
646 phi = atan(tan(THYOUT(1))/tan(THXOUT(1)))
647 theta = atan(tan(THXOUT(1))/cos(phi))
648 xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
649 xkorr=xkorr/hepratio
650 tof11(left,i,iadc)=xkorr/cos(theta)
651 adcflag(ch11a(i),hb11a(i)) = 1
652 endif
653 if (tof11(right,i,iadc).eq.4095) then
654 phi = atan(tan(THYOUT(1))/tan(THXOUT(1)))
655 theta = atan(tan(THXOUT(1))/cos(phi))
656 xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
657 xkorr=xkorr/hepratio
658 tof11(right,i,iadc)=xkorr/cos(theta)
659 adcflag(ch11b(i),hb11b(i)) = 1
660 endif
661 ENDIF
662
663 xhelp=xout(2)
664 IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN
665 i = tof12_i
666 if (tof12(left,i,iadc).eq.4095) then
667 phi = atan(tan(THYOUT(2))/tan(THXOUT(2)))
668 theta = atan(tan(THXOUT(2))/cos(phi))
669 xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
670 xkorr=xkorr/hepratio
671 tof12(left,i,iadc) = xkorr/cos(theta)
672 adcflag(ch12a(i),hb12a(i)) = 1
673 endif
674 if (tof12(right,i,iadc).eq.4095) then
675 phi = atan(tan(THYOUT(2))/tan(THXOUT(2)))
676 theta = atan(tan(THXOUT(2))/cos(phi))
677 xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
678 xkorr=xkorr/hepratio
679 tof12(right,i,iadc) = xkorr/cos(theta)
680 adcflag(ch12b(i),hb12b(i)) = 1
681 endif
682 ENDIF
683
684 C-----------------------------S2 --------------------------------
685
686 xhelp=xout(3)
687 IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN
688 i = tof21_i
689 if (tof21(left,i,iadc).eq.4095) then
690 phi = atan(tan(THYOUT(3))/tan(THXOUT(3)))
691 theta = atan(tan(THXOUT(3))/cos(phi))
692 xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
693 xkorr=xkorr/hepratio
694 tof21(left,i,iadc) = xkorr/cos(theta)
695 adcflag(ch21a(i),hb21a(i)) = 1
696 endif
697 if (tof21(right,i,iadc).eq.4095) then
698 phi = atan(tan(THYOUT(3))/tan(THXOUT(3)))
699 theta = atan(tan(THXOUT(3))/cos(phi))
700 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
701 xkorr=xkorr/hepratio
702 tof21(right,i,iadc) = xkorr/cos(theta)
703 adcflag(ch21b(i),hb21b(i)) = 1
704 endif
705 ENDIF
706
707
708 yhelp=yout(4)
709 IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN
710 i = tof22_i
711 if (tof22(left,i,iadc).eq.4095) then
712 phi = atan(tan(THYOUT(4))/tan(THXOUT(4)))
713 theta = atan(tan(THXOUT(4))/cos(phi))
714 xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
715 xkorr=xkorr/hepratio
716 tof22(left,i,iadc) = xkorr/cos(theta)
717 adcflag(ch22a(i),hb22a(i)) = 1
718 endif
719 if (tof22(right,i,iadc).eq.4095) then
720 phi = atan(tan(THYOUT(4))/tan(THXOUT(4)))
721 theta = atan(tan(THXOUT(4))/cos(phi))
722 xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
723 xkorr=xkorr/hepratio
724 tof22(right,i,iadc) = xkorr/cos(theta)
725 adcflag(ch22b(i),hb22b(i)) = 1
726 endif
727 ENDIF
728
729 C-----------------------------S3 --------------------------------
730
731 yhelp=yout(5)
732 IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN
733 i = tof31_i
734 if (tof31(left,i,iadc).eq.4095) then
735 phi = atan(tan(THYOUT(5))/tan(THXOUT(5)))
736 theta = atan(tan(THXOUT(5))/cos(phi))
737 xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
738 xkorr=xkorr/hepratio
739 tof31(left,i,iadc) = xkorr/cos(theta)
740 adcflag(ch31a(i),hb31a(i)) = 1
741 endif
742 if (tof31(right,i,iadc).eq.4095) then
743 phi = atan(tan(THYOUT(5))/tan(THXOUT(5)))
744 theta = atan(tan(THXOUT(5))/cos(phi))
745 xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
746 xkorr=xkorr/hepratio
747 tof31(right,i,iadc) = xkorr/cos(theta)
748 adcflag(ch31b(i),hb31b(i)) = 1
749 endif
750 ENDIF
751
752
753 xhelp=xout(6)
754 IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
755 i = tof32_i
756 if (tof32(left,i,iadc).eq.4095) then
757 phi = atan(tan(THYOUT(6))/tan(THXOUT(6)))
758 theta = atan(tan(THXOUT(6))/cos(phi))
759 xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
760 xkorr=xkorr/hepratio
761 tof32(left,i,iadc) = xkorr/cos(theta)
762 adcflag(ch32a(i),hb32a(i)) = 1
763 endif
764 if (tof32(right,i,iadc).eq.4095) then
765 phi = atan(tan(THYOUT(6))/tan(THXOUT(6)))
766 theta = atan(tan(THXOUT(6))/cos(phi))
767 xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
768 xkorr=xkorr/hepratio
769 tof32(right,i,iadc) = xkorr/cos(theta)
770 adcflag(ch32b(i),hb32b(i)) = 1
771 endif
772 ENDIF
773
774
775 C------------------------------------------------------------------
776 C--- calculate track position in paddle using timing difference
777 C------------------------------------------------------------------
778
779 do i=1,3
780 xtofpos(i)=100.
781 ytofpos(i)=100.
782 enddo
783 C-----------------------------S1 --------------------------------
784
785 IF (tof11_i.GT.none_find) THEN
786 IF ((tof11(1,tof11_i,itdc).NE.4095).AND.
787 & (tof11(2,tof11_i,itdc).NE.4095)) THEN
788 ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
789 + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
790 if (abs(ytofpos(1)).gt.26.) ytofpos(1)=101.
791 endif
792 endif
793
794 IF (tof12_i.GT.none_find) THEN
795 IF ((tof12(1,tof12_i,itdc).NE.4095).AND.
796 & (tof12(2,tof12_i,itdc).NE.4095)) THEN
797 xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
798 + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
799 if (abs(xtofpos(1)).gt.31.) xtofpos(1)=101.
800 endif
801 endif
802
803 C-----------------------------S2 --------------------------------
804
805 IF (tof21_i.GT.none_find) THEN
806 IF ((tof21(1,tof21_i,itdc).NE.4095).AND.
807 & (tof21(2,tof21_i,itdc).NE.4095)) THEN
808 xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
809 + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
810 if (abs(xtofpos(2)).gt.19.) xtofpos(2)=101.
811 endif
812 endif
813
814 IF (tof22_i.GT.none_find) THEN
815 IF ((tof22(1,tof22_i,itdc).NE.4095).AND.
816 & (tof22(2,tof22_i,itdc).NE.4095)) THEN
817 ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
818 + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
819 if (abs(ytofpos(2)).gt.18.) ytofpos(2)=101.
820 endif
821 endif
822
823 C-----------------------------S3 --------------------------------
824
825 IF (tof31_i.GT.none_find) THEN
826 IF ((tof31(1,tof31_i,itdc).NE.4095).AND.
827 & (tof31(2,tof31_i,itdc).NE.4095)) THEN
828 ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
829 + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
830 if (abs(ytofpos(3)).gt.18.) ytofpos(3)=101.
831 endif
832 endif
833
834 IF (tof32_i.GT.none_find) THEN
835 IF ((tof32(1,tof32_i,itdc).NE.4095).AND.
836 & (tof32(2,tof32_i,itdc).NE.4095)) THEN
837 xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
838 + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
839 if (abs(xtofpos(3)).gt.19.) xtofpos(3)=101.
840 endif
841 endif
842
843 c do i=1,3
844 c if (abs(xtofpos(i)).gt.100.) then
845 c xtofpos(i)=101.
846 c endif
847 c if (abs(ytofpos(i)).gt.100.) then
848 c ytofpos(i)=101.
849 c endif
850 c enddo
851
852
853
854
855 C--------------------------------------------------------------------
856 C--------------------Time walk correction -------------------------
857 C--------------------------------------------------------------------
858
859 DO i=1,8
860 xhelp_a = tof11(left,i,iadc)
861 xhelp_t = tof11(left,i,itdc)
862 if(xhelp_a<4095) xhelp = tw11(left,i)/sqrt(xhelp_a)
863 tof11(left,i,itdc) = xhelp_t + xhelp
864 tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
865 xhelp_a = tof11(right,i,iadc)
866 xhelp_t = tof11(right,i,itdc)
867 if(xhelp_a<4095) xhelp = tw11(right,i)/sqrt(xhelp_a)
868 tof11(right,i,itdc) = xhelp_t + xhelp
869 tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
870 ENDDO
871
872 DO i=1,6
873 xhelp_a = tof12(left,i,iadc)
874 xhelp_t = tof12(left,i,itdc)
875 if(xhelp_a<4095) xhelp = tw12(left,i)/sqrt(xhelp_a)
876 tof12(left,i,itdc) = xhelp_t + xhelp
877 tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
878 xhelp_a = tof12(right,i,iadc)
879 xhelp_t = tof12(right,i,itdc)
880 if(xhelp_a<4095) xhelp = tw12(right,i)/sqrt(xhelp_a)
881 tof12(right,i,itdc) = xhelp_t + xhelp
882 tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
883 ENDDO
884 C----
885 DO i=1,2
886 xhelp_a = tof21(left,i,iadc)
887 xhelp_t = tof21(left,i,itdc)
888 if(xhelp_a<4095) xhelp = tw21(left,i)/sqrt(xhelp_a)
889 tof21(left,i,itdc) = xhelp_t + xhelp
890 tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
891 xhelp_a = tof21(right,i,iadc)
892 xhelp_t = tof21(right,i,itdc)
893 if(xhelp_a<4095) xhelp = tw21(right,i)/sqrt(xhelp_a)
894 tof21(right,i,itdc) = xhelp_t + xhelp
895 tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
896 ENDDO
897
898 DO i=1,2
899 xhelp_a = tof22(left,i,iadc)
900 xhelp_t = tof22(left,i,itdc)
901 if(xhelp_a<4095) xhelp = tw22(left,i)/sqrt(xhelp_a)
902 tof22(left,i,itdc) = xhelp_t + xhelp
903 tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
904 xhelp_a = tof22(right,i,iadc)
905 xhelp_t = tof22(right,i,itdc)
906 if(xhelp_a<4095) xhelp = tw22(right,i)/sqrt(xhelp_a)
907 tof22(right,i,itdc) = xhelp_t + xhelp
908 tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
909 ENDDO
910 C----
911
912 DO i=1,3
913 xhelp_a = tof31(left,i,iadc)
914 xhelp_t = tof31(left,i,itdc)
915 if(xhelp_a<4095) xhelp = tw31(left,i)/sqrt(xhelp_a)
916 tof31(left,i,itdc) = xhelp_t + xhelp
917 tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
918 xhelp_a = tof31(right,i,iadc)
919 xhelp_t = tof31(right,i,itdc)
920 if(xhelp_a<4095) xhelp = tw31(right,i)/sqrt(xhelp_a)
921 tof31(right,i,itdc) = xhelp_t + xhelp
922 tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
923 ENDDO
924
925 DO i=1,3
926 xhelp_a = tof32(left,i,iadc)
927 xhelp_t = tof32(left,i,itdc)
928 if(xhelp_a<4095) xhelp = tw32(left,i)/sqrt(xhelp_a)
929 tof32(left,i,itdc) = xhelp_t + xhelp
930 tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
931 xhelp_a = tof32(right,i,iadc)
932 xhelp_t = tof32(right,i,itdc)
933 if(xhelp_a<4095) xhelp = tw32(right,i)/sqrt(xhelp_a)
934 tof32(right,i,itdc) = xhelp_t + xhelp
935 tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
936 ENDDO
937
938
939 C---------------------------------------------------------------------
940 C--------------------Corrections on ADC-data -------------------------
941 C-----------------angle and ADC(x) correction -----------------------
942
943 C-----------------------------S1 -------------------------------------
944
945 yhelp=yout(1)
946
947 phi = atan(tan(THYOUT(1))/tan(THXOUT(1)))
948 theta = atan(tan(THXOUT(1))/cos(phi))
949
950 IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
951
952 i = tof11_i
953
954 if (tof11(left,i,iadc).lt.4095) then
955 tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta)
956 xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
957 xkorr=xkorr/hepratio
958 adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
959 endif
960
961
962 if (tof11(right,i,iadc).lt.4095) then
963 tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta)
964 xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
965 xkorr=xkorr/hepratio
966 adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
967 endif
968 ENDIF
969
970
971 xhelp=xout(2)
972 phi = atan(tan(THYOUT(2))/tan(THXOUT(2)))
973 theta = atan(tan(THXOUT(2))/cos(phi))
974 c write(*,*) 'theta12 ',theta
975 IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
976
977 i = tof12_i
978 if (tof12(left,i,iadc).lt.4095) then
979 tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta)
980 xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
981 xkorr=xkorr/hepratio
982 adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
983 endif
984
985 if (tof12(right,i,iadc).lt.4095) then
986 tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta)
987 xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
988 xkorr=xkorr/hepratio
989 adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
990 endif
991 ENDIF
992
993 C-----------------------------S2 --------------------------------
994
995 xhelp=xout(3)
996 phi = atan(tan(THYOUT(3))/tan(THXOUT(3)))
997 theta = atan(tan(THXOUT(3))/cos(phi))
998 c write(*,*) 'theta21 ',theta
999 IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
1000
1001 i = tof21_i
1002 if (tof21(left,i,iadc).lt.4095) then
1003 tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta)
1004 xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
1005 xkorr=xkorr/hepratio
1006 adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
1007 endif
1008
1009 if (tof21(right,i,iadc).lt.4095) then
1010 tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta)
1011 xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
1012 xkorr=xkorr/hepratio
1013 adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
1014 endif
1015 ENDIF
1016
1017 yhelp=yout(4)
1018 phi = atan(tan(THYOUT(4))/tan(THXOUT(4)))
1019 theta = atan(tan(THXOUT(4))/cos(phi))
1020 c write(*,*) 'theta22 ',theta
1021
1022 IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
1023
1024 i = tof22_i
1025 if (tof22(left,i,iadc).lt.4095) then
1026 tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta)
1027 xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
1028 xkorr=xkorr/hepratio
1029 adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
1030 endif
1031
1032 if (tof22(right,i,iadc).lt.4095) then
1033 tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta)
1034 xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
1035 xkorr=xkorr/hepratio
1036 adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
1037 endif
1038 ENDIF
1039
1040 C-----------------------------S3 --------------------------------
1041
1042 yhelp=yout(5)
1043 phi = atan(tan(THYOUT(5))/tan(THXOUT(5)))
1044 theta = atan(tan(THXOUT(5))/cos(phi))
1045 c write(*,*) 'theta31 ',theta
1046
1047 IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
1048
1049 i = tof31_i
1050 if (tof31(left,i,iadc).lt.4095) then
1051 tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta)
1052 xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
1053 xkorr=xkorr/hepratio
1054 adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
1055 endif
1056
1057 if (tof31(right,i,iadc).lt.4095) then
1058 tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta)
1059 xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
1060 xkorr=xkorr/hepratio
1061 adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
1062 endif
1063 ENDIF
1064
1065 xhelp=xout(6)
1066 phi = atan(tan(THYOUT(6))/tan(THXOUT(6)))
1067 theta = atan(tan(THXOUT(6))/cos(phi))
1068 c write(*,*) 'theta32 ',theta
1069
1070 IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
1071
1072 i = tof32_i
1073 if (tof32(left,i,iadc).lt.4095) then
1074 tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta)
1075 xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
1076 xkorr=xkorr/hepratio
1077 adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
1078 endif
1079
1080 if (tof32(right,i,iadc).lt.4095) then
1081 tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta)
1082 xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
1083 xkorr=xkorr/hepratio
1084 adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
1085 endif
1086 ENDIF
1087
1088 C-----------------------------------------------------------------------
1089 C----------------------calculate Beta ------------------------------
1090 C-----------------------------------------------------------------------
1091 C-------------------difference of sums ---------------------------
1092 C
1093 C DS = (t1+t2) - t3+t4)
1094 C DS = c1 + c2/beta*cos(theta)
1095 C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
1096 C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
1097 C since TDC resolution varies slightly c2 has to be calibrated
1098 C instead of cos(theta) use factor F:
1099 C F = pathlength/d
1100 C => beta = c2*F/(DS-c1))
1101
1102 dist = ZTOF(1) - ZTOF(5)
1103 dl = 0.
1104 DO I=1,5
1105 dl = dl + TLOUT(i)
1106 ENDDO
1107 F = dl/dist
1108
1109 C S11 - S31
1110 C IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1111 IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1112 & (ytofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1113 t1 = tof11(1,tof11_i,itdc)
1114 t2 = tof11(2,tof11_i,itdc)
1115 t3 = tof31(1,tof31_i,itdc)
1116 t4 = tof31(2,tof31_i,itdc)
1117 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1118 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1119 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1120 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1121 ds = xhelp1-xhelp2
1122 ihelp=(tof11_i-1)*3+tof31_i
1123 c1 = k_S11S31(1,ihelp)
1124 c2 = k_S11S31(2,ihelp)
1125 beta_a(1) = c2*F/(ds-c1)
1126 C write(*,*) 'S11-S31 ',xhelp1,xhelp2, beta_a(1)
1127 C-------ToF Mask - S11 - S31
1128
1129 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1130 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1131 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1132 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1133
1134 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1135 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1136 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1137 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1138
1139 ENDIF
1140 ENDIF
1141
1142 dist = ZTOF(1) - ZTOF(6)
1143 dl = 0.
1144 DO I=1,6
1145 dl = dl + TLOUT(i)
1146 ENDDO
1147 F = dl/dist
1148
1149 C S11 - S32
1150 C IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1151 IF ((tof11_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1152 & (ytofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1153 t1 = tof11(1,tof11_i,itdc)
1154 t2 = tof11(2,tof11_i,itdc)
1155 t3 = tof32(1,tof32_i,itdc)
1156 t4 = tof32(2,tof32_i,itdc)
1157 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1158 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1159 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1160 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1161 ds = xhelp1-xhelp2
1162 ihelp=(tof11_i-1)*3+tof32_i
1163 c1 = k_S11S32(1,ihelp)
1164 c2 = k_S11S32(2,ihelp)
1165 beta_a(2) = c2*F/(ds-c1)
1166 C write(*,*) 'S11-S32 ',xhelp1,xhelp2, beta_a(2)
1167
1168 C-------ToF Mask - S11 - S32
1169
1170 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1171 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1172 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1173 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1174
1175 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1176 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1177 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1178 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1179
1180 C-------
1181
1182 ENDIF
1183 ENDIF
1184
1185 C S12 - S31
1186 dist = ZTOF(2) - ZTOF(5)
1187 dl = 0.
1188 DO I=2,5
1189 dl = dl + TLOUT(i)
1190 ENDDO
1191 F = dl/dist
1192
1193 C IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1194 IF ((tof12_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1195 & (xtofpos(1).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1196 t1 = tof12(1,tof12_i,itdc)
1197 t2 = tof12(2,tof12_i,itdc)
1198 t3 = tof31(1,tof31_i,itdc)
1199 t4 = tof31(2,tof31_i,itdc)
1200 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1201 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1202 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1203 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1204 ds = xhelp1-xhelp2
1205 ihelp=(tof12_i-1)*3+tof31_i
1206 c1 = k_S12S31(1,ihelp)
1207 c2 = k_S12S31(2,ihelp)
1208 beta_a(3) = c2*F/(ds-c1)
1209 C write(*,*) 'S12-S31 ',xhelp1,xhelp2, beta_a(3)
1210
1211 C-------ToF Mask - S12 - S31
1212
1213 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1214 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1215 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1216 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1217
1218 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1219 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1220 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1221 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1222
1223 C-------
1224
1225 ENDIF
1226 ENDIF
1227
1228 C S12 - S32
1229
1230 dist = ZTOF(2) - ZTOF(6)
1231 dl = 0.
1232 DO I=2,6
1233 dl = dl + TLOUT(i)
1234 ENDDO
1235 F = dl/dist
1236
1237 C IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1238 IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1239 & (xtofpos(1).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1240 t1 = tof12(1,tof12_i,itdc)
1241 t2 = tof12(2,tof12_i,itdc)
1242 t3 = tof32(1,tof32_i,itdc)
1243 t4 = tof32(2,tof32_i,itdc)
1244 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1245 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1246 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1247 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1248 ds = xhelp1-xhelp2
1249 ihelp=(tof12_i-1)*3+tof32_i
1250 c1 = k_S12S32(1,ihelp)
1251 c2 = k_S12S32(2,ihelp)
1252 beta_a(4) = c2*F/(ds-c1)
1253 C write(*,*) 'S12-S32 ',xhelp1,xhelp2, beta_a(4)
1254
1255 C-------ToF Mask - S12 - S32
1256
1257 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1258 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1259 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1260 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1261
1262 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1263 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1264 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1265 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1266
1267 C-------
1268
1269 ENDIF
1270 ENDIF
1271
1272 C S21 - S31
1273
1274 dist = ZTOF(3) - ZTOF(5)
1275 dl = 0.
1276 DO I=3,5
1277 dl = dl + TLOUT(i)
1278 ENDDO
1279 F = dl/dist
1280
1281 C IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1282 IF ((tof21_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1283 & (xtofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1284 t1 = tof21(1,tof21_i,itdc)
1285 t2 = tof21(2,tof21_i,itdc)
1286 t3 = tof31(1,tof31_i,itdc)
1287 t4 = tof31(2,tof31_i,itdc)
1288 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1289 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1290 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1291 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1292 ds = xhelp1-xhelp2
1293 ihelp=(tof21_i-1)*3+tof31_i
1294 c1 = k_S21S31(1,ihelp)
1295 c2 = k_S21S31(2,ihelp)
1296 beta_a(5) = c2*F/(ds-c1)
1297
1298 C-------ToF Mask - S21 - S31
1299
1300 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1301 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1302 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1303 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1304
1305 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1306 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1307 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1308 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1309
1310 C-------
1311
1312 ENDIF
1313 ENDIF
1314
1315 C S21 - S32
1316
1317 dist = ZTOF(3) - ZTOF(6)
1318 dl = 0.
1319 DO I=3,6
1320 dl = dl + TLOUT(i)
1321 ENDDO
1322 F = dl/dist
1323
1324 C IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1325 IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1326 & (xtofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1327 t1 = tof21(1,tof21_i,itdc)
1328 t2 = tof21(2,tof21_i,itdc)
1329 t3 = tof32(1,tof32_i,itdc)
1330 t4 = tof32(2,tof32_i,itdc)
1331 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1332 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1333 xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1334 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1335 ds = xhelp1-xhelp2
1336 ihelp=(tof21_i-1)*3+tof32_i
1337 c1 = k_S21S32(1,ihelp)
1338 c2 = k_S21S32(2,ihelp)
1339 beta_a(6) = c2*F/(ds-c1)
1340
1341 C-------ToF Mask - S21 - S32
1342
1343 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1344 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1345 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1346 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1347
1348 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1349 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1350 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1351 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1352
1353 C-------
1354
1355 ENDIF
1356 ENDIF
1357
1358 C S22 - S31
1359
1360 dist = ZTOF(4) - ZTOF(5)
1361 dl = 0.
1362 DO I=4,5
1363 dl = dl + TLOUT(i)
1364 ENDDO
1365 F = dl/dist
1366
1367 C IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
1368 IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find).AND.
1369 & (ytofpos(2).NE.101.).AND.(ytofpos(3).NE.101.)) THEN
1370 t1 = tof22(1,tof22_i,itdc)
1371 t2 = tof22(2,tof22_i,itdc)
1372 t3 = tof31(1,tof31_i,itdc)
1373 t4 = tof31(2,tof31_i,itdc)
1374 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1375 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1376 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1377 xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
1378 ds = xhelp1-xhelp2
1379 ihelp=(tof22_i-1)*3+tof31_i
1380 c1 = k_S22S31(1,ihelp)
1381 c2 = k_S22S31(2,ihelp)
1382 beta_a(7) = c2*F/(ds-c1)
1383
1384 C-------ToF Mask - S22 - S31
1385
1386 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1387 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1388 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1389 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1390
1391 tofmask(ch31a(tof31_i),hb31a(tof31_i)) =
1392 $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1
1393 tofmask(ch31b(tof31_i),hb31b(tof31_i)) =
1394 $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1
1395
1396 C-------
1397
1398 ENDIF
1399 ENDIF
1400
1401 C S22 - S32
1402
1403 dist = ZTOF(4) - ZTOF(6)
1404 dl = 0.
1405 DO I=4,6
1406 dl = dl + TLOUT(i)
1407 ENDDO
1408 F = dl/dist
1409
1410 C IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
1411 IF ((tof22_i.GT.none_find).AND.(tof32_i.GT.none_find).AND.
1412 & (ytofpos(2).NE.101.).AND.(xtofpos(3).NE.101.)) THEN
1413 t1 = tof22(1,tof22_i,itdc)
1414 t2 = tof22(2,tof22_i,itdc)
1415 t3 = tof32(1,tof32_i,itdc)
1416 t4 = tof32(2,tof32_i,itdc)
1417 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1418 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1419 xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1420 xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
1421 ds = xhelp1-xhelp2
1422 ihelp=(tof22_i-1)*3+tof32_i
1423 c1 = k_S22S32(1,ihelp)
1424 c2 = k_S22S32(2,ihelp)
1425 beta_a(8) = c2*F/(ds-c1)
1426
1427 C-------ToF Mask - S22 - S32
1428
1429 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1430 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1431 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1432 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1433
1434 tofmask(ch32a(tof32_i),hb32a(tof32_i)) =
1435 $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1
1436 tofmask(ch32b(tof32_i),hb32b(tof32_i)) =
1437 $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1
1438
1439 C-------
1440
1441 ENDIF
1442 ENDIF
1443
1444 C S11 - S21
1445
1446 dist = ZTOF(1) - ZTOF(3)
1447 dl = 0.
1448 DO I=1,3
1449 dl = dl + TLOUT(i)
1450 ENDDO
1451 F = dl/dist
1452
1453 C IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1454 IF ((tof11_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1455 & (ytofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1456 t1 = tof11(1,tof11_i,itdc)
1457 t2 = tof11(2,tof11_i,itdc)
1458 t3 = tof21(1,tof21_i,itdc)
1459 t4 = tof21(2,tof21_i,itdc)
1460 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1461 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1462 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1463 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1464 ds = xhelp1-xhelp2
1465 ihelp=(tof11_i-1)*2+tof21_i
1466 c1 = k_S11S21(1,ihelp)
1467 c2 = k_S11S21(2,ihelp)
1468 beta_a(9) = c2*F/(ds-c1)
1469
1470 C-------ToF Mask - S11 - S21
1471
1472 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1473 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1474 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1475 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1476
1477 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1478 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1479 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1480 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1481
1482 C-------
1483
1484 ENDIF
1485 ENDIF
1486
1487 C S11 - S22
1488
1489 dist = ZTOF(1) - ZTOF(4)
1490 dl = 0.
1491 DO I=1,4
1492 dl = dl + TLOUT(i)
1493 ENDDO
1494 F = dl/dist
1495
1496 C IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1497 IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1498 & (ytofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1499 t1 = tof11(1,tof11_i,itdc)
1500 t2 = tof11(2,tof11_i,itdc)
1501 t3 = tof22(1,tof22_i,itdc)
1502 t4 = tof22(2,tof22_i,itdc)
1503 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1504 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1505 xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
1506 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1507 ds = xhelp1-xhelp2
1508 ihelp=(tof11_i-1)*2+tof22_i
1509 c1 = k_S11S22(1,ihelp)
1510 c2 = k_S11S22(2,ihelp)
1511 beta_a(10) = c2*F/(ds-c1)
1512
1513 C-------ToF Mask - S11 - S22
1514
1515 tofmask(ch11a(tof11_i),hb11a(tof11_i)) =
1516 $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1
1517 tofmask(ch11b(tof11_i),hb11b(tof11_i)) =
1518 $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1
1519
1520 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1521 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1522 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1523 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1524
1525 C-------
1526
1527 ENDIF
1528 ENDIF
1529
1530 C S12 - S21
1531
1532 dist = ZTOF(2) - ZTOF(3)
1533 dl = 0.
1534 DO I=2,3
1535 dl = dl + TLOUT(i)
1536 ENDDO
1537 F = dl/dist
1538
1539 C IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
1540 IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find).AND.
1541 & (xtofpos(1).NE.101.).AND.(xtofpos(2).NE.101.)) THEN
1542 t1 = tof12(1,tof12_i,itdc)
1543 t2 = tof12(2,tof12_i,itdc)
1544 t3 = tof21(1,tof21_i,itdc)
1545 t4 = tof21(2,tof21_i,itdc)
1546 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1547 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1548 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1549 xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
1550 ds = xhelp1-xhelp2
1551 ihelp=(tof12_i-1)*2+tof21_i
1552 c1 = k_S12S21(1,ihelp)
1553 c2 = k_S12S21(2,ihelp)
1554 beta_a(11) = c2*F/(ds-c1)
1555
1556 C-------ToF Mask - S12 - S21
1557
1558 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1559 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1560 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1561 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1562
1563 tofmask(ch21a(tof21_i),hb21a(tof21_i)) =
1564 $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1
1565 tofmask(ch21b(tof21_i),hb21b(tof21_i)) =
1566 $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1
1567
1568 C-------
1569
1570 ENDIF
1571 ENDIF
1572
1573 C S12 - S22
1574
1575 dist = ZTOF(2) - ZTOF(4)
1576 dl = 0.
1577 DO I=2,4
1578 dl = dl + TLOUT(i)
1579 ENDDO
1580 F = dl/dist
1581
1582 C IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
1583 IF ((tof12_i.GT.none_find).AND.(tof22_i.GT.none_find).AND.
1584 & (xtofpos(1).NE.101.).AND.(ytofpos(2).NE.101.)) THEN
1585 t1 = tof12(1,tof12_i,itdc)
1586 t2 = tof12(2,tof12_i,itdc)
1587 t3 = tof22(1,tof22_i,itdc)
1588 t4 = tof22(2,tof22_i,itdc)
1589 IF ((t1.lt.4095).and.(t2.lt.4095).and.
1590 & (t3.lt.4095).and.(t4.lt.4095)) THEN
1591 xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
1592 xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
1593 ds = xhelp1-xhelp2
1594 ihelp=(tof12_i-1)*2+tof22_i
1595 c1 = k_S12S22(1,ihelp)
1596 c2 = k_S12S22(2,ihelp)
1597 beta_a(12) = c2*F/(ds-c1)
1598
1599 C-------ToF Mask - S12 - S22
1600
1601 tofmask(ch12a(tof12_i),hb12a(tof12_i)) =
1602 $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1
1603 tofmask(ch12b(tof12_i),hb12b(tof12_i)) =
1604 $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1
1605
1606 tofmask(ch22a(tof22_i),hb22a(tof22_i)) =
1607 $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1
1608 tofmask(ch22b(tof22_i),hb22b(tof22_i)) =
1609 $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1
1610
1611 C-------
1612
1613 ENDIF
1614 ENDIF
1615
1616 C-------
1617
1618 icount=0
1619 sw=0.
1620 sxw=0.
1621 beta_mean=100.
1622
1623 do i=1,12
1624 if ((beta_a(i).gt.-1.5).and.(beta_a(i).lt.1.5)) then
1625 icount= icount+1
1626 if (i.le.4) w_i=1./(0.13**2.)
1627 if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
1628 if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
1629 sxw=sxw + beta_a(i)*w_i
1630 sw =sw + w_i
1631 endif
1632 enddo
1633
1634 if (icount.gt.0) beta_mean=sxw/sw
1635 beta_a(13) = beta_mean
1636
1637
1638 c IF (tof11_i.GT.none_find)
1639 c & write(*,*) '11 ',tof11(1,tof11_i,itdc),tof11(2,tof11_i,itdc)
1640 c IF (tof12_i.GT.none_find)
1641 c & write(*,*) '12 ',tof12(1,tof12_i,itdc),tof12(2,tof12_i,itdc)
1642
1643 c IF (tof21_i.GT.none_find)
1644 c & write(*,*) '21 ',tof21(1,tof21_i,itdc),tof21(2,tof21_i,itdc)
1645 c IF (tof22_i.GT.none_find)
1646 c & write(*,*) '22 ',tof22(1,tof22_i,itdc),tof22(2,tof22_i,itdc)
1647
1648 c IF (tof31_i.GT.none_find)
1649 c & write(*,*) '31 ',tof31(1,tof31_i,itdc),tof31(2,tof31_i,itdc)
1650 c IF (tof32_i.GT.none_find)
1651 c & write(*,*) '32 ',tof32(1,tof32_i,itdc),tof32(2,tof32_i,itdc)
1652
1653 c write(*,*) xtofpos
1654 c write(*,*) ytofpos
1655 c write(*,*) beta_a
1656 C write(*,*) adcflagtof
1657
1658
1659 C write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4)
1660
1661 RETURN
1662 END
1663
1664
1665

  ViewVC Help
Powered by ViewVC 1.1.23