*file member=acf_exe library=snoman language=fortran77 date=21:Mar:2002 <<< subroutine acf_exe(FTpos,FTdir,iFitIndx,histflag,RETVALUE,DISCARD) * ACF: Main angular correlation routine * Contact: W. Heintzelman, Penn * Verified:* Refereed: IMPLICIT NONE INCLUDE 'zunit.inc' include 'z.inc' include 'acf_evalconst.inc' data NEvtType/2/ data EvtType/'electron','NCsalt '/ * Argument Declarations:- * ===================== integer NValue parameter (NValue=17) real FTpos(4),FTdir(3),RetValue(NValue) LOGICAL histflag,DISCARD *ENDHEADER * External Functions:- * =========================== real vdot * Local Variable Declarations:- * =========================== integer i,nHitPMT,iFitIndx,FirstRTCPMT,LastRTCPMT real PMTpos(3,maxhits),rEvt,udotr,finnerprod(2) real chisq(0:1,MaxEvtType),Probchisq(0:1,MaxEvtType) + ,Delcdf(0:1,MaxEvtType),aLnDetCM(0:1,MaxEvtType) + , etaAvg(0:1) SAVE do i=1,NValue retvalue(i) = -9999. enddo * write(iqlog,*)'acf_exe A. DISCARD =',DISCARD * write(iqlog,*)' FTpos =',FTpos ! Get list of locations of hit PMTs relative to the fitted event ! location and the number hit: call acf_genPMTlist + (FTpos,nHitPMT,PMTpos,FirstRTCPMT,LastRTCPMT,DISCARD) * write(iqlog,*)'acf_exe B. nHitPMT,DISCARD =',nHitPMT,DISCARD * write(*,*)'acf_exe B. nHitPMT,DISCARD =',nHitPMT,DISCARD ! write(iqlog*,*)'FirstRTCPMT,LastRTCPMT =',FirstRTCPMT,LastRTCPMT if(.not.DISCARD) then ! Calculate the angular correlation functions for the event: call acf_AngCorFn (nHitPMT,PMTpos,FirstRTCPMT,LastRTCPMT, + iFitIndx,histflag,etaAvg) ! Calculate inner products of event correl fn with comparison fns: call acf_fnip(101,finnerprod) rEvt = sqrt(FTpos(1)**2 + FTpos(2)**2 + FTpos(3)**2) * udotr = * + (FTpos(1)*FTdir(1)+FTpos(2)*FTdir(2)+FTpos(3)*FTdir(3))/rEvt udotr = vdot(FTpos,FTdir,3)/rEvt ! Calculate the chisquares relative to the standard ! correlation functions: call acf_corChisq(nHitPMT,FirstRTCPMT,LastRTCPMT,rEvt,udotr, + chisq,Probchisq,aLnDetCM,delCDF,DISCARD) endif * write(*,*) 'acf_exe: DISCARD = ',DISCARD if(.not.DISCARD) then do i=0,1 retvalue(1+i) = etaAvg(i) enddo do i=0,3 retvalue(3+3*i) = chisq(i,1) retvalue(4+3*i) = aLnDetCM(i,1) retvalue(5+3*i) = delCDF(i,1) ! I am no longer outputting Probchisq ! retvalue(3+i) = Probchisq(i,1) enddo retvalue(15) = float( LastRTCPMT-FirstRTCPMT+1) retvalue(16) = finnerprod(1) retvalue(17) = finnerprod(2) * write(*,*) 'acf_exe: retvalue =',retvalue endif return end *endfile member=acf_exe* Parameters:- * ========== * FTpos(4) in Fitted event location and time * FTdir(3) in Fitted event direction * histflag in Logical - set to .true. if overall correlation function * histograms should be accumulated and output in HBOOK * file. * RETVALUE out Set to calculated output values unless unable to compute * them, in which RETVALUE()=-9999. * DISCARD in/ = .FALSE. * out Set = .TRUE. if outputs could not be calculated * Common Block Access:- * =================== * None * Specification:- * ============= * Call various angular correlation routines, and return data in RETVALUE * Set DISCARD=.true. and leave RETVALUE()=-9999. if parameters could not * be calculated. * RetValue(1-2) = mean pair separation angle in degrees, without and * with RTC * RetValue(3) = chi-square of event correlation function relative to * the standard correlation function * RetValue(4) = Natural logarithm of the determinant of the * correlation function covariance matrix * RetValue(5) = Greatest difference between the cumulative event * correlation fn and the cumulative standard fn * RetValue(3-5) are calculated using the electron std fn without RTC * RetValue(6-8) = Same as 3-5, using the electron std fn with RTC * RetValue(9-11) = Same as 3-5, using the NCsalt std fn without RTC * RetValue(12-14) = Same as 3-5, using the NCsalt std fn with RTC * RetValue(15) = Number of PMTs passing RTC * RetValue(16) = Inner product of event correlation function with that * of an ideal ring * RetValue(17) = Inner product of event correlation function with * CC/NC average correl fn difference * Program Notes:- * ============= * Revision History:- * ================ * 4.02 W. Heintzelman First version * W. Heintzelman Second version * W. Heintzelman Third version, added outputs 15 .. 17 (Mar 02)