/[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.10 - (show annotations) (download)
Wed Feb 7 08:17:17 2007 UTC (17 years, 9 months ago) by mocchiut
Branch: MAIN
Changes since 1.9: +10 -1 lines
Bug fixed: sometimes tdc_tw is incorrect due to leftover xhelp

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

  ViewVC Help
Powered by ViewVC 1.1.23