summaryrefslogtreecommitdiff
path: root/ghc/includes/RednCounts.lh
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/includes/RednCounts.lh')
-rw-r--r--ghc/includes/RednCounts.lh849
1 files changed, 849 insertions, 0 deletions
diff --git a/ghc/includes/RednCounts.lh b/ghc/includes/RednCounts.lh
new file mode 100644
index 0000000000..c2a1fef355
--- /dev/null
+++ b/ghc/includes/RednCounts.lh
@@ -0,0 +1,849 @@
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
+%
+%************************************************************************
+%* *
+\section[RednCounts.lh]{Interface (and macros) for reduction-count statistics}
+%* *
+%************************************************************************
+
+Multi-slurp protection:
+\begin{code}
+#ifndef REDNCOUNTS_H
+#define REDNCOUNTS_H
+\end{code}
+
+There are macros in here for:
+\begin{enumerate}
+\item
+``SPAT-profiling'' (\tr{DO_SPAT_PROFILING}), counting instructions
+per ``activity,'' using the SPAT instruction-trace analysis tools.
+\item
+``Ticky-ticky profiling'' (\tr{DO_REDN_COUNTING}), counting the
+number of various STG-events (updates, enters, etc.)
+
+This file goes with \tr{RednCounts.lc}, which initialises the counters
+and does the printing [ticky-ticky only].
+
+%************************************************************************
+%* *
+\subsection[SPAT-macros]{Macros for SPAT instruction counting}
+%* *
+%************************************************************************
+
+These definitions are for instruction tracing, e.g. using SPAT on the
+SPARC.
+
+\begin{code}
+#ifdef DO_SPAT_PROFILING
+
+#define ACT_BASE 0x000000ab /* random; to fit in 13 bits */
+
+#define ACT_UNKNOWN (0+ACT_BASE)
+#define ACT_GC (1+ACT_BASE)
+#define ACT_REDN (2+ACT_BASE)
+#define ACT_ASTK_STUB (3+ACT_BASE)
+#define ACT_FILL_IN_HEAP (4+ACT_BASE)
+#define ACT_HEAP_CHK (5+ACT_BASE)
+#define ACT_RETURN (6+ACT_BASE)
+#define ACT_UPDATE (7+ACT_BASE)
+#define ACT_PUSH_UPDF (8+ACT_BASE)
+#define ACT_ARGS_CHK (9+ACT_BASE)
+#define ACT_UPDATE_PAP (10+ACT_BASE)
+#define ACT_INDIRECT (11+ACT_BASE)
+#define ACT_PRIM (12+ACT_BASE)
+
+#define ACT_OVERHEAD (14+ACT_BASE) /* only used in analyser */
+#define ACT_TAILCALL (15+ACT_BASE)
+ /* Note: quite a lot gets lumped under TAILCALL; the analyser
+ untangles it with other info. WDP 95/01
+ */
+
+#define ACTIVITIES 16
+
+#define ACT_GC_STOP (ACTIVITIES+1)
+#define ACT_PRIM_STOP (ACTIVITIES+2)
+
+/* values that "signal" the start/stop of something,
+ thus suggesting to the analyser that it stop/start something.
+
+ I do not think they are used (WDP 95/01)
+*/
+
+#define ACT_SIGNAL_BASE 0xbababa00 /* pretty random; yes */
+
+#define ACT_START_GOING (1+ACT_SIGNAL_BASE)
+#define ACT_STOP_GOING (2+ACT_SIGNAL_BASE)
+#define ACT_START_GC (3+ACT_SIGNAL_BASE)
+#define ACT_STOP_GC (4+ACT_SIGNAL_BASE)
+
+#define SET_ACTIVITY(act) do { /* ActivityReg = (act) */ \
+ __asm__ volatile ("or %%g0,%1,%0" \
+ : "=r" (ActivityReg) \
+ : "I" (act)); \
+ } while(0)
+
+#define ALLOC_HEAP(n) /* nothing */
+#define UN_ALLOC_HEAP(n) /* nothing */
+#define DO_ASTK_HWM() /* nothing */
+#define DO_BSTK_HWM() /* nothing */
+
+#define A_STK_STUB(n) /* nothing */
+#define A_STK_REUSE(n) /* not used at all */
+#define B_STK_REUSE(n) /* ditto */
+
+#define ALLOC_FUN(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_THK(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_CON(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_TUP(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_BH(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+/*#define ALLOC_PAP(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)*/
+#define ALLOC_UPD_PAP(a,g,s,t) SET_ACTIVITY(ACT_UPDATE_PAP) /* NB */
+/*#define ALLOC_UPD_CON(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP) */
+#define ALLOC_PRIM(a,g,s,t) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_PRIM2(w) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_STK(a,g,s) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_TSO(a,g,s) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_FMBQ(a,g,s) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_FME(a,g,s) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+#define ALLOC_BF(a,g,s) SET_ACTIVITY(ACT_FILL_IN_HEAP)
+
+/* we only use the ENT_ macros to be sure activity is set to "reduction" */
+#define ENT_VIA_NODE() /* nothing */
+#define ENT_THK() SET_ACTIVITY(ACT_REDN)
+#define ENT_FUN_STD() SET_ACTIVITY(ACT_REDN)
+#define ENT_FUN_DIRECT(f,f_str,f_arity,Aargs,Bargs,arg_kinds,wrap,wrap_kinds) \
+ SET_ACTIVITY(ACT_REDN)
+#define ENT_CON(n) SET_ACTIVITY(ACT_REDN)
+#define ENT_IND(n) SET_ACTIVITY(ACT_REDN)
+#define ENT_PAP(n) SET_ACTIVITY(ACT_UPDATE_PAP) /* NB */
+
+#define RET_NEW_IN_HEAP() SET_ACTIVITY(ACT_RETURN)
+#define RET_NEW_IN_REGS() SET_ACTIVITY(ACT_RETURN)
+#define RET_OLD_IN_HEAP() SET_ACTIVITY(ACT_RETURN)
+#define RET_OLD_IN_REGS() SET_ACTIVITY(ACT_RETURN)
+#define RET_SEMI_BY_DEFAULT() SET_ACTIVITY(ACT_RETURN)
+#define RET_SEMI_IN_HEAP() SET_ACTIVITY(ACT_RETURN)
+#define RET_SEMI_IN_REGS() SET_ACTIVITY(ACT_RETURN)
+#define VEC_RETURN() /* nothing */
+
+#define UPDF_OMITTED() /* nothing (set directly by PUSH_STD_UPD_FRAME) */
+#define UPDF_STD_PUSHED() SET_ACTIVITY(ACT_PUSH_UPDF)
+#define UPDF_CON_PUSHED() /* nothing */
+#define UPDF_HOLE_PUSHED() /* nothing */
+#define UPDF_RCC_PUSHED() /* nothing */
+#define UPDF_RCC_OMITTED() /* nothing */
+
+#define UPD_EXISTING() /* nothing -- used in .lc code */
+#define UPD_CON_W_NODE() SET_ACTIVITY(ACT_UPDATE)
+#define UPD_CON_IN_PLACE() SET_ACTIVITY(ACT_UPDATE)
+#define UPD_PAP_IN_PLACE() /* nothing -- UpdatePAP has its own activity */
+#define UPD_CON_IN_NEW() SET_ACTIVITY(ACT_UPDATE)
+#define UPD_PAP_IN_NEW() /* nothing -- UpdatePAP has its own activity */
+\end{code}
+
+For special subsequent enter counting:
+\begin{code}
+#define UPDATED_SET_UPDATED(n) /* nothing */
+#define ENTERED_CHECK_UPDATED(n) /* nothing */
+\end{code}
+
+For a generational collector:
+\begin{code}
+#define UPD_NEW_IND() /* nothing (set elsewhere [?]) */
+#define UPD_NEW_IN_PLACE_PTRS() /* nothing */
+#define UPD_NEW_IN_PLACE_NOPTRS() /* nothing */
+#define UPD_OLD_IND() /* nothing */
+#define UPD_OLD_IN_PLACE_PTRS() /* nothing */
+#define UPD_OLD_IN_PLACE_NOPTRS() /* nothing */
+
+#endif /* DO_SPAT_PROFILING */
+\end{code}
+
+%************************************************************************
+%* *
+\subsection[ticky-ticky-macros]{Stuff for ``ticky-ticky'' profiling}
+%* *
+%************************************************************************
+
+\begin{code}
+#ifdef DO_REDN_COUNTING
+
+#define SET_ACTIVITY(act) /* quickly: make this do NOTHING */
+\end{code}
+
+Measure what proportion of ...:
+\begin{itemize}
+\item
+... Enters are to data values, function values, thunks.
+\item
+... allocations are for data values, functions values, thunks.
+\item
+... updates are for data values, function values.
+\item
+... updates ``fit''
+\item
+... return-in-heap (dynamic)
+\item
+... vectored return (dynamic)
+\item
+... updates are wasted (never re-entered).
+\item
+... constructor returns get away without hitting an update.
+\end{enumerate}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-stk-heap-use]{Stack and heap usage}
+%* *
+%************************************************************************
+
+Things we are interested in here:
+\begin{itemize}
+\item
+How many times we do a heap check and move @Hp@; comparing this with
+the allocations gives an indication of how many things we get per trip
+to the well:
+\begin{code}
+#define ALLOC_HEAP(n) ALLOC_HEAP_ctr++; ALLOC_HEAP_tot += (n)
+\end{code}
+
+If we do a ``heap lookahead,'' we haven't really allocated any
+heap, so we need to undo the effects of an \tr{ALLOC_HEAP}:
+\begin{code}
+#define UN_ALLOC_HEAP(n) ALLOC_HEAP_ctr--; ALLOC_HEAP_tot -= (n)
+\end{code}
+
+\item
+The stack high-water marks. This is {\em direction-sensitive}!!
+(A stack grows downward, B stack upwards)
+\begin{code}
+#ifndef CONCURRENT
+#define DO_ASTK_HWM() if (SpA < max_SpA) { max_SpA = SpA; }
+#define DO_BSTK_HWM() if (SpB > max_SpB) { max_SpB = SpB; }
+#else
+/*
+ * This is not direction sensitive, because we threads people are well-behaved.
+ * However, it might be a good idea to cache the constant bits (DEP + BOT and
+ * HWM) from the STKO and TSO in more readily accessible places. -- ToDo!
+ */
+#define DO_ASTK_HWM() { \
+ I_ depth = STKO_ADEP(StkOReg) + AREL((I_) STKO_ASTK_BOT(StkOReg) - (I_) SpA);\
+ if (depth > TSO_AHWM(CurrentTSO)) \
+ TSO_AHWM(CurrentTSO) = depth; \
+}
+#define DO_BSTK_HWM() { \
+ I_ depth = STKO_BDEP(StkOReg) + BREL((I_) STKO_BSTK_BOT(StkOReg) - (I_) SpB);\
+ if (depth > TSO_BHWM(CurrentTSO)) \
+ TSO_BHWM(CurrentTSO) = depth; \
+}
+#endif
+\end{code}
+
+\item
+Re-use of stack slots, and stubbing of stack slots:
+\begin{code}
+#define A_STK_STUB(n) A_STK_STUB_ctr += (n)
+#define A_STK_REUSE(n) A_STK_REUSE_ctr += (n) /* not used at all? */
+#define B_STK_REUSE(n) B_STK_REUSE_ctr += (n) /* not used at all? */
+\end{code}
+\end{itemize}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-allocs]{Allocations}
+%* *
+%************************************************************************
+
+We count things every time we allocate something in the dynamic heap.
+For each, we count the number of words of (1)~``admin'' (header),
+(2)~good stuff (useful pointers and data), and (3)~``slop'' (extra
+space, in hopes it will allow an in-place update).
+
+The first five macros are inserted when the compiler generates code
+to allocate something; the categories correspond to the @ClosureClass@
+datatype (manifest functions, thunks, constructors, big tuples, and
+partial applications).
+\begin{code}
+#define ALLOC_FUN(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_FUN_ctr++; ALLOC_FUN_adm += (a); \
+ ALLOC_FUN_gds += (g); ALLOC_FUN_slp += (s); \
+ ALLOC_HISTO(FUN,a,g,s)
+#define ALLOC_THK(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_THK_ctr++; ALLOC_THK_adm += (a); \
+ ALLOC_THK_gds += (g); ALLOC_THK_slp += (s); \
+ ALLOC_HISTO(THK,a,g,s)
+#define ALLOC_CON(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_CON_ctr++; ALLOC_CON_adm += (a); \
+ ALLOC_CON_gds += (g); ALLOC_CON_slp += (s); \
+ ALLOC_HISTO(CON,a,g,s)
+#define ALLOC_TUP(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_TUP_ctr++; ALLOC_TUP_adm += (a); \
+ ALLOC_TUP_gds += (g); ALLOC_TUP_slp += (s); \
+ ALLOC_HISTO(TUP,a,g,s)
+#define ALLOC_BH(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_BH_ctr++; ALLOC_BH_adm += (a); \
+ ALLOC_BH_gds += (g); ALLOC_BH_slp += (s); \
+ ALLOC_HISTO(BH,a,g,s)
+#if 0
+#define ALLOC_PAP(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_PAP_ctr++; ALLOC_PAP_adm += (a); \
+ ALLOC_PAP_gds += (g); ALLOC_PAP_slp += (s); \
+ ALLOC_HISTO(PAP,a,g,s)
+#endif
+\end{code}
+
+We may also allocate space when we do an update, and there isn't
+enough space. These macros suffice (for: updating with a partial
+application and a constructor):
+\begin{code}
+#define ALLOC_UPD_PAP(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_UPD_PAP_ctr++; ALLOC_UPD_PAP_adm += (a); \
+ ALLOC_UPD_PAP_gds += (g); ALLOC_UPD_PAP_slp += (s); \
+ ALLOC_HISTO(UPD_PAP,a,g,s)
+#if 0
+#define ALLOC_UPD_CON(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_UPD_CON_ctr++; ALLOC_UPD_CON_adm += (a); \
+ ALLOC_UPD_CON_gds += (g); ALLOC_UPD_CON_slp += (s); \
+ ALLOC_HISTO(UPD_CON,a,g,s)
+#endif /* 0 */
+\end{code}
+
+In the threaded world, we allocate space for the spark pool, stack objects,
+and thread state objects.
+
+\begin{code}
+
+#define ALLOC_STK(a,g,s) ALLOC_STK_ctr++; ALLOC_STK_adm += (a); \
+ ALLOC_STK_gds += (g); ALLOC_STK_slp += (s); \
+ ALLOC_HISTO(STK,a,g,s)
+
+#define ALLOC_TSO(a,g,s) ALLOC_TSO_ctr++; ALLOC_TSO_adm += (a); \
+ ALLOC_TSO_gds += (g); ALLOC_TSO_slp += (s); \
+ ALLOC_HISTO(TSO,a,g,s)
+
+#define ALLOC_FMBQ(a,g,s) ALLOC_FMBQ_ctr++; ALLOC_FMBQ_adm += (a); \
+ ALLOC_FMBQ_gds += (g); ALLOC_FMBQ_slp += (s); \
+ ALLOC_HISTO(FMBQ,a,g,s)
+
+#define ALLOC_FME(a,g,s) ALLOC_FME_ctr++; ALLOC_FME_adm += (a); \
+ ALLOC_FME_gds += (g); ALLOC_FME_slp += (s); \
+ ALLOC_HISTO(FME,a,g,s)
+
+#define ALLOC_BF(a,g,s) ALLOC_BF_ctr++; ALLOC_BF_adm += (a); \
+ ALLOC_BF_gds += (g); ALLOC_BF_slp += (s); \
+ ALLOC_HISTO(BF,a,g,s)
+
+\end{code}
+
+The histogrammy bit is fairly straightforward; the \tr{-2} is: one for
+0-origin C arrays; the other one because we do {\em no} one-word
+allocations, so we would never inc that histogram slot; so we shift
+everything over by one.
+\begin{code}
+#define ALLOC_HISTO(categ,a,g,s) \
+ { I_ __idx; \
+ __idx = (a) + (g) + (s) - 2; \
+ CAT3(ALLOC_,categ,_hst)[((__idx > 4) ? 4 : __idx)] += 1;}
+\end{code}
+
+Some hard-to-account-for words are allocated by/for primitives,
+includes Integer support. @ALLOC_PRIM2@ tells us about these. We
+count everything as ``goods'', which is not strictly correct.
+(@ALLOC_PRIM@ is the same sort of stuff, but we know the
+admin/goods/slop breakdown.)
+\begin{code}
+#define ALLOC_PRIM(a,g,s,t) ASSERT((t) == (a)+(g)+(s)); \
+ ALLOC_PRIM_ctr++; ALLOC_PRIM_adm += (a); \
+ ALLOC_PRIM_gds += (g); ALLOC_PRIM_slp += (s); \
+ ALLOC_HISTO(PRIM,a,g,s)
+#define ALLOC_PRIM2(w) ALLOC_PRIM_ctr++; ALLOC_PRIM_gds +=(w); \
+ ALLOC_HISTO(PRIM,0,w,0)
+\end{code}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-enters]{Enters}
+%* *
+%************************************************************************
+
+\begin{code}
+#define ENT_VIA_NODE() ENT_VIA_NODE_ctr++ /* via ENT_ macro */
+
+#define ENT_THK() ENT_THK_ctr++
+#define ENT_FUN_STD() ENT_FUN_STD_ctr++ /* manifest fun; std entry pt */
+
+#define ENT_CON(n) ENTERED_CHECK_UPDATED(n); ENT_CON_ctr++ /* enter code for constructor */
+#define ENT_IND(n) ENTERED_CHECK_UPDATED(n); ENT_IND_ctr++ /* enter indirection */
+#define ENT_PAP(n) ENTERED_CHECK_UPDATED(n); ENT_PAP_ctr++ /* enter partial application */
+\end{code}
+
+We do more magical things with @ENT_FUN_DIRECT@. Besides simply knowing
+how many ``fast-entry-point'' enters there were, we'd like {\em simple}
+information about where those enters were, and the properties thereof.
+\begin{code}
+struct ent_counter {
+ unsigned registeredp:16, /* 0 == no, 1 == yes */
+ arity:16, /* arity (static info) */
+ Astk_args:16, /* # of args off A stack */
+ Bstk_args:16; /* # of args off B stack */
+ /* (rest of args are in registers) */
+ StgChar *f_str; /* name of the thing */
+ StgChar *f_arg_kinds; /* info about the args types */
+ StgChar *wrap_str; /* name of its wrapper (if any) */
+ StgChar *wrap_arg_kinds;/* info about the orig wrapper's arg types */
+ I_ ctr; /* the actual counter */
+ struct ent_counter *link; /* link to chain them all together */
+};
+
+/* OLD: extern void RegisterEntryPt PROTO((struct ent_counter *)); */
+extern struct ent_counter *ListOfEntryCtrs;
+
+#define ENT_FUN_DIRECT(f_ct,f_str,f_arity,Aargs,Bargs,arg_kinds,wrap,wrap_kinds) \
+ static struct ent_counter f_ct \
+ = { 0, \
+ (f_arity), (Aargs), (Bargs), (f_str), (arg_kinds),\
+ (wrap), (wrap_kinds), \
+ 0, NULL }; \
+ if ( ! f_ct.registeredp ) { \
+ /* hook this one onto the front of the list */ \
+ f_ct.link = ListOfEntryCtrs; \
+ ListOfEntryCtrs = & (f_ct); \
+ \
+ /* mark it as "registered" */ \
+ f_ct.registeredp = 1; \
+ } \
+ f_ct.ctr += 1; \
+ ENT_FUN_DIRECT_ctr++ /* the old boring one */
+\end{code}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-returns]{Returns}
+%* *
+%************************************************************************
+
+Whenever a ``return'' occurs, it is returning the constituent parts of
+a data constructor. The parts can be returned either in registers, or
+by allocating some heap to put it in (the @ALLOC_*@ macros account for
+the allocation). The constructor can either be an existing one
+(\tr{*OLD*}) or we could have {\em just} figured out this stuff
+(\tr{*NEW*}).
+
+Here's some special magic that Simon wants [edited to match names
+actually used]:
+\begin{display}
+From: Simon L Peyton Jones <simonpj>
+To: partain, simonpj
+Subject: counting updates
+Date: Wed, 25 Mar 92 08:39:48 +0000
+
+I'd like to count how many times we update in place when actually Node
+points to the thing. Here's how:
+
+\tr{RET_OLD_IN_REGS} sets the variable \tr{ReturnInRegsNodeValid} to \tr{True};
+\tr{RET_NEW_IN_REGS} sets it to \tr{False}.
+
+\tr{RET_SEMI_???} sets it to??? ToDo [WDP]
+
+\tr{UPD_CON_IN_PLACE} tests the variable, and increments \tr{UPD_IN_PLACE_COPY_ctr}
+if it is true.
+
+Then we need to report it along with the update-in-place info.
+\end{display}
+
+\begin{code}
+#define RET_NEW_IN_HEAP() RET_NEW_IN_HEAP_ctr++
+#define RET_OLD_IN_HEAP() RET_OLD_IN_HEAP_ctr++
+
+#define RET_NEW_IN_REGS() RET_NEW_IN_REGS_ctr++; \
+ ReturnInRegsNodeValid = 0
+#define RET_OLD_IN_REGS() RET_OLD_IN_REGS_ctr++; \
+ ReturnInRegsNodeValid = 1
+
+#define RET_SEMI_BY_DEFAULT() RET_SEMI_BY_DEFAULT_ctr++
+#define RET_SEMI_IN_HEAP() RET_SEMI_IN_HEAP_ctr++
+#define RET_SEMI_IN_REGS() RET_SEMI_IN_REGS_ctr++
+\end{code}
+
+Of all the returns (sum of four categories above), how many were
+vectored? (The rest were obviously unvectored).
+\begin{code}
+#define VEC_RETURN() VEC_RETURN_ctr++
+\end{code}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-update-frames]{Update frames}
+%* *
+%************************************************************************
+
+These macros count up the following update information.
+
+%partain:\begin{center}
+\begin{tabular}{ll} \hline
+Macro & Counts \\ \hline
+ & \\
+\tr{UPDF_STD_PUSHED} & Update frame pushed \\
+\tr{UPDF_CON_PUSHED} & Constructor update frame pushed \\
+\tr{UPDF_HOLE_PUSHED} & An update frame to update a black hole \\
+\tr{UPDF_OMITTED} & A thunk decided not to push an update frame \\
+ & (all subsets of \tr{ENT_THK}) \\
+\tr{UPDF_RCC_PUSHED} & Cost Centre restore frame pushed \\
+\tr{UPDF_RCC_OMITTED} & Cost Centres not required -- not pushed \\\hline
+\end{tabular}
+%partain:\end{center}
+
+\begin{code}
+#define UPDF_OMITTED() UPDF_OMITTED_ctr++
+
+#define UPDF_STD_PUSHED() UPDF_STD_PUSHED_ctr++
+#define UPDF_CON_PUSHED() UPDF_CON_PUSHED_ctr++
+#define UPDF_HOLE_PUSHED() UPDF_HOLE_PUSHED_ctr++
+
+#define UPDF_RCC_PUSHED() UPDF_RCC_PUSHED_ctr++
+#define UPDF_RCC_OMITTED() UPDF_RCC_OMITTED_ctr++
+\end{code}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-updates]{Updates}
+%* *
+%************************************************************************
+
+These macros record information when we do an update. We always
+update either with a data constructor (CON) or a partial application
+(PAP).
+
+%partain:\begin{center}
+\begin{tabular}{|l|l|}\hline
+Macro & Where \\ \hline
+ & \\
+\tr{UPD_EXISTING} & Updating with an indirection to something \\
+ & already in the heap \\
+
+\tr{UPD_CON_W_NODE} & Updating with a CON: by indirecting to Node \\
+
+\tr{UPD_CON_IN_PLACE} & Ditto, but in place \\
+\tr{UPD_CON_IN_NEW} & Ditto, but allocating the object \\
+
+\tr{UPD_PAP_IN_PLACE} & Same, but updating w/ a PAP \\
+\tr{UPD_PAP_IN_NEW} & \\\hline
+\end{tabular}
+%partain:\end{center}
+
+\begin{code}
+#define UPD_EXISTING() UPD_EXISTING_ctr++
+
+#define UPD_CON_W_NODE() UPD_CON_W_NODE_ctr++
+
+#define UPD_CON_IN_NEW() UPD_CON_IN_NEW_ctr++
+#define UPD_PAP_IN_NEW() UPD_PAP_IN_NEW_ctr++
+/* ToDo: UPD_NEW_COPY_ctr, as below */
+
+#define UPD_CON_IN_PLACE() UPD_CON_IN_PLACE_ctr++ ; \
+ UPD_IN_PLACE_COPY_ctr += ReturnInRegsNodeValid
+ /* increments if True; otherwise, no */
+#define UPD_PAP_IN_PLACE() UPD_PAP_IN_PLACE_ctr++ ; \
+ UPD_IN_PLACE_COPY_ctr += ReturnInRegsNodeValid
+ /* increments if True; otherwise, no */
+\end{code}
+
+For a generational collector:
+\begin{code}
+#define UPD_NEW_IND() UPD_NEW_IND_ctr++;
+#define UPD_NEW_IN_PLACE_PTRS() UPD_NEW_IN_PLACE_PTRS_ctr++;
+#define UPD_NEW_IN_PLACE_NOPTRS() UPD_NEW_IN_PLACE_NOPTRS_ctr++;
+#define UPD_OLD_IND() UPD_OLD_IND_ctr++;
+#define UPD_OLD_IN_PLACE_PTRS() UPD_OLD_IN_PLACE_PTRS_ctr++;
+#define UPD_OLD_IN_PLACE_NOPTRS() UPD_OLD_IN_PLACE_NOPTRS_ctr++;
+\end{code}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-updates-entered]{Updates Subsequently Entered}
+%* *
+%************************************************************************
+
+If @UPDATES_ENTERED_COUNT@ is defined we add the Age word to the
+closures. This is used to record indicate if a closure has been
+updated but not yet entered. It is set when the closure is updated and
+cleared when subsequently entered.
+
+The commoning up of @CONST@, @CHARLIKE@ and @INTLIKE@ closures is
+turned if this is required. This has only been done for 2s collection.
+It is done using a nasty hack which defines the @_Evacuate@ and
+@_Scavenge@ code for @CONST@, @CHARLIKE@ and @INTLIKE@ info tables to
+be @_Evacuate_1@ and @_Scavenge_1_0@.
+
+Unfortunately this broke everything so it has not been done ;-(.
+Instead we have to run with enough heap so no garbage collection is
+needed for accurate numbers. ToDo: Fix this!
+
+As implemented it can not be used in conjunction with heap profiling
+or lifetime profiling becasue they make conflicting use the Age word!
+
+\begin{code}
+#if defined(UPDATES_ENTERED_COUNT)
+
+#define UPDATED_SET_UPDATED(n) AGE_HDR(n) = 1
+
+#define ENTERED_CHECK_UPDATED(n) \
+ if (AGE_HDR(n)) { \
+ if (AGE_HDR(n) == 1) { \
+ UPD_ENTERED_ctr++; \
+ AGE_HDR(n) += 1; \
+ } else { \
+ UPD_ENTERED_AGAIN_ctr++; \
+ AGE_HDR(n) = 0; \
+ }}
+
+#else /* ! UPDATES_ENTERED_COUNT */
+
+#define UPDATED_SET_UPDATED(n) /* nothing */
+#define ENTERED_CHECK_UPDATED(n) /* nothing */
+
+#endif /* ! UPDATES_ENTERED_COUNT */
+\end{code}
+
+%************************************************************************
+%* *
+\subsubsection[ticky-counters]{The accumulators (extern decls)}
+%* *
+%************************************************************************
+
+\begin{code}
+extern I_ ALLOC_HEAP_ctr;
+extern I_ ALLOC_HEAP_tot;
+
+extern PP_ max_SpA;
+extern P_ max_SpB;
+
+extern I_ A_STK_STUB_ctr;
+/* not used at all?
+extern I_ A_STK_REUSE_ctr;
+extern I_ B_STK_REUSE_ctr;
+*/
+
+extern I_ ALLOC_FUN_ctr;
+extern I_ ALLOC_FUN_adm;
+extern I_ ALLOC_FUN_gds;
+extern I_ ALLOC_FUN_slp;
+extern I_ ALLOC_FUN_hst[5];
+extern I_ ALLOC_THK_ctr;
+extern I_ ALLOC_THK_adm;
+extern I_ ALLOC_THK_gds;
+extern I_ ALLOC_THK_slp;
+extern I_ ALLOC_THK_hst[5];
+extern I_ ALLOC_CON_ctr;
+extern I_ ALLOC_CON_adm;
+extern I_ ALLOC_CON_gds;
+extern I_ ALLOC_CON_slp;
+extern I_ ALLOC_CON_hst[5];
+extern I_ ALLOC_TUP_ctr;
+extern I_ ALLOC_TUP_adm;
+extern I_ ALLOC_TUP_gds;
+extern I_ ALLOC_TUP_slp;
+extern I_ ALLOC_TUP_hst[5];
+extern I_ ALLOC_BH_ctr;
+extern I_ ALLOC_BH_adm;
+extern I_ ALLOC_BH_gds;
+extern I_ ALLOC_BH_slp;
+extern I_ ALLOC_BH_hst[5];
+/*
+extern I_ ALLOC_PAP_ctr;
+extern I_ ALLOC_PAP_adm;
+extern I_ ALLOC_PAP_gds;
+extern I_ ALLOC_PAP_slp;
+extern I_ ALLOC_PAP_hst[5];
+*/
+/*
+extern I_ ALLOC_UPD_CON_ctr;
+extern I_ ALLOC_UPD_CON_adm;
+extern I_ ALLOC_UPD_CON_gds;
+extern I_ ALLOC_UPD_CON_slp;
+extern I_ ALLOC_UPD_CON_hst[5];
+*/
+extern I_ ALLOC_UPD_PAP_ctr;
+extern I_ ALLOC_UPD_PAP_adm;
+extern I_ ALLOC_UPD_PAP_gds;
+extern I_ ALLOC_UPD_PAP_slp;
+extern I_ ALLOC_UPD_PAP_hst[5];
+extern I_ ALLOC_PRIM_ctr;
+extern I_ ALLOC_PRIM_adm;
+extern I_ ALLOC_PRIM_gds;
+extern I_ ALLOC_PRIM_slp;
+extern I_ ALLOC_PRIM_hst[5];
+
+#ifdef CONCURRENT
+extern I_ ALLOC_STK_ctr;
+extern I_ ALLOC_STK_adm;
+extern I_ ALLOC_STK_gds;
+extern I_ ALLOC_STK_slp;
+extern I_ ALLOC_STK_hst[5];
+extern I_ ALLOC_TSO_ctr;
+extern I_ ALLOC_TSO_adm;
+extern I_ ALLOC_TSO_gds;
+extern I_ ALLOC_TSO_slp;
+extern I_ ALLOC_TSO_hst[5];
+#ifdef PAR
+extern I_ ALLOC_FMBQ_ctr;
+extern I_ ALLOC_FMBQ_adm;
+extern I_ ALLOC_FMBQ_gds;
+extern I_ ALLOC_FMBQ_slp;
+extern I_ ALLOC_FMBQ_hst[5];
+extern I_ ALLOC_FME_ctr;
+extern I_ ALLOC_FME_adm;
+extern I_ ALLOC_FME_gds;
+extern I_ ALLOC_FME_slp;
+extern I_ ALLOC_FME_hst[5];
+extern I_ ALLOC_BF_ctr;
+extern I_ ALLOC_BF_adm;
+extern I_ ALLOC_BF_gds;
+extern I_ ALLOC_BF_slp;
+extern I_ ALLOC_BF_hst[5];
+#endif
+#endif
+
+extern I_ ENT_VIA_NODE_ctr;
+
+extern I_ ENT_CON_ctr;
+extern I_ ENT_FUN_STD_ctr;
+extern I_ ENT_FUN_DIRECT_ctr;
+extern I_ ENT_IND_ctr;
+extern I_ ENT_PAP_ctr;
+extern I_ ENT_THK_ctr;
+
+extern I_ UPD_ENTERED_ctr;
+extern I_ UPD_ENTERED_AGAIN_ctr;
+
+extern I_ RET_NEW_IN_HEAP_ctr;
+extern I_ RET_NEW_IN_REGS_ctr;
+extern I_ RET_OLD_IN_HEAP_ctr;
+extern I_ RET_OLD_IN_REGS_ctr;
+extern I_ RET_SEMI_BY_DEFAULT_ctr;
+extern I_ RET_SEMI_IN_HEAP_ctr;
+extern I_ RET_SEMI_IN_REGS_ctr;
+extern I_ VEC_RETURN_ctr;
+
+extern I_ ReturnInRegsNodeValid; /* see below */
+
+extern I_ UPDF_OMITTED_ctr;
+extern I_ UPDF_STD_PUSHED_ctr;
+extern I_ UPDF_CON_PUSHED_ctr;
+extern I_ UPDF_HOLE_PUSHED_ctr;
+
+extern I_ UPDF_RCC_PUSHED_ctr;
+extern I_ UPDF_RCC_OMITTED_ctr;
+
+extern I_ UPD_EXISTING_ctr;
+extern I_ UPD_CON_W_NODE_ctr;
+extern I_ UPD_CON_IN_PLACE_ctr;
+extern I_ UPD_PAP_IN_PLACE_ctr;
+extern I_ UPD_CON_IN_NEW_ctr;
+extern I_ UPD_PAP_IN_NEW_ctr;
+
+extern I_ UPD_NEW_IND_ctr;
+extern I_ UPD_NEW_IN_PLACE_PTRS_ctr;
+extern I_ UPD_NEW_IN_PLACE_NOPTRS_ctr;
+extern I_ UPD_OLD_IND_ctr;
+extern I_ UPD_OLD_IN_PLACE_PTRS_ctr;
+extern I_ UPD_OLD_IN_PLACE_NOPTRS_ctr;
+
+extern I_ UPD_IN_PLACE_COPY_ctr; /* see below */
+
+#endif /* DO_REDN_COUNTING */
+\end{code}
+
+%************************************************************************
+%* *
+\subsection[RednCounts-nonmacros]{Un-macros for ``none of the above''}
+%* *
+%************************************************************************
+
+\begin{code}
+#if ! (defined(DO_SPAT_PROFILING) || defined(DO_REDN_COUNTING))
+
+#define SET_ACTIVITY(act) /* nothing */
+
+#define ALLOC_HEAP(n) /* nothing */
+#define UN_ALLOC_HEAP(n) /* nothing */
+#define DO_ASTK_HWM() /* nothing */
+#define DO_BSTK_HWM() /* nothing */
+
+#define A_STK_STUB(n) /* nothing */
+#define A_STK_REUSE(n) /* not used at all */
+#define B_STK_REUSE(n) /* not used at all */
+
+#define ALLOC_FUN(a,g,s,t) /* nothing */
+#define ALLOC_THK(a,g,s,t) /* nothing */
+#define ALLOC_CON(a,g,s,t) /* nothing */
+#define ALLOC_TUP(a,g,s,t) /* nothing */
+#define ALLOC_BH(a,g,s,t) /* nothing */
+/*#define ALLOC_PAP(a,g,s,t) /? nothing */
+#define ALLOC_PRIM(a,g,s,t) /* nothing */
+#define ALLOC_PRIM2(w) /* nothing */
+#define ALLOC_UPD_PAP(a,g,s,t) /* nothing */
+/*#define ALLOC_UPD_CON(a,g,s,t) /? nothing */
+#define ALLOC_STK(a,g,s) /* nothing */
+#define ALLOC_TSO(a,g,s) /* nothing */
+#define ALLOC_FMBQ(a,g,s) /* nothing */
+#define ALLOC_FME(a,g,s) /* nothing */
+#define ALLOC_BF(a,g,s) /* nothing */
+
+#define ENT_VIA_NODE() /* nothing */
+#define ENT_THK() /* nothing */
+#define ENT_FUN_STD() /* nothing */
+#define ENT_FUN_DIRECT(f,f_str,f_arity,Aargs,Bargs,arg_kinds,wrap,wrap_kinds) \
+ /* nothing */
+#define ENT_CON(n) /* nothing */
+#define ENT_IND(n) /* nothing */
+#define ENT_PAP(n) /* nothing */
+
+#define RET_NEW_IN_HEAP() /* nothing */
+#define RET_NEW_IN_REGS() /* nothing */
+#define RET_OLD_IN_HEAP() /* nothing */
+#define RET_OLD_IN_REGS() /* nothing */
+#define RET_SEMI_BY_DEFAULT() /* nothing */
+#define RET_SEMI_IN_HEAP() /* nothing */
+#define RET_SEMI_IN_REGS() /* nothing */
+#define VEC_RETURN() /* nothing */
+
+#define UPDF_OMITTED() /* nothing */
+#define UPDF_STD_PUSHED() /* nothing */
+#define UPDF_CON_PUSHED() /* nothing */
+#define UPDF_HOLE_PUSHED() /* nothing */
+
+#define UPDF_RCC_PUSHED() /* nothing */
+#define UPDF_RCC_OMITTED() /* nothing */
+
+#define UPD_EXISTING() /* nothing */
+#define UPD_CON_W_NODE() /* nothing */
+#define UPD_CON_IN_PLACE() /* nothing */
+#define UPD_PAP_IN_PLACE() /* nothing */
+#define UPD_CON_IN_NEW() /* nothing */
+#define UPD_PAP_IN_NEW() /* nothing */
+\end{code}
+
+For special subsequent enter counting:
+\begin{code}
+#define UPDATED_SET_UPDATED(n) /* nothing */
+#define ENTERED_CHECK_UPDATED(n) /* nothing */
+\end{code}
+
+For a generational collector:
+\begin{code}
+#define UPD_NEW_IND() /* nothing */
+#define UPD_NEW_IN_PLACE_PTRS() /* nothing */
+#define UPD_NEW_IN_PLACE_NOPTRS() /* nothing */
+#define UPD_OLD_IND() /* nothing */
+#define UPD_OLD_IN_PLACE_PTRS() /* nothing */
+#define UPD_OLD_IN_PLACE_NOPTRS() /* nothing */
+
+#endif /* <none-of-the-above> */
+\end{code}
+
+End of file multi-slurp protection:
+\begin{code}
+#endif /* ! REDNCOUNTS_H */
+\end{code}