***************************************************************************** INTEGER FUNCTION TOFL2COM() c IMPLICIT NONE C include 'input_tof.txt' include 'output_tof.txt' include 'tofcomm.txt' INTEGER icounter DATA icounter / 0/ LOGICAL check REAL secure INTEGER j REAL xhelp_a,xhelp_t REAL dx,dy,dr,ds REAL yhelp,xdummy,xkorr0,xhelp,xhelp1,xhelp2 REAL c1,c2,sw,sxw,w_i INTEGER icount INTEGER tof11_j,tof21_j,tof31_j INTEGER tof12_j,tof22_j,tof32_j REAL beta_mean c value for status of each PM-data c first index : 1 = left, 2 = right c second index : 1... number of paddle INTEGER tof11_event(2,8),tof12_event(2,6) INTEGER tof21_event(2,2),tof22_event(2,2) INTEGER tof31_event(2,3),tof32_event(2,3) REAL theta12,theta13,theta23 C-- DATA ZTOF/53.74,53.04,23.94,23.44,-23.49,-24.34/ !Sergio 9.05.2006 REAL tofarm12 PARAMETER (tofarm12 = 29.70) ! from 53.39 to 23.69 REAL tofarm23 PARAMETER (tofarm23 = 47.61) ! from 23.69 to -23.92 REAL tofarm13 PARAMETER (tofarm13 = 77.31) ! from 53.39 to -23.92 INTEGER ihelp REAL xkorr C--------------------------------------- C C Begin ! C TOFL2COM = 0 C C CALCULATE COMMON VARIABLES C ******************************************************************* icounter = icounter + 1 * amplitude has to be 'secure' higher than pedestal for an adc event secure = 2. offset = 1 slope = 2 left = 1 right = 2 none_ev = 0 none_find = 0 tdc_ev = 1 adc_ev = 1 itdc = 1 iadc = 2 do i=1,13 betatof_a(i) = 100. ! As in "troftrk.for" enddo do i=1,4 do j=1,12 adctof_c(i,j) = 1000. enddo enddo do i=1,4 do j=1,12 tdc_c(i,j) = 4095. enddo enddo do i=1,12 do j=1,4 tofmask(j,i) = 0 enddo enddo c the calibration files are read in the main program from xxx_tofcalib.rz c-------------------------get ToF data -------------------------------- c put the adc and tdc values from ntuple into tofxx(i,j,k) variables do j=1,8 tof11(1,j,2) = adc(ch11a(j),hb11a(j)) tof11(2,j,2) = adc(ch11b(j),hb11b(j)) tof11(1,j,1) = tdc(ch11a(j),hb11a(j)) tof11(2,j,1) = tdc(ch11b(j),hb11b(j)) enddo do j=1,6 tof12(1,j,2) = adc(ch12a(j),hb12a(j)) tof12(2,j,2) = adc(ch12b(j),hb12b(j)) tof12(1,j,1) = tdc(ch12a(j),hb12a(j)) tof12(2,j,1) = tdc(ch12b(j),hb12b(j)) enddo do j=1,2 tof21(1,j,2) = adc(ch21a(j),hb21a(j)) tof21(2,j,2) = adc(ch21b(j),hb21b(j)) tof21(1,j,1) = tdc(ch21a(j),hb21a(j)) tof21(2,j,1) = tdc(ch21b(j),hb21b(j)) enddo do j=1,2 tof22(1,j,2) = adc(ch22a(j),hb22a(j)) tof22(2,j,2) = adc(ch22b(j),hb22b(j)) tof22(1,j,1) = tdc(ch22a(j),hb22a(j)) tof22(2,j,1) = tdc(ch22b(j),hb22b(j)) enddo do j=1,3 tof31(1,j,2) = adc(ch31a(j),hb31a(j)) tof31(2,j,2) = adc(ch31b(j),hb31b(j)) tof31(1,j,1) = tdc(ch31a(j),hb31a(j)) tof31(2,j,1) = tdc(ch31b(j),hb31b(j)) enddo do j=1,3 tof32(1,j,2) = adc(ch32a(j),hb32a(j)) tof32(2,j,2) = adc(ch32b(j),hb32b(j)) tof32(1,j,1) = tdc(ch32a(j),hb32a(j)) tof32(2,j,1) = tdc(ch32b(j),hb32b(j)) enddo C---------------------------------------------------------------------- DO i = 1,8 if (abs(tof11(1,i,itdc)).gt.10000.) tof11(1,i,itdc)= 10000. if (abs(tof11(2,i,itdc)).gt.10000.) tof11(2,i,itdc)= 10000. if (abs(tof11(1,i,iadc)).gt.10000.) tof11(1,i,iadc)= 10000. if (abs(tof11(2,i,iadc)).gt.10000.) tof11(2,i,iadc)= 10000. ENDDO DO i = 1,6 if (abs(tof12(1,i,itdc)).gt.10000.) tof12(1,i,itdc)= 10000. if (abs(tof12(2,i,itdc)).gt.10000.) tof12(2,i,itdc)= 10000. if (abs(tof12(1,i,iadc)).gt.10000.) tof12(1,i,iadc)= 10000. if (abs(tof12(2,i,iadc)).gt.10000.) tof12(2,i,iadc)= 10000. ENDDO DO i = 1,2 if (abs(tof21(1,i,itdc)).gt.10000.) tof21(1,i,itdc)= 10000. if (abs(tof21(2,i,itdc)).gt.10000.) tof21(2,i,itdc)= 10000. if (abs(tof21(1,i,iadc)).gt.10000.) tof21(1,i,iadc)= 10000. if (abs(tof21(2,i,iadc)).gt.10000.) tof21(2,i,iadc)= 10000. ENDDO DO i = 1,2 if (abs(tof22(1,i,itdc)).gt.10000.) tof22(1,i,itdc)= 10000. if (abs(tof22(2,i,itdc)).gt.10000.) tof22(2,i,itdc)= 10000. if (abs(tof22(1,i,iadc)).gt.10000.) tof22(1,i,iadc)= 10000. if (abs(tof22(2,i,iadc)).gt.10000.) tof22(2,i,iadc)= 10000. ENDDO DO i = 1,3 if (abs(tof31(1,i,itdc)).gt.10000.) tof31(1,i,itdc)= 10000. if (abs(tof31(2,i,itdc)).gt.10000.) tof31(2,i,itdc)= 10000. if (abs(tof31(1,i,iadc)).gt.10000.) tof31(1,i,iadc)= 10000. if (abs(tof31(2,i,iadc)).gt.10000.) tof31(2,i,iadc)= 10000. ENDDO DO i = 1,3 if (abs(tof32(1,i,itdc)).gt.10000.) tof32(1,i,itdc)= 10000. if (abs(tof32(2,i,itdc)).gt.10000.) tof32(2,i,itdc)= 10000. if (abs(tof32(1,i,iadc)).gt.10000.) tof32(1,i,iadc)= 10000. if (abs(tof32(2,i,iadc)).gt.10000.) tof32(2,i,iadc)= 10000. ENDDO C---------------------------------------------------------------- C------------Check Paddles for hits ----------------------- C---------------------------------------------------------------- C upper tof S11 DO i = 1,8 DO j = 1,2 tof11_event(j,i) = none_ev IF ((tof11(j,i,itdc).LT.2000).AND.(tof11(j,i,itdc).GT.100)) + tof11_event(j,i) = tof11_event(j,i) + tdc_ev IF ((tof11(j,i,iadc).GT.secure).AND. + (tof11(j,i,iadc).LT.4095)) + tof11_event(j,i) = tof11_event(j,i) + adc_ev ENDDO ENDDO c find single paddle in upper tof with tdc and adc signal tof11_i = none_find tof11_j = none_find check = .TRUE. DO i = 1, 8 IF ((tof11_event(left,i).GE.1).AND.(tof11_event(right,i).GE.1)) + THEN c check if an other paddle has also an event - then set flag tof11_j = tof11_j + 2**(i-1) IF (check.EQV..TRUE.) THEN IF (tof11_i.EQ.none_find) THEN tof11_i = i ELSE tof11_i = -1 check = .FALSE. ENDIF ENDIF ENDIF ENDDO C upper tof S12 DO i = 1,6 DO j = 1,2 tof12_event(j,i) = none_ev IF ((tof12(j,i,itdc).LT.2000).AND.(tof12(j,i,itdc).GT.100)) + tof12_event(j,i) = tof12_event(j,i) + tdc_ev IF ((tof12(j,i,iadc).GT.secure).AND. + (tof12(j,i,iadc).LT.4095)) + tof12_event(j,i) = tof12_event(j,i) + adc_ev ENDDO ENDDO c find single paddle in upper tof with tdc and adc signal tof12_i = none_find tof12_j = none_find check = .TRUE. DO i = 1, 6 IF ((tof12_event(left,i).GE.1).AND.(tof12_event(right,i).GE.1)) + THEN c check if an other paddle has also an event - then set flag tof12_j = tof12_j + 2**(i-1) IF (check.EQV..TRUE.) THEN IF (tof12_i.EQ.none_find) THEN tof12_i = i ELSE tof12_i = -1 check = .FALSE. ENDIF ENDIF ENDIF ENDDO C middle tof S21 DO i = 1,2 DO j = 1,2 tof21_event(j,i) = none_ev IF ((tof21(j,i,itdc).LT.2000).AND.(tof21(j,i,itdc).GT.100)) + tof21_event(j,i) = tof21_event(j,i) + tdc_ev IF ((tof21(j,i,iadc).GT.secure).AND. + (tof21(j,i,iadc).LT.4095)) + tof21_event(j,i) = tof21_event(j,i) + adc_ev ENDDO ENDDO c find single paddle in upper tof with tdc and adc signal tof21_i = none_find tof21_j = none_find check = .TRUE. DO i = 1, 2 IF ((tof21_event(left,i).GE.1).AND.(tof21_event(right,i).GE.1)) + THEN c check if an other paddle has also an event - then set flag tof21_j = tof21_j + 2**(i-1) IF (check.EQV..TRUE.) THEN IF (tof21_i.EQ.none_find) THEN tof21_i = i ELSE tof21_i = -1 check = .FALSE. ENDIF ENDIF ENDIF ENDDO C middle tof S22 DO i = 1,2 DO j = 1,2 tof22_event(j,i) = none_ev IF ((tof22(j,i,itdc).LT.2000).AND.(tof22(j,i,itdc).GT.100)) + tof22_event(j,i) = tof22_event(j,i) + tdc_ev IF ((tof22(j,i,iadc).GT.secure).AND. + (tof22(j,i,iadc).LT.4095)) + tof22_event(j,i) = tof22_event(j,i) + adc_ev ENDDO ENDDO c find single paddle in upper tof with tdc and adc signal tof22_i = none_find tof22_j = none_find check = .TRUE. DO i = 1, 2 IF ((tof22_event(left,i).GE.1).AND.(tof22_event(right,i).GE.1)) + THEN c check if an other paddle has also an event - then set flag tof22_j = tof22_j + 2**(i-1) IF (check.EQV..TRUE.) THEN IF (tof22_i.EQ.none_find) THEN tof22_i = i ELSE tof22_i = -1 check = .FALSE. ENDIF ENDIF ENDIF ENDDO C bottom tof S31 DO i = 1,3 DO j = 1,2 tof31_event(j,i) = none_ev IF ((tof31(j,i,itdc).LT.2000).AND.(tof31(j,i,itdc).GT.100)) + tof31_event(j,i) = tof31_event(j,i) + tdc_ev IF ((tof31(j,i,iadc).GT.secure).AND. + (tof31(j,i,iadc).LT.4095)) + tof31_event(j,i) = tof31_event(j,i) + adc_ev ENDDO ENDDO c find single paddle in upper tof with tdc and adc signal tof31_i = none_find tof31_j = none_find check = .TRUE. DO i = 1, 3 IF ((tof31_event(left,i).GE.1).AND.(tof31_event(right,i).GE.1)) + THEN c check if an other paddle has also an event - then set flag tof31_j = tof31_j + 2**(i-1) IF (check.EQV..TRUE.) THEN IF (tof31_i.EQ.none_find) THEN tof31_i = i ELSE tof31_i = -1 check = .FALSE. ENDIF ENDIF ENDIF ENDDO C bottom tof S32 DO i = 1,3 DO j = 1,2 tof32_event(j,i) = none_ev IF ((tof32(j,i,itdc).LT.2000).AND.(tof32(j,i,itdc).GT.100)) + tof32_event(j,i) = tof32_event(j,i) + tdc_ev IF ((tof32(j,i,iadc).GT.secure).AND. + (tof32(j,i,iadc).LT.4095)) + tof32_event(j,i) = tof32_event(j,i) + adc_ev ENDDO ENDDO c find single paddle in upper tof with tdc and adc signal tof32_i = none_find tof32_j = none_find check = .TRUE. DO i = 1, 3 IF ((tof32_event(left,i).GE.1).AND.(tof32_event(right,i).GE.1)) + THEN c check if an other paddle has also an event - then set flag tof32_j = tof32_j + 2**(i-1) IF (check.EQV..TRUE.) THEN IF (tof32_i.EQ.none_find) THEN tof32_i = i ELSE tof32_i = -1 check = .FALSE. ENDIF ENDIF ENDIF ENDDO do i=1,6 tof_i_flag(i)=0 tof_j_flag(i)=0 enddo tof_i_flag(1)=tof11_i tof_i_flag(2)=tof12_i tof_i_flag(3)=tof21_i tof_i_flag(4)=tof22_i tof_i_flag(5)=tof31_i tof_i_flag(6)=tof32_i tof_j_flag(1)=tof11_j tof_j_flag(2)=tof12_j tof_j_flag(3)=tof21_j tof_j_flag(4)=tof22_j tof_j_flag(5)=tof31_j tof_j_flag(6)=tof32_j C-------------------------------------------------------------------- C--------------------Time walk correction ------------------------- C-------------------------------------------------------------------- DO i=1,8 xhelp_a = tof11(left,i,iadc) xhelp_t = tof11(left,i,itdc) if(xhelp_a>0) xhelp = tw11(left,i)/sqrt(xhelp_a) tof11(left,i,itdc) = xhelp_t + xhelp tdc_c(ch11a(i),hb11a(i))=tof11(left,i,itdc) xhelp_a = tof11(right,i,iadc) xhelp_t = tof11(right,i,itdc) if(xhelp_a>0) xhelp = tw11(right,i)/sqrt(xhelp_a) tof11(right,i,itdc) = xhelp_t + xhelp tdc_c(ch11b(i),hb11b(i))=tof11(right,i,itdc) ENDDO DO i=1,6 xhelp_a = tof12(left,i,iadc) xhelp_t = tof12(left,i,itdc) if(xhelp_a>0) xhelp = tw12(left,i)/sqrt(xhelp_a) tof12(left,i,itdc) = xhelp_t + xhelp tdc_c(ch12a(i),hb12a(i))=tof12(left,i,itdc) xhelp_a = tof12(right,i,iadc) xhelp_t = tof12(right,i,itdc) if(xhelp_a>0) xhelp = tw12(right,i)/sqrt(xhelp_a) tof12(right,i,itdc) = xhelp_t + xhelp tdc_c(ch12b(i),hb12b(i))=tof12(right,i,itdc) ENDDO C---- DO i=1,2 xhelp_a = tof21(left,i,iadc) xhelp_t = tof21(left,i,itdc) if(xhelp_a>0) xhelp = tw21(left,i)/sqrt(xhelp_a) tof21(left,i,itdc) = xhelp_t + xhelp tdc_c(ch21a(i),hb21a(i))=tof21(left,i,itdc) xhelp_a = tof21(right,i,iadc) xhelp_t = tof21(right,i,itdc) if(xhelp_a>0) xhelp = tw21(right,i)/sqrt(xhelp_a) tof21(right,i,itdc) = xhelp_t + xhelp tdc_c(ch21b(i),hb21b(i))=tof21(right,i,itdc) ENDDO DO i=1,2 xhelp_a = tof22(left,i,iadc) xhelp_t = tof22(left,i,itdc) if(xhelp_a>0) xhelp = tw22(left,i)/sqrt(xhelp_a) tof22(left,i,itdc) = xhelp_t + xhelp tdc_c(ch22a(i),hb22a(i))=tof22(left,i,itdc) xhelp_a = tof22(right,i,iadc) xhelp_t = tof22(right,i,itdc) if(xhelp_a>0) xhelp = tw22(right,i)/sqrt(xhelp_a) tof22(right,i,itdc) = xhelp_t + xhelp tdc_c(ch22b(i),hb22b(i))=tof22(right,i,itdc) ENDDO C---- DO i=1,3 xhelp_a = tof31(left,i,iadc) xhelp_t = tof31(left,i,itdc) if(xhelp_a>0) xhelp = tw31(left,i)/sqrt(xhelp_a) tof31(left,i,itdc) = xhelp_t + xhelp tdc_c(ch31a(i),hb31a(i))=tof31(left,i,itdc) xhelp_a = tof31(right,i,iadc) xhelp_t = tof31(right,i,itdc) if(xhelp_a>0) xhelp = tw31(right,i)/sqrt(xhelp_a) tof31(right,i,itdc) = xhelp_t + xhelp tdc_c(ch31b(i),hb31b(i))=tof31(right,i,itdc) ENDDO DO i=1,3 xhelp_a = tof32(left,i,iadc) xhelp_t = tof32(left,i,itdc) if(xhelp_a>0) xhelp = tw32(left,i)/sqrt(xhelp_a) tof32(left,i,itdc) = xhelp_t + xhelp tdc_c(ch32a(i),hb32a(i))=tof32(left,i,itdc) xhelp_a = tof32(right,i,iadc) xhelp_t = tof32(right,i,itdc) if(xhelp_a>0) xhelp = tw32(right,i)/sqrt(xhelp_a) tof32(right,i,itdc) = xhelp_t + xhelp tdc_c(ch32b(i),hb32b(i))=tof32(right,i,itdc) ENDDO C---- C------------------------------------------------------------------ C--- calculate track position in paddle using timing difference C------------------------------------------------------------------ do i=1,3 xtofpos(i)=100. ytofpos(i)=100. enddo C-----------------------------S1 -------------------------------- IF (tof11_i.GT.none_find) THEN ytofpos(1) = ((tof11(1,tof11_i,itdc)-tof11(2,tof11_i,itdc))/2. + -y_coor_lin11(tof11_i,offset))/y_coor_lin11(tof11_i,slope) endif IF (tof12_i.GT.none_find) THEN xtofpos(1) = ((tof12(1,tof12_i,itdc)-tof12(2,tof12_i,itdc))/2. + -x_coor_lin12(tof12_i,offset))/x_coor_lin12(tof12_i,slope) endif C-----------------------------S2 -------------------------------- IF (tof21_i.GT.none_find) THEN xtofpos(2) = ((tof21(1,tof21_i,itdc)-tof21(2,tof21_i,itdc))/2. + -x_coor_lin21(tof21_i,offset))/x_coor_lin21(tof21_i,slope) endif IF (tof22_i.GT.none_find) THEN ytofpos(2) = ((tof22(1,tof22_i,itdc)-tof22(2,tof22_i,itdc))/2. + -y_coor_lin22(tof22_i,offset))/y_coor_lin22(tof22_i,slope) endif C-----------------------------S3 -------------------------------- IF (tof31_i.GT.none_find) THEN ytofpos(3) = ((tof31(1,tof31_i,itdc)-tof31(2,tof31_i,itdc))/2. + -y_coor_lin31(tof31_i,offset))/y_coor_lin31(tof31_i,slope) endif IF (tof32_i.GT.none_find) THEN xtofpos(3) = ((tof32(1,tof32_i,itdc)-tof32(2,tof32_i,itdc))/2. + -x_coor_lin32(tof32_i,offset))/x_coor_lin32(tof32_i,slope) endif do i=1,3 if (abs(xtofpos(i)).gt.100.) then xtofpos(i)=101. endif if (abs(ytofpos(i)).gt.100.) then ytofpos(i)=101. endif enddo C---------------------------------------------------------------------- C--------------------Corrections on ADC-data ------------------------- C---------------------zenith angle theta --------------------------- C---------------------------------------------------------------------- dx=0. dy=0. dr=0. theta13 = 0. IF ((tof12_i.GT.none_find).AND.(tof32_i.GT.none_find)) & dx = xtofpos(1) - xtofpos(3) IF ((tof11_i.GT.none_find).AND.(tof31_i.GT.none_find)) & dy = ytofpos(1) - ytofpos(3) dr = sqrt(dx*dx+dy*dy) theta13 = atan(dr/tofarm13) dx=0. dy=0. dr=0. theta12 = 0. IF ((tof12_i.GT.none_find).AND.(tof21_i.GT.none_find)) & dx = xtofpos(1) - xtofpos(2) IF ((tof11_i.GT.none_find).AND.(tof22_i.GT.none_find)) & dy = ytofpos(1) - ytofpos(2) dr = sqrt(dx*dx+dy*dy) theta12 = atan(dr/tofarm12) dx=0. dy=0. dr=0. theta23 = 0. IF ((tof21_i.GT.none_find).AND.(tof32_i.GT.none_find)) & dx = xtofpos(2) - xtofpos(3) IF ((tof22_i.GT.none_find).AND.(tof31_i.GT.none_find)) & dy = ytofpos(2) - ytofpos(3) dr = sqrt(dx*dx+dy*dy) theta23 = atan(dr/tofarm23) C---------------------------------------------------------------------- C------------------angle and ADC(x) correction C---------------------------------------------------------------------- C-----------------------------S1 -------------------------------- c middle y (or x) position of the upper and middle ToF-Paddle c DATA tof11_x/ -17.85,-12.75,-7.65,-2.55,2.55,7.65,12.75,17.85/ c DATA tof12_y/ -13.75,-8.25,-2.75,2.75,8.25,13.75/ c DATA tof21_y/ -3.75,3.75/ c DATA tof22_x/ -4.5,4.5/ c DATA tof31_x/ -6.0,0.,6.0/ c DATA tof32_y/ -5.0,0.0,5.0/ yhelp=0. if (tof12_i.GT.none_find) yhelp=tof12_y(tof12_i) if (ytofpos(1).lt.100) yhelp=ytofpos(1) IF (tof11_i.GT.none_find.AND.abs(yhelp).lt.100) THEN i = tof11_i xdummy=tof11(left,i,iadc) tof11(left,i,iadc) = tof11(left,i,iadc)*cos(theta13) if (tof11(left,i,iadc).lt.4095) then xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2)) xkorr0=adcx11(left,i,1) adctof_c(ch11a(i),hb11a(i))=tof11(left,i,iadc)/xkorr endif tof11(right,i,iadc) = tof11(right,i,iadc)*cos(theta13) if (tof11(right,i,iadc).lt.4095) then xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2)) xkorr0=adcx11(right,i,1) adctof_c(ch11b(i),hb11b(i))=tof11(right,i,iadc)/xkorr endif ENDIF xhelp=0. if (tof11_i.GT.none_find) xhelp=tof11_x(tof11_i) if (xtofpos(1).lt.100) xhelp=xtofpos(1) IF (tof12_i.GT.none_find.AND.abs(xhelp).lt.100) THEN i = tof12_i tof12(left,i,iadc) = tof12(left,i,iadc)*cos(theta13) if (tof12(left,i,iadc).lt.4095) then xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2)) xkorr0=adcx12(left,i,1) adctof_c(ch12a(i),hb12a(i))=tof12(left,i,iadc)/xkorr endif tof12(right,i,iadc) = tof12(right,i,iadc)*cos(theta13) if (tof12(right,i,iadc).lt.4095) then xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2)) xkorr0=adcx12(right,i,1) adctof_c(ch12b(i),hb12b(i))=tof12(right,i,iadc)/xkorr endif ENDIF C-----------------------------S2 -------------------------------- xhelp=0. if (tof22_i.GT.none_find) xhelp=tof22_x(tof22_i) if (xtofpos(2).lt.100) xhelp=xtofpos(2) IF (tof21_i.GT.none_find.AND.abs(xhelp).lt.100) THEN i = tof21_i tof21(left,i,iadc) = tof21(left,i,iadc)*cos(theta13) if (tof21(left,i,iadc).lt.4095) then xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2)) xkorr0=adcx21(left,i,1) adctof_c(ch21a(i),hb21a(i))=tof21(left,i,iadc)/xkorr endif tof21(right,i,iadc) = tof21(right,i,iadc)*cos(theta13) if (tof21(right,i,iadc).lt.4095) then xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2)) xkorr0=adcx21(right,i,1) adctof_c(ch21b(i),hb21b(i))=tof21(right,i,iadc)/xkorr endif ENDIF yhelp=0. if (tof21_i.GT.none_find) yhelp=tof21_y(tof21_i) if (ytofpos(2).lt.100) yhelp=ytofpos(2) IF (tof22_i.GT.none_find.AND.abs(yhelp).lt.100) THEN i = tof22_i tof22(left,i,iadc) = tof22(left,i,iadc)*cos(theta13) if (tof22(left,i,iadc).lt.4095) then xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2)) xkorr0=adcx22(left,i,1) adctof_c(ch22a(i),hb22a(i))=tof22(left,i,iadc)/xkorr endif tof22(right,i,iadc) = tof22(right,i,iadc)*cos(theta13) if (tof22(right,i,iadc).lt.4095) then xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2)) xkorr0=adcx22(right,i,1) adctof_c(ch22b(i),hb22b(i))=tof22(right,i,iadc)/xkorr endif ENDIF C-----------------------------S3 -------------------------------- yhelp=0. if (tof32_i.GT.none_find) yhelp=tof32_y(tof32_i) if (ytofpos(3).lt.100) yhelp=ytofpos(3) IF (tof31_i.GT.none_find.AND.abs(yhelp).lt.100) THEN i = tof31_i tof31(left,i,iadc) = tof31(left,i,iadc)*cos(theta13) if (tof31(left,i,iadc).lt.4095) then xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2)) xkorr0=adcx31(left,i,1) adctof_c(ch31a(i),hb31a(i))=tof31(left,i,iadc)/xkorr endif tof31(right,i,iadc) = tof31(right,i,iadc)*cos(theta13) if (tof31(right,i,iadc).lt.4095) then xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2)) xkorr0=adcx31(right,i,1) adctof_c(ch31b(i),hb31b(i))=tof31(right,i,iadc)/xkorr endif ENDIF xhelp=0. if (tof31_i.GT.none_find) xhelp=tof31_x(tof31_i) if (xtofpos(3).lt.100) xhelp=xtofpos(3) IF (tof32_i.GT.none_find.AND.abs(xhelp).lt.100) THEN i = tof32_i tof32(left,i,iadc) = tof32(left,i,iadc)*cos(theta13) if (tof32(left,i,iadc).lt.4095) then xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2)) xkorr0=adcx32(left,i,1) adctof_c(ch32a(i),hb32a(i))=tof32(left,i,iadc)/xkorr endif tof32(right,i,iadc) = tof32(right,i,iadc)*cos(theta13) if (tof32(right,i,iadc).lt.4095) then xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2)) xkorr0=adcx32(right,i,1) adctof_c(ch32b(i),hb32b(i))=tof32(right,i,iadc)/xkorr endif ENDIF C----------------------------------------------------------------------- C----------------------calculate Beta ------------------------------ C----------------------------------------------------------------------- C-------------------difference of sums --------------------------- C C DS = (t1+t2) - t3+t4) C DS = c1 + c2/beta*cos(theta) C c2 = 2d/c gives c2 = 2d/(c*TDCresolution) TDC=50ps/channel C => c2 = ca.60 for 0.45 m c2 = ca.109 for 0.81 m C since TDC resolution varies slightly c2 has to be calibrated C S11 - S31 IF (tof11_i.GT.none_find.AND.tof31_i.GT.none_find) THEN xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc) xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof11_i-1)*3+tof31_i c1 = k_S11S31(1,ihelp) c2 = k_S11S31(2,ihelp) betatof_a(1) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S11 - S31 tofmask(ch11a(tof11_i),hb11a(tof11_i)) = $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1 tofmask(ch11b(tof11_i),hb11b(tof11_i)) = $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1 tofmask(ch31a(tof31_i),hb31a(tof31_i)) = $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1 tofmask(ch31b(tof31_i),hb31b(tof31_i)) = $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1 C------- ENDIF C S11 - S32 IF (tof11_i.GT.none_find.AND.tof32_i.GT.none_find) THEN xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc) xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof11_i-1)*3+tof32_i c1 = k_S11S32(1,ihelp) c2 = k_S11S32(2,ihelp) betatof_a(2) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S11 - S32 tofmask(ch11a(tof11_i),hb11a(tof11_i)) = $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1 tofmask(ch11b(tof11_i),hb11b(tof11_i)) = $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1 tofmask(ch32a(tof32_i),hb32a(tof32_i)) = $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1 tofmask(ch32b(tof32_i),hb32b(tof32_i)) = $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1 C------- ENDIF C S12 - S31 IF (tof12_i.GT.none_find.AND.tof31_i.GT.none_find) THEN xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc) xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof12_i-1)*3+tof31_i c1 = k_S12S31(1,ihelp) c2 = k_S12S31(2,ihelp) betatof_a(3) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S12 - S31 tofmask(ch12a(tof12_i),hb12a(tof12_i)) = $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1 tofmask(ch12b(tof12_i),hb12b(tof12_i)) = $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1 tofmask(ch31a(tof31_i),hb31a(tof31_i)) = $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1 tofmask(ch31b(tof31_i),hb31b(tof31_i)) = $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1 C------- ENDIF C S12 - S32 IF (tof12_i.GT.none_find.AND.tof32_i.GT.none_find) THEN xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc) xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof12_i-1)*3+tof32_i c1 = k_S12S32(1,ihelp) c2 = k_S12S32(2,ihelp) betatof_a(4) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S12 - S32 tofmask(ch12a(tof12_i),hb12a(tof12_i)) = $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1 tofmask(ch12b(tof12_i),hb12b(tof12_i)) = $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1 tofmask(ch32a(tof32_i),hb32a(tof32_i)) = $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1 tofmask(ch32b(tof32_i),hb32b(tof32_i)) = $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1 C------- ENDIF C S21 - S31 IF (tof21_i.GT.none_find.AND.tof31_i.GT.none_find) THEN xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc) xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof21_i-1)*3+tof31_i c1 = k_S21S31(1,ihelp) c2 = k_S21S31(2,ihelp) betatof_a(5) = c2/(cos(theta23)*(ds-c1)) C------- ToF Mask - S21 - S31 tofmask(ch21a(tof21_i),hb21a(tof21_i)) = $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1 tofmask(ch21b(tof21_i),hb21b(tof21_i)) = $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1 tofmask(ch31a(tof31_i),hb31a(tof31_i)) = $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1 tofmask(ch31b(tof31_i),hb31b(tof31_i)) = $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1 C------- ENDIF C S21 - S32 IF (tof21_i.GT.none_find.AND.tof32_i.GT.none_find) THEN xhelp1 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc) xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof21_i-1)*3+tof32_i c1 = k_S21S32(1,ihelp) c2 = k_S21S32(2,ihelp) betatof_a(6) = c2/(cos(theta23)*(ds-c1)) C------- ToF Mask - S21 - S32 tofmask(ch21a(tof21_i),hb21a(tof21_i)) = $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1 tofmask(ch21b(tof21_i),hb21b(tof21_i)) = $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1 tofmask(ch32a(tof32_i),hb32a(tof32_i)) = $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1 tofmask(ch32b(tof32_i),hb32b(tof32_i)) = $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1 C------- ENDIF C S22 - S31 IF (tof22_i.GT.none_find.AND.tof31_i.GT.none_find) THEN xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc) xhelp2 = tof31(1,tof31_i,itdc)+tof31(2,tof31_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof22_i-1)*3+tof31_i c1 = k_S22S31(1,ihelp) c2 = k_S22S31(2,ihelp) betatof_a(7) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S22 - S31 tofmask(ch22a(tof22_i),hb22a(tof22_i)) = $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1 tofmask(ch22b(tof22_i),hb22b(tof22_i)) = $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1 tofmask(ch31a(tof31_i),hb31a(tof31_i)) = $ tofmask(ch31a(tof31_i),hb31a(tof31_i)) + 1 tofmask(ch31b(tof31_i),hb31b(tof31_i)) = $ tofmask(ch31b(tof31_i),hb31b(tof31_i)) + 1 C------- ENDIF C S22 - S32 IF (tof22_i.GT.none_find.AND.tof32_i.GT.none_find) THEN xhelp1 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc) xhelp2 = tof32(1,tof32_i,itdc)+tof32(2,tof32_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof22_i-1)*3+tof32_i c1 = k_S22S32(1,ihelp) c2 = k_S22S32(2,ihelp) betatof_a(8) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S22 - S32 tofmask(ch22a(tof22_i),hb22a(tof22_i)) = $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1 tofmask(ch22b(tof22_i),hb22b(tof22_i)) = $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1 tofmask(ch32a(tof32_i),hb32a(tof32_i)) = $ tofmask(ch32a(tof32_i),hb32a(tof32_i)) + 1 tofmask(ch32b(tof32_i),hb32b(tof32_i)) = $ tofmask(ch32b(tof32_i),hb32b(tof32_i)) + 1 C------- ENDIF C S11 - S21 IF (tof11_i.GT.none_find.AND.tof21_i.GT.none_find) THEN xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc) xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof11_i-1)*2+tof21_i c1 = k_S11S21(1,ihelp) c2 = k_S11S21(2,ihelp) betatof_a(9) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S11 - S21 tofmask(ch11a(tof11_i),hb11a(tof11_i)) = $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1 tofmask(ch11b(tof11_i),hb11b(tof11_i)) = $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1 tofmask(ch21a(tof21_i),hb21a(tof21_i)) = $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1 tofmask(ch21b(tof21_i),hb21b(tof21_i)) = $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1 C------- ENDIF C S11 - S22 IF (tof11_i.GT.none_find.AND.tof22_i.GT.none_find) THEN xhelp1 = tof11(1,tof11_i,itdc)+tof11(2,tof11_i,itdc) xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof11_i-1)*2+tof22_i c1 = k_S11S22(1,ihelp) c2 = k_S11S22(2,ihelp) betatof_a(10) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S11 - S22 tofmask(ch11a(tof11_i),hb11a(tof11_i)) = $ tofmask(ch11a(tof11_i),hb11a(tof11_i)) + 1 tofmask(ch11b(tof11_i),hb11b(tof11_i)) = $ tofmask(ch11b(tof11_i),hb11b(tof11_i)) + 1 tofmask(ch22a(tof22_i),hb22a(tof22_i)) = $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1 tofmask(ch22b(tof22_i),hb22b(tof22_i)) = $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1 C------- ENDIF C S12 - S21 IF (tof12_i.GT.none_find.AND.tof21_i.GT.none_find) THEN xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc) xhelp2 = tof21(1,tof21_i,itdc)+tof21(2,tof21_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof12_i-1)*2+tof21_i c1 = k_S12S21(1,ihelp) c2 = k_S12S21(2,ihelp) betatof_a(11) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S12 - S21 tofmask(ch12a(tof12_i),hb12a(tof12_i)) = $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1 tofmask(ch12b(tof12_i),hb12b(tof12_i)) = $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1 tofmask(ch21a(tof21_i),hb21a(tof21_i)) = $ tofmask(ch21a(tof21_i),hb21a(tof21_i)) + 1 tofmask(ch21b(tof21_i),hb21b(tof21_i)) = $ tofmask(ch21b(tof21_i),hb21b(tof21_i)) + 1 C------- ENDIF C S12 - S22 IF (tof12_i.GT.none_find.AND.tof22_i.GT.none_find) THEN xhelp1 = tof12(1,tof12_i,itdc)+tof12(2,tof12_i,itdc) xhelp2 = tof22(1,tof22_i,itdc)+tof22(2,tof22_i,itdc) ds = xhelp1-xhelp2 ihelp=(tof12_i-1)*2+tof22_i c1 = k_S12S22(1,ihelp) c2 = k_S12S22(2,ihelp) betatof_a(12) = c2/(cos(theta13)*(ds-c1)) C------- ToF Mask - S12 - S22 tofmask(ch12a(tof12_i),hb12a(tof12_i)) = $ tofmask(ch12a(tof12_i),hb12a(tof12_i)) + 1 tofmask(ch12b(tof12_i),hb12b(tof12_i)) = $ tofmask(ch12b(tof12_i),hb12b(tof12_i)) + 1 tofmask(ch22a(tof22_i),hb22a(tof22_i)) = $ tofmask(ch22a(tof22_i),hb22a(tof22_i)) + 1 tofmask(ch22b(tof22_i),hb22b(tof22_i)) = $ tofmask(ch22b(tof22_i),hb22b(tof22_i)) + 1 C------- ENDIF C--------------------------------------------------------- icount=0 sw=0. sxw=0. beta_mean=100. do i=1,12 if ((betatof_a(i).gt.-1.5).and.(betatof_a(i).lt.1.5)) then icount= icount+1 if (i.le.4) w_i=1./(0.13**2.) if ((i.ge.5).and.(i.le.8)) w_i=1./(0.16**2.) if (i.ge.9) w_i=1./(0.25**2.) ! to be checked sxw=sxw + betatof_a(i)*w_i sw =sw + w_i endif enddo if (icount.gt.0) beta_mean=sxw/sw betatof_a(13) = beta_mean 100 continue C RETURN END