*file member=acf_AngCorMain  library=snoman language=fortran77 date=09:Jul:2004
 <<<      subroutine acf_AngCorMain(LINKS,FitterFlag,RETVALUE,DISCARD)
     
    *     ACF: Alternate way of entering angular correlation routines
    *          The standard way of using the ACF code is through acf_exe.
     
    *     Contact:  W. Heintzelman, Penn
    *     Verified: 
    *     Refereed: 
     
    *     Parameters:-
    *     ==========
    *     LINKS     in      Pointer to event number in array IQ
    *     FitterFlag in     One-character input to specify fitter from which
    *                       event location should be taken (m, e, g, p, q, or t)
    *     RETVALUE  out     Set to calculated output values unless unable to
    *                       compute them.
    *     DISCARD   in      = .FALSE.
    *               out     Set = .TRUE. if outputs could not be calculated
     
    *     Common Block Access:-
    *     ===================
    *        , Banks: 
     
    *     Specification:-
    *     =============
    *     Call Angular Correlation Routines and return following values
    *     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
     
    *     RevValue(6-8)   = Same as 3-5, using the electron std fn with    RTC
    *     RevValue(9-11)  = Same as 3-5, using the NCsalt   std fn without RTC
    *     RevValue(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
     
     
    *       Allows acf parameters to be accumulated for different fitters in
    *       the same run.
    *       If routine was just called for the same event and the same fitter,
    *       it returns values previously computed rather than re-executing.
     
    *     Program Notes:-
    *     =============
     
    *     Revision History:-
    *     ================
    *     4.02   W. Heintzelman   First version
    *            W. Heintzelman   Second version
    *            W. Heintzelman   Third version, added outputs 15 and 16 (Mar 02)
    *     5.00   N. West          Extend Fittertypes for FTK/FTR.
          IMPLICIT NONE
     
            INCLUDE 'zunit.inc'
            include 'z.inc'
            include 'acf_evalconst.inc'
     
    *     Argument Declarations:-
    *     =====================
          INTEGER           LINKS(1)
          Character*1       FitterFlag
          integer NValue
          parameter (NValue=17)
          REAL              RetValue(NValue)
          LOGICAL           DISCARD
    *ENDHEADER
     
    *     Local Variable Declarations:-
    *     ===========================
            real FTpos(4),FTdir(3),rEvt,udotr,finnerprod(2)
            logical lastDISCARD
            integer i,nHitPMT,LK1,iLastEvt,iFitIndx
            integer FirstRTCPMT,LastRTCPMT
            real PMTpos(3,maxhits)
            real chisq(0:1,MaxEvtType),Probchisq(0:1,MaxEvtType)
         +      ,Delcdf(0:1,MaxEvtType),aLnDetCM(0:1,MaxEvtType)
         +      , etaAvg(0:1)
            character*1 LastFitter,FitterTypes(NFitters)
     
    *       iLastEvt is used to save the event number on the previous call to this
    *       routine so a test can be made so that the computations are done
    *       only once for each event.
            data iLastEvt/-1/,LastFitter/' '/
            data Fittertypes/'1','2','3','e','t','q','g','m','p','u',
         +                   'r','k',' ',' ',' ',' ',' ',' ',' ',' '/
    *       1, 2, 3 - three user fitters
    *       e - Elastic         m - Muon            k - Energy
    *       t - Time            p - Path
    *       q - Quad            u - QPDF
    *       g - Grid            r - Track
     
            SAVE
     
     
          LK1 = LINKS(1)  ! Link to event number
          if(IQ(LK1).ne.ILastEvt .or. FitterFlag.ne.LastFitter) then
            ILastEvt = IQ(LK1)
            LastFitter = FitterFlag
     
            iFitIndx=0
            do i=1,NFitters
                if(FitterFlag.eq.FitterTypes(i)) iFitIndx = i
            enddo
            if(iFitIndx.eq.0) then
                write(iqlog,*) 'In angcormain.  Unknown fitter type.',
         +          '  FitterFlag = ',FitterFlag
                stop
            endif
     
            do i=1,NValue
              retvalue(i) = -9999.
            enddo
     
            ! Get the event location & direction calculated by the desired fitter:
            call getftxloc(FitterFlag,FTpos,FTdir,DISCARD)
    *        write(*,*)'In AngCorMain. FTpos,FTdir,DISCARD =',
    *     +                 FTpos,FTdir,DISCARD
     
            ! Get list of locations of hit PMTs relative to the fitted event
            ! location and the number hit:
            if(.not.DISCARD) call acf_genPMTlist
         +          (FTpos,nHitPMT,PMTpos,FirstRTCPMT,LastRTCPMT,DISCARD)
            ! write(*,*)'In AngCorMain. nHitPMT,DISCARD =',nHitPMT,DISCARD
            ! write(*,*) 'FirstRTCPMT,LastRTCPMT =',FirstRTCPMT,LastRTCPMT
     
            if(.not.DISCARD) then
                ! Calculate the angular correlation functions for the event:
                call acf_AngCorFn (nHitPMT,PMTpos,FirstRTCPMT,LastRTCPMT,
         +                      iFitIndx,.true.,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
                ! Calculate the chisquares relative to the standard
                ! correlation functions:
                call acf_corChisq(nHitPMT,FirstRTCPMT,LastRTCPMT,rEvt,udotr,
         +                          chisq,Probchisq,aLnDetCM,delCDF,DISCARD)
            endif
     
            lastDISCARD = DISCARD
          else
            DISCARD = lastDISCARD
          endif
     
            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(*,*) 'AngCorMain:  retvalue =',retvalue
            endif
     
          return
          end
    *endfile member=acf_AngCorMain