24 |
C inserted. In the old code one would still calculate a |
C inserted. In the old code one would still calculate a |
25 |
C xtofpos-value even if the TDC information was missing |
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 |
C jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift |
27 |
|
C jan-05 WM: bug fixed: calculation of zenith angles using DOTRACK2 |
28 |
|
C was incorrect |
29 |
|
C jan-07 WM: bug fixed: in some cases tdc_tw was calculated due to a |
30 |
|
C leftover "xhelp" value |
31 |
|
C apr-07 WM: attenuation fit curve is now a double exponential fit |
32 |
|
C conversion from raw ADC to pC using calibration function |
33 |
|
C new variables xtr_tof(6) and ytr_tof(6) give track position |
34 |
|
C at ToF layers |
35 |
C |
C |
36 |
C**************************************************************************** |
C**************************************************************************** |
37 |
IMPLICIT NONE |
IMPLICIT NONE |
61 |
|
|
62 |
|
|
63 |
INTEGER IFAIL |
INTEGER IFAIL |
64 |
c REAL dx,dy,dr,xdummy |
c REAL dx,dy,dr |
65 |
REAL ds |
REAL ds |
66 |
REAL t1,t2,t3,t4 |
REAL t1,t2,t3,t4 |
67 |
REAL yhelp,xhelp,xhelp1,xhelp2 |
REAL yhelp,xhelp,xhelp1,xhelp2 |
75 |
|
|
76 |
INTEGER j |
INTEGER j |
77 |
|
|
78 |
|
real atten,pc_adc |
79 |
|
|
80 |
|
|
81 |
REAL theta,phi |
REAL theta,phi |
82 |
C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006 |
C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006 |
83 |
REAL tofarm12 |
REAL tofarm12 |
113 |
ievent = ievent +1 |
ievent = ievent +1 |
114 |
|
|
115 |
C ratio helium to proton ca. 4 |
C ratio helium to proton ca. 4 |
116 |
hepratio = 4.5 |
hepratio = 4. |
117 |
|
|
118 |
offset = 1 |
offset = 1 |
119 |
slope = 2 |
slope = 2 |
156 |
|
|
157 |
pmt_id=0 |
pmt_id=0 |
158 |
|
|
159 |
|
do j=1,6 |
160 |
|
THXOUT(j) = 0. |
161 |
|
THYOUT(j) = 0. |
162 |
|
enddo |
163 |
|
|
164 |
|
do j=1,6 |
165 |
|
xtr_tof(j) = 100. |
166 |
|
ytr_tof(j) = 100. |
167 |
|
enddo |
168 |
|
|
169 |
C---------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
170 |
C-------------------------get ToF data -------------------------------- |
C-------------------------get ToF data -------------------------------- |
171 |
C we cannot use the tofxx(x,x,x) data from tofl2com since it is |
C we cannot use the tofxx(x,x,x) data from tofl2com since it is |
172 |
C manipulated (Time-walk, artificila ADc and TDC values using ToF |
C manipulated (Time-walk, artificila ADc and TDC values using ToF |
173 |
C standalone information |
C standalone information |
174 |
C---------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
|
C put the adc and tdc values from ntuple into tofxx(i,j,k) variables |
|
175 |
|
|
176 |
|
c put the adc and tdc values from ntuple into tofxx(i,j,k) variables |
177 |
|
|
178 |
do j=1,8 |
do j=1,8 |
179 |
tof11(1,j,2) = adc(ch11a(j),hb11a(j)) |
tof11(1,j,2) = pc_adc(adc(ch11a(j),hb11a(j))) |
180 |
tof11(2,j,2) = adc(ch11b(j),hb11b(j)) |
tof11(2,j,2) = pc_adc(adc(ch11b(j),hb11b(j))) |
181 |
tof11(1,j,1) = tdc(ch11a(j),hb11a(j)) |
tof11(1,j,1) = (tdc(ch11a(j),hb11a(j))) |
182 |
tof11(2,j,1) = tdc(ch11b(j),hb11b(j)) |
tof11(2,j,1) = (tdc(ch11b(j),hb11b(j))) |
183 |
enddo |
enddo |
184 |
|
|
185 |
|
|
186 |
do j=1,6 |
do j=1,6 |
187 |
tof12(1,j,2) = adc(ch12a(j),hb12a(j)) |
tof12(1,j,2) = pc_adc(adc(ch12a(j),hb12a(j))) |
188 |
tof12(2,j,2) = adc(ch12b(j),hb12b(j)) |
tof12(2,j,2) = pc_adc(adc(ch12b(j),hb12b(j))) |
189 |
tof12(1,j,1) = tdc(ch12a(j),hb12a(j)) |
tof12(1,j,1) = (tdc(ch12a(j),hb12a(j))) |
190 |
tof12(2,j,1) = tdc(ch12b(j),hb12b(j)) |
tof12(2,j,1) = (tdc(ch12b(j),hb12b(j))) |
191 |
enddo |
enddo |
192 |
|
|
193 |
do j=1,2 |
do j=1,2 |
194 |
tof21(1,j,2) = adc(ch21a(j),hb21a(j)) |
tof21(1,j,2) = pc_adc(adc(ch21a(j),hb21a(j))) |
195 |
tof21(2,j,2) = adc(ch21b(j),hb21b(j)) |
tof21(2,j,2) = pc_adc(adc(ch21b(j),hb21b(j))) |
196 |
tof21(1,j,1) = tdc(ch21a(j),hb21a(j)) |
tof21(1,j,1) = (tdc(ch21a(j),hb21a(j))) |
197 |
tof21(2,j,1) = tdc(ch21b(j),hb21b(j)) |
tof21(2,j,1) = (tdc(ch21b(j),hb21b(j))) |
198 |
enddo |
enddo |
199 |
|
|
200 |
do j=1,2 |
do j=1,2 |
201 |
tof22(1,j,2) = adc(ch22a(j),hb22a(j)) |
tof22(1,j,2) = pc_adc(adc(ch22a(j),hb22a(j))) |
202 |
tof22(2,j,2) = adc(ch22b(j),hb22b(j)) |
tof22(2,j,2) = pc_adc(adc(ch22b(j),hb22b(j))) |
203 |
tof22(1,j,1) = tdc(ch22a(j),hb22a(j)) |
tof22(1,j,1) = (tdc(ch22a(j),hb22a(j))) |
204 |
tof22(2,j,1) = tdc(ch22b(j),hb22b(j)) |
tof22(2,j,1) = (tdc(ch22b(j),hb22b(j))) |
205 |
enddo |
enddo |
206 |
|
|
207 |
do j=1,3 |
do j=1,3 |
208 |
tof31(1,j,2) = adc(ch31a(j),hb31a(j)) |
tof31(1,j,2) = pc_adc(adc(ch31a(j),hb31a(j))) |
209 |
tof31(2,j,2) = adc(ch31b(j),hb31b(j)) |
tof31(2,j,2) = pc_adc(adc(ch31b(j),hb31b(j))) |
210 |
tof31(1,j,1) = tdc(ch31a(j),hb31a(j)) |
tof31(1,j,1) = (tdc(ch31a(j),hb31a(j))) |
211 |
tof31(2,j,1) = tdc(ch31b(j),hb31b(j)) |
tof31(2,j,1) = (tdc(ch31b(j),hb31b(j))) |
212 |
enddo |
enddo |
213 |
|
|
214 |
do j=1,3 |
do j=1,3 |
215 |
tof32(1,j,2) = adc(ch32a(j),hb32a(j)) |
tof32(1,j,2) = pc_adc(adc(ch32a(j),hb32a(j))) |
216 |
tof32(2,j,2) = adc(ch32b(j),hb32b(j)) |
tof32(2,j,2) = pc_adc(adc(ch32b(j),hb32b(j))) |
217 |
tof32(1,j,1) = tdc(ch32a(j),hb32a(j)) |
tof32(1,j,1) = (tdc(ch32a(j),hb32a(j))) |
218 |
tof32(2,j,1) = tdc(ch32b(j),hb32b(j)) |
tof32(2,j,1) = (tdc(ch32b(j),hb32b(j))) |
219 |
enddo |
enddo |
220 |
|
|
221 |
C---------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
263 |
if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000. |
if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000. |
264 |
ENDDO |
ENDDO |
265 |
|
|
266 |
C------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
267 |
|
|
268 |
C------read tracking routine |
C------read tracking routine |
269 |
* igoodevent = igoodevent+1 |
* igoodevent = igoodevent+1 |
278 |
AL_P(i) = al_pp(i) |
AL_P(i) = al_pp(i) |
279 |
enddo |
enddo |
280 |
|
|
281 |
c write(*,*) AL_P |
c write(*,*) AL_P |
282 |
|
|
283 |
if (al_p(5).eq.0.) THEN |
if (al_p(5).eq.0.) THEN |
284 |
PRINT *,' TOF - WARNING F77: track with R = 0, discarded' |
c PRINT *,' TOF - WARNING F77: track with R = 0, discarded' |
285 |
GOTO 969 |
GOTO 969 |
286 |
ENDIF |
ENDIF |
287 |
* -------- *** tracking routine *** -------- |
* -------- *** tracking routine *** -------- |
289 |
C call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL) |
C call DOTRACK(NPTOF,ZIN,XOUT,YOUT,AL_P,IFAIL) |
290 |
call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL) |
call DOTRACK2(NPTOF,ZIN,XOUT,YOUT,THXOUT,THYOUT,TLOUT,AL_P,IFAIL) |
291 |
|
|
|
|
|
292 |
C write(*,*) (TLOUT(i),i=1,6) |
C write(*,*) (TLOUT(i),i=1,6) |
293 |
|
|
294 |
if(IFAIL.ne.0)then |
if(IFAIL.ne.0)then |
295 |
print *,' TOF - WARNING F77: tracking failed ' |
c print *,' TOF - WARNING F77: tracking failed ' |
296 |
goto 969 |
goto 969 |
297 |
endif |
endif |
298 |
* ------------------------------------------ |
* ------------------------------------------ |
299 |
|
|
300 |
969 continue |
969 continue |
301 |
|
|
302 |
|
C--- Fill xtr_tof and ytr_tof: positions from tracker at ToF layers |
303 |
|
do j=1,6 |
304 |
|
xtr_tof(j) = XOUT(j) |
305 |
|
ytr_tof(j) = YOUT(j) |
306 |
|
enddo |
307 |
|
|
308 |
|
|
309 |
|
C--- convert angles to radian |
310 |
|
do j=1,6 |
311 |
|
THXOUT(j) = 3.1415927*THXOUT(j)/180. |
312 |
|
THYOUT(j) = 3.1415927*THYOUT(j)/180. |
313 |
|
enddo |
314 |
|
|
315 |
|
do j=1,6 |
316 |
|
c write (*,*) j,THXOUT(j),THYOUT(j) |
317 |
|
enddo |
318 |
|
|
319 |
|
|
320 |
C---------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
321 |
C------------------ set ADC & TDC flag = 0 ------------------------ |
C------------------ set ADC & TDC flag = 0 ------------------------ |
368 |
tof11(1,6,1) = 4095 |
tof11(1,6,1) = 4095 |
369 |
tdcflagtof(ch11a(6),hb11a(6))=2 |
tdcflagtof(ch11a(6),hb11a(6))=2 |
370 |
endif |
endif |
371 |
|
|
372 |
C---- S222B TDC=819 |
C---- S222B TDC=819 |
373 |
if (tof22(2,2,1).EQ.819) then |
if (tof22(2,2,1).EQ.819) then |
374 |
tof22(2,2,1) = 4095 |
tof22(2,2,1) = 4095 |
375 |
tdcflagtof(ch22b(2),hb22b(2))=2 |
tdcflagtof(ch22b(2),hb22b(2))=2 |
376 |
endif |
endif |
377 |
|
|
378 |
C------------------------------------------------------------- |
C------------------------------------------------------------- |
379 |
C-------check which paddle penetrated the track ----------- |
C-------check which paddle penetrated the track ----------- |
380 |
C------------------------------------------------------------- |
C------------------------------------------------------------- |
663 |
yhelp=yout(1) |
yhelp=yout(1) |
664 |
IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN |
IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN |
665 |
i = tof11_i |
i = tof11_i |
666 |
if (tof11(left,i,iadc).eq.4095) then |
c if (tof11(left,i,iadc).eq.4095) then |
667 |
phi = atan(tan(THXOUT(1))/tan(THYOUT(1))) |
if (adc(ch11a(i),hb11a(i)).eq.4095) then |
668 |
c theta = atan(tan(THXOUT(1))/cos(phi) |
phi = atan(tan(THYOUT(1))/tan(THXOUT(1))) |
669 |
theta = atan(tan(THXOUT(1))/cos(phi)) |
theta = atan(tan(THXOUT(1))/cos(phi)) |
670 |
xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) |
c xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) |
671 |
|
xkorr = atten(left,11,i,yhelp) |
672 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
673 |
tof11(left,i,iadc)=xkorr/cos(theta) |
tof11(left,i,iadc)=xkorr/cos(theta) |
674 |
adcflag(ch11a(i),hb11a(i)) = 1 |
adcflag(ch11a(i),hb11a(i)) = 1 |
675 |
endif |
endif |
676 |
if (tof11(right,i,iadc).eq.4095) then |
c if (tof11(right,i,iadc).eq.4095) then |
677 |
phi = atan(tan(THXOUT(1))/tan(THYOUT(1))) |
if (adc(ch11b(i),hb11b(i)).eq.4095) then |
678 |
c theta = atan(tan(THXOUT(1))/cos(phi) |
phi = atan(tan(THYOUT(1))/tan(THXOUT(1))) |
679 |
theta = atan(tan(THXOUT(1))/cos(phi)) |
theta = atan(tan(THXOUT(1))/cos(phi)) |
680 |
xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) |
c xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) |
681 |
|
xkorr = atten(right,11,i,yhelp) |
682 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
683 |
tof11(right,i,iadc)=xkorr/cos(theta) |
tof11(right,i,iadc)=xkorr/cos(theta) |
684 |
adcflag(ch11b(i),hb11b(i)) = 1 |
adcflag(ch11b(i),hb11b(i)) = 1 |
688 |
xhelp=xout(2) |
xhelp=xout(2) |
689 |
IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN |
IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN |
690 |
i = tof12_i |
i = tof12_i |
691 |
if (tof12(left,i,iadc).eq.4095) then |
c if (tof12(left,i,iadc).eq.4095) then |
692 |
phi = atan(tan(THXOUT(2))/tan(THYOUT(2))) |
if (adc(ch12a(i),hb12a(i)).eq.4095) then |
693 |
c theta = atan(tan(THXOUT(2))/cos(phi) |
phi = atan(tan(THYOUT(2))/tan(THXOUT(2))) |
694 |
theta = atan(tan(THXOUT(2))/cos(phi)) |
theta = atan(tan(THXOUT(2))/cos(phi)) |
695 |
xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) |
c xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) |
696 |
|
xkorr = atten(left,12,i,xhelp) |
697 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
698 |
tof12(left,i,iadc) = xkorr/cos(theta) |
tof12(left,i,iadc) = xkorr/cos(theta) |
699 |
adcflag(ch12a(i),hb12a(i)) = 1 |
adcflag(ch12a(i),hb12a(i)) = 1 |
700 |
endif |
endif |
701 |
if (tof12(right,i,iadc).eq.4095) then |
c if (tof12(right,i,iadc).eq.4095) then |
702 |
phi = atan(tan(THXOUT(2))/tan(THYOUT(2))) |
if (adc(ch12b(i),hb12b(i)).eq.4095) then |
703 |
c theta = atan(tan(THXOUT(2))/cos(phi) |
phi = atan(tan(THYOUT(2))/tan(THXOUT(2))) |
704 |
theta = atan(tan(THXOUT(2))/cos(phi)) |
theta = atan(tan(THXOUT(2))/cos(phi)) |
705 |
xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) |
c xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) |
706 |
|
xkorr = atten(right,12,i,xhelp) |
707 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
708 |
tof12(right,i,iadc) = xkorr/cos(theta) |
tof12(right,i,iadc) = xkorr/cos(theta) |
709 |
adcflag(ch12b(i),hb12b(i)) = 1 |
adcflag(ch12b(i),hb12b(i)) = 1 |
715 |
xhelp=xout(3) |
xhelp=xout(3) |
716 |
IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN |
IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN |
717 |
i = tof21_i |
i = tof21_i |
718 |
if (tof21(left,i,iadc).eq.4095) then |
c if (tof21(left,i,iadc).eq.4095) then |
719 |
phi = atan(tan(THXOUT(3))/tan(THYOUT(3))) |
if (adc(ch21a(i),hb21a(i)).eq.4095) then |
720 |
c theta = atan(tan(THXOUT(3))/cos(phi) |
phi = atan(tan(THYOUT(3))/tan(THXOUT(3))) |
721 |
theta = atan(tan(THXOUT(3))/cos(phi)) |
theta = atan(tan(THXOUT(3))/cos(phi)) |
722 |
xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) |
c xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) |
723 |
|
xkorr = atten(left,21,i,xhelp) |
724 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
725 |
tof21(left,i,iadc) = xkorr/cos(theta) |
tof21(left,i,iadc) = xkorr/cos(theta) |
726 |
adcflag(ch21a(i),hb21a(i)) = 1 |
adcflag(ch21a(i),hb21a(i)) = 1 |
727 |
endif |
endif |
728 |
if (tof21(right,i,iadc).eq.4095) then |
c if (tof21(right,i,iadc).eq.4095) then |
729 |
phi = atan(tan(THXOUT(3))/tan(THYOUT(3))) |
if (adc(ch21b(i),hb21b(i)).eq.4095) then |
730 |
c theta = atan(tan(THXOUT(3))/cos(phi) |
phi = atan(tan(THYOUT(3))/tan(THXOUT(3))) |
731 |
theta = atan(tan(THXOUT(3))/cos(phi)) |
theta = atan(tan(THXOUT(3))/cos(phi)) |
732 |
xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) |
c xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) |
733 |
|
xkorr = atten(right,21,i,xhelp) |
734 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
735 |
tof21(right,i,iadc) = xkorr/cos(theta) |
tof21(right,i,iadc) = xkorr/cos(theta) |
736 |
adcflag(ch21b(i),hb21b(i)) = 1 |
adcflag(ch21b(i),hb21b(i)) = 1 |
741 |
yhelp=yout(4) |
yhelp=yout(4) |
742 |
IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN |
IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN |
743 |
i = tof22_i |
i = tof22_i |
744 |
if (tof22(left,i,iadc).eq.4095) then |
c if (tof22(left,i,iadc).eq.4095) then |
745 |
phi = atan(tan(THXOUT(4))/tan(THYOUT(4))) |
if (adc(ch22a(i),hb22a(i)).eq.4095) then |
746 |
c theta = atan(tan(THXOUT(4))/cos(phi) |
phi = atan(tan(THYOUT(4))/tan(THXOUT(4))) |
747 |
theta = atan(tan(THXOUT(4))/cos(phi)) |
theta = atan(tan(THXOUT(4))/cos(phi)) |
748 |
xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) |
c xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) |
749 |
|
xkorr = atten(left,22,i,yhelp) |
750 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
751 |
tof22(left,i,iadc) = xkorr/cos(theta) |
tof22(left,i,iadc) = xkorr/cos(theta) |
752 |
adcflag(ch22a(i),hb22a(i)) = 1 |
adcflag(ch22a(i),hb22a(i)) = 1 |
753 |
endif |
endif |
754 |
if (tof22(right,i,iadc).eq.4095) then |
c if (tof22(right,i,iadc).eq.4095) then |
755 |
phi = atan(tan(THXOUT(4))/tan(THYOUT(4))) |
if (adc(ch22b(i),hb22b(i)).eq.4095) then |
756 |
c theta = atan(tan(THXOUT(4))/cos(phi) |
phi = atan(tan(THYOUT(4))/tan(THXOUT(4))) |
757 |
theta = atan(tan(THXOUT(4))/cos(phi)) |
theta = atan(tan(THXOUT(4))/cos(phi)) |
758 |
xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) |
c xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) |
759 |
|
xkorr = atten(right,22,i,yhelp) |
760 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
761 |
tof22(right,i,iadc) = xkorr/cos(theta) |
tof22(right,i,iadc) = xkorr/cos(theta) |
762 |
adcflag(ch22b(i),hb22b(i)) = 1 |
adcflag(ch22b(i),hb22b(i)) = 1 |
768 |
yhelp=yout(5) |
yhelp=yout(5) |
769 |
IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN |
IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN |
770 |
i = tof31_i |
i = tof31_i |
771 |
if (tof31(left,i,iadc).eq.4095) then |
c if (tof31(left,i,iadc).eq.4095) then |
772 |
phi = atan(tan(THXOUT(5))/tan(THYOUT(5))) |
if (adc(ch31a(i),hb31a(i)).eq.4095) then |
773 |
c theta = atan(tan(THXOUT(5))/cos(phi) |
phi = atan(tan(THYOUT(5))/tan(THXOUT(5))) |
774 |
theta = atan(tan(THXOUT(5))/cos(phi)) |
theta = atan(tan(THXOUT(5))/cos(phi)) |
775 |
xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) |
c xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) |
776 |
|
xkorr = atten(left,31,i,yhelp) |
777 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
778 |
tof31(left,i,iadc) = xkorr/cos(theta) |
tof31(left,i,iadc) = xkorr/cos(theta) |
779 |
adcflag(ch31a(i),hb31a(i)) = 1 |
adcflag(ch31a(i),hb31a(i)) = 1 |
780 |
endif |
endif |
781 |
if (tof31(right,i,iadc).eq.4095) then |
c if (tof31(right,i,iadc).eq.4095) then |
782 |
phi = atan(tan(THXOUT(5))/tan(THYOUT(5))) |
if (adc(ch31b(i),hb31b(i)).eq.4095) then |
783 |
c theta = atan(tan(THXOUT(5))/cos(phi) |
phi = atan(tan(THYOUT(5))/tan(THXOUT(5))) |
784 |
theta = atan(tan(THXOUT(5))/cos(phi)) |
theta = atan(tan(THXOUT(5))/cos(phi)) |
785 |
xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) |
c xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) |
786 |
|
xkorr = atten(right,31,i,yhelp) |
787 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
788 |
tof31(right,i,iadc) = xkorr/cos(theta) |
tof31(right,i,iadc) = xkorr/cos(theta) |
789 |
adcflag(ch31b(i),hb31b(i)) = 1 |
adcflag(ch31b(i),hb31b(i)) = 1 |
794 |
xhelp=xout(6) |
xhelp=xout(6) |
795 |
IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN |
IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN |
796 |
i = tof32_i |
i = tof32_i |
797 |
if (tof32(left,i,iadc).eq.4095) then |
c if (tof32(left,i,iadc).eq.4095) then |
798 |
phi = atan(tan(THXOUT(6))/tan(THYOUT(6))) |
if (adc(ch32a(i),hb32a(i)).eq.4095) then |
799 |
c theta = atan(tan(THXOUT(6))/cos(phi) |
phi = atan(tan(THYOUT(6))/tan(THXOUT(6))) |
800 |
theta = atan(tan(THXOUT(6))/cos(phi)) |
theta = atan(tan(THXOUT(6))/cos(phi)) |
801 |
xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) |
c xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) |
802 |
|
xkorr = atten(left,32,i,xhelp) |
803 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
804 |
tof32(left,i,iadc) = xkorr/cos(theta) |
tof32(left,i,iadc) = xkorr/cos(theta) |
805 |
adcflag(ch32a(i),hb32a(i)) = 1 |
adcflag(ch32a(i),hb32a(i)) = 1 |
806 |
endif |
endif |
807 |
if (tof32(right,i,iadc).eq.4095) then |
c if (tof32(right,i,iadc).eq.4095) then |
808 |
phi = atan(tan(THXOUT(6))/tan(THYOUT(6))) |
if (adc(ch32b(i),hb32b(i)).eq.4095) then |
809 |
c theta = atan(tan(THXOUT(6))/cos(phi) |
phi = atan(tan(THYOUT(6))/tan(THXOUT(6))) |
810 |
theta = atan(tan(THXOUT(6))/cos(phi)) |
theta = atan(tan(THXOUT(6))/cos(phi)) |
811 |
xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) |
c xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) |
812 |
|
xkorr = atten(right,32,i,xhelp) |
813 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
814 |
tof32(right,i,iadc) = xkorr/cos(theta) |
tof32(right,i,iadc) = xkorr/cos(theta) |
815 |
adcflag(ch32b(i),hb32b(i)) = 1 |
adcflag(ch32b(i),hb32b(i)) = 1 |
901 |
C--------------------Time walk correction ------------------------- |
C--------------------Time walk correction ------------------------- |
902 |
C-------------------------------------------------------------------- |
C-------------------------------------------------------------------- |
903 |
|
|
904 |
|
|
905 |
DO i=1,8 |
DO i=1,8 |
906 |
|
xhelp= 0. |
907 |
xhelp_a = tof11(left,i,iadc) |
xhelp_a = tof11(left,i,iadc) |
908 |
xhelp_t = tof11(left,i,itdc) |
xhelp_t = tof11(left,i,itdc) |
909 |
if(xhelp_a<4095) xhelp = tw11(left,i)/sqrt(xhelp_a) |
c if (xhelp_a .eq.0) write (*,*) 'trk 11 ',i,xhelp_a |
910 |
|
|
911 |
|
if(xhelp_a<3786) xhelp = tw11(left,i)/sqrt(xhelp_a) |
912 |
tof11(left,i,itdc) = xhelp_t + xhelp |
tof11(left,i,itdc) = xhelp_t + xhelp |
913 |
tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc) |
tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc) |
914 |
xhelp_a = tof11(right,i,iadc) |
xhelp_a = tof11(right,i,iadc) |
915 |
xhelp_t = tof11(right,i,itdc) |
xhelp_t = tof11(right,i,itdc) |
916 |
if(xhelp_a<4095) xhelp = tw11(right,i)/sqrt(xhelp_a) |
if(xhelp_a<3786) xhelp = tw11(right,i)/sqrt(xhelp_a) |
917 |
tof11(right,i,itdc) = xhelp_t + xhelp |
tof11(right,i,itdc) = xhelp_t + xhelp |
918 |
tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc) |
tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc) |
919 |
ENDDO |
ENDDO |
920 |
|
|
921 |
DO i=1,6 |
DO i=1,6 |
922 |
|
xhelp= 0. |
923 |
xhelp_a = tof12(left,i,iadc) |
xhelp_a = tof12(left,i,iadc) |
924 |
xhelp_t = tof12(left,i,itdc) |
xhelp_t = tof12(left,i,itdc) |
925 |
if(xhelp_a<4095) xhelp = tw12(left,i)/sqrt(xhelp_a) |
c if (xhelp_a .eq.0) write (*,*) 'trk 12 ',i,xhelp_a |
926 |
|
if(xhelp_a<3786) xhelp = tw12(left,i)/sqrt(xhelp_a) |
927 |
tof12(left,i,itdc) = xhelp_t + xhelp |
tof12(left,i,itdc) = xhelp_t + xhelp |
928 |
tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc) |
tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc) |
929 |
xhelp_a = tof12(right,i,iadc) |
xhelp_a = tof12(right,i,iadc) |
930 |
xhelp_t = tof12(right,i,itdc) |
xhelp_t = tof12(right,i,itdc) |
931 |
if(xhelp_a<4095) xhelp = tw12(right,i)/sqrt(xhelp_a) |
if(xhelp_a<3786) xhelp = tw12(right,i)/sqrt(xhelp_a) |
932 |
tof12(right,i,itdc) = xhelp_t + xhelp |
tof12(right,i,itdc) = xhelp_t + xhelp |
933 |
tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc) |
tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc) |
934 |
ENDDO |
ENDDO |
935 |
C---- |
C---- |
936 |
DO i=1,2 |
DO i=1,2 |
937 |
|
xhelp= 0. |
938 |
xhelp_a = tof21(left,i,iadc) |
xhelp_a = tof21(left,i,iadc) |
939 |
xhelp_t = tof21(left,i,itdc) |
xhelp_t = tof21(left,i,itdc) |
940 |
if(xhelp_a<4095) xhelp = tw21(left,i)/sqrt(xhelp_a) |
c if (xhelp_a .eq.0) write (*,*) ' trk 21 ',i,xhelp_a |
941 |
|
|
942 |
|
if(xhelp_a<3786) xhelp = tw21(left,i)/sqrt(xhelp_a) |
943 |
tof21(left,i,itdc) = xhelp_t + xhelp |
tof21(left,i,itdc) = xhelp_t + xhelp |
944 |
tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc) |
tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc) |
945 |
xhelp_a = tof21(right,i,iadc) |
xhelp_a = tof21(right,i,iadc) |
946 |
xhelp_t = tof21(right,i,itdc) |
xhelp_t = tof21(right,i,itdc) |
947 |
if(xhelp_a<4095) xhelp = tw21(right,i)/sqrt(xhelp_a) |
if(xhelp_a<3786) xhelp = tw21(right,i)/sqrt(xhelp_a) |
948 |
tof21(right,i,itdc) = xhelp_t + xhelp |
tof21(right,i,itdc) = xhelp_t + xhelp |
949 |
tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc) |
tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc) |
950 |
ENDDO |
ENDDO |
951 |
|
|
952 |
DO i=1,2 |
DO i=1,2 |
953 |
|
xhelp= 0. |
954 |
xhelp_a = tof22(left,i,iadc) |
xhelp_a = tof22(left,i,iadc) |
955 |
xhelp_t = tof22(left,i,itdc) |
xhelp_t = tof22(left,i,itdc) |
956 |
if(xhelp_a<4095) xhelp = tw22(left,i)/sqrt(xhelp_a) |
c if (xhelp_a .eq.0) write (*,*) ' trk 22 ',i,xhelp_a |
957 |
|
if(xhelp_a<3786) xhelp = tw22(left,i)/sqrt(xhelp_a) |
958 |
tof22(left,i,itdc) = xhelp_t + xhelp |
tof22(left,i,itdc) = xhelp_t + xhelp |
959 |
tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc) |
tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc) |
960 |
xhelp_a = tof22(right,i,iadc) |
xhelp_a = tof22(right,i,iadc) |
961 |
xhelp_t = tof22(right,i,itdc) |
xhelp_t = tof22(right,i,itdc) |
962 |
if(xhelp_a<4095) xhelp = tw22(right,i)/sqrt(xhelp_a) |
if(xhelp_a<3786) xhelp = tw22(right,i)/sqrt(xhelp_a) |
963 |
tof22(right,i,itdc) = xhelp_t + xhelp |
tof22(right,i,itdc) = xhelp_t + xhelp |
964 |
tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc) |
tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc) |
965 |
ENDDO |
ENDDO |
966 |
C---- |
C---- |
967 |
|
|
968 |
DO i=1,3 |
DO i=1,3 |
969 |
|
xhelp= 0. |
970 |
xhelp_a = tof31(left,i,iadc) |
xhelp_a = tof31(left,i,iadc) |
971 |
xhelp_t = tof31(left,i,itdc) |
xhelp_t = tof31(left,i,itdc) |
972 |
if(xhelp_a<4095) xhelp = tw31(left,i)/sqrt(xhelp_a) |
c if (xhelp_a .eq.0) write (*,*) ' trk 31 ',i,xhelp_a |
973 |
|
|
974 |
|
if(xhelp_a<3786) xhelp = tw31(left,i)/sqrt(xhelp_a) |
975 |
tof31(left,i,itdc) = xhelp_t + xhelp |
tof31(left,i,itdc) = xhelp_t + xhelp |
976 |
tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc) |
tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc) |
977 |
xhelp_a = tof31(right,i,iadc) |
xhelp_a = tof31(right,i,iadc) |
978 |
xhelp_t = tof31(right,i,itdc) |
xhelp_t = tof31(right,i,itdc) |
979 |
if(xhelp_a<4095) xhelp = tw31(right,i)/sqrt(xhelp_a) |
if(xhelp_a<3786) xhelp = tw31(right,i)/sqrt(xhelp_a) |
980 |
tof31(right,i,itdc) = xhelp_t + xhelp |
tof31(right,i,itdc) = xhelp_t + xhelp |
981 |
tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc) |
tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc) |
982 |
ENDDO |
ENDDO |
983 |
|
|
984 |
DO i=1,3 |
DO i=1,3 |
985 |
|
xhelp= 0. |
986 |
xhelp_a = tof32(left,i,iadc) |
xhelp_a = tof32(left,i,iadc) |
987 |
xhelp_t = tof32(left,i,itdc) |
xhelp_t = tof32(left,i,itdc) |
988 |
if(xhelp_a<4095) xhelp = tw32(left,i)/sqrt(xhelp_a) |
c if (xhelp_a .eq.0) write (*,*) ' trk 32 ',i,xhelp_a |
989 |
|
|
990 |
|
if(xhelp_a<3786) xhelp = tw32(left,i)/sqrt(xhelp_a) |
991 |
tof32(left,i,itdc) = xhelp_t + xhelp |
tof32(left,i,itdc) = xhelp_t + xhelp |
992 |
tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc) |
tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc) |
993 |
xhelp_a = tof32(right,i,iadc) |
xhelp_a = tof32(right,i,iadc) |
994 |
xhelp_t = tof32(right,i,itdc) |
xhelp_t = tof32(right,i,itdc) |
995 |
if(xhelp_a<4095) xhelp = tw32(right,i)/sqrt(xhelp_a) |
if(xhelp_a<3786) xhelp = tw32(right,i)/sqrt(xhelp_a) |
996 |
tof32(right,i,itdc) = xhelp_t + xhelp |
tof32(right,i,itdc) = xhelp_t + xhelp |
997 |
tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc) |
tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc) |
998 |
ENDDO |
ENDDO |
1005 |
C-----------------------------S1 ------------------------------------- |
C-----------------------------S1 ------------------------------------- |
1006 |
|
|
1007 |
yhelp=yout(1) |
yhelp=yout(1) |
1008 |
phi = atan(tan(THXOUT(1))/tan(THYOUT(1))) |
|
1009 |
c theta = atan(tan(THXOUT(1))/cos(phi) |
phi = atan(tan(THYOUT(1))/tan(THXOUT(1))) |
1010 |
theta = atan(tan(THXOUT(1))/cos(phi)) |
theta = atan(tan(THXOUT(1))/cos(phi)) |
1011 |
|
|
1012 |
IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN |
IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN |
1013 |
|
|
1014 |
i = tof11_i |
i = tof11_i |
1015 |
|
|
1016 |
if (tof11(left,i,iadc).lt.4095) then |
if (tof11(left,i,iadc).lt.3786) then |
1017 |
|
c if (adc(ch11a(i),hb11a(i)).lt.4095) then |
1018 |
tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta) |
tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta) |
1019 |
xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) |
c xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) |
1020 |
|
xkorr = atten(left,11,i,yhelp) |
1021 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1022 |
adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr |
adc_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr |
1023 |
endif |
endif |
1024 |
|
|
1025 |
|
|
1026 |
if (tof11(right,i,iadc).lt.4095) then |
if (tof11(right,i,iadc).lt.3786) then |
1027 |
|
c if (adc(ch11b(i),hb11b(i)).lt.4095) then |
1028 |
tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta) |
tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta) |
1029 |
xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) |
c xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) |
1030 |
|
xkorr = atten(right,11,i,yhelp) |
1031 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1032 |
adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr |
adc_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr |
1033 |
endif |
endif |
1035 |
|
|
1036 |
|
|
1037 |
xhelp=xout(2) |
xhelp=xout(2) |
1038 |
phi = atan(tan(THXOUT(2))/tan(THYOUT(2))) |
phi = atan(tan(THYOUT(2))/tan(THXOUT(2))) |
|
c theta = atan(tan(THXOUT(2))/cos(phi) |
|
1039 |
theta = atan(tan(THXOUT(2))/cos(phi)) |
theta = atan(tan(THXOUT(2))/cos(phi)) |
1040 |
|
c write(*,*) 'theta12 ',theta |
1041 |
IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN |
IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN |
1042 |
|
|
1043 |
i = tof12_i |
i = tof12_i |
1044 |
if (tof12(left,i,iadc).lt.4095) then |
if (tof12(left,i,iadc).lt.3786) then |
1045 |
|
c if (adc(ch12a(i),hb12a(i)).lt.4095) then |
1046 |
tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta) |
tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta) |
1047 |
xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) |
c xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) |
1048 |
|
xkorr = atten(left,12,i,xhelp) |
1049 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1050 |
adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr |
adc_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr |
1051 |
endif |
endif |
1052 |
|
|
1053 |
if (tof12(right,i,iadc).lt.4095) then |
if (tof12(right,i,iadc).lt.3786) then |
1054 |
|
c if (adc(ch12b(i),hb12b(i)).lt.4095) then |
1055 |
tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta) |
tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta) |
1056 |
xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) |
c xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) |
1057 |
|
xkorr = atten(right,12,i,xhelp) |
1058 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1059 |
adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr |
adc_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr |
1060 |
endif |
endif |
1063 |
C-----------------------------S2 -------------------------------- |
C-----------------------------S2 -------------------------------- |
1064 |
|
|
1065 |
xhelp=xout(3) |
xhelp=xout(3) |
1066 |
phi = atan(tan(THXOUT(3))/tan(THYOUT(3))) |
phi = atan(tan(THYOUT(3))/tan(THXOUT(3))) |
|
c theta = atan(tan(THXOUT(3))/cos(phi) |
|
1067 |
theta = atan(tan(THXOUT(3))/cos(phi)) |
theta = atan(tan(THXOUT(3))/cos(phi)) |
1068 |
|
c write(*,*) 'theta21 ',theta |
1069 |
IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN |
IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN |
1070 |
|
|
1071 |
i = tof21_i |
i = tof21_i |
1072 |
if (tof21(left,i,iadc).lt.4095) then |
if (tof21(left,i,iadc).lt.3786) then |
1073 |
|
c if (adc(ch21a(i),hb21a(i)).lt.4095) then |
1074 |
tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta) |
tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta) |
1075 |
xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) |
c xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) |
1076 |
|
xkorr = atten(left,21,i,xhelp) |
1077 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1078 |
adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr |
adc_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr |
1079 |
endif |
endif |
1080 |
|
|
1081 |
if (tof21(right,i,iadc).lt.4095) then |
if (tof21(right,i,iadc).lt.3786) then |
1082 |
|
c if (adc(ch21b(i),hb21b(i)).lt.4095) then |
1083 |
tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta) |
tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta) |
1084 |
xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) |
c xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) |
1085 |
|
xkorr = atten(right,21,i,xhelp) |
1086 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1087 |
adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr |
adc_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr |
1088 |
endif |
endif |
1089 |
ENDIF |
ENDIF |
1090 |
|
|
1091 |
yhelp=yout(4) |
yhelp=yout(4) |
1092 |
phi = atan(tan(THXOUT(4))/tan(THYOUT(4))) |
phi = atan(tan(THYOUT(4))/tan(THXOUT(4))) |
|
c theta = atan(tan(THXOUT(4))/cos(phi) |
|
1093 |
theta = atan(tan(THXOUT(4))/cos(phi)) |
theta = atan(tan(THXOUT(4))/cos(phi)) |
1094 |
|
c write(*,*) 'theta22 ',theta |
1095 |
|
|
1096 |
IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN |
IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN |
1097 |
|
|
1098 |
i = tof22_i |
i = tof22_i |
1099 |
if (tof22(left,i,iadc).lt.4095) then |
if (tof22(left,i,iadc).lt.3786) then |
1100 |
|
c if (adc(ch22a(i),hb22a(i)).lt.4095) then |
1101 |
tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta) |
tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta) |
1102 |
xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) |
c xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) |
1103 |
|
xkorr = atten(left,22,i,yhelp) |
1104 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1105 |
adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr |
adc_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr |
1106 |
endif |
endif |
1107 |
|
|
1108 |
if (tof22(right,i,iadc).lt.4095) then |
if (tof22(right,i,iadc).lt.3786) then |
1109 |
|
c if (adc(ch22b(i),hb22b(i)).lt.4095) then |
1110 |
tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta) |
tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta) |
1111 |
xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) |
c xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) |
1112 |
|
xkorr = atten(right,22,i,yhelp) |
1113 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1114 |
adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr |
adc_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr |
1115 |
endif |
endif |
1118 |
C-----------------------------S3 -------------------------------- |
C-----------------------------S3 -------------------------------- |
1119 |
|
|
1120 |
yhelp=yout(5) |
yhelp=yout(5) |
1121 |
phi = atan(tan(THXOUT(5))/tan(THYOUT(5))) |
phi = atan(tan(THYOUT(5))/tan(THXOUT(5))) |
|
c theta = atan(tan(THXOUT(5))/cos(phi) |
|
1122 |
theta = atan(tan(THXOUT(5))/cos(phi)) |
theta = atan(tan(THXOUT(5))/cos(phi)) |
1123 |
|
c write(*,*) 'theta31 ',theta |
1124 |
|
|
1125 |
IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN |
IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN |
1126 |
|
|
1127 |
i = tof31_i |
i = tof31_i |
1128 |
if (tof31(left,i,iadc).lt.4095) then |
if (tof31(left,i,iadc).lt.3786) then |
1129 |
|
c if (adc(ch31a(i),hb31a(i)).lt.4095) then |
1130 |
tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta) |
tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta) |
1131 |
xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) |
c xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) |
1132 |
|
xkorr = atten(left,31,i,yhelp) |
1133 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1134 |
adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr |
adc_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr |
1135 |
endif |
endif |
1136 |
|
|
1137 |
if (tof31(right,i,iadc).lt.4095) then |
if (tof31(right,i,iadc).lt.3786) then |
1138 |
|
c if (adc(ch31b(i),hb31b(i)).lt.4095) then |
1139 |
tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta) |
tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta) |
1140 |
xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) |
c xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) |
1141 |
|
xkorr = atten(right,31,i,yhelp) |
1142 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1143 |
adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr |
adc_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr |
1144 |
endif |
endif |
1145 |
ENDIF |
ENDIF |
1146 |
|
|
1147 |
xhelp=xout(6) |
xhelp=xout(6) |
1148 |
phi = atan(tan(THXOUT(6))/tan(THYOUT(6))) |
phi = atan(tan(THYOUT(6))/tan(THXOUT(6))) |
|
c theta = atan(tan(THXOUT(6))/cos(phi) |
|
1149 |
theta = atan(tan(THXOUT(6))/cos(phi)) |
theta = atan(tan(THXOUT(6))/cos(phi)) |
1150 |
|
c write(*,*) 'theta32 ',theta |
1151 |
|
|
1152 |
IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN |
IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN |
1153 |
|
|
1154 |
i = tof32_i |
i = tof32_i |
1155 |
if (tof32(left,i,iadc).lt.4095) then |
if (tof32(left,i,iadc).lt.3786) then |
1156 |
|
c if (adc(ch32a(i),hb32a(i)).lt.4095) then |
1157 |
tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta) |
tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta) |
1158 |
xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) |
c xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) |
1159 |
|
xkorr = atten(left,32,i,xhelp) |
1160 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1161 |
adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr |
adc_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr |
1162 |
endif |
endif |
1163 |
|
|
1164 |
if (tof32(right,i,iadc).lt.4095) then |
if (tof32(right,i,iadc).lt.3786) then |
1165 |
|
c if (adc(ch32b(i),hb32b(i)).lt.4095) then |
1166 |
tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta) |
tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta) |
1167 |
xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) |
c xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) |
1168 |
|
xkorr = atten(right,32,i,xhelp) |
1169 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
1170 |
adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr |
adc_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr |
1171 |
endif |
endif |
1738 |
|
|
1739 |
c write(*,*) xtofpos |
c write(*,*) xtofpos |
1740 |
c write(*,*) ytofpos |
c write(*,*) ytofpos |
1741 |
c write(*,*) beta_a |
C write(*,*)'toftrk beta', beta_a |
1742 |
C write(*,*) adcflagtof |
C write(*,*) adcflagtof |
1743 |
|
C write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4) |
1744 |
|
c write(*,*) 'toftrk' |
1745 |
|
c write(*,*) xtofpos |
1746 |
|
c write(*,*) ytofpos |
1747 |
|
c write(*,*) xtr_tof |
1748 |
|
c write(*,*) ytr_tof |
1749 |
|
|
1750 |
|
|
|
C write(*,*)'TOFTRK ',ievent,beta_a(1),beta_a(2),beta_a(3),beta_a(4) |
|
1751 |
|
|
1752 |
RETURN |
RETURN |
1753 |
END |
END |
1754 |
|
|
1755 |
|
|
1756 |
|
|
1757 |
|
|
1758 |
|
C------------------------------------------------------------------ |
1759 |
|
C------------------------------------------------------------------ |