*file member=anxx_tubes_exe library=snoman language=fortran77 date=08:Nov:2004 <<< subroutine anxx_tubes_exe(ipro_mode,iretc) * ANX: ANXX Banks Processor. Determine bad channels. * Contact: M. Huang, Texas. * Parameters:- * ========== * ipro_mode in Process mode e.g. KSU_INSERT (see su_mnemonics.inc). * iretc out return code (see su_mnemonics.inc):- * KSU_NOOP No need to process event. * KSU_OK Processing O.K. * Common Block Access:- * =================== * (ignoring internal and environmental access) * /ANXX_COUNT_COM/ in *. * out *. * /MT/ in Banks: ANCT. * Specification:- * ============= * Determine bad channels beyond those bad channels from DQXX banks * and from eca & pca calibration. * Revision History:- * ================ * 5.01 M. Huang First version. * N. McCauley Fix some bugs. * C. Kyba Add QHS/QLX gain test. * N. McCauley Update orphan check. implicit none include 'bank_ev.inc' include 'bank_mast.inc' include 'bank_pmt.inc' include 'bank_zdab_pmt.inc' include 'su_mnemonics.inc' include 'mt.inc' include 'trigger_mask_bits.inc' include 'anxx_count_com.inc' include 'anxx_cut_com.inc' include 'zunit.inc' include 'z.inc' * Argument Declarations:- * ===================== integer ipro_mode, iretc *endheader * Local Variable Declarations:- * =========================== logical good_n16, good_pca, good_neutrino, good_event, + iflag, pulse_gt, first_event, warned integer map_ccc_lcn, ccc, lcn, ncell, lpbun, pbun_gtid, + trig_word, gtid, nhit integer lfecd, chan, crate, card double precision universal_date_compare, nsec_sec parameter (nsec_sec = 1.0d+9) integer start_time(3), event_time(3), iperiod real tac, qlx, qhl, qhs integer sync_compare(3), flag_err, itype, jbyt external universal_date_compare, jbyt data sync_compare / 4, 5, 9/ data first_event /.true./ data warned /.false./ save * ------------------------------------------------------------------------ * ... To invent a use for the MODE parameter, reject append mode. if ( ipro_mode .eq. KSU_APPEND ) then write(iqlog,*) ' ANX does not support append mode.' iretc = KSU_UNSUPPORTED return endif * ... Quit if processing a permanent data structure ... if (lmast .ne. 0 .and. btest( iq(lmast), KMAST_PERM ) ) then iretc = KSU_NOOP return endif * ------------------------------------------------------------------------ * ... Now get down to work ... lev = lq(lmast - KMAST_EV) if (lev .eq. 0 ) return gtid = iq(lev+KEV_gtr_id) trig_word = iq(lev+KEV_TRG_TYPE) * Our first test is for pedestals. We do not use these events in ANxx. if (btest(trig_word,KTRIG_MB_PEDESTAL)) return pulse_gt = btest(trig_word,KTRIG_MB_PULSE_GT) nhit = iq(lev+kev_npm) call hf1 (1104,real(nhit),1.0) * * ........ check if good event for analysis ............ * good_pca = .false. good_n16 = .false. good_neutrino = .false. if (data_type .eq. 1) then ! check if good PCA event if ( ( btest(trig_word,KTRIG_MB_EXT_ASYNC) ) ) + good_pca = .true. else if (data_type .eq. 2) then ! check if good n16 event lfecd = lq(lev-kev_fecd) if (lfecd .ne. 0) then ccc = iq(lfecd+kpmt_pn) chan = jbyt(ccc, 1, 5) crate = jbyt(ccc, 6, 5) card = jbyt(ccc, 11, 4) if((crate.eq.17).and.(card.eq.15).and.(chan.eq.4)) + good_n16 = .true. if((crate.eq.17).and.(card.eq.15).and.(chan.eq.6)) + good_n16 = .true. endif else if (data_type .eq. 3) then ! check if good neutrino event if ( (btest(trig_word,KTRIG_MB_NHIT100MED) .or. + btest(trig_word,KTRIG_MB_NHIT100HI) .or. + btest(trig_word,KTRIG_MB_NHIT20) ) + .and. (nhit.ge.15 .and. nhit.le.150) ) + good_neutrino = .true. endif good_event = good_pca .or. good_n16 .or. good_neutrino * * .......... begin to loop through all events ............ * if (lev.ne.0) then * *first count the total number of hits for each tube in all events* lpmt = lq(lev - kev_pmt) do while (lpmt.ne.0) ccc = IQ(LPMT + KPMT_PIN) lcn = map_ccc_lcn(ccc) tot_hits(lcn) = tot_hits(lcn) + 1.0 lpmt = lq(lpmt) enddo lpmt = lq(lev - kev_pmt) if ( .not. btest(iq(lev),KEV_ORPHAN) ) then if (pulse_gt) ! accumulate events for high occ calc + event_high_occ_count = event_high_occ_count + 1.0 * * ... get elapse_time & period (iperiod) for low occ calc ... * if (first_event .and. good_event) then start_time(1) = iq(lev+KEV_JDY) start_time(2) = iq(lev+KEV_UT1) start_time(3) = iq(lev+KEV_UT2) first_event = .false. endif if (good_event) then event_low_occ_count = event_low_occ_count + 1.0 event_time(1) = iq(lev+KEV_JDY) event_time(2) = iq(lev+KEV_UT1) event_time(3) = iq(lev+KEV_UT2) elapse_time = + universal_date_compare(event_time,start_time)/nsec_sec iperiod = int(elapse_time/time_interval) + 1 if (iperiod .gt. nperiod ) then iperiod = -1 if (.not. warned)then write(iqlog,90000) write(iqprnt,90000) endif endif iperiod_orphan = int(elapse_time/(time_interval/3.)) + 1 if(iperiod_orphan .gt. iperiod_orphan_max) + iperiod_orphan_max = iperiod_orphan endif * * ..... loop through all pmt hits for the event ....... * do while (lpmt.ne.0) ccc = IQ(LPMT + KPMT_PIN) lcn = map_ccc_lcn(ccc) * Increment orphan hit counter (normalization). if (iperiod_orphan .gt. 0) + non_orphan_hit_count_period(lcn,iperiod_orphan) = + non_orphan_hit_count_period(lcn,iperiod_orphan) +1 TAC = RQ(LPMT + KPMT_PT) QHS = RQ(LPMT + KPMT_EHS) QHL = RQ(LPMT + KPMT_EHL) QLX = RQ(LPMT + KPMT_ELX) NCELL = IQ(LPMT + KPMT_CELL) if (good_event) then call hf1 (6100,tac,1.0) call hf1 (6101,qhs,1.0) call hf1 (6102,qhl,1.0) call hf1 (6103,qlx,1.0) occ_count(lcn) = occ_count(lcn) + 1.0 if (tac.gt.tac_lo .and. tac.lt.tac_up) + tac_count(lcn) = tac_count(lcn) + 1.0 if (qhs.gt.qhs_lo .and. qhs.lt.qhs_up) + qhs_count(lcn) = qhs_count(lcn) + 1.0 if (qhl.gt.qhl_lo .and. qhl.lt.qhl_up) + qhl_count(lcn) = qhl_count(lcn) + 1.0 if (qlx.gt.qlx_lo .and. qlx.lt.qlx_up) + qlx_count(lcn) = qlx_count(lcn) + 1.0 if (tac.lt.tac_lo) + tac_lo_count(lcn) = tac_lo_count(lcn) + 1.0 if (tac.gt.tac_up) + tac_hi_count(lcn) = tac_hi_count(lcn) + 1.0 if (qhs.lt.qhs_lo) + qhs_lo_count(lcn) = qhs_lo_count(lcn) + 1.0 if (qhs.gt.qhs_up) + qhs_hi_count(lcn) = qhs_hi_count(lcn) + 1.0 if (qhl.lt.qhl_lo) + qhl_lo_count(lcn) = qhl_lo_count(lcn) + 1.0 if (qhl.gt.qhl_up) + qhl_hi_count(lcn) = qhl_hi_count(lcn) + 1.0 if (qlx.lt.qlx_lo) + qlx_lo_count(lcn) = qlx_lo_count(lcn) + 1.0 if (qlx.gt.qlx_up) + qlx_hi_count(lcn) = qlx_hi_count(lcn) + 1.0 if ((qhs.gt.400.) + .and.(qlx.gt.0.) + .and.(RQ(LPMT+KPMT_PIHS).lt.4095.)) then gr_occ(lcn) = gr_occ(lcn) + 1.0 if (abs(((qhs/11.7)-qlx)/qlx).gt.0.6) + gr_count(lcn) = gr_count(lcn) + 1.0 endif * * .. count low_occ hits for each fired tube during the period ..* if (iperiod .gt. 0) low_occ_count(lcn,iperiod) + = low_occ_count(lcn,iperiod)+1.0 endif * * ... count high_occ hits for each fired tube .......... * if (pulse_gt) + high_occ_count(lcn) = high_occ_count(lcn) + 1.0 * * ..... check synclear error ........................... * flag_err = iq(lpmt + KPMT_PIF) if ( gtid .gt. 65536) then do itype = 1, 3 if (btest(flag_err, sync_compare(itype))) then sync_clear_err(itype,lcn) = + sync_clear_err(itype,lcn) + 1.0 end if enddo endif * * ..... check cell id increment ........................ * call anxx_cell_check(lcn,ncell,iflag) if (iflag) then cell_correct(lcn) = cell_correct(lcn) + 1.0 cell_flag(lcn) = .true. else cell_err(lcn) = cell_err(lcn) + 1.0 cell_flag(lcn) = .false. endif lpmt = lq(lpmt) enddo ! end of do while(lpmt) else if ( btest(iq(lev),KEV_ORPHAN) ) then * * .......... check orphan_hit ...................... * lzdab = lq(lev-KEV_ZDAB) lpbun = lq(lzdab-KZDAB_PBUN) do while (lpbun .ne. 0) pbun_gtid = iq(lpbun+KPMT_PN) if ( mod(pbun_gtid,256) .ne. 0) then ccc = iq(lpbun + kpmt_pin) lcn = map_ccc_lcn(ccc) orphan_hit_count(lcn) = + orphan_hit_count(lcn) + 1.0 * Increment orphan rate hit counter. if (iperiod_orphan .gt. 0) + orphan_hit_count_period(lcn,iperiod_orphan) = + orphan_hit_count_period(lcn,iperiod_orphan) +1 endif lpbun = lq(lpbun) end do * * .......... check cell id increment ............. * do while (lpmt.ne.0) ccc = IQ(LPMT + KPMT_PIN) lcn = map_ccc_lcn(ccc) NCELL = IQ(LPMT + KPMT_CELL) call anxx_cell_check(lcn,ncell,iflag) if (iflag) then cell_correct(lcn)=cell_correct(lcn)+1.0 cell_flag(lcn) = .true. else cell_err(lcn) = cell_err(lcn) + 1.0 cell_flag(lcn) = .false. endif lpmt = lq(lpmt) enddo ! end of do while(lpmt) endif ! end of if (KEV_ORPHAN) else call ztell(900,1) endif ! end of if (lev.ne.0) * ========================================================================== 911 continue iretc = KSU_OK return 90000 format('ANxx: Run duration longer than expected given size of ', + 'time window.',/, + 'Additional events will not contributre to rate check') end *endfile member=anxx_tubes_exe