*file member=anxx_tubes_trm library=snoman language=fortran77 date=08:Nov:2004
     
 <<<      subroutine anxx_tubes_trm(iretc)
     
    *     ANX: ANXX Banks Processor. Determine bad channels.
     
    *     Contact:  M. Huang,  Texas
     
    *     Parameters:-
    *     ==========
     
    *     iretc     out     return code:-
    *                       >  0  error
    *                       <= 0  o.k.
     
    *     Common Block Access:-
    *     ===================
    *     (ignoring internal and environmental access)
     
    *     /ANXX_COUNT_COM/         in      *.
     
    *     Specification:-
    *     =============
     
    *     Determine bad channels beyond those bad channels from DQXX banks
    *     And report the bad channles in ANXX Banks.
     
    *     Revision History:-
    *     ================
     
    *     5.01  M. Huang     First version.
    *           N. McCauley  Add flagging old tubes and some minor bug fixes.
    *           C. Kyba      Add gain ratio cut and mnemonics.
    *           N. McCauley  Make sure we calculate num_period.
     
          implicit none
     
          include 'bank_ev.inc'
          include 'mt.inc'
          include 'su_mnemonics.inc'
          include 'anxx_data_com.inc'
          include 'anxx_count_com.inc'
          include 'anxx_run_info.inc'
          include 'anxx_cut_com.inc'
          include 'io.inc'
          include 'zunit.inc'
          include 'z.inc'
     
    *     Argument Declarations:-
    *     =====================
     
          integer           iretc
     
    *endheader
     
     
    *     Local Variable Declarations:-
    *     ===========================
     
          integer ipmt, itype, tmp_chan, mask
          integer tag_flag(0:ntag), tag_count, tag(ntag+1)
          real    tac_stat, qhs_stat, qhl_stat, qlx_stat,
         +        tac_lo_stat, tac_hi_stat, qhs_lo_stat, qhs_hi_stat,
         +        qhl_lo_stat, qhl_hi_stat, qlx_lo_stat, qlx_hi_stat,
         +        low_occ_stat, high_occ_stat, orphan_stat, gr_stat,
         +        sync_stat, cell_stat
          integer tac_fail, qhs_fail, qhl_fail, qlx_fail,
         +        tac_lo_fail, tac_hi_fail, qhs_lo_fail, qhs_hi_fail,
         +        qhl_lo_fail, qhl_hi_fail, qlx_lo_fail, qlx_hi_fail,
         +        low_occ_fail, high_occ_fail, orphan_fail, gr_fail,
         +        sync_fail, cell_fail, zero_occ_fail, tot_pmt_fail
          integer iperiod, num_period, num_low_occ
     
          integer anx_num_bank, anx_nout
          integer anx_date(2), delta_days, delta_mins
     
          logical anxx_is_online, warn_short
     
          character anx_contact*50, anx_title_format*50,
         +          anx_titles_bank*4
     
          real orph_array(nperiod_orphan),median,width
          integer i,hit_pmts
     
          warn_short = .false.
     
    * ... create ANXX banks titles header ..............................
     
    * ... for longer period ............
          anx_date(1) = 19750101
          anx_date(2) = 0
          delta_days  = 21900
          delta_mins  = 0
     
    * ... for short period .............
    *      call ucopy(iq(lev+KEV_JDY),anx_jdy,3)
    *      call universal_date_local(anx_jdy,anx_date)
    *      delta_days = 30
    *      delta_mins = 0
     
          anx_titles_bank = 'ANXX'
     
          anx_num_bank = data_type
          anx_nout = 100000
          anx_contact = '  M. Huang, Texas'
          anx_title_format = '-I'
     
          call write_titles_header(lun_anx_txt,file_name,anx_titles_bank,
         +     anx_num_bank,anx_contact,anx_title_format,anx_nout,
         +     anx_date(1),anx_date(2),delta_days,delta_mins)
     
          tmp_chan = 9728
          write(lun_anx_txt,9001) tmp_chan
     
          write(lun_anx_txt,9004)
          write(lun_anx_txt,9005)
          write(lun_anx_txt,9006)
          write(lun_anx_txt,9009)
     
    * ... initialization for counting failure pmts .....................
          tac_fail = 0
          qhs_fail = 0
          qhl_fail = 0
          qlx_fail = 0
     
          tac_lo_fail = 0
          tac_hi_fail = 0
          qhs_lo_fail = 0
          qhs_hi_fail = 0
          qhl_lo_fail = 0
          qhl_hi_fail = 0
          qlx_lo_fail = 0
          qlx_hi_fail = 0
     
          gr_fail       = 0
          low_occ_fail  = 0
          high_occ_fail = 0
          orphan_fail   = 0
          sync_fail     = 0
          cell_fail     = 0
          zero_occ_fail = 0
          tot_pmt_fail  = 0
     
    * --- deal with low occ first ----------------------------------------
     
          call anxx_search_lowocc_cut
     
    * --- Setup num period incase we don't get to it elsewhere. ---------
          num_period = int(elapse_time/time_interval)
          if (num_period .gt. nperiod) num_period = nperiod
     
    *--- tagging bad channels ------------------------------------------
     
          do ipmt = 0, npmt
     
             do itype = 0, ntag
                tag_flag(itype) = -9
             end do
     
    *     Fill a small number of bits with previous results, if required.
             if (flag_old_tubes .eq. 1)then
    *     Former TAC failures.
                mask = 2**(KANX_FLAG_TAC_LO)+2**(KANX_FLAG_TAC_HI)
                if (.not.anxx_is_online(ipmt,mask,0))
         +          tag_flag(KANX_FLAG_FORMER_TAC) = KANX_FLAG_FORMER_TAC
    *     Former QHS failures
                mask = 2**(KANX_FLAG_QHS_LO)+2**(KANX_FLAG_QHS_HI)
                if (.not.anxx_is_online(ipmt,mask,0))
         +          tag_flag(KANX_FLAG_FORMER_QHS) = KANX_FLAG_FORMER_QHS
    *     Former QHL failures
                mask = 2**(KANX_FLAG_QHL_LO)+2**(KANX_FLAG_QHL_HI)
                if (.not.anxx_is_online(ipmt,mask,0))
         +          tag_flag(KANX_FLAG_FORMER_QHL) = KANX_FLAG_FORMER_QHL
    *     Former QLX failures
                mask = 2**(KANX_FLAG_QLX_LO)+2**(KANX_FLAG_QLX_HI)
                if (.not.anxx_is_online(ipmt,mask,0))
         +          tag_flag(KANX_FLAG_FORMER_QLX) = KANX_FLAG_FORMER_QLX
    *     Former QHS/QLx ratio failures.
                mask = 2**(KANX_FLAG_GAIN_RATIO)
                if (.not.anxx_is_online(ipmt,mask,0))
         +          tag_flag(KANX_FLAG_FORMER_GR) = KANX_FLAG_FORMER_GR
             endif
     
             if (occ_count(ipmt) .gt. 0.0) then
     
                if (data_type.eq.1 .or. data_type.eq.2) then
     
                   tac_stat = tac_count(ipmt)/occ_count(ipmt)
                   qhs_stat = qhs_count(ipmt)/occ_count(ipmt)
                   qhl_stat = qhl_count(ipmt)/occ_count(ipmt)
                   qlx_stat = qlx_count(ipmt)/occ_count(ipmt)
     
                   tac_lo_stat = tac_lo_count(ipmt)/occ_count(ipmt)
                   tac_hi_stat = tac_hi_count(ipmt)/occ_count(ipmt)
                   qhs_lo_stat = qhs_lo_count(ipmt)/occ_count(ipmt)
                   qhs_hi_stat = qhs_hi_count(ipmt)/occ_count(ipmt)
                   qhl_lo_stat = qhl_lo_count(ipmt)/occ_count(ipmt)
                   qhl_hi_stat = qhl_hi_count(ipmt)/occ_count(ipmt)
                   qlx_lo_stat = qlx_lo_count(ipmt)/occ_count(ipmt)
                   qlx_hi_stat = qlx_hi_count(ipmt)/occ_count(ipmt)
     
                   if (gr_occ(ipmt).ge.1.) then
                      gr_stat = gr_count(ipmt)/gr_occ(ipmt)
                   else
                      gr_stat = -9999.
                   endif
     
                   call hf1 (2000,tac_stat,1.0)
                   call hf1 (2001,qhs_stat,1.0)
                   call hf1 (2002,qhl_stat,1.0)
                   call hf1 (2003,qlx_stat,1.0)
     
                   call hf1 (2010,tac_lo_stat,1.0)
                   call hf1 (2011,qhs_lo_stat,1.0)
                   call hf1 (2012,qhl_lo_stat,1.0)
                   call hf1 (2013,qlx_lo_stat,1.0)
                   call hf1 (2020,tac_hi_stat,1.0)
                   call hf1 (2021,qhs_hi_stat,1.0)
                   call hf1 (2022,qhl_hi_stat,1.0)
                   call hf1 (2023,qlx_hi_stat,1.0)
                   call hf1 (2006,    gr_stat,1.0)
     
                   if (tac_stat .lt. tac_cut) then      ! Bad TAC
                       tag_flag(KANX_FLAG_TAC_ORIG) = KANX_FLAG_TAC_ORIG
                       tac_fail = tac_fail + 1
                   endif
                   if (tac_lo_stat .gt. tac_lo_cut) then
                       tag_flag(KANX_FLAG_TAC_LO) = KANX_FLAG_TAC_LO
                       tac_lo_fail = tac_lo_fail + 1
                   endif
                   if (tac_hi_stat .gt. tac_hi_cut) then
                       tag_flag(KANX_FLAG_TAC_HI) = KANX_FLAG_TAC_HI
                       tac_hi_fail = tac_hi_fail + 1
                   endif
     
                   if (qhs_stat .lt. qhs_cut) then      ! Bad QHS
                       tag_flag(KANX_FLAG_QHS_ORIG) = KANX_FLAG_QHS_ORIG
                       qhs_fail = qhs_fail + 1
                   endif
                   if (qhs_lo_stat .gt. qhs_lo_cut) then
                       tag_flag(KANX_FLAG_QHS_LO) = KANX_FLAG_QHS_LO
                       qhs_lo_fail = qhs_lo_fail + 1
                   endif
                   if (qhs_hi_stat .gt. qhs_hi_cut) then
                       tag_flag(KANX_FLAG_QHS_HI) = KANX_FLAG_QHS_HI
                       qhs_hi_fail = qhs_hi_fail + 1
                   endif
     
                   if (qhl_stat .lt. qhl_cut) then      ! Bad QHL
                       tag_flag(KANX_FLAG_QHL_ORIG) = KANX_FLAG_QHL_ORIG
                       qhl_fail = qhl_fail + 1
                   endif
                   if (qhl_lo_stat .gt. qhl_lo_cut) then
                       tag_flag(KANX_FLAG_QHL_LO) = KANX_FLAG_QHL_LO
                       qhl_lo_fail = qhl_lo_fail + 1
                   endif
                   if (qhl_hi_stat .gt. qhl_hi_cut) then
                       tag_flag(KANX_FLAG_QHL_HI) = KANX_FLAG_QHL_HI
                       qhl_hi_fail = qhl_hi_fail + 1
                   endif
     
                   if (qlx_stat .lt. qlx_cut) then      ! Bad QLX
                       tag_flag(KANX_FLAG_QLX_ORIG) = KANX_FLAG_QLX_ORIG
                       qlx_fail = qlx_fail + 1
                   endif
                   if (qlx_lo_stat .gt. qlx_lo_cut) then
                       tag_flag(KANX_FLAG_QLX_LO) = KANX_FLAG_QLX_LO
                       qlx_lo_fail = qlx_lo_fail + 1
                   endif
                   if (qlx_hi_stat .gt. qlx_hi_cut) then
                       tag_flag(KANX_FLAG_QLX_HI) = KANX_FLAG_QLX_HI
                       qlx_hi_fail = qlx_hi_fail + 1
                   endif
     
                   if (gr_stat .gt. gr_cut) then        ! Bad gain ratio
                      tag_flag(KANX_FLAG_GAIN_RATIO) = KANX_FLAG_GAIN_RATIO
                      gr_fail = gr_fail + 1
                   endif
                endif
     
    *           * .............. sync_clear_err, cell_id_err .............. *
     
                if ( (sync_clear_err(1,ipmt)+sync_clear_err(2,ipmt)+
         +          sync_clear_err(3,ipmt) ) .ge. sync_fail_cut ) then
                    sync_stat = 1.0
                else
                    sync_stat = 0.0
                endif
     
                if (sync_stat .ge. sync_fail_cut) then   ! Synclear error
                    tag_flag(KANX_FLAG_SYNC) = KANX_FLAG_SYNC
                    sync_fail = sync_fail + 1
                endif
     
                cell_stat = cell_err(ipmt)/
         +                 ( cell_err(ipmt) + cell_correct(ipmt) )
     
                if ( .not. cell_flag(ipmt) .and.         ! cell ID increment
         +            (cell_stat .gt. cell_cut) ) then
                     tag_flag(KANX_FLAG_CELL_ID) = KANX_FLAG_CELL_ID
                    cell_fail = cell_fail + 1
                endif
     
    *           * ............... excessive orphan hits .................. *
     
    *     Replace orphan stat calculation.
                orphan_stat = 0.
                do i=1,iperiod_orphan_max
                   hit_pmts = non_orphan_hit_count_period(ipmt,i) +
         +              orphan_hit_count_period(ipmt,i)
                   if (hit_pmts.gt.0)then
                      orph_array(i)= orphan_hit_count_period(ipmt,i)/
         +                 float(hit_pmts)
                   else
                      orph_array(i)=0.
                   endif
                enddo
                orphan_stat = median(iperiod_orphan_max,orph_array,width)
     
    *     orphan_stat = orphan_hit_count(ipmt)/tot_hits(ipmt)
                call hf1 (2005,orphan_stat,1.0)
     
                if (orphan_stat .gt. orphan_cut) then  ! Excessive Orphan hits
                    tag_flag(KANX_FLAG_ORPHAN) = KANX_FLAG_ORPHAN
                    orphan_fail = orphan_fail + 1
                endif
     
    *           * ...................... high occ ........................ *
     
                high_occ_stat = high_occ_count(ipmt)/event_high_occ_count
                call hf1 (2004,high_occ_stat,1.0)
     
               if ( high_occ_stat .gt. high_occ_cut ) then  ! High Occupancy
                       tag_flag(KANX_FLAG_HIGH_OCC) = KANX_FLAG_HIGH_OCC
                       high_occ_fail = high_occ_fail + 1
                endif
     
    *           * ...................... low occ ........................ *
     
                num_period = int(elapse_time/time_interval)
                if (num_period .le. 0) then
                    tag_flag(KANX_FLAG_LOW_OCC) = -9
                else
                   if (num_period .gt. nperiod) num_period = nperiod
                   num_low_occ = 0
                   do iperiod = 1, num_period+1
                      if (iperiod .le. num_period) then
                          low_occ_stat = low_occ_count(ipmt,iperiod)
                      else
                          low_occ_stat = occ_count(ipmt)/float(num_period)
                      endif
                      if (low_occ_stat .lt. low_occ_rate_cut(iperiod) )
         +                num_low_occ = num_low_occ + 1
                   end do
     
                   if (num_low_occ .ge. 1) then       ! Low Occupancy
                      tag_flag(KANX_FLAG_LOW_OCC) = KANX_FLAG_LOW_OCC
                      low_occ_fail = low_occ_fail + 1
                   endif
                endif
     
             else
                tag_flag(KANX_FLAG_ZERO_OCC) = KANX_FLAG_ZERO_OCC
                zero_occ_fail = zero_occ_fail + 1
             endif   ! end of if(occ_count(ipmt) = 0)
     
    *     * .... tag bad tube if any ................................. *
             tag_count = 0
             do itype = 0, ntag
                if (tag_flag(itype) .gt. -9) then
                   tag_count = tag_count + 1
                   tag(tag_count) = tag_flag(itype)
                endif
             end do
     
             if (tag_count .gt. 0) then ! write out flagged types
                tot_pmt_fail = tot_pmt_fail + 1
                write(lun_anx_txt,*)
         +           ipmt, tag_count, (tag(itype),itype=1,tag_count)
             endif
     
          end do     ! end of ipmt loop
     
          tmp_chan = -9999
          write(lun_anx_txt,9011) tmp_chan
     
     
    * ... summary for how many bad channels in ANXX banks ..............
    *     This is written to the log file.
     
          write(iqlog,*) 'ANX Terminating ..'
          write(iqlog,*) '          '
          write(iqlog,*) 'Statistical Summary: '
          write(iqlog,*) 'tac_fail = ', tac_fail
          write(iqlog,*) 'qhs_fail = ', qhs_fail
          write(iqlog,*) 'qhl_fail = ', qhl_fail
          write(iqlog,*) 'qlx_fail = ', qlx_fail
          write(iqlog,*) 'gr_fail  = ', gr_fail
          write(iqlog,*) '       '
          write(iqlog,*) 'tac_lo_fail = ', tac_lo_fail
          write(iqlog,*) 'tac_hi_fail = ', tac_hi_fail
          write(iqlog,*) 'qhs_lo_fail = ', qhs_lo_fail
          write(iqlog,*) 'qhs_hi_fail = ', qhs_hi_fail
          write(iqlog,*) 'qhl_lo_fail = ', qhl_lo_fail
          write(iqlog,*) 'qhl_hi_fail = ', qhl_hi_fail
          write(iqlog,*) 'qlx_lo_fail = ', qlx_lo_fail
          write(iqlog,*) 'qlx_hi_fail = ', qlx_hi_fail
          write(iqlog,*) '       '
          write(iqlog,*) 'sync_fail = ', sync_fail
          write(iqlog,*) 'cell_fail = ', cell_fail
          write(iqlog,*) 'orphan_fail = ', orphan_fail
          write(iqlog,*) 'high_occ_fail = ', high_occ_fail
          write(iqlog,*) 'low_occ_fail = ', low_occ_fail
          write(iqlog,*) 'zero_occ_fail = ', zero_occ_fail
          write(iqlog,*) '          '
          write(iqlog,*) 'Low Occ Criterion Cuts: '
          write(iqlog,*) 'low_occ_rate_cut = ',
         +               (low_occ_rate_cut(iperiod),iperiod=1,num_period+1)
          write(iqlog,*) '          '
          write(iqlog,*) 'Tube Failure Summary: '
          write(iqlog,*) 'tot_pmt_fail = ', tot_pmt_fail
          write(iqlog,*) 'num_period = ', num_period
     
          write(iqprnt,90007)
          write(iqlog,90007)
     
          call anxx_trm_ntp
     
    * ----------------------------------------------------------------------
     
          iretc = KSU_OK
     
    9001  format(i4,'      #. max number of bad channels')
     
    9004  format('#.  Format:    ')
    9005  format('#.  first  column : logical channel number     ')
    9006  format('#.  second column : number of flagged types    ')
    9009  format('#.  third to last columns : flagged types      ')
     
    9011  format(i5,'      #.  end of ANNX banks         ')
     
    90004 format('Neutrino run is too short for low occupancy check')
    90007 format('  Terminating ANX ...')
     
          return
          end
     
    *endfile member=anxx_tubes_trm