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 |
C jan-05 WM: bug fixed: claculation of zenith angles using DOTRACK2 |
28 |
|
C was incorrect |
29 |
C**************************************************************************** |
C**************************************************************************** |
30 |
IMPLICIT NONE |
IMPLICIT NONE |
31 |
C |
C |
54 |
|
|
55 |
|
|
56 |
INTEGER IFAIL |
INTEGER IFAIL |
57 |
c REAL dx,dy,dr,xdummy |
c REAL dx,dy,dr |
58 |
REAL ds |
REAL ds |
59 |
REAL t1,t2,t3,t4 |
REAL t1,t2,t3,t4 |
60 |
REAL yhelp,xhelp,xhelp1,xhelp2 |
REAL yhelp,xhelp,xhelp1,xhelp2 |
146 |
|
|
147 |
pmt_id=0 |
pmt_id=0 |
148 |
|
|
149 |
|
do j=1,6 |
150 |
|
THXOUT(j) = 0. |
151 |
|
THYOUT(j) = 0. |
152 |
|
enddo |
153 |
|
|
154 |
C---------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
155 |
C-------------------------get ToF data -------------------------------- |
C-------------------------get ToF data -------------------------------- |
156 |
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 |
263 |
AL_P(i) = al_pp(i) |
AL_P(i) = al_pp(i) |
264 |
enddo |
enddo |
265 |
|
|
266 |
c write(*,*) AL_P |
c write(*,*) AL_P |
267 |
|
|
268 |
if (al_p(5).eq.0.) THEN |
if (al_p(5).eq.0.) THEN |
269 |
PRINT *,' TOF - WARNING F77: track with R = 0, discarded' |
PRINT *,' TOF - WARNING F77: track with R = 0, discarded' |
285 |
|
|
286 |
969 continue |
969 continue |
287 |
|
|
288 |
|
C--- convert angles to radian |
289 |
|
do j=1,6 |
290 |
|
THXOUT(j) = 3.1415927*THXOUT(j)/180. |
291 |
|
THYOUT(j) = 3.1415927*THYOUT(j)/180. |
292 |
|
enddo |
293 |
|
|
294 |
|
do j=1,6 |
295 |
|
c write (*,*) j,THXOUT(j),THYOUT(j) |
296 |
|
enddo |
297 |
|
|
298 |
|
|
299 |
C---------------------------------------------------------------------- |
C---------------------------------------------------------------------- |
300 |
C------------------ set ADC & TDC flag = 0 ------------------------ |
C------------------ set ADC & TDC flag = 0 ------------------------ |
643 |
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 |
644 |
i = tof11_i |
i = tof11_i |
645 |
if (tof11(left,i,iadc).eq.4095) then |
if (tof11(left,i,iadc).eq.4095) then |
646 |
phi = atan(tan(THXOUT(1))/tan(THYOUT(1))) |
phi = atan(tan(THYOUT(1))/tan(THXOUT(1))) |
|
c theta = atan(tan(THXOUT(1))/cos(phi) |
|
647 |
theta = atan(tan(THXOUT(1))/cos(phi)) |
theta = atan(tan(THXOUT(1))/cos(phi)) |
648 |
xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) |
xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) |
649 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
651 |
adcflag(ch11a(i),hb11a(i)) = 1 |
adcflag(ch11a(i),hb11a(i)) = 1 |
652 |
endif |
endif |
653 |
if (tof11(right,i,iadc).eq.4095) then |
if (tof11(right,i,iadc).eq.4095) then |
654 |
phi = atan(tan(THXOUT(1))/tan(THYOUT(1))) |
phi = atan(tan(THYOUT(1))/tan(THXOUT(1))) |
|
c theta = atan(tan(THXOUT(1))/cos(phi) |
|
655 |
theta = atan(tan(THXOUT(1))/cos(phi)) |
theta = atan(tan(THXOUT(1))/cos(phi)) |
656 |
xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) |
xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) |
657 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
664 |
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 |
665 |
i = tof12_i |
i = tof12_i |
666 |
if (tof12(left,i,iadc).eq.4095) then |
if (tof12(left,i,iadc).eq.4095) then |
667 |
phi = atan(tan(THXOUT(2))/tan(THYOUT(2))) |
phi = atan(tan(THYOUT(2))/tan(THXOUT(2))) |
|
c theta = atan(tan(THXOUT(2))/cos(phi) |
|
668 |
theta = atan(tan(THXOUT(2))/cos(phi)) |
theta = atan(tan(THXOUT(2))/cos(phi)) |
669 |
xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) |
xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) |
670 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
672 |
adcflag(ch12a(i),hb12a(i)) = 1 |
adcflag(ch12a(i),hb12a(i)) = 1 |
673 |
endif |
endif |
674 |
if (tof12(right,i,iadc).eq.4095) then |
if (tof12(right,i,iadc).eq.4095) then |
675 |
phi = atan(tan(THXOUT(2))/tan(THYOUT(2))) |
phi = atan(tan(THYOUT(2))/tan(THXOUT(2))) |
|
c theta = atan(tan(THXOUT(2))/cos(phi) |
|
676 |
theta = atan(tan(THXOUT(2))/cos(phi)) |
theta = atan(tan(THXOUT(2))/cos(phi)) |
677 |
xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) |
xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) |
678 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
687 |
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 |
688 |
i = tof21_i |
i = tof21_i |
689 |
if (tof21(left,i,iadc).eq.4095) then |
if (tof21(left,i,iadc).eq.4095) then |
690 |
phi = atan(tan(THXOUT(3))/tan(THYOUT(3))) |
phi = atan(tan(THYOUT(3))/tan(THXOUT(3))) |
|
c theta = atan(tan(THXOUT(3))/cos(phi) |
|
691 |
theta = atan(tan(THXOUT(3))/cos(phi)) |
theta = atan(tan(THXOUT(3))/cos(phi)) |
692 |
xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) |
xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) |
693 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
695 |
adcflag(ch21a(i),hb21a(i)) = 1 |
adcflag(ch21a(i),hb21a(i)) = 1 |
696 |
endif |
endif |
697 |
if (tof21(right,i,iadc).eq.4095) then |
if (tof21(right,i,iadc).eq.4095) then |
698 |
phi = atan(tan(THXOUT(3))/tan(THYOUT(3))) |
phi = atan(tan(THYOUT(3))/tan(THXOUT(3))) |
|
c theta = atan(tan(THXOUT(3))/cos(phi) |
|
699 |
theta = atan(tan(THXOUT(3))/cos(phi)) |
theta = atan(tan(THXOUT(3))/cos(phi)) |
700 |
xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) |
xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) |
701 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
709 |
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 |
710 |
i = tof22_i |
i = tof22_i |
711 |
if (tof22(left,i,iadc).eq.4095) then |
if (tof22(left,i,iadc).eq.4095) then |
712 |
phi = atan(tan(THXOUT(4))/tan(THYOUT(4))) |
phi = atan(tan(THYOUT(4))/tan(THXOUT(4))) |
|
c theta = atan(tan(THXOUT(4))/cos(phi) |
|
713 |
theta = atan(tan(THXOUT(4))/cos(phi)) |
theta = atan(tan(THXOUT(4))/cos(phi)) |
714 |
xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) |
xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) |
715 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
717 |
adcflag(ch22a(i),hb22a(i)) = 1 |
adcflag(ch22a(i),hb22a(i)) = 1 |
718 |
endif |
endif |
719 |
if (tof22(right,i,iadc).eq.4095) then |
if (tof22(right,i,iadc).eq.4095) then |
720 |
phi = atan(tan(THXOUT(4))/tan(THYOUT(4))) |
phi = atan(tan(THYOUT(4))/tan(THXOUT(4))) |
|
c theta = atan(tan(THXOUT(4))/cos(phi) |
|
721 |
theta = atan(tan(THXOUT(4))/cos(phi)) |
theta = atan(tan(THXOUT(4))/cos(phi)) |
722 |
xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) |
xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) |
723 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
732 |
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 |
733 |
i = tof31_i |
i = tof31_i |
734 |
if (tof31(left,i,iadc).eq.4095) then |
if (tof31(left,i,iadc).eq.4095) then |
735 |
phi = atan(tan(THXOUT(5))/tan(THYOUT(5))) |
phi = atan(tan(THYOUT(5))/tan(THXOUT(5))) |
|
c theta = atan(tan(THXOUT(5))/cos(phi) |
|
736 |
theta = atan(tan(THXOUT(5))/cos(phi)) |
theta = atan(tan(THXOUT(5))/cos(phi)) |
737 |
xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) |
xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) |
738 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
740 |
adcflag(ch31a(i),hb31a(i)) = 1 |
adcflag(ch31a(i),hb31a(i)) = 1 |
741 |
endif |
endif |
742 |
if (tof31(right,i,iadc).eq.4095) then |
if (tof31(right,i,iadc).eq.4095) then |
743 |
phi = atan(tan(THXOUT(5))/tan(THYOUT(5))) |
phi = atan(tan(THYOUT(5))/tan(THXOUT(5))) |
|
c theta = atan(tan(THXOUT(5))/cos(phi) |
|
744 |
theta = atan(tan(THXOUT(5))/cos(phi)) |
theta = atan(tan(THXOUT(5))/cos(phi)) |
745 |
xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) |
xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) |
746 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
754 |
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 |
755 |
i = tof32_i |
i = tof32_i |
756 |
if (tof32(left,i,iadc).eq.4095) then |
if (tof32(left,i,iadc).eq.4095) then |
757 |
phi = atan(tan(THXOUT(6))/tan(THYOUT(6))) |
phi = atan(tan(THYOUT(6))/tan(THXOUT(6))) |
|
c theta = atan(tan(THXOUT(6))/cos(phi) |
|
758 |
theta = atan(tan(THXOUT(6))/cos(phi)) |
theta = atan(tan(THXOUT(6))/cos(phi)) |
759 |
xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) |
xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) |
760 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
762 |
adcflag(ch32a(i),hb32a(i)) = 1 |
adcflag(ch32a(i),hb32a(i)) = 1 |
763 |
endif |
endif |
764 |
if (tof32(right,i,iadc).eq.4095) then |
if (tof32(right,i,iadc).eq.4095) then |
765 |
phi = atan(tan(THXOUT(6))/tan(THYOUT(6))) |
phi = atan(tan(THYOUT(6))/tan(THXOUT(6))) |
|
c theta = atan(tan(THXOUT(6))/cos(phi) |
|
766 |
theta = atan(tan(THXOUT(6))/cos(phi)) |
theta = atan(tan(THXOUT(6))/cos(phi)) |
767 |
xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) |
xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) |
768 |
xkorr=xkorr/hepratio |
xkorr=xkorr/hepratio |
943 |
C-----------------------------S1 ------------------------------------- |
C-----------------------------S1 ------------------------------------- |
944 |
|
|
945 |
yhelp=yout(1) |
yhelp=yout(1) |
946 |
phi = atan(tan(THXOUT(1))/tan(THYOUT(1))) |
|
947 |
c theta = atan(tan(THXOUT(1))/cos(phi) |
phi = atan(tan(THYOUT(1))/tan(THXOUT(1))) |
948 |
theta = atan(tan(THXOUT(1))/cos(phi)) |
theta = atan(tan(THXOUT(1))/cos(phi)) |
949 |
|
|
950 |
IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN |
IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN |
969 |
|
|
970 |
|
|
971 |
xhelp=xout(2) |
xhelp=xout(2) |
972 |
phi = atan(tan(THXOUT(2))/tan(THYOUT(2))) |
phi = atan(tan(THYOUT(2))/tan(THXOUT(2))) |
|
c theta = atan(tan(THXOUT(2))/cos(phi) |
|
973 |
theta = atan(tan(THXOUT(2))/cos(phi)) |
theta = atan(tan(THXOUT(2))/cos(phi)) |
974 |
|
c write(*,*) 'theta12 ',theta |
975 |
IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN |
IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN |
976 |
|
|
977 |
i = tof12_i |
i = tof12_i |
993 |
C-----------------------------S2 -------------------------------- |
C-----------------------------S2 -------------------------------- |
994 |
|
|
995 |
xhelp=xout(3) |
xhelp=xout(3) |
996 |
phi = atan(tan(THXOUT(3))/tan(THYOUT(3))) |
phi = atan(tan(THYOUT(3))/tan(THXOUT(3))) |
|
c theta = atan(tan(THXOUT(3))/cos(phi) |
|
997 |
theta = atan(tan(THXOUT(3))/cos(phi)) |
theta = atan(tan(THXOUT(3))/cos(phi)) |
998 |
|
c write(*,*) 'theta21 ',theta |
999 |
IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN |
IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN |
1000 |
|
|
1001 |
i = tof21_i |
i = tof21_i |
1015 |
ENDIF |
ENDIF |
1016 |
|
|
1017 |
yhelp=yout(4) |
yhelp=yout(4) |
1018 |
phi = atan(tan(THXOUT(4))/tan(THYOUT(4))) |
phi = atan(tan(THYOUT(4))/tan(THXOUT(4))) |
|
c theta = atan(tan(THXOUT(4))/cos(phi) |
|
1019 |
theta = atan(tan(THXOUT(4))/cos(phi)) |
theta = atan(tan(THXOUT(4))/cos(phi)) |
1020 |
|
c write(*,*) 'theta22 ',theta |
1021 |
|
|
1022 |
IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN |
IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN |
1023 |
|
|
1040 |
C-----------------------------S3 -------------------------------- |
C-----------------------------S3 -------------------------------- |
1041 |
|
|
1042 |
yhelp=yout(5) |
yhelp=yout(5) |
1043 |
phi = atan(tan(THXOUT(5))/tan(THYOUT(5))) |
phi = atan(tan(THYOUT(5))/tan(THXOUT(5))) |
|
c theta = atan(tan(THXOUT(5))/cos(phi) |
|
1044 |
theta = atan(tan(THXOUT(5))/cos(phi)) |
theta = atan(tan(THXOUT(5))/cos(phi)) |
1045 |
|
c write(*,*) 'theta31 ',theta |
1046 |
|
|
1047 |
IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN |
IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN |
1048 |
|
|
1063 |
ENDIF |
ENDIF |
1064 |
|
|
1065 |
xhelp=xout(6) |
xhelp=xout(6) |
1066 |
phi = atan(tan(THXOUT(6))/tan(THYOUT(6))) |
phi = atan(tan(THYOUT(6))/tan(THXOUT(6))) |
|
c theta = atan(tan(THXOUT(6))/cos(phi) |
|
1067 |
theta = atan(tan(THXOUT(6))/cos(phi)) |
theta = atan(tan(THXOUT(6))/cos(phi)) |
1068 |
|
c write(*,*) 'theta32 ',theta |
1069 |
|
|
1070 |
IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN |
IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN |
1071 |
|
|