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

Annotation of /DarthVader/ToFLevel2/src/tofl2com.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (hide annotations) (download)
Sat Jun 17 12:14:56 2006 UTC (18 years, 5 months ago) by mocchiut
Branch: MAIN
Branch point for: ToFLevel2
Initial revision

1 mocchiut 1.1 *****************************************************************************
2     INTEGER FUNCTION TOFL2COM()
3     c
4     IMPLICIT NONE
5     C
6     include 'input_tof.txt'
7     include 'output_tof.txt'
8     include 'tofcomm.txt'
9    
10     INTEGER icounter
11     DATA icounter / 0/
12    
13     LOGICAL check
14     REAL secure
15    
16     INTEGER j
17     REAL xhelp_a,xhelp_t
18    
19     REAL dx,dy,dr,ds
20     REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2
21     REAL c1,c2,sw,sxw,w_i
22     INTEGER icount
23    
24     INTEGER tof11_j,tof21_j,tof31_j
25     INTEGER tof12_j,tof22_j,tof32_j
26    
27     REAL beta_mean
28    
29    
30     c value for status of each PM-data
31     c first index : 1 = left, 2 = right
32     c second index : 1... number of paddle
33     INTEGER tof11_event(2,8),tof12_event(2,6)
34     INTEGER tof21_event(2,2),tof22_event(2,2)
35     INTEGER tof31_event(2,3),tof32_event(2,3)
36    
37    
38     REAL theta12,theta13,theta23
39     C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006
40     REAL tofarm12
41     PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69
42     REAL tofarm23
43     PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92
44     REAL tofarm13
45     PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92
46    
47    
48     INTEGER ihelp
49     REAL xkorr
50    
51     C---------------------------------------
52     C
53     C Begin !
54     C
55     TOFL2COM = 0
56     C
57     C CALCULATE COMMON VARIABLES
58     C
59    
60     *******************************************************************
61     icounter = icounter + 1
62    
63     * amplitude has to be 'secure' higher than pedestal for an adc event
64     secure = 2.
65    
66     offset = 1
67     slope = 2
68     left = 1
69     right = 2
70     none_ev = 0
71     none_find = 0
72     tdc_ev = 1
73     adc_ev = 1
74     itdc = 1
75     iadc = 2
76    
77     do i=1,13
78     betatof_a(i) = 100. ! As in "troftrk.for"
79     enddo
80    
81     do i=1,4
82     do j=1,12
83     adctof_c(i,j) = 1000.
84     enddo
85     enddo
86    
87    
88     do i=1,4
89     do j=1,12
90     tdc_c(i,j) = 4095.
91     enddo
92     enddo
93    
94    
95     c the calibration files are read in the main program from xxx_tofcalib.rz
96    
97    
98     c-------------------------get ToF data --------------------------------
99    
100     c put the adc and tdc values from ntuple into tofxx(i,j,k) variables
101    
102    
103     do j=1,8
104     tof11(1,j,2) = adc(ch11a(j),hb11a(j))
105     tof11(2,j,2) = adc(ch11b(j),hb11b(j))
106     tof11(1,j,1) = tdc(ch11a(j),hb11a(j))
107     tof11(2,j,1) = tdc(ch11b(j),hb11b(j))
108     enddo
109    
110    
111     do j=1,6
112     tof12(1,j,2) = adc(ch12a(j),hb12a(j))
113     tof12(2,j,2) = adc(ch12b(j),hb12b(j))
114     tof12(1,j,1) = tdc(ch12a(j),hb12a(j))
115     tof12(2,j,1) = tdc(ch12b(j),hb12b(j))
116     enddo
117    
118     do j=1,2
119     tof21(1,j,2) = adc(ch21a(j),hb21a(j))
120     tof21(2,j,2) = adc(ch21b(j),hb21b(j))
121     tof21(1,j,1) = tdc(ch21a(j),hb21a(j))
122     tof21(2,j,1) = tdc(ch21b(j),hb21b(j))
123     enddo
124    
125     do j=1,2
126     tof22(1,j,2) = adc(ch22a(j),hb22a(j))
127     tof22(2,j,2) = adc(ch22b(j),hb22b(j))
128     tof22(1,j,1) = tdc(ch22a(j),hb22a(j))
129     tof22(2,j,1) = tdc(ch22b(j),hb22b(j))
130     enddo
131    
132     do j=1,3
133     tof31(1,j,2) = adc(ch31a(j),hb31a(j))
134     tof31(2,j,2) = adc(ch31b(j),hb31b(j))
135     tof31(1,j,1) = tdc(ch31a(j),hb31a(j))
136     tof31(2,j,1) = tdc(ch31b(j),hb31b(j))
137     enddo
138    
139     do j=1,3
140     tof32(1,j,2) = adc(ch32a(j),hb32a(j))
141     tof32(2,j,2) = adc(ch32b(j),hb32b(j))
142     tof32(1,j,1) = tdc(ch32a(j),hb32a(j))
143     tof32(2,j,1) = tdc(ch32b(j),hb32b(j))
144     enddo
145    
146     C----------------------------------------------------------------------
147    
148     DO i = 1,8
149     if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000.
150     if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000.
151     if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000.
152     if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000.
153     ENDDO
154    
155     DO i = 1,6
156     if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000.
157     if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000.
158     if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000.
159     if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000.
160     ENDDO
161    
162    
163     DO i = 1,2
164     if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000.
165     if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000.
166     if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000.
167     if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000.
168     ENDDO
169    
170     DO i = 1,2
171     if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000.
172     if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000.
173     if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000.
174     if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000.
175     ENDDO
176    
177     DO i = 1,3
178     if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000.
179     if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000.
180     if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000.
181     if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000.
182     ENDDO
183    
184     DO i = 1,3
185     if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000.
186     if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000.
187     if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000.
188     if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000.
189     ENDDO
190    
191     C----------------------------------------------------------------
192     C------------Check Paddles for hits -----------------------
193     C----------------------------------------------------------------
194    
195     C upper tof S11
196     DO i = 1,8
197    
198     DO j = 1,2
199     tof11_event(j,i) = none_ev
200     IF ((tof11(j,i,itdc).LT.2000).AND.(tof11(j,i,itdc).GT.100))
201     + tof11_event(j,i) = tof11_event(j,i) + tdc_ev
202     IF ((tof11(j,i,iadc).GT.secure).AND.
203     + (tof11(j,i,iadc).LT.4095))
204     + tof11_event(j,i) = tof11_event(j,i) + adc_ev
205     ENDDO
206     ENDDO
207    
208     c find single paddle in upper tof with tdc and adc signal
209     tof11_i = none_find
210     tof11_j = none_find
211     check = .TRUE.
212     DO i = 1, 8
213     IF ((tof11_event(left,i).GE.1).AND.(tof11_event(right,i).GE.1))
214     + THEN
215     c check if an other paddle has also an event - then set flag
216     tof11_j = tof11_j + 2**(i-1)
217     IF (check.EQV..TRUE.) THEN
218     IF (tof11_i.EQ.none_find) THEN
219     tof11_i = i
220     ELSE
221     tof11_i = -1
222     check = .FALSE.
223     ENDIF
224     ENDIF
225     ENDIF
226     ENDDO
227    
228    
229     C upper tof S12
230     DO i = 1,6
231     DO j = 1,2
232     tof12_event(j,i) = none_ev
233     IF ((tof12(j,i,itdc).LT.2000).AND.(tof12(j,i,itdc).GT.100))
234     + tof12_event(j,i) = tof12_event(j,i) + tdc_ev
235     IF ((tof12(j,i,iadc).GT.secure).AND.
236     + (tof12(j,i,iadc).LT.4095))
237     + tof12_event(j,i) = tof12_event(j,i) + adc_ev
238     ENDDO
239     ENDDO
240    
241     c find single paddle in upper tof with tdc and adc signal
242     tof12_i = none_find
243     tof12_j = none_find
244     check = .TRUE.
245     DO i = 1, 6
246     IF ((tof12_event(left,i).GE.1).AND.(tof12_event(right,i).GE.1))
247     + THEN
248     c check if an other paddle has also an event - then set flag
249     tof12_j = tof12_j + 2**(i-1)
250     IF (check.EQV..TRUE.) THEN
251     IF (tof12_i.EQ.none_find) THEN
252     tof12_i = i
253     ELSE
254     tof12_i = -1
255     check = .FALSE.
256     ENDIF
257     ENDIF
258     ENDIF
259     ENDDO
260    
261    
262     C middle tof S21
263     DO i = 1,2
264     DO j = 1,2
265     tof21_event(j,i) = none_ev
266     IF ((tof21(j,i,itdc).LT.2000).AND.(tof21(j,i,itdc).GT.100))
267     + tof21_event(j,i) = tof21_event(j,i) + tdc_ev
268     IF ((tof21(j,i,iadc).GT.secure).AND.
269     + (tof21(j,i,iadc).LT.4095))
270     + tof21_event(j,i) = tof21_event(j,i) + adc_ev
271     ENDDO
272     ENDDO
273    
274     c find single paddle in upper tof with tdc and adc signal
275     tof21_i = none_find
276     tof21_j = none_find
277     check = .TRUE.
278     DO i = 1, 2
279     IF ((tof21_event(left,i).GE.1).AND.(tof21_event(right,i).GE.1))
280     + THEN
281     c check if an other paddle has also an event - then set flag
282     tof21_j = tof21_j + 2**(i-1)
283     IF (check.EQV..TRUE.) THEN
284     IF (tof21_i.EQ.none_find) THEN
285     tof21_i = i
286     ELSE
287     tof21_i = -1
288     check = .FALSE.
289     ENDIF
290     ENDIF
291     ENDIF
292     ENDDO
293    
294     C middle tof S22
295     DO i = 1,2
296     DO j = 1,2
297     tof22_event(j,i) = none_ev
298     IF ((tof22(j,i,itdc).LT.2000).AND.(tof22(j,i,itdc).GT.100))
299     + tof22_event(j,i) = tof22_event(j,i) + tdc_ev
300     IF ((tof22(j,i,iadc).GT.secure).AND.
301     + (tof22(j,i,iadc).LT.4095))
302     + tof22_event(j,i) = tof22_event(j,i) + adc_ev
303     ENDDO
304     ENDDO
305    
306     c find single paddle in upper tof with tdc and adc signal
307     tof22_i = none_find
308     tof22_j = none_find
309     check = .TRUE.
310     DO i = 1, 2
311     IF ((tof22_event(left,i).GE.1).AND.(tof22_event(right,i).GE.1))
312     + THEN
313     c check if an other paddle has also an event - then set flag
314     tof22_j = tof22_j + 2**(i-1)
315     IF (check.EQV..TRUE.) THEN
316     IF (tof22_i.EQ.none_find) THEN
317     tof22_i = i
318     ELSE
319     tof22_i = -1
320     check = .FALSE.
321     ENDIF
322     ENDIF
323     ENDIF
324     ENDDO
325    
326    
327     C bottom tof S31
328     DO i = 1,3
329     DO j = 1,2
330     tof31_event(j,i) = none_ev
331     IF ((tof31(j,i,itdc).LT.2000).AND.(tof31(j,i,itdc).GT.100))
332     + tof31_event(j,i) = tof31_event(j,i) + tdc_ev
333     IF ((tof31(j,i,iadc).GT.secure).AND.
334     + (tof31(j,i,iadc).LT.4095))
335     + tof31_event(j,i) = tof31_event(j,i) + adc_ev
336     ENDDO
337     ENDDO
338    
339     c find single paddle in upper tof with tdc and adc signal
340     tof31_i = none_find
341     tof31_j = none_find
342     check = .TRUE.
343     DO i = 1, 3
344     IF ((tof31_event(left,i).GE.1).AND.(tof31_event(right,i).GE.1))
345     + THEN
346     c check if an other paddle has also an event - then set flag
347     tof31_j = tof31_j + 2**(i-1)
348     IF (check.EQV..TRUE.) THEN
349     IF (tof31_i.EQ.none_find) THEN
350     tof31_i = i
351     ELSE
352     tof31_i = -1
353     check = .FALSE.
354     ENDIF
355     ENDIF
356     ENDIF
357     ENDDO
358    
359     C bottom tof S32
360     DO i = 1,3
361     DO j = 1,2
362     tof32_event(j,i) = none_ev
363     IF ((tof32(j,i,itdc).LT.2000).AND.(tof32(j,i,itdc).GT.100))
364     + tof32_event(j,i) = tof32_event(j,i) + tdc_ev
365     IF ((tof32(j,i,iadc).GT.secure).AND.
366     + (tof32(j,i,iadc).LT.4095))
367     + tof32_event(j,i) = tof32_event(j,i) + adc_ev
368     ENDDO
369     ENDDO
370    
371     c find single paddle in upper tof with tdc and adc signal
372     tof32_i = none_find
373     tof32_j = none_find
374     check = .TRUE.
375     DO i = 1, 3
376     IF ((tof32_event(left,i).GE.1).AND.(tof32_event(right,i).GE.1))
377     + THEN
378     c check if an other paddle has also an event - then set flag
379     tof32_j = tof32_j + 2**(i-1)
380     IF (check.EQV..TRUE.) THEN
381     IF (tof32_i.EQ.none_find) THEN
382     tof32_i = i
383     ELSE
384     tof32_i = -1
385     check = .FALSE.
386     ENDIF
387     ENDIF
388     ENDIF
389     ENDDO
390    
391     do i=1,6
392     tof_i_flag(i)=0
393     tof_j_flag(i)=0
394     enddo
395    
396     tof_i_flag(1)=tof11_i
397     tof_i_flag(2)=tof12_i
398     tof_i_flag(3)=tof21_i
399     tof_i_flag(4)=tof22_i
400     tof_i_flag(5)=tof31_i
401     tof_i_flag(6)=tof32_i
402    
403     tof_j_flag(1)=tof11_j
404     tof_j_flag(2)=tof12_j
405     tof_j_flag(3)=tof21_j
406     tof_j_flag(4)=tof22_j
407     tof_j_flag(5)=tof31_j
408     tof_j_flag(6)=tof32_j
409    
410    
411     C--------------------------------------------------------------------
412     C--------------------Time walk correction -------------------------
413     C--------------------------------------------------------------------
414    
415     DO i=1,8
416     xhelp_a = tof11(left,i,iadc)
417     xhelp_t = tof11(left,i,itdc)
418     if(xhelp_a>0) xhelp = tw11(left,i)/sqrt(xhelp_a)
419     tof11(left,i,itdc) = xhelp_t + xhelp
420     tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc)
421     xhelp_a = tof11(right,i,iadc)
422     xhelp_t = tof11(right,i,itdc)
423     if(xhelp_a>0) xhelp = tw11(right,i)/sqrt(xhelp_a)
424     tof11(right,i,itdc) = xhelp_t + xhelp
425     tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc)
426     ENDDO
427    
428     DO i=1,6
429     xhelp_a = tof12(left,i,iadc)
430     xhelp_t = tof12(left,i,itdc)
431     if(xhelp_a>0) xhelp = tw12(left,i)/sqrt(xhelp_a)
432     tof12(left,i,itdc) = xhelp_t + xhelp
433     tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc)
434     xhelp_a = tof12(right,i,iadc)
435     xhelp_t = tof12(right,i,itdc)
436     if(xhelp_a>0) xhelp = tw12(right,i)/sqrt(xhelp_a)
437     tof12(right,i,itdc) = xhelp_t + xhelp
438     tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc)
439     ENDDO
440     C----
441     DO i=1,2
442     xhelp_a = tof21(left,i,iadc)
443     xhelp_t = tof21(left,i,itdc)
444     if(xhelp_a>0) xhelp = tw21(left,i)/sqrt(xhelp_a)
445     tof21(left,i,itdc) = xhelp_t + xhelp
446     tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc)
447     xhelp_a = tof21(right,i,iadc)
448     xhelp_t = tof21(right,i,itdc)
449     if(xhelp_a>0) xhelp = tw21(right,i)/sqrt(xhelp_a)
450     tof21(right,i,itdc) = xhelp_t + xhelp
451     tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc)
452     ENDDO
453    
454     DO i=1,2
455     xhelp_a = tof22(left,i,iadc)
456     xhelp_t = tof22(left,i,itdc)
457     if(xhelp_a>0) xhelp = tw22(left,i)/sqrt(xhelp_a)
458     tof22(left,i,itdc) = xhelp_t + xhelp
459     tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc)
460     xhelp_a = tof22(right,i,iadc)
461     xhelp_t = tof22(right,i,itdc)
462     if(xhelp_a>0) xhelp = tw22(right,i)/sqrt(xhelp_a)
463     tof22(right,i,itdc) = xhelp_t + xhelp
464     tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc)
465     ENDDO
466     C----
467    
468     DO i=1,3
469     xhelp_a = tof31(left,i,iadc)
470     xhelp_t = tof31(left,i,itdc)
471     if(xhelp_a>0) xhelp = tw31(left,i)/sqrt(xhelp_a)
472     tof31(left,i,itdc) = xhelp_t + xhelp
473     tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc)
474     xhelp_a = tof31(right,i,iadc)
475     xhelp_t = tof31(right,i,itdc)
476     if(xhelp_a>0) xhelp = tw31(right,i)/sqrt(xhelp_a)
477     tof31(right,i,itdc) = xhelp_t + xhelp
478     tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc)
479     ENDDO
480    
481     DO i=1,3
482     xhelp_a = tof32(left,i,iadc)
483     xhelp_t = tof32(left,i,itdc)
484     if(xhelp_a>0) xhelp = tw32(left,i)/sqrt(xhelp_a)
485     tof32(left,i,itdc) = xhelp_t + xhelp
486     tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc)
487     xhelp_a = tof32(right,i,iadc)
488     xhelp_t = tof32(right,i,itdc)
489     if(xhelp_a>0) xhelp = tw32(right,i)/sqrt(xhelp_a)
490     tof32(right,i,itdc) = xhelp_t + xhelp
491     tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc)
492     ENDDO
493     C----
494    
495     C------------------------------------------------------------------
496     C--- calculate track position in paddle using timing difference
497     C------------------------------------------------------------------
498    
499     do i=1,3
500     xtofpos(i)=100.
501     ytofpos(i)=100.
502     enddo
503     C-----------------------------S1 --------------------------------
504    
505     IF (tof11_i.GT.none_find) THEN
506     ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2.
507     + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope)
508     endif
509    
510     IF (tof12_i.GT.none_find) THEN
511     xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2.
512     + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope)
513     endif
514    
515    
516     C-----------------------------S2 --------------------------------
517    
518     IF (tof21_i.GT.none_find) THEN
519     xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2.
520     + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope)
521     endif
522    
523     IF (tof22_i.GT.none_find) THEN
524     ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2.
525     + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope)
526     endif
527    
528    
529     C-----------------------------S3 --------------------------------
530    
531     IF (tof31_i.GT.none_find) THEN
532     ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2.
533     + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope)
534     endif
535    
536     IF (tof32_i.GT.none_find) THEN
537     xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2.
538     + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope)
539     endif
540    
541    
542     do i=1,3
543     if (abs(xtofpos(i)).gt.100.) then
544     xtofpos(i)=101.
545     endif
546     if (abs(ytofpos(i)).gt.100.) then
547     ytofpos(i)=101.
548     endif
549     enddo
550    
551     C----------------------------------------------------------------------
552     C--------------------Corrections on ADC-data -------------------------
553     C---------------------zenith angle theta ---------------------------
554     C----------------------------------------------------------------------
555    
556     dx=0.
557     dy=0.
558     dr=0.
559     theta13 = 0.
560    
561     IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find))
562     & dx = xtofpos(1) - xtofpos(3)
563     IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find))
564     & dy = ytofpos(1) - ytofpos(3)
565     dr = sqrt(dx*dx+dy*dy)
566     theta13 = atan(dr/tofarm13)
567    
568     dx=0.
569     dy=0.
570     dr=0.
571     theta12 = 0.
572    
573     IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find))
574     & dx = xtofpos(1) - xtofpos(2)
575     IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find))
576     & dy = ytofpos(1) - ytofpos(2)
577     dr = sqrt(dx*dx+dy*dy)
578     theta12 = atan(dr/tofarm12)
579    
580     dx=0.
581     dy=0.
582     dr=0.
583     theta23 = 0.
584    
585     IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find))
586     & dx = xtofpos(2) - xtofpos(3)
587     IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find))
588     & dy = ytofpos(2) - ytofpos(3)
589     dr = sqrt(dx*dx+dy*dy)
590     theta23 = atan(dr/tofarm23)
591    
592    
593     C----------------------------------------------------------------------
594     C------------------angle and ADC(x) correction
595     C----------------------------------------------------------------------
596     C-----------------------------S1 --------------------------------
597     c middle y (or x) position of the upper and middle ToF-Paddle
598     c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/
599     c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/
600     c DATA tof21_y/ -3.75,3.75/
601     c DATA tof22_x/ -4.5,4.5/
602     c DATA tof31_x/ -6.0,0.,6.0/
603     c DATA tof32_y/ -5.0,0.0,5.0/
604    
605     yhelp=0.
606     if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i)
607     if (ytofpos(1).lt.100) yhelp=ytofpos(1)
608    
609     IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
610    
611     i = tof11_i
612     xdummy=tof11(left,i,iadc)
613     tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13)
614     if (tof11(left,i,iadc).lt.1000) then
615     xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
616     xkorr0=adcx11(left,i,1)
617     adctof_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr
618     endif
619    
620     tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13)
621     if (tof11(right,i,iadc).lt.1000) then
622     xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
623     xkorr0=adcx11(right,i,1)
624     adctof_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr
625     endif
626     ENDIF
627    
628     xhelp=0.
629     if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i)
630     if (xtofpos(1).lt.100) xhelp=xtofpos(1)
631    
632     IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
633    
634     i = tof12_i
635     tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13)
636     if (tof12(left,i,iadc).lt.1000) then
637     xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
638     xkorr0=adcx12(left,i,1)
639     adctof_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr
640     endif
641    
642     tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13)
643     if (tof12(right,i,iadc).lt.1000) then
644     xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
645     xkorr0=adcx12(right,i,1)
646     adctof_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr
647     endif
648     ENDIF
649    
650     C-----------------------------S2 --------------------------------
651    
652     xhelp=0.
653     if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i)
654     if (xtofpos(2).lt.100) xhelp=xtofpos(2)
655    
656     IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
657    
658     i = tof21_i
659     tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13)
660     if (tof21(left,i,iadc).lt.1000) then
661     xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
662     xkorr0=adcx21(left,i,1)
663     adctof_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr
664     endif
665    
666     tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13)
667     if (tof21(right,i,iadc).lt.1000) then
668     xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
669     xkorr0=adcx21(right,i,1)
670     adctof_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr
671     endif
672     ENDIF
673    
674    
675     yhelp=0.
676     if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i)
677     if (ytofpos(2).lt.100) yhelp=ytofpos(2)
678    
679     IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
680    
681     i = tof22_i
682     tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13)
683     if (tof22(left,i,iadc).lt.1000) then
684     xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
685     xkorr0=adcx22(left,i,1)
686     adctof_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr
687     endif
688    
689     tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13)
690     if (tof22(right,i,iadc).lt.1000) then
691     xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
692     xkorr0=adcx22(right,i,1)
693     adctof_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr
694     endif
695     ENDIF
696    
697     C-----------------------------S3 --------------------------------
698    
699     yhelp=0.
700     if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i)
701     if (ytofpos(3).lt.100) yhelp=ytofpos(3)
702    
703     IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN
704    
705     i = tof31_i
706     tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13)
707     if (tof31(left,i,iadc).lt.1000) then
708     xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
709     xkorr0=adcx31(left,i,1)
710     adctof_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr
711     endif
712    
713     tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13)
714     if (tof31(right,i,iadc).lt.1000) then
715     xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
716     xkorr0=adcx31(right,i,1)
717     adctof_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr
718     endif
719     ENDIF
720    
721     xhelp=0.
722     if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i)
723     if (xtofpos(3).lt.100) xhelp=xtofpos(3)
724    
725     IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN
726    
727     i = tof32_i
728     tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13)
729     if (tof32(left,i,iadc).lt.1000) then
730     xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
731     xkorr0=adcx32(left,i,1)
732     adctof_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr
733     endif
734    
735     tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13)
736     if (tof32(right,i,iadc).lt.1000) then
737     xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
738     xkorr0=adcx32(right,i,1)
739     adctof_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr
740     endif
741     ENDIF
742    
743     C-----------------------------------------------------------------------
744     C----------------------calculate Beta ------------------------------
745     C-----------------------------------------------------------------------
746     C-------------------difference of sums ---------------------------
747     C
748     C DS = (t1+t2) - t3+t4)
749     C DS = c1 + c2/beta*cos(theta)
750     C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel
751     C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m
752     C since TDC resolution varies slightly c2 has to be calibrated
753    
754     C S11 - S31
755     IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
756     xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
757     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
758     ds = xhelp1-xhelp2
759     ihelp=(tof11_i-1)*3+tof31_i
760     c1 = k_S11S31(1,ihelp)
761     c2 = k_S11S31(2,ihelp)
762     betatof_a(1) = c2/(cos(theta13)*(ds-c1))
763     ENDIF
764    
765     C S11 - S32
766     IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
767     xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
768     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
769     ds = xhelp1-xhelp2
770     ihelp=(tof11_i-1)*3+tof32_i
771     c1 = k_S11S32(1,ihelp)
772     c2 = k_S11S32(2,ihelp)
773     betatof_a(2) = c2/(cos(theta13)*(ds-c1))
774     ENDIF
775    
776     C S12 - S31
777     IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
778     xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
779     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
780     ds = xhelp1-xhelp2
781     ihelp=(tof12_i-1)*3+tof31_i
782     c1 = k_S12S31(1,ihelp)
783     c2 = k_S12S31(2,ihelp)
784     betatof_a(3) = c2/(cos(theta13)*(ds-c1))
785     ENDIF
786    
787     C S12 - S32
788     IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
789     xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
790     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
791     ds = xhelp1-xhelp2
792     ihelp=(tof12_i-1)*3+tof32_i
793     c1 = k_S12S32(1,ihelp)
794     c2 = k_S12S32(2,ihelp)
795     betatof_a(4) = c2/(cos(theta13)*(ds-c1))
796     ENDIF
797    
798     C S21 - S31
799     IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
800     xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
801     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
802     ds = xhelp1-xhelp2
803     ihelp=(tof21_i-1)*3+tof31_i
804     c1 = k_S21S31(1,ihelp)
805     c2 = k_S21S31(2,ihelp)
806     betatof_a(5) = c2/(cos(theta23)*(ds-c1))
807     ENDIF
808    
809     C S21 - S32
810     IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
811     xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
812     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
813     ds = xhelp1-xhelp2
814     ihelp=(tof21_i-1)*3+tof32_i
815     c1 = k_S21S32(1,ihelp)
816     c2 = k_S21S32(2,ihelp)
817     betatof_a(6) = c2/(cos(theta23)*(ds-c1))
818     ENDIF
819    
820     C S22 - S31
821     IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN
822     xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
823     xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc)
824     ds = xhelp1-xhelp2
825     ihelp=(tof22_i-1)*3+tof31_i
826     c1 = k_S22S31(1,ihelp)
827     c2 = k_S22S31(2,ihelp)
828     betatof_a(7) = c2/(cos(theta13)*(ds-c1))
829     ENDIF
830    
831     C S22 - S32
832     IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN
833     xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
834     xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc)
835     ds = xhelp1-xhelp2
836     ihelp=(tof22_i-1)*3+tof32_i
837     c1 = k_S22S32(1,ihelp)
838     c2 = k_S22S32(2,ihelp)
839     betatof_a(8) = c2/(cos(theta13)*(ds-c1))
840     ENDIF
841    
842     C S11 - S21
843     IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
844     xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
845     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
846     ds = xhelp1-xhelp2
847     ihelp=(tof11_i-1)*2+tof21_i
848     c1 = k_S11S21(1,ihelp)
849     c2 = k_S11S21(2,ihelp)
850     betatof_a(9) = c2/(cos(theta13)*(ds-c1))
851     ENDIF
852    
853     C S11 - S22
854     IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
855     xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc)
856     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
857     ds = xhelp1-xhelp2
858     ihelp=(tof11_i-1)*2+tof22_i
859     c1 = k_S11S22(1,ihelp)
860     c2 = k_S11S22(2,ihelp)
861     betatof_a(10) = c2/(cos(theta13)*(ds-c1))
862     ENDIF
863    
864     C S12 - S21
865     IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN
866     xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
867     xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc)
868     ds = xhelp1-xhelp2
869     ihelp=(tof12_i-1)*2+tof21_i
870     c1 = k_S12S21(1,ihelp)
871     c2 = k_S12S21(2,ihelp)
872     betatof_a(11) = c2/(cos(theta13)*(ds-c1))
873     ENDIF
874    
875     C S12 - S22
876     IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN
877     xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc)
878     xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc)
879     ds = xhelp1-xhelp2
880     ihelp=(tof12_i-1)*2+tof22_i
881     c1 = k_S12S22(1,ihelp)
882     c2 = k_S12S22(2,ihelp)
883     betatof_a(12) = c2/(cos(theta13)*(ds-c1))
884     ENDIF
885    
886     C-------
887    
888     icount=0
889     sw=0.
890     sxw=0.
891     beta_mean=100.
892    
893     do i=1,12
894     if ((betatof_a(i).gt.-1.5).and.(betatof_a(i).lt.1.5)) then
895     icount= icount+1
896     if (i.le.4) w_i=1./(0.13**2.)
897     if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.)
898     if (i.ge.9) w_i=1./(0.25**2.) ! to be checked
899     sxw=sxw + betatof_a(i)*w_i
900     sw =sw + w_i
901     endif
902     enddo
903    
904     if (icount.gt.0) beta_mean=sxw/sw
905     betatof_a(13) = beta_mean
906     c write(*,*) '------------- end tofl2com ----------'
907    
908     100 continue
909    
910     C
911     RETURN
912     END

  ViewVC Help
Powered by ViewVC 1.1.23