Hannes Siebenhandl pushed to branch wip/fendor/ccs-index-table at Glasgow Haskell Compiler / GHC
Commits:
b328b307 by fendor at 2025-08-05T09:03:05+02:00
HashTable in IndexTable
- - - - -
15 changed files:
- libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc
- rts/Hash.c
- rts/Hash.h
- + rts/IndexTable.c
- rts/ProfilerReport.c
- rts/ProfilerReportJson.c
- rts/Profiling.c
- rts/Profiling.h
- rts/include/Rts.h
- rts/include/rts/prof/CCS.h
- + rts/include/rts/prof/IndexTable.h
- rts/rts.cabal
- testsuite/tests/perf/should_run/T26147.stdout
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/perf/should_run/genT26147
Changes:
=====================================
libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc
=====================================
@@ -138,21 +138,21 @@ peekCostCentre costCenterCacheRef ptr = do
peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable)
peekIndexTable _ _ ptr | ptr == nullPtr = return Nothing
-peekIndexTable loopBreakers costCenterCacheRef ptr = do
- it_cc_ptr <- (#peek struct IndexTable_, cc) ptr
- it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr
- it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr
- it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr
- it_next_ptr <- (#peek struct IndexTable_, next) ptr
- it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr
- it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr
-
- return $ Just IndexTable {
- it_cc = it_cc',
- it_ccs = it_ccs',
- it_next = it_next',
- it_back_edge = it_back_edge'
- }
+peekIndexTable _ _ _ = pure Nothing
+ -- it_cc_ptr <- (#peek struct IndexTable_, cc) ptr
+ -- it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr
+ -- it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr
+ -- it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr
+ -- it_next_ptr <- (#peek struct IndexTable_, next) ptr
+ -- it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr
+ -- it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr
+
+ -- return $ Just IndexTable {
+ -- it_cc = it_cc',
+ -- it_ccs = it_ccs',
+ -- it_next = it_next',
+ -- it_back_edge = it_back_edge'
+ -- }
-- | casts a @Ptr@ to an @Int@
ptrToInt :: Ptr a -> Int
=====================================
rts/Hash.c
=====================================
@@ -515,6 +515,52 @@ mapHashTableKeys(HashTable *table, void *data, MapHashFnKeys fn)
}
}
+void initHashIterator(HashTable *table, struct HashIterator_* iter) {
+ /* The last bucket with something in it is table->max + table->split - 1 */
+ long segment = (table->max + table->split - 1) / HSEGSIZE;
+ long index = (table->max + table->split - 1) % HSEGSIZE;
+ iter->table = table;
+ iter->segment = segment;
+ iter->index = index;
+ iter->data = NULL;
+}
+
+struct HashIterator_* hashTableIterator(HashTable *table) {
+ struct HashIterator_* iter;
+ iter = stgMallocBytes(sizeof(HashIterator),"hashTableIterator");
+ initHashIterator(table, iter);
+ return iter;
+}
+
+const void *hashIteratorItem(struct HashIterator_* iter) {
+ return iter->data;
+}
+
+int hashIteratorNext(struct HashIterator_* iter) {
+ long segment = iter->segment;
+ long index = iter->index;
+
+ while (segment >= 0) {
+ while (index >= 0) {
+ for (HashList *hl = iter->table->dir[segment][index]; hl != NULL; hl = hl->next) {
+ iter->segment = segment;
+ /* make sure we advance the index */
+ iter->index = index - 1;
+ iter->data = hl->data;
+ return 1;
+ }
+ index--;
+ }
+ segment--;
+ index = HSEGSIZE - 1;
+ }
+ return 0;
+}
+
+void freeHashIterator(struct HashIterator_* iter) {
+ stgFree(iter);
+}
+
void
iterHashTable(HashTable *table, void *data, IterHashFn fn)
{
@@ -536,6 +582,7 @@ iterHashTable(HashTable *table, void *data, IterHashFn fn)
}
}
+
/* -----------------------------------------------------------------------------
* When we initialize a hash table, we set up the first segment as well,
* initializing all of the first segment's hash buckets to NULL.
=====================================
rts/Hash.h
=====================================
@@ -42,6 +42,21 @@ void mapHashTable(HashTable *table, void *data, MapHashFn fn);
void mapHashTableKeys(HashTable *table, void *data, MapHashFnKeys fn);
void iterHashTable(HashTable *table, void *data, IterHashFn);
+struct HashIterator_ {
+ HashTable *table;
+ long segment;
+ long index;
+ const void* data;
+};
+typedef struct HashIterator_ HashIterator;
+
+void initHashIterator(HashTable *, struct HashIterator_*);
+struct HashIterator_* hashTableIterator(HashTable *table);
+const void *hashIteratorItem(struct HashIterator_* iter);
+int hashIteratorNext(struct HashIterator_* iter);
+void freeHashIterator(struct HashIterator_* iter);
+
+
/* Hash table access where the keys are C strings (the strings are
* assumed to be allocated by the caller, and mustn't be deallocated
* until the corresponding hash table entry has been removed).
=====================================
rts/IndexTable.c
=====================================
@@ -0,0 +1,116 @@
+#if defined(PROFILING)
+
+#include "Rts.h"
+#include "rts/prof/IndexTable.h"
+#include "RtsFlags.h"
+#include "RtsUtils.h"
+#include "rts/PosixSource.h"
+#include "rts/prof/CCS.h"
+#include "Hash.h"
+#include "assert.h"
+
+#include "Profiling.h"
+#include "Arena.h"
+
+#include
+#include
+
+#if defined(DEBUG) || defined(PROFILING)
+#include "Trace.h"
+#endif
+
+
+typedef struct IndexTable_ IndexTable;
+
+void
+freeIndexTable(IndexTable * it) {
+ assert(it != EMPTY_TABLE);
+ if (it != EMPTY_TABLE && it->children != NULL) {
+ freeHashTable(it->children, NULL);
+ it->children = NULL;
+ }
+}
+
+CostCentreStack *
+isInIndexTable(IndexTable *it, CostCentre *cc) {
+ if (EMPTY_TABLE == it) {
+ return EMPTY_TABLE;
+ }
+ if (NULL == it->children) {
+ return EMPTY_TABLE;
+ }
+
+ IndexTableNode * node;
+ node = (IndexTableNode *) lookupHashTable(it->children, (StgWord) cc->ccID);
+ if (node == NULL) {
+ /* Not found */
+ return EMPTY_TABLE;
+ }
+ return node->ccs;
+}
+
+
+IndexTable *
+addToIndexTable(IndexTable *it, CostCentreStack *new_ccs,
+ CostCentre *cc, bool back_edge) {
+ if (it == EMPTY_TABLE) {
+ it = arenaAlloc(prof_arena, sizeof(IndexTable));
+ it->children = NULL;
+ }
+ assert(it != EMPTY_TABLE);
+
+ IndexTableNode *node;
+ node = arenaAlloc(prof_arena, sizeof(IndexTableNode));
+
+ node->cc = cc;
+ node->ccs = new_ccs;
+ node->back_edge = back_edge;
+
+ if (it->children == NULL) {
+ it->children = allocHashTable();
+ }
+
+ insertHashTable(it->children, (StgWord) node->cc->ccID, (const void *) node);
+
+ return it;
+}
+
+struct IndexTableIter_ {
+ struct HashIterator_ *iterator;
+};
+
+IndexTableIter*
+indexTableIterator(IndexTable *it) {
+ IndexTableIter *iter;
+ HashIterator *hashIter = NULL;
+ iter = arenaAlloc(prof_arena, sizeof(IndexTableIter));
+
+ if (it != EMPTY_TABLE && it->children != NULL) {
+ hashIter = arenaAlloc(prof_arena, sizeof(struct HashIterator_));
+ initHashIterator(it->children, hashIter);
+ }
+
+ iter->iterator = hashIter;
+ return iter;
+}
+
+int
+indexTableIterNext (IndexTableIter *iter) {
+ assert(iter != NULL);
+ if (iter->iterator == NULL) {
+ return 0;
+ }
+ return hashIteratorNext(iter->iterator);
+};
+
+
+IndexTableNode*
+indexTableIterItem(IndexTableIter *it) {
+ assert(it != NULL);
+ if (it->iterator == NULL) {
+ return EMPTY_TABLE;
+ }
+ return (IndexTableNode *) hashIteratorItem(it->iterator);
+}
+
+#endif /* PROFILING */
=====================================
rts/ProfilerReport.c
=====================================
@@ -14,6 +14,7 @@
#include "RtsUtils.h"
#include "ProfilerReport.h"
#include "Profiling.h"
+#include "rts/prof/IndexTable.h"
static uint32_t numDigits ( StgInt i );
static void findCCSMaxLens ( CostCentreStack const *ccs,
@@ -189,7 +190,7 @@ static void
findCCSMaxLens(CostCentreStack const *ccs, uint32_t indent, uint32_t *max_label_len,
uint32_t *max_module_len, uint32_t *max_src_len, uint32_t *max_id_len) {
CostCentre *cc;
- IndexTable *i;
+ IndexTableIter *i;
cc = ccs->cc;
@@ -198,14 +199,17 @@ findCCSMaxLens(CostCentreStack const *ccs, uint32_t indent, uint32_t *max_label_
*max_src_len = stg_max(*max_src_len, strlen_utf8(cc->srcloc));
*max_id_len = stg_max(*max_id_len, numDigits(ccs->ccsID));
- for (i = ccs->indexTable; i != 0; i = i->next) {
- if (!i->back_edge) {
- findCCSMaxLens(i->ccs, indent+1,
+ for ( i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; ) {
+ if (!indexTableIterItem(i)->back_edge) {
+ findCCSMaxLens(indexTableIterItem(i)->ccs, indent+1,
max_label_len, max_module_len, max_src_len, max_id_len);
}
}
}
+
static void
logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
uint32_t indent,
@@ -213,7 +217,7 @@ logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
uint32_t max_src_len, uint32_t max_id_len)
{
CostCentre *cc;
- IndexTable *i;
+ IndexTableIter *i;
cc = ccs->cc;
@@ -248,9 +252,11 @@ logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
fprintf(prof_file, "\n");
}
- for (i = ccs->indexTable; i != 0; i = i->next) {
- if (!i->back_edge) {
- logCCS(prof_file, i->ccs, totals, indent+1,
+ for ( i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; ) {
+ if (!indexTableIterItem(i)->back_edge) {
+ logCCS(prof_file, indexTableIterItem(i)->ccs, totals, indent+1,
max_label_len, max_module_len, max_src_len, max_id_len);
}
}
=====================================
rts/ProfilerReportJson.c
=====================================
@@ -6,6 +6,7 @@
*
* ---------------------------------------------------------------------------*/
+#include
#if defined(PROFILING)
#include "rts/PosixSource.h"
@@ -14,6 +15,7 @@
#include "RtsUtils.h"
#include "ProfilerReportJson.h"
#include "Profiling.h"
+#include "rts/prof/IndexTable.h"
#include
@@ -232,12 +234,14 @@ logCostCentreStack(FILE *prof_file, CostCentreStack const *ccs)
bool need_comma = false;
fprintf(prof_file, "\"children\": [");
- for (IndexTable *i = ccs->indexTable; i != 0; i = i->next) {
- if (!i->back_edge) {
+ for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; ) {
+ if (!indexTableIterItem(i)->back_edge) {
if (need_comma) {
fprintf(prof_file, ",");
}
- logCostCentreStack(prof_file, i->ccs);
+ logCostCentreStack(prof_file, indexTableIterItem(i)->ccs);
need_comma = true;
}
}
=====================================
rts/Profiling.c
=====================================
@@ -22,6 +22,7 @@
#include "ProfilerReportJson.h"
#include "Printer.h"
#include "Capability.h"
+#include "rts/prof/IndexTable.h"
#include
#include
@@ -33,11 +34,11 @@
/*
* Profiling allocation arena.
*/
-#if defined(DEBUG)
+// #if defined(DEBUG)
Arena *prof_arena;
-#else
-static Arena *prof_arena;
-#endif
+// #else
+// static Arena *prof_arena;
+// #endif
/*
* Global variables used to assign unique IDs to cc's, ccs's, and
@@ -119,9 +120,6 @@ static CostCentreStack * checkLoop ( CostCentreStack *ccs,
static void sortCCSTree ( CostCentreStack *ccs );
static CostCentreStack * pruneCCSTree ( CostCentreStack *ccs );
static CostCentreStack * actualPush ( CostCentreStack *, CostCentre * );
-static CostCentreStack * isInIndexTable ( IndexTable *, CostCentre * );
-static IndexTable * addToIndexTable ( IndexTable *, CostCentreStack *,
- CostCentre *, bool );
static void ccsSetSelected ( CostCentreStack *ccs );
static void aggregateCCCosts( CostCentreStack *ccs );
static void registerCC ( CostCentre *cc );
@@ -621,13 +619,13 @@ static CostCentreStack *
actualPush_ (CostCentreStack *ccs, CostCentre *cc, CostCentreStack *new_ccs)
{
/* assign values to each member of the structure */
+ new_ccs->indexTable = 0;
new_ccs->ccsID = CCS_ID++;
new_ccs->cc = cc;
new_ccs->prevStack = ccs;
new_ccs->root = ccs->root;
new_ccs->depth = ccs->depth + 1;
- new_ccs->indexTable = EMPTY_TABLE;
/* Initialise the various _scc_ counters to zero
*/
@@ -652,38 +650,6 @@ actualPush_ (CostCentreStack *ccs, CostCentre *cc, CostCentreStack *new_ccs)
return new_ccs;
}
-
-static CostCentreStack *
-isInIndexTable(IndexTable *it, CostCentre *cc)
-{
- while (it!=EMPTY_TABLE)
- {
- if (it->cc == cc)
- return it->ccs;
- else
- it = it->next;
- }
-
- /* otherwise we never found it so return EMPTY_TABLE */
- return EMPTY_TABLE;
-}
-
-
-static IndexTable *
-addToIndexTable (IndexTable *it, CostCentreStack *new_ccs,
- CostCentre *cc, bool back_edge)
-{
- IndexTable *new_it;
-
- new_it = arenaAlloc(prof_arena, sizeof(IndexTable));
-
- new_it->cc = cc;
- new_it->ccs = new_ccs;
- new_it->next = it;
- new_it->back_edge = back_edge;
- return new_it;
-}
-
/* -----------------------------------------------------------------------------
Generating a time & allocation profiling report.
-------------------------------------------------------------------------- */
@@ -744,9 +710,11 @@ countTickss_(CostCentreStack const *ccs, ProfilerTotals *totals)
totals->total_alloc += ccs->mem_alloc;
totals->total_prof_ticks += ccs->time_ticks;
}
- for (IndexTable *i = ccs->indexTable; i != NULL; i = i->next) {
- if (!i->back_edge) {
- countTickss_(i->ccs, totals);
+ for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; ) {
+ if (!indexTableIterItem(i)->back_edge) {
+ countTickss_(indexTableIterItem(i)->ccs, totals);
}
}
}
@@ -767,18 +735,19 @@ countTickss(CostCentreStack const *ccs)
static void
inheritCosts(CostCentreStack *ccs)
{
- IndexTable *i;
if (ignoreCCS(ccs)) { return; }
ccs->inherited_ticks += ccs->time_ticks;
ccs->inherited_alloc += ccs->mem_alloc;
- for (i = ccs->indexTable; i != NULL; i = i->next)
- if (!i->back_edge) {
- inheritCosts(i->ccs);
- ccs->inherited_ticks += i->ccs->inherited_ticks;
- ccs->inherited_alloc += i->ccs->inherited_alloc;
+ for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; )
+ if (!indexTableIterItem(i)->back_edge) {
+ inheritCosts(indexTableIterItem(i)->ccs);
+ ccs->inherited_ticks += indexTableIterItem(i)->ccs->inherited_ticks;
+ ccs->inherited_alloc += indexTableIterItem(i)->ccs->inherited_alloc;
}
return;
@@ -787,14 +756,14 @@ inheritCosts(CostCentreStack *ccs)
static void
aggregateCCCosts( CostCentreStack *ccs )
{
- IndexTable *i;
-
ccs->cc->mem_alloc += ccs->mem_alloc;
ccs->cc->time_ticks += ccs->time_ticks;
- for (i = ccs->indexTable; i != 0; i = i->next) {
- if (!i->back_edge) {
- aggregateCCCosts(i->ccs);
+ for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; ) {
+ if (!indexTableIterItem(i)->back_edge) {
+ aggregateCCCosts(indexTableIterItem(i)->ccs);
}
}
}
@@ -806,19 +775,22 @@ aggregateCCCosts( CostCentreStack *ccs )
static CostCentreStack *
pruneCCSTree (CostCentreStack *ccs)
{
- CostCentreStack *ccs1;
- IndexTable *i, **prev;
+ // CostCentreStack *ccs1;
+ // IndexTable *i, **prev;
- prev = &ccs->indexTable;
- for (i = ccs->indexTable; i != 0; i = i->next) {
- if (i->back_edge) { continue; }
+ // prev = &ccs->indexTable;
+ for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(i) != 0
+ ; ) {
+ if (indexTableIterItem(i)->back_edge) { continue; }
- ccs1 = pruneCCSTree(i->ccs);
- if (ccs1 == NULL) {
- *prev = i->next;
- } else {
- prev = &(i->next);
- }
+ // TODO: @fendor implement pruning
+ // ccs1 = pruneCCSTree(indexTableIterItem(i)->ccs);
+ // if (ccs1 == NULL) {
+ // *prev = i->next;
+ // } else {
+ // prev = &(i->next);
+ // }
}
if ( (RtsFlags.CcFlags.doCostCentres >= COST_CENTRES_ALL
@@ -833,59 +805,62 @@ pruneCCSTree (CostCentreStack *ccs)
}
}
-static IndexTable*
-insertIndexTableInSortedList(IndexTable* tbl, IndexTable* sortedList)
-{
- StgWord tbl_ticks = tbl->ccs->scc_count;
- char* tbl_label = tbl->ccs->cc->label;
-
- IndexTable *prev = NULL;
- IndexTable *cursor = sortedList;
-
- while (cursor != NULL) {
- StgWord cursor_ticks = cursor->ccs->scc_count;
- char* cursor_label = cursor->ccs->cc->label;
-
- if (tbl_ticks > cursor_ticks ||
- (tbl_ticks == cursor_ticks && strcmp(tbl_label, cursor_label) < 0)) {
- if (prev == NULL) {
- tbl->next = sortedList;
- return tbl;
- } else {
- prev->next = tbl;
- tbl->next = cursor;
- return sortedList;
- }
- } else {
- prev = cursor;
- cursor = cursor->next;
- }
- }
-
- prev->next = tbl;
- return sortedList;
-}
+// static IndexTable*
+// insertIndexTableInSortedList(IndexTable* tbl, IndexTable* sortedList)
+// {
+// StgWord tbl_ticks = tbl->ccs->scc_count;
+// char* tbl_label = tbl->ccs->cc->label;
+
+// IndexTable *prev = NULL;
+// IndexTable *cursor = sortedList;
+
+// while (cursor != NULL) {
+// StgWord cursor_ticks = cursor->ccs->scc_count;
+// char* cursor_label = cursor->ccs->cc->label;
+
+// if (tbl_ticks > cursor_ticks ||
+// (tbl_ticks == cursor_ticks && strcmp(tbl_label, cursor_label) < 0)) {
+// if (prev == NULL) {
+// tbl->next = sortedList;
+// return tbl;
+// } else {
+// prev->next = tbl;
+// tbl->next = cursor;
+// return sortedList;
+// }
+// } else {
+// prev = cursor;
+// cursor = cursor->next;
+// }
+// }
+
+// prev->next = tbl;
+// return sortedList;
+// }
static void
sortCCSTree(CostCentreStack *ccs)
{
if (ccs->indexTable == NULL) return;
- for (IndexTable *tbl = ccs->indexTable; tbl != NULL; tbl = tbl->next)
- if (!tbl->back_edge)
- sortCCSTree(tbl->ccs);
+ for ( IndexTableIter *iter = indexTableIterator(ccs->indexTable)
+ ; indexTableIterNext(iter) != 0
+ ; )
+ if (!indexTableIterItem(iter)->back_edge)
+ sortCCSTree(indexTableIterItem(iter)->ccs);
IndexTable *sortedList = ccs->indexTable;
- IndexTable *nonSortedList = sortedList->next;
- sortedList->next = NULL;
-
- while (nonSortedList != NULL)
- {
- IndexTable *nonSortedTail = nonSortedList->next;
- nonSortedList->next = NULL;
- sortedList = insertIndexTableInSortedList(nonSortedList, sortedList);
- nonSortedList = nonSortedTail;
- }
+ // TODO @fendor: reimplement sorting
+ // IndexTable *nonSortedList = sortedList->next;
+ // sortedList->next = NULL;
+
+ // while (nonSortedList != NULL)
+ // {
+ // IndexTable *nonSortedTail = nonSortedList->next;
+ // nonSortedList->next = NULL;
+ // sortedList = insertIndexTableInSortedList(nonSortedList, sortedList);
+ // nonSortedList = nonSortedTail;
+ // }
ccs->indexTable = sortedList;
}
=====================================
rts/Profiling.h
=====================================
@@ -11,9 +11,9 @@
#include
#include "Rts.h"
-#if defined(DEBUG)
+// #if defined(DEBUG)
#include "Arena.h"
-#endif
+// #endif
#include "BeginPrivate.h"
@@ -49,9 +49,9 @@ void fprintCCS_stderr (CostCentreStack *ccs, StgClosure *exception, StgTSO *tso)
bool ignoreCCS (CostCentreStack const *ccs);
bool ignoreCC (CostCentre const *cc);
-#if defined(DEBUG)
extern Arena *prof_arena;
+#if defined(DEBUG)
void debugCCS( CostCentreStack *ccs );
#endif
=====================================
rts/include/Rts.h
=====================================
@@ -231,6 +231,7 @@ void _warnFail(const char *filename, unsigned int linenum);
/* Profiling information */
#include "rts/prof/CCS.h"
+#include "rts/prof/IndexTable.h"
#include "rts/prof/Heap.h"
#include "rts/prof/LDV.h"
=====================================
rts/include/rts/prof/CCS.h
=====================================
@@ -99,27 +99,6 @@ void startProfTimer ( void );
/* Constants used to set is_caf flag on CostCentres */
#define CC_IS_CAF true
#define CC_NOT_CAF false
-/* -----------------------------------------------------------------------------
- * Data Structures
- * ---------------------------------------------------------------------------*/
-
-// IndexTable is the list of children of a CCS. (Alternatively it is a
-// cache of the results of pushing onto a CCS, so that the second and
-// subsequent times we push a certain CC on a CCS we get the same
-// result).
-
-typedef struct IndexTable_ {
- // Just a linked list of (cc, ccs) pairs, where the `ccs` is the result of
- // pushing `cc` to the owner of the index table (another CostCentreStack).
- CostCentre *cc;
- CostCentreStack *ccs;
- struct IndexTable_ *next;
- // back_edge is true when `cc` is already in the stack, so pushing it
- // truncates or drops (see RECURSION_DROPS and RECURSION_TRUNCATES in
- // Profiling.c).
- bool back_edge;
-} IndexTable;
-
/* -----------------------------------------------------------------------------
Pre-defined cost centres and cost centre stacks
=====================================
rts/include/rts/prof/IndexTable.h
=====================================
@@ -0,0 +1,51 @@
+#pragma once
+
+/* -----------------------------------------------------------------------------
+ * Data Structures
+ * ---------------------------------------------------------------------------*/
+
+// IndexTable is the list of children of a CCS. (Alternatively it is a
+// cache of the results of pushing onto a CCS, so that the second and
+// subsequent times we push a certain CC on a CCS we get the same
+// result).
+
+typedef struct IndexTableNode_ {
+ // Just a linked list of (cc, ccs) pairs, where the `ccs` is the result of
+ // pushing `cc` to the owner of the index table (another CostCentreStack).
+ CostCentre *cc;
+ CostCentreStack *ccs;
+ // back_edge is true when `cc` is already in the stack, so pushing it
+ // truncates or drops (see RECURSION_DROPS and RECURSION_TRUNCATES in
+ // Profiling.c).
+ bool back_edge;
+} IndexTableNode;
+
+typedef struct IndexTableNode_ IndexTableNode;
+
+typedef struct IndexTable_ {
+ // IndexTableNode *node;
+ // // Just a linked list of (cc, ccs) pairs, where the `ccs` is the result of
+ // // pushing `cc` to the owner of the index table (another CostCentreStack).
+ // CostCentre *cc;
+ // CostCentreStack *ccs;
+ // // back_edge is true when `cc` is already in the stack, so pushing it
+ // // truncates or drops (see RECURSION_DROPS and RECURSION_TRUNCATES in
+ // // Profiling.c).
+ // bool back_edge;
+ struct hashtable *children;
+} IndexTable;
+
+typedef struct IndexTable_ IndexTable;
+
+IndexTable * allocateIndexTable( void );
+void freeIndexTable( IndexTable * );
+CostCentreStack * isInIndexTable ( IndexTable *, CostCentre * );
+IndexTable * addToIndexTable ( IndexTable *, CostCentreStack *,
+ CostCentre *, bool );
+
+typedef struct IndexTableIter_ IndexTableIter;
+
+
+IndexTableIter* indexTableIterator ( IndexTable * );
+int indexTableIterNext ( IndexTableIter * );
+IndexTableNode* indexTableIterItem ( IndexTableIter * );
=====================================
rts/rts.cabal
=====================================
@@ -322,6 +322,7 @@ library
rts/Utils.h
rts/prof/CCS.h
rts/prof/Heap.h
+ rts/prof/IndexTable.h
rts/prof/LDV.h
rts/storage/Block.h
rts/storage/ClosureMacros.h
@@ -436,6 +437,7 @@ library
ProfilerReport.c
ProfilerReportJson.c
Profiling.c
+ IndexTable.c
IPE.c
Proftimer.c
RaiseAsync.c
=====================================
testsuite/tests/perf/should_run/T26147.stdout
=====================================
@@ -1,1001 +1 @@
-Test value: 0
-Test value: 1
-Test value: 2
-Test value: 3
-Test value: 4
-Test value: 5
-Test value: 6
-Test value: 7
-Test value: 8
-Test value: 9
-Test value: 10
-Test value: 11
-Test value: 12
-Test value: 13
-Test value: 14
-Test value: 15
-Test value: 16
-Test value: 17
-Test value: 18
-Test value: 19
-Test value: 20
-Test value: 21
-Test value: 22
-Test value: 23
-Test value: 24
-Test value: 25
-Test value: 26
-Test value: 27
-Test value: 28
-Test value: 29
-Test value: 30
-Test value: 31
-Test value: 32
-Test value: 33
-Test value: 34
-Test value: 35
-Test value: 36
-Test value: 37
-Test value: 38
-Test value: 39
-Test value: 40
-Test value: 41
-Test value: 42
-Test value: 43
-Test value: 44
-Test value: 45
-Test value: 46
-Test value: 47
-Test value: 48
-Test value: 49
-Test value: 50
-Test value: 51
-Test value: 52
-Test value: 53
-Test value: 54
-Test value: 55
-Test value: 56
-Test value: 57
-Test value: 58
-Test value: 59
-Test value: 60
-Test value: 61
-Test value: 62
-Test value: 63
-Test value: 64
-Test value: 65
-Test value: 66
-Test value: 67
-Test value: 68
-Test value: 69
-Test value: 70
-Test value: 71
-Test value: 72
-Test value: 73
-Test value: 74
-Test value: 75
-Test value: 76
-Test value: 77
-Test value: 78
-Test value: 79
-Test value: 80
-Test value: 81
-Test value: 82
-Test value: 83
-Test value: 84
-Test value: 85
-Test value: 86
-Test value: 87
-Test value: 88
-Test value: 89
-Test value: 90
-Test value: 91
-Test value: 92
-Test value: 93
-Test value: 94
-Test value: 95
-Test value: 96
-Test value: 97
-Test value: 98
-Test value: 99
-Test value: 100
-Test value: 101
-Test value: 102
-Test value: 103
-Test value: 104
-Test value: 105
-Test value: 106
-Test value: 107
-Test value: 108
-Test value: 109
-Test value: 110
-Test value: 111
-Test value: 112
-Test value: 113
-Test value: 114
-Test value: 115
-Test value: 116
-Test value: 117
-Test value: 118
-Test value: 119
-Test value: 120
-Test value: 121
-Test value: 122
-Test value: 123
-Test value: 124
-Test value: 125
-Test value: 126
-Test value: 127
-Test value: 128
-Test value: 129
-Test value: 130
-Test value: 131
-Test value: 132
-Test value: 133
-Test value: 134
-Test value: 135
-Test value: 136
-Test value: 137
-Test value: 138
-Test value: 139
-Test value: 140
-Test value: 141
-Test value: 142
-Test value: 143
-Test value: 144
-Test value: 145
-Test value: 146
-Test value: 147
-Test value: 148
-Test value: 149
-Test value: 150
-Test value: 151
-Test value: 152
-Test value: 153
-Test value: 154
-Test value: 155
-Test value: 156
-Test value: 157
-Test value: 158
-Test value: 159
-Test value: 160
-Test value: 161
-Test value: 162
-Test value: 163
-Test value: 164
-Test value: 165
-Test value: 166
-Test value: 167
-Test value: 168
-Test value: 169
-Test value: 170
-Test value: 171
-Test value: 172
-Test value: 173
-Test value: 174
-Test value: 175
-Test value: 176
-Test value: 177
-Test value: 178
-Test value: 179
-Test value: 180
-Test value: 181
-Test value: 182
-Test value: 183
-Test value: 184
-Test value: 185
-Test value: 186
-Test value: 187
-Test value: 188
-Test value: 189
-Test value: 190
-Test value: 191
-Test value: 192
-Test value: 193
-Test value: 194
-Test value: 195
-Test value: 196
-Test value: 197
-Test value: 198
-Test value: 199
-Test value: 200
-Test value: 201
-Test value: 202
-Test value: 203
-Test value: 204
-Test value: 205
-Test value: 206
-Test value: 207
-Test value: 208
-Test value: 209
-Test value: 210
-Test value: 211
-Test value: 212
-Test value: 213
-Test value: 214
-Test value: 215
-Test value: 216
-Test value: 217
-Test value: 218
-Test value: 219
-Test value: 220
-Test value: 221
-Test value: 222
-Test value: 223
-Test value: 224
-Test value: 225
-Test value: 226
-Test value: 227
-Test value: 228
-Test value: 229
-Test value: 230
-Test value: 231
-Test value: 232
-Test value: 233
-Test value: 234
-Test value: 235
-Test value: 236
-Test value: 237
-Test value: 238
-Test value: 239
-Test value: 240
-Test value: 241
-Test value: 242
-Test value: 243
-Test value: 244
-Test value: 245
-Test value: 246
-Test value: 247
-Test value: 248
-Test value: 249
-Test value: 250
-Test value: 251
-Test value: 252
-Test value: 253
-Test value: 254
-Test value: 255
-Test value: 256
-Test value: 257
-Test value: 258
-Test value: 259
-Test value: 260
-Test value: 261
-Test value: 262
-Test value: 263
-Test value: 264
-Test value: 265
-Test value: 266
-Test value: 267
-Test value: 268
-Test value: 269
-Test value: 270
-Test value: 271
-Test value: 272
-Test value: 273
-Test value: 274
-Test value: 275
-Test value: 276
-Test value: 277
-Test value: 278
-Test value: 279
-Test value: 280
-Test value: 281
-Test value: 282
-Test value: 283
-Test value: 284
-Test value: 285
-Test value: 286
-Test value: 287
-Test value: 288
-Test value: 289
-Test value: 290
-Test value: 291
-Test value: 292
-Test value: 293
-Test value: 294
-Test value: 295
-Test value: 296
-Test value: 297
-Test value: 298
-Test value: 299
-Test value: 300
-Test value: 301
-Test value: 302
-Test value: 303
-Test value: 304
-Test value: 305
-Test value: 306
-Test value: 307
-Test value: 308
-Test value: 309
-Test value: 310
-Test value: 311
-Test value: 312
-Test value: 313
-Test value: 314
-Test value: 315
-Test value: 316
-Test value: 317
-Test value: 318
-Test value: 319
-Test value: 320
-Test value: 321
-Test value: 322
-Test value: 323
-Test value: 324
-Test value: 325
-Test value: 326
-Test value: 327
-Test value: 328
-Test value: 329
-Test value: 330
-Test value: 331
-Test value: 332
-Test value: 333
-Test value: 334
-Test value: 335
-Test value: 336
-Test value: 337
-Test value: 338
-Test value: 339
-Test value: 340
-Test value: 341
-Test value: 342
-Test value: 343
-Test value: 344
-Test value: 345
-Test value: 346
-Test value: 347
-Test value: 348
-Test value: 349
-Test value: 350
-Test value: 351
-Test value: 352
-Test value: 353
-Test value: 354
-Test value: 355
-Test value: 356
-Test value: 357
-Test value: 358
-Test value: 359
-Test value: 360
-Test value: 361
-Test value: 362
-Test value: 363
-Test value: 364
-Test value: 365
-Test value: 366
-Test value: 367
-Test value: 368
-Test value: 369
-Test value: 370
-Test value: 371
-Test value: 372
-Test value: 373
-Test value: 374
-Test value: 375
-Test value: 376
-Test value: 377
-Test value: 378
-Test value: 379
-Test value: 380
-Test value: 381
-Test value: 382
-Test value: 383
-Test value: 384
-Test value: 385
-Test value: 386
-Test value: 387
-Test value: 388
-Test value: 389
-Test value: 390
-Test value: 391
-Test value: 392
-Test value: 393
-Test value: 394
-Test value: 395
-Test value: 396
-Test value: 397
-Test value: 398
-Test value: 399
-Test value: 400
-Test value: 401
-Test value: 402
-Test value: 403
-Test value: 404
-Test value: 405
-Test value: 406
-Test value: 407
-Test value: 408
-Test value: 409
-Test value: 410
-Test value: 411
-Test value: 412
-Test value: 413
-Test value: 414
-Test value: 415
-Test value: 416
-Test value: 417
-Test value: 418
-Test value: 419
-Test value: 420
-Test value: 421
-Test value: 422
-Test value: 423
-Test value: 424
-Test value: 425
-Test value: 426
-Test value: 427
-Test value: 428
-Test value: 429
-Test value: 430
-Test value: 431
-Test value: 432
-Test value: 433
-Test value: 434
-Test value: 435
-Test value: 436
-Test value: 437
-Test value: 438
-Test value: 439
-Test value: 440
-Test value: 441
-Test value: 442
-Test value: 443
-Test value: 444
-Test value: 445
-Test value: 446
-Test value: 447
-Test value: 448
-Test value: 449
-Test value: 450
-Test value: 451
-Test value: 452
-Test value: 453
-Test value: 454
-Test value: 455
-Test value: 456
-Test value: 457
-Test value: 458
-Test value: 459
-Test value: 460
-Test value: 461
-Test value: 462
-Test value: 463
-Test value: 464
-Test value: 465
-Test value: 466
-Test value: 467
-Test value: 468
-Test value: 469
-Test value: 470
-Test value: 471
-Test value: 472
-Test value: 473
-Test value: 474
-Test value: 475
-Test value: 476
-Test value: 477
-Test value: 478
-Test value: 479
-Test value: 480
-Test value: 481
-Test value: 482
-Test value: 483
-Test value: 484
-Test value: 485
-Test value: 486
-Test value: 487
-Test value: 488
-Test value: 489
-Test value: 490
-Test value: 491
-Test value: 492
-Test value: 493
-Test value: 494
-Test value: 495
-Test value: 496
-Test value: 497
-Test value: 498
-Test value: 499
-Test value: 500
-Test value: 501
-Test value: 502
-Test value: 503
-Test value: 504
-Test value: 505
-Test value: 506
-Test value: 507
-Test value: 508
-Test value: 509
-Test value: 510
-Test value: 511
-Test value: 512
-Test value: 513
-Test value: 514
-Test value: 515
-Test value: 516
-Test value: 517
-Test value: 518
-Test value: 519
-Test value: 520
-Test value: 521
-Test value: 522
-Test value: 523
-Test value: 524
-Test value: 525
-Test value: 526
-Test value: 527
-Test value: 528
-Test value: 529
-Test value: 530
-Test value: 531
-Test value: 532
-Test value: 533
-Test value: 534
-Test value: 535
-Test value: 536
-Test value: 537
-Test value: 538
-Test value: 539
-Test value: 540
-Test value: 541
-Test value: 542
-Test value: 543
-Test value: 544
-Test value: 545
-Test value: 546
-Test value: 547
-Test value: 548
-Test value: 549
-Test value: 550
-Test value: 551
-Test value: 552
-Test value: 553
-Test value: 554
-Test value: 555
-Test value: 556
-Test value: 557
-Test value: 558
-Test value: 559
-Test value: 560
-Test value: 561
-Test value: 562
-Test value: 563
-Test value: 564
-Test value: 565
-Test value: 566
-Test value: 567
-Test value: 568
-Test value: 569
-Test value: 570
-Test value: 571
-Test value: 572
-Test value: 573
-Test value: 574
-Test value: 575
-Test value: 576
-Test value: 577
-Test value: 578
-Test value: 579
-Test value: 580
-Test value: 581
-Test value: 582
-Test value: 583
-Test value: 584
-Test value: 585
-Test value: 586
-Test value: 587
-Test value: 588
-Test value: 589
-Test value: 590
-Test value: 591
-Test value: 592
-Test value: 593
-Test value: 594
-Test value: 595
-Test value: 596
-Test value: 597
-Test value: 598
-Test value: 599
-Test value: 600
-Test value: 601
-Test value: 602
-Test value: 603
-Test value: 604
-Test value: 605
-Test value: 606
-Test value: 607
-Test value: 608
-Test value: 609
-Test value: 610
-Test value: 611
-Test value: 612
-Test value: 613
-Test value: 614
-Test value: 615
-Test value: 616
-Test value: 617
-Test value: 618
-Test value: 619
-Test value: 620
-Test value: 621
-Test value: 622
-Test value: 623
-Test value: 624
-Test value: 625
-Test value: 626
-Test value: 627
-Test value: 628
-Test value: 629
-Test value: 630
-Test value: 631
-Test value: 632
-Test value: 633
-Test value: 634
-Test value: 635
-Test value: 636
-Test value: 637
-Test value: 638
-Test value: 639
-Test value: 640
-Test value: 641
-Test value: 642
-Test value: 643
-Test value: 644
-Test value: 645
-Test value: 646
-Test value: 647
-Test value: 648
-Test value: 649
-Test value: 650
-Test value: 651
-Test value: 652
-Test value: 653
-Test value: 654
-Test value: 655
-Test value: 656
-Test value: 657
-Test value: 658
-Test value: 659
-Test value: 660
-Test value: 661
-Test value: 662
-Test value: 663
-Test value: 664
-Test value: 665
-Test value: 666
-Test value: 667
-Test value: 668
-Test value: 669
-Test value: 670
-Test value: 671
-Test value: 672
-Test value: 673
-Test value: 674
-Test value: 675
-Test value: 676
-Test value: 677
-Test value: 678
-Test value: 679
-Test value: 680
-Test value: 681
-Test value: 682
-Test value: 683
-Test value: 684
-Test value: 685
-Test value: 686
-Test value: 687
-Test value: 688
-Test value: 689
-Test value: 690
-Test value: 691
-Test value: 692
-Test value: 693
-Test value: 694
-Test value: 695
-Test value: 696
-Test value: 697
-Test value: 698
-Test value: 699
-Test value: 700
-Test value: 701
-Test value: 702
-Test value: 703
-Test value: 704
-Test value: 705
-Test value: 706
-Test value: 707
-Test value: 708
-Test value: 709
-Test value: 710
-Test value: 711
-Test value: 712
-Test value: 713
-Test value: 714
-Test value: 715
-Test value: 716
-Test value: 717
-Test value: 718
-Test value: 719
-Test value: 720
-Test value: 721
-Test value: 722
-Test value: 723
-Test value: 724
-Test value: 725
-Test value: 726
-Test value: 727
-Test value: 728
-Test value: 729
-Test value: 730
-Test value: 731
-Test value: 732
-Test value: 733
-Test value: 734
-Test value: 735
-Test value: 736
-Test value: 737
-Test value: 738
-Test value: 739
-Test value: 740
-Test value: 741
-Test value: 742
-Test value: 743
-Test value: 744
-Test value: 745
-Test value: 746
-Test value: 747
-Test value: 748
-Test value: 749
-Test value: 750
-Test value: 751
-Test value: 752
-Test value: 753
-Test value: 754
-Test value: 755
-Test value: 756
-Test value: 757
-Test value: 758
-Test value: 759
-Test value: 760
-Test value: 761
-Test value: 762
-Test value: 763
-Test value: 764
-Test value: 765
-Test value: 766
-Test value: 767
-Test value: 768
-Test value: 769
-Test value: 770
-Test value: 771
-Test value: 772
-Test value: 773
-Test value: 774
-Test value: 775
-Test value: 776
-Test value: 777
-Test value: 778
-Test value: 779
-Test value: 780
-Test value: 781
-Test value: 782
-Test value: 783
-Test value: 784
-Test value: 785
-Test value: 786
-Test value: 787
-Test value: 788
-Test value: 789
-Test value: 790
-Test value: 791
-Test value: 792
-Test value: 793
-Test value: 794
-Test value: 795
-Test value: 796
-Test value: 797
-Test value: 798
-Test value: 799
-Test value: 800
-Test value: 801
-Test value: 802
-Test value: 803
-Test value: 804
-Test value: 805
-Test value: 806
-Test value: 807
-Test value: 808
-Test value: 809
-Test value: 810
-Test value: 811
-Test value: 812
-Test value: 813
-Test value: 814
-Test value: 815
-Test value: 816
-Test value: 817
-Test value: 818
-Test value: 819
-Test value: 820
-Test value: 821
-Test value: 822
-Test value: 823
-Test value: 824
-Test value: 825
-Test value: 826
-Test value: 827
-Test value: 828
-Test value: 829
-Test value: 830
-Test value: 831
-Test value: 832
-Test value: 833
-Test value: 834
-Test value: 835
-Test value: 836
-Test value: 837
-Test value: 838
-Test value: 839
-Test value: 840
-Test value: 841
-Test value: 842
-Test value: 843
-Test value: 844
-Test value: 845
-Test value: 846
-Test value: 847
-Test value: 848
-Test value: 849
-Test value: 850
-Test value: 851
-Test value: 852
-Test value: 853
-Test value: 854
-Test value: 855
-Test value: 856
-Test value: 857
-Test value: 858
-Test value: 859
-Test value: 860
-Test value: 861
-Test value: 862
-Test value: 863
-Test value: 864
-Test value: 865
-Test value: 866
-Test value: 867
-Test value: 868
-Test value: 869
-Test value: 870
-Test value: 871
-Test value: 872
-Test value: 873
-Test value: 874
-Test value: 875
-Test value: 876
-Test value: 877
-Test value: 878
-Test value: 879
-Test value: 880
-Test value: 881
-Test value: 882
-Test value: 883
-Test value: 884
-Test value: 885
-Test value: 886
-Test value: 887
-Test value: 888
-Test value: 889
-Test value: 890
-Test value: 891
-Test value: 892
-Test value: 893
-Test value: 894
-Test value: 895
-Test value: 896
-Test value: 897
-Test value: 898
-Test value: 899
-Test value: 900
-Test value: 901
-Test value: 902
-Test value: 903
-Test value: 904
-Test value: 905
-Test value: 906
-Test value: 907
-Test value: 908
-Test value: 909
-Test value: 910
-Test value: 911
-Test value: 912
-Test value: 913
-Test value: 914
-Test value: 915
-Test value: 916
-Test value: 917
-Test value: 918
-Test value: 919
-Test value: 920
-Test value: 921
-Test value: 922
-Test value: 923
-Test value: 924
-Test value: 925
-Test value: 926
-Test value: 927
-Test value: 928
-Test value: 929
-Test value: 930
-Test value: 931
-Test value: 932
-Test value: 933
-Test value: 934
-Test value: 935
-Test value: 936
-Test value: 937
-Test value: 938
-Test value: 939
-Test value: 940
-Test value: 941
-Test value: 942
-Test value: 943
-Test value: 944
-Test value: 945
-Test value: 946
-Test value: 947
-Test value: 948
-Test value: 949
-Test value: 950
-Test value: 951
-Test value: 952
-Test value: 953
-Test value: 954
-Test value: 955
-Test value: 956
-Test value: 957
-Test value: 958
-Test value: 959
-Test value: 960
-Test value: 961
-Test value: 962
-Test value: 963
-Test value: 964
-Test value: 965
-Test value: 966
-Test value: 967
-Test value: 968
-Test value: 969
-Test value: 970
-Test value: 971
-Test value: 972
-Test value: 973
-Test value: 974
-Test value: 975
-Test value: 976
-Test value: 977
-Test value: 978
-Test value: 979
-Test value: 980
-Test value: 981
-Test value: 982
-Test value: 983
-Test value: 984
-Test value: 985
-Test value: 986
-Test value: 987
-Test value: 988
-Test value: 989
-Test value: 990
-Test value: 991
-Test value: 992
-Test value: 993
-Test value: 994
-Test value: 995
-Test value: 996
-Test value: 997
-Test value: 998
-Test value: 999
-Test value: 1000
+Test value: 30000
=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -446,7 +446,6 @@ test('T26147',
[ collect_stats('all', 5),
pre_cmd('./genT26147'),
extra_files(['genT26147']),
- extra_run_opts('+RTS -p'),
test_opts_dot_prof,
],
compile_and_run,
=====================================
testsuite/tests/perf/should_run/genT26147
=====================================
@@ -16,7 +16,6 @@ for i in $(seq $NUMFUN); do
costCenter${i} :: Int -> IO ()
costCenter${i} n = do
- putStrLn $ "Test value: " ++ show n
costCenter$((i + 1)) (n+1)
EOF
done
@@ -25,5 +24,7 @@ cat >> T26147.hs << EOF
costCenter$((i + 1)) :: Int -> IO ()
costCenter$((i + 1)) n = do
- putStrLn $ "Test value: " ++ show n
+ if n < $NUMFUN * 30
+ then costCenter1 n
+ else putStrLn $ "Test value: " ++ show n
EOF
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b328b3070cd700ff98957ade4b42bef0...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b328b3070cd700ff98957ade4b42bef0...
You're receiving this email because of your account on gitlab.haskell.org.