Hannes Siebenhandl pushed to branch wip/fendor/ccs-index-table at Glasgow Haskell Compiler / GHC

Commits:

17 changed files:

Changes:

  • libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc
    ... ... @@ -138,21 +138,21 @@ peekCostCentre costCenterCacheRef ptr = do
    138 138
     
    
    139 139
     peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable)
    
    140 140
     peekIndexTable _ _ ptr | ptr == nullPtr = return Nothing
    
    141
    -peekIndexTable loopBreakers costCenterCacheRef ptr = do
    
    142
    -        it_cc_ptr <- (#peek struct IndexTable_, cc) ptr
    
    143
    -        it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr
    
    144
    -        it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr
    
    145
    -        it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr
    
    146
    -        it_next_ptr <- (#peek struct IndexTable_, next) ptr
    
    147
    -        it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr
    
    148
    -        it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr
    
    149
    -
    
    150
    -        return $ Just IndexTable {
    
    151
    -            it_cc = it_cc',
    
    152
    -            it_ccs = it_ccs',
    
    153
    -            it_next = it_next',
    
    154
    -            it_back_edge = it_back_edge'
    
    155
    -        }
    
    141
    +peekIndexTable _ _ _ = pure Nothing
    
    142
    +        -- it_cc_ptr <- (#peek struct IndexTable_, cc) ptr
    
    143
    +        -- it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr
    
    144
    +        -- it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr
    
    145
    +        -- it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr
    
    146
    +        -- it_next_ptr <- (#peek struct IndexTable_, next) ptr
    
    147
    +        -- it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr
    
    148
    +        -- it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr
    
    149
    +
    
    150
    +        -- return $ Just IndexTable {
    
    151
    +        --     it_cc = it_cc',
    
    152
    +        --     it_ccs = it_ccs',
    
    153
    +        --     it_next = it_next',
    
    154
    +        --     it_back_edge = it_back_edge'
    
    155
    +        -- }
    
    156 156
     
    
    157 157
     -- | casts a @Ptr@ to an @Int@
    
    158 158
     ptrToInt :: Ptr a -> Int
    

  • rts/FileLock.c
    ... ... @@ -46,7 +46,7 @@ STATIC_INLINE int hashLock(const HashTable *table, StgWord w)
    46 46
         Lock *l = (Lock *)w;
    
    47 47
         StgWord key = l->inode ^ (l->inode >> 32) ^ l->device ^ (l->device >> 32);
    
    48 48
         // Just xor all 32-bit words of inode and device, hope this is good enough.
    
    49
    -    return hashWord(table, key);
    
    49
    +    return hashAddress(table, key);
    
    50 50
     }
    
    51 51
     
    
    52 52
     void
    

  • rts/Hash.c
    ... ... @@ -36,7 +36,7 @@
    36 36
                                 /* Also the minimum size of a hash table */
    
    37 37
     #define HDIRSIZE    1024    /* Size of the segment directory */
    
    38 38
                                 /* Maximum hash table size is HSEGSIZE * HDIRSIZE */
    
    39
    -#define HLOAD       5       /* Maximum average load of a single hash bucket */
    
    39
    +#define HLOAD       1       /* Maximum average load of a single hash bucket */
    
    40 40
     
    
    41 41
     #define HCHUNK      (1024 * sizeof(W_) / sizeof(HashList))
    
    42 42
                                 /* Number of HashList cells to allocate in one go */
    
    ... ... @@ -76,12 +76,27 @@ struct strhashtable { struct hashtable table; };
    76 76
      * next bucket to be split, re-hash using the larger table.
    
    77 77
      * -------------------------------------------------------------------------- */
    
    78 78
     int
    
    79
    -hashWord(const HashTable *table, StgWord key)
    
    79
    +hashAddress(const HashTable *table, StgWord key)
    
    80 80
     {
    
    81 81
         int bucket;
    
    82 82
     
    
    83 83
         /* Strip the boring zero bits */
    
    84
    -    key >>= sizeof(StgWord);
    
    84
    +    key /= sizeof(StgWord);
    
    85
    +
    
    86
    +    /* Mod the size of the hash table (a power of 2) */
    
    87
    +    bucket = key & table->mask1;
    
    88
    +
    
    89
    +    if (bucket < table->split) {
    
    90
    +        /* Mod the size of the expanded hash table (also a power of 2) */
    
    91
    +        bucket = key & table->mask2;
    
    92
    +    }
    
    93
    +    return bucket;
    
    94
    +}
    
    95
    +
    
    96
    +int
    
    97
    +hashWord(const HashTable *table, StgWord key)
    
    98
    +{
    
    99
    +    int bucket;
    
    85 100
     
    
    86 101
         /* Mod the size of the hash table (a power of 2) */
    
    87 102
         bucket = key & table->mask1;
    
    ... ... @@ -169,14 +184,14 @@ expand(HashTable *table, HashFunction f)
    169 184
             return;
    
    170 185
     
    
    171 186
         /* Calculate indices of bucket to split */
    
    172
    -    oldsegment = table->split / HSEGSIZE;
    
    173
    -    oldindex = table->split % HSEGSIZE;
    
    187
    +    oldsegment = table->split / HSEGSIZE; // 0
    
    188
    +    oldindex = table->split % HSEGSIZE; // 0
    
    174 189
     
    
    175
    -    newbucket = table->max + table->split;
    
    190
    +    newbucket = table->max + table->split; // 1024
    
    176 191
     
    
    177 192
         /* And the indices of the new bucket */
    
    178
    -    newsegment = newbucket / HSEGSIZE;
    
    179
    -    newindex = newbucket % HSEGSIZE;
    
    193
    +    newsegment = newbucket / HSEGSIZE; // 1
    
    194
    +    newindex = newbucket % HSEGSIZE; // 0
    
    180 195
     
    
    181 196
         if (newindex == 0)
    
    182 197
             allocSegment(table, newsegment);
    
    ... ... @@ -238,10 +253,17 @@ lookupHashTable_(const HashTable *table, StgWord key,
    238 253
         return lookupHashTable_inlined(table, key, f, cmp);
    
    239 254
     }
    
    240 255
     
    
    256
    +void *
    
    257
    +lookupHashTable_indexTable_(const HashTable *table, StgWord key,
    
    258
    +                 HashFunction f)
    
    259
    +{
    
    260
    +    return lookupHashTable_inlined(table, key, f, compareWord);
    
    261
    +}
    
    262
    +
    
    241 263
     void *
    
    242 264
     lookupHashTable(const HashTable *table, StgWord key)
    
    243 265
     {
    
    244
    -    return lookupHashTable_inlined(table, key, hashWord, compareWord);
    
    266
    +    return lookupHashTable_inlined(table, key, hashAddress, compareWord);
    
    245 267
     }
    
    246 268
     
    
    247 269
     void *
    
    ... ... @@ -371,7 +393,7 @@ insertHashTable_(HashTable *table, StgWord key,
    371 393
     void
    
    372 394
     insertHashTable(HashTable *table, StgWord key, const void *data)
    
    373 395
     {
    
    374
    -    insertHashTable_inlined(table, key, data, hashWord);
    
    396
    +    insertHashTable_inlined(table, key, data, hashAddress);
    
    375 397
     }
    
    376 398
     
    
    377 399
     void
    
    ... ... @@ -422,7 +444,7 @@ removeHashTable_(HashTable *table, StgWord key, const void *data,
    422 444
     void *
    
    423 445
     removeHashTable(HashTable *table, StgWord key, const void *data)
    
    424 446
     {
    
    425
    -    return removeHashTable_inlined(table, key, data, hashWord, compareWord);
    
    447
    +    return removeHashTable_inlined(table, key, data, hashAddress, compareWord);
    
    426 448
     }
    
    427 449
     
    
    428 450
     void *
    
    ... ... @@ -515,6 +537,52 @@ mapHashTableKeys(HashTable *table, void *data, MapHashFnKeys fn)
    515 537
         }
    
    516 538
     }
    
    517 539
     
    
    540
    +void initHashIterator(HashTable *table, struct HashIterator_* iter) {
    
    541
    +  /* The last bucket with something in it is table->max + table->split - 1 */
    
    542
    +  long segment = (table->max + table->split - 1) / HSEGSIZE;
    
    543
    +  long index = (table->max + table->split - 1) % HSEGSIZE;
    
    544
    +  iter->table = table;
    
    545
    +  iter->segment = segment;
    
    546
    +  iter->index = index;
    
    547
    +  iter->data = NULL;
    
    548
    +}
    
    549
    +
    
    550
    +struct HashIterator_* hashTableIterator(HashTable *table) {
    
    551
    +    struct HashIterator_* iter;
    
    552
    +    iter = stgMallocBytes(sizeof(HashIterator),"hashTableIterator");
    
    553
    +    initHashIterator(table, iter);
    
    554
    +    return iter;
    
    555
    +}
    
    556
    +
    
    557
    +const void *hashIteratorItem(struct HashIterator_* iter) {
    
    558
    +  return iter->data;
    
    559
    +}
    
    560
    +
    
    561
    +int hashIteratorNext(struct HashIterator_* iter) {
    
    562
    +    long segment = iter->segment;
    
    563
    +    long index = iter->index;
    
    564
    +
    
    565
    +    while (segment >= 0) {
    
    566
    +        while (index >= 0) {
    
    567
    +            for (HashList *hl = iter->table->dir[segment][index]; hl != NULL; hl = hl->next) {
    
    568
    +              iter->segment = segment;
    
    569
    +              /* make sure we advance the index */
    
    570
    +              iter->index = index - 1;
    
    571
    +              iter->data = hl->data;
    
    572
    +              return 1;
    
    573
    +            }
    
    574
    +            index--;
    
    575
    +        }
    
    576
    +        segment--;
    
    577
    +        index = HSEGSIZE - 1;
    
    578
    +    }
    
    579
    +    return 0;
    
    580
    +}
    
    581
    +
    
    582
    +void freeHashIterator(struct HashIterator_* iter) {
    
    583
    +  stgFree(iter);
    
    584
    +}
    
    585
    +
    
    518 586
     void
    
    519 587
     iterHashTable(HashTable *table, void *data, IterHashFn fn)
    
    520 588
     {
    
    ... ... @@ -536,6 +604,7 @@ iterHashTable(HashTable *table, void *data, IterHashFn fn)
    536 604
         }
    
    537 605
     }
    
    538 606
     
    
    607
    +
    
    539 608
     /* -----------------------------------------------------------------------------
    
    540 609
      * When we initialize a hash table, we set up the first segment as well,
    
    541 610
      * 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);
    42 42
     void mapHashTableKeys(HashTable *table, void *data, MapHashFnKeys fn);
    
    43 43
     void iterHashTable(HashTable *table, void *data, IterHashFn);
    
    44 44
     
    
    45
    +struct HashIterator_ {
    
    46
    +  HashTable *table;
    
    47
    +  long segment;
    
    48
    +  long index;
    
    49
    +  const void* data;
    
    50
    +};
    
    51
    +typedef struct HashIterator_ HashIterator;
    
    52
    +
    
    53
    +void initHashIterator(HashTable *, struct HashIterator_*);
    
    54
    +struct HashIterator_* hashTableIterator(HashTable *table);
    
    55
    +const void *hashIteratorItem(struct HashIterator_* iter);
    
    56
    +int hashIteratorNext(struct HashIterator_* iter);
    
    57
    +void freeHashIterator(struct HashIterator_* iter);
    
    58
    +
    
    59
    +
    
    45 60
     /* Hash table access where the keys are C strings (the strings are
    
    46 61
      * assumed to be allocated by the caller, and mustn't be deallocated
    
    47 62
      * until the corresponding hash table entry has been removed).
    
    ... ... @@ -73,6 +88,7 @@ typedef int CompareFunction(StgWord key1, StgWord key2);
    73 88
     // Helper for implementing hash functions
    
    74 89
     int hashBuffer(const HashTable *table, const void *buf, size_t len);
    
    75 90
     
    
    91
    +int hashAddress(const HashTable *table, StgWord key);
    
    76 92
     int hashWord(const HashTable *table, StgWord key);
    
    77 93
     int hashStr(const HashTable *table, StgWord w);
    
    78 94
     void        insertHashTable_ ( HashTable *table, StgWord key,
    

  • rts/IndexTable.c
    1
    +#if defined(PROFILING)
    
    2
    +
    
    3
    +#include "Rts.h"
    
    4
    +#include "rts/prof/IndexTable.h"
    
    5
    +#include "RtsFlags.h"
    
    6
    +#include "RtsUtils.h"
    
    7
    +#include "rts/PosixSource.h"
    
    8
    +#include "rts/prof/CCS.h"
    
    9
    +#include "Hash.h"
    
    10
    +#include "assert.h"
    
    11
    +
    
    12
    +#include "Profiling.h"
    
    13
    +#include "Arena.h"
    
    14
    +
    
    15
    +#include <fs_rts.h>
    
    16
    +#include <string.h>
    
    17
    +
    
    18
    +#if defined(DEBUG) || defined(PROFILING)
    
    19
    +#include "Trace.h"
    
    20
    +#endif
    
    21
    +
    
    22
    +
    
    23
    +typedef struct IndexTable_ IndexTable;
    
    24
    +
    
    25
    +void
    
    26
    +freeIndexTable(IndexTable * it) {
    
    27
    +  assert(it != EMPTY_TABLE);
    
    28
    +  if (it != EMPTY_TABLE) {
    
    29
    +    freeHashTable(it->children, NULL);
    
    30
    +    it->children = NULL;
    
    31
    +  }
    
    32
    +}
    
    33
    +
    
    34
    +STATIC_INLINE int
    
    35
    +compareWord(StgWord key1, StgWord key2)
    
    36
    +{
    
    37
    +    return (key1 == key2);
    
    38
    +}
    
    39
    +
    
    40
    +CostCentreStack *
    
    41
    +isInIndexTable(IndexTable *it, CostCentre *cc) {
    
    42
    +    if (EMPTY_TABLE == it) {
    
    43
    +        return EMPTY_TABLE;
    
    44
    +    }
    
    45
    +    // IF_DEBUG(prof,
    
    46
    +    //         traceBegin("isInIndexTable %s ", cc->label);
    
    47
    +    //         debugBelch("<%d>", keyCountHashTable(it->children));
    
    48
    +    //         traceEnd(););
    
    49
    +
    
    50
    +    IndexTableNode * node;
    
    51
    +    node = (IndexTableNode *) lookupHashTable_(it->children, (StgWord) cc->ccID, hashWord, compareWord);
    
    52
    +    if (node == NULL) {
    
    53
    +      /* Not found */
    
    54
    +      return EMPTY_TABLE;
    
    55
    +    }
    
    56
    +    return node->ccs;
    
    57
    +}
    
    58
    +
    
    59
    +
    
    60
    +IndexTable *
    
    61
    +addToIndexTable(IndexTable *it, CostCentreStack *new_ccs,
    
    62
    +                CostCentre *cc, bool back_edge) {
    
    63
    +    if (it == EMPTY_TABLE) {
    
    64
    +      it = arenaAlloc(prof_arena, sizeof(IndexTable));
    
    65
    +      it->children = allocHashTable();
    
    66
    +    }
    
    67
    +    assert(it != EMPTY_TABLE);
    
    68
    +
    
    69
    +    IndexTableNode *node;
    
    70
    +    node = arenaAlloc(prof_arena, sizeof(IndexTableNode));
    
    71
    +
    
    72
    +    node->cc = cc;
    
    73
    +    node->ccs = new_ccs;
    
    74
    +    node->back_edge = back_edge;
    
    75
    +
    
    76
    +    insertHashTable_(it->children, (StgWord) node->cc->ccID, (const void *) node, hashWord);
    
    77
    +
    
    78
    +    return it;
    
    79
    +}
    
    80
    +
    
    81
    +struct IndexTableIter_ {
    
    82
    +    struct HashIterator_ *iterator;
    
    83
    +};
    
    84
    +
    
    85
    +IndexTableIter*
    
    86
    +indexTableIterator(IndexTable *it) {
    
    87
    +    IndexTableIter *iter;
    
    88
    +    HashIterator *hashIter = NULL;
    
    89
    +    iter = arenaAlloc(prof_arena, sizeof(IndexTableIter));
    
    90
    +
    
    91
    +    if (it != EMPTY_TABLE) {
    
    92
    +        hashIter = arenaAlloc(prof_arena, sizeof(struct HashIterator_));
    
    93
    +        initHashIterator(it->children, hashIter);
    
    94
    +    }
    
    95
    +
    
    96
    +    iter->iterator = hashIter;
    
    97
    +    return iter;
    
    98
    +}
    
    99
    +
    
    100
    +int
    
    101
    +indexTableIterNext (IndexTableIter *iter) {
    
    102
    +    assert(iter != NULL);
    
    103
    +    if (iter->iterator == NULL) {
    
    104
    +      return 0;
    
    105
    +    }
    
    106
    +    return hashIteratorNext(iter->iterator);
    
    107
    +};
    
    108
    +
    
    109
    +
    
    110
    +IndexTableNode*
    
    111
    +indexTableIterItem(IndexTableIter *it) {
    
    112
    +    assert(it != NULL);
    
    113
    +    if (it->iterator == NULL) {
    
    114
    +      return EMPTY_TABLE;
    
    115
    +    }
    
    116
    +    return (IndexTableNode *) hashIteratorItem(it->iterator);
    
    117
    +}
    
    118
    +
    
    119
    +#endif /* PROFILING */

  • rts/ProfilerReport.c
    ... ... @@ -14,6 +14,7 @@
    14 14
     #include "RtsUtils.h"
    
    15 15
     #include "ProfilerReport.h"
    
    16 16
     #include "Profiling.h"
    
    17
    +#include "rts/prof/IndexTable.h"
    
    17 18
     
    
    18 19
     static  uint32_t          numDigits       ( StgInt i );
    
    19 20
     static  void              findCCSMaxLens  ( CostCentreStack const *ccs,
    
    ... ... @@ -189,7 +190,7 @@ static void
    189 190
     findCCSMaxLens(CostCentreStack const *ccs, uint32_t indent, uint32_t *max_label_len,
    
    190 191
                    uint32_t *max_module_len, uint32_t *max_src_len, uint32_t *max_id_len) {
    
    191 192
         CostCentre *cc;
    
    192
    -    IndexTable *i;
    
    193
    +    IndexTableIter *i;
    
    193 194
     
    
    194 195
         cc = ccs->cc;
    
    195 196
     
    
    ... ... @@ -198,14 +199,17 @@ findCCSMaxLens(CostCentreStack const *ccs, uint32_t indent, uint32_t *max_label_
    198 199
         *max_src_len = stg_max(*max_src_len, strlen_utf8(cc->srcloc));
    
    199 200
         *max_id_len = stg_max(*max_id_len, numDigits(ccs->ccsID));
    
    200 201
     
    
    201
    -    for (i = ccs->indexTable; i != 0; i = i->next) {
    
    202
    -        if (!i->back_edge) {
    
    203
    -            findCCSMaxLens(i->ccs, indent+1,
    
    202
    +    for ( i = indexTableIterator(ccs->indexTable)
    
    203
    +        ; indexTableIterNext(i) != 0
    
    204
    +        ; ) {
    
    205
    +        if (!indexTableIterItem(i)->back_edge) {
    
    206
    +            findCCSMaxLens(indexTableIterItem(i)->ccs, indent+1,
    
    204 207
                         max_label_len, max_module_len, max_src_len, max_id_len);
    
    205 208
             }
    
    206 209
         }
    
    207 210
     }
    
    208 211
     
    
    212
    +
    
    209 213
     static void
    
    210 214
     logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
    
    211 215
            uint32_t indent,
    
    ... ... @@ -213,7 +217,7 @@ logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
    213 217
            uint32_t max_src_len, uint32_t max_id_len)
    
    214 218
     {
    
    215 219
         CostCentre *cc;
    
    216
    -    IndexTable *i;
    
    220
    +    IndexTableIter *i;
    
    217 221
     
    
    218 222
         cc = ccs->cc;
    
    219 223
     
    
    ... ... @@ -248,9 +252,11 @@ logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
    248 252
             fprintf(prof_file, "\n");
    
    249 253
         }
    
    250 254
     
    
    251
    -    for (i = ccs->indexTable; i != 0; i = i->next) {
    
    252
    -        if (!i->back_edge) {
    
    253
    -            logCCS(prof_file, i->ccs, totals, indent+1,
    
    255
    +    for ( i = indexTableIterator(ccs->indexTable)
    
    256
    +        ; indexTableIterNext(i) != 0
    
    257
    +        ; ) {
    
    258
    +        if (!indexTableIterItem(i)->back_edge) {
    
    259
    +            logCCS(prof_file, indexTableIterItem(i)->ccs, totals, indent+1,
    
    254 260
                        max_label_len, max_module_len, max_src_len, max_id_len);
    
    255 261
             }
    
    256 262
         }
    

  • rts/ProfilerReportJson.c
    ... ... @@ -6,6 +6,7 @@
    6 6
      *
    
    7 7
      * ---------------------------------------------------------------------------*/
    
    8 8
     
    
    9
    +#include <stdio.h>
    
    9 10
     #if defined(PROFILING)
    
    10 11
     
    
    11 12
     #include "rts/PosixSource.h"
    
    ... ... @@ -14,6 +15,7 @@
    14 15
     #include "RtsUtils.h"
    
    15 16
     #include "ProfilerReportJson.h"
    
    16 17
     #include "Profiling.h"
    
    18
    +#include "rts/prof/IndexTable.h"
    
    17 19
     
    
    18 20
     #include <string.h>
    
    19 21
     
    
    ... ... @@ -232,12 +234,14 @@ logCostCentreStack(FILE *prof_file, CostCentreStack const *ccs)
    232 234
     
    
    233 235
         bool need_comma = false;
    
    234 236
         fprintf(prof_file, "\"children\": [");
    
    235
    -    for (IndexTable *i = ccs->indexTable; i != 0; i = i->next) {
    
    236
    -        if (!i->back_edge) {
    
    237
    +    for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
    
    238
    +        ; indexTableIterNext(i) != 0
    
    239
    +        ; ) {
    
    240
    +        if (!indexTableIterItem(i)->back_edge) {
    
    237 241
                 if (need_comma) {
    
    238 242
                     fprintf(prof_file, ",");
    
    239 243
                 }
    
    240
    -            logCostCentreStack(prof_file, i->ccs);
    
    244
    +            logCostCentreStack(prof_file, indexTableIterItem(i)->ccs);
    
    241 245
                 need_comma = true;
    
    242 246
             }
    
    243 247
         }
    

  • rts/Profiling.c
    ... ... @@ -22,6 +22,7 @@
    22 22
     #include "ProfilerReportJson.h"
    
    23 23
     #include "Printer.h"
    
    24 24
     #include "Capability.h"
    
    25
    +#include "rts/prof/IndexTable.h"
    
    25 26
     
    
    26 27
     #include <fs_rts.h>
    
    27 28
     #include <string.h>
    
    ... ... @@ -33,11 +34,11 @@
    33 34
     /*
    
    34 35
      * Profiling allocation arena.
    
    35 36
      */
    
    36
    -#if defined(DEBUG)
    
    37
    +// #if defined(DEBUG)
    
    37 38
     Arena *prof_arena;
    
    38
    -#else
    
    39
    -static Arena *prof_arena;
    
    40
    -#endif
    
    39
    +// #else
    
    40
    +// static Arena *prof_arena;
    
    41
    +// #endif
    
    41 42
     
    
    42 43
     /*
    
    43 44
      * Global variables used to assign unique IDs to cc's, ccs's, and
    
    ... ... @@ -119,9 +120,6 @@ static CostCentreStack * checkLoop ( CostCentreStack *ccs,
    119 120
     static  void              sortCCSTree     ( CostCentreStack *ccs );
    
    120 121
     static  CostCentreStack * pruneCCSTree    ( CostCentreStack *ccs );
    
    121 122
     static  CostCentreStack * actualPush      ( CostCentreStack *, CostCentre * );
    
    122
    -static  CostCentreStack * isInIndexTable  ( IndexTable *, CostCentre * );
    
    123
    -static  IndexTable *      addToIndexTable ( IndexTable *, CostCentreStack *,
    
    124
    -                                            CostCentre *, bool );
    
    125 123
     static  void              ccsSetSelected  ( CostCentreStack *ccs );
    
    126 124
     static  void              aggregateCCCosts( CostCentreStack *ccs );
    
    127 125
     static  void              registerCC      ( CostCentre *cc );
    
    ... ... @@ -552,6 +550,7 @@ pushCostCentre (CostCentreStack *ccs, CostCentre *cc)
    552 550
                     // not in the IndexTable, now we take the lock:
    
    553 551
                     ACQUIRE_LOCK(&ccs_mutex);
    
    554 552
     
    
    553
    +                // TODO @fendor: this check can never succeed
    
    555 554
                     if (ccs->indexTable != ixtable)
    
    556 555
                     {
    
    557 556
                         // someone modified ccs->indexTable while
    
    ... ... @@ -595,6 +594,7 @@ pushCostCentre (CostCentreStack *ccs, CostCentre *cc)
    595 594
         return ret;
    
    596 595
     }
    
    597 596
     
    
    597
    +// ALSO LINEAR
    
    598 598
     static CostCentreStack *
    
    599 599
     checkLoop (CostCentreStack *ccs, CostCentre *cc)
    
    600 600
     {
    
    ... ... @@ -621,13 +621,13 @@ static CostCentreStack *
    621 621
     actualPush_ (CostCentreStack *ccs, CostCentre *cc, CostCentreStack *new_ccs)
    
    622 622
     {
    
    623 623
         /* assign values to each member of the structure */
    
    624
    +    new_ccs->indexTable = 0;
    
    624 625
         new_ccs->ccsID = CCS_ID++;
    
    625 626
         new_ccs->cc = cc;
    
    626 627
         new_ccs->prevStack = ccs;
    
    627 628
         new_ccs->root = ccs->root;
    
    628 629
         new_ccs->depth = ccs->depth + 1;
    
    629 630
     
    
    630
    -    new_ccs->indexTable = EMPTY_TABLE;
    
    631 631
     
    
    632 632
         /* Initialise the various _scc_ counters to zero
    
    633 633
          */
    
    ... ... @@ -652,38 +652,6 @@ actualPush_ (CostCentreStack *ccs, CostCentre *cc, CostCentreStack *new_ccs)
    652 652
         return new_ccs;
    
    653 653
     }
    
    654 654
     
    
    655
    -
    
    656
    -static CostCentreStack *
    
    657
    -isInIndexTable(IndexTable *it, CostCentre *cc)
    
    658
    -{
    
    659
    -    while (it!=EMPTY_TABLE)
    
    660
    -    {
    
    661
    -        if (it->cc == cc)
    
    662
    -            return it->ccs;
    
    663
    -        else
    
    664
    -            it = it->next;
    
    665
    -    }
    
    666
    -
    
    667
    -    /* otherwise we never found it so return EMPTY_TABLE */
    
    668
    -    return EMPTY_TABLE;
    
    669
    -}
    
    670
    -
    
    671
    -
    
    672
    -static IndexTable *
    
    673
    -addToIndexTable (IndexTable *it, CostCentreStack *new_ccs,
    
    674
    -                 CostCentre *cc, bool back_edge)
    
    675
    -{
    
    676
    -    IndexTable *new_it;
    
    677
    -
    
    678
    -    new_it = arenaAlloc(prof_arena, sizeof(IndexTable));
    
    679
    -
    
    680
    -    new_it->cc = cc;
    
    681
    -    new_it->ccs = new_ccs;
    
    682
    -    new_it->next = it;
    
    683
    -    new_it->back_edge = back_edge;
    
    684
    -    return new_it;
    
    685
    -}
    
    686
    -
    
    687 655
     /* -----------------------------------------------------------------------------
    
    688 656
        Generating a time & allocation profiling report.
    
    689 657
        -------------------------------------------------------------------------- */
    
    ... ... @@ -744,9 +712,11 @@ countTickss_(CostCentreStack const *ccs, ProfilerTotals *totals)
    744 712
             totals->total_alloc += ccs->mem_alloc;
    
    745 713
             totals->total_prof_ticks += ccs->time_ticks;
    
    746 714
         }
    
    747
    -    for (IndexTable *i = ccs->indexTable; i != NULL; i = i->next) {
    
    748
    -        if (!i->back_edge) {
    
    749
    -            countTickss_(i->ccs, totals);
    
    715
    +    for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
    
    716
    +        ; indexTableIterNext(i) != 0
    
    717
    +        ; ) {
    
    718
    +        if (!indexTableIterItem(i)->back_edge) {
    
    719
    +            countTickss_(indexTableIterItem(i)->ccs, totals);
    
    750 720
             }
    
    751 721
         }
    
    752 722
     }
    
    ... ... @@ -767,18 +737,19 @@ countTickss(CostCentreStack const *ccs)
    767 737
     static void
    
    768 738
     inheritCosts(CostCentreStack *ccs)
    
    769 739
     {
    
    770
    -    IndexTable *i;
    
    771 740
     
    
    772 741
         if (ignoreCCS(ccs)) { return; }
    
    773 742
     
    
    774 743
         ccs->inherited_ticks += ccs->time_ticks;
    
    775 744
         ccs->inherited_alloc += ccs->mem_alloc;
    
    776 745
     
    
    777
    -    for (i = ccs->indexTable; i != NULL; i = i->next)
    
    778
    -        if (!i->back_edge) {
    
    779
    -            inheritCosts(i->ccs);
    
    780
    -            ccs->inherited_ticks += i->ccs->inherited_ticks;
    
    781
    -            ccs->inherited_alloc += i->ccs->inherited_alloc;
    
    746
    +    for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
    
    747
    +        ; indexTableIterNext(i) != 0
    
    748
    +        ; )
    
    749
    +        if (!indexTableIterItem(i)->back_edge) {
    
    750
    +            inheritCosts(indexTableIterItem(i)->ccs);
    
    751
    +            ccs->inherited_ticks += indexTableIterItem(i)->ccs->inherited_ticks;
    
    752
    +            ccs->inherited_alloc += indexTableIterItem(i)->ccs->inherited_alloc;
    
    782 753
             }
    
    783 754
     
    
    784 755
         return;
    
    ... ... @@ -787,14 +758,14 @@ inheritCosts(CostCentreStack *ccs)
    787 758
     static void
    
    788 759
     aggregateCCCosts( CostCentreStack *ccs )
    
    789 760
     {
    
    790
    -    IndexTable *i;
    
    791
    -
    
    792 761
         ccs->cc->mem_alloc += ccs->mem_alloc;
    
    793 762
         ccs->cc->time_ticks += ccs->time_ticks;
    
    794 763
     
    
    795
    -    for (i = ccs->indexTable; i != 0; i = i->next) {
    
    796
    -        if (!i->back_edge) {
    
    797
    -            aggregateCCCosts(i->ccs);
    
    764
    +    for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
    
    765
    +        ; indexTableIterNext(i) != 0
    
    766
    +        ; ) {
    
    767
    +        if (!indexTableIterItem(i)->back_edge) {
    
    768
    +            aggregateCCCosts(indexTableIterItem(i)->ccs);
    
    798 769
             }
    
    799 770
         }
    
    800 771
     }
    
    ... ... @@ -806,19 +777,22 @@ aggregateCCCosts( CostCentreStack *ccs )
    806 777
     static CostCentreStack *
    
    807 778
     pruneCCSTree (CostCentreStack *ccs)
    
    808 779
     {
    
    809
    -    CostCentreStack *ccs1;
    
    810
    -    IndexTable *i, **prev;
    
    780
    +    // CostCentreStack *ccs1;
    
    781
    +    // IndexTable *i, **prev;
    
    811 782
     
    
    812
    -    prev = &ccs->indexTable;
    
    813
    -    for (i = ccs->indexTable; i != 0; i = i->next) {
    
    814
    -        if (i->back_edge) { continue; }
    
    783
    +    // prev = &ccs->indexTable;
    
    784
    +    for ( IndexTableIter *i = indexTableIterator(ccs->indexTable)
    
    785
    +        ; indexTableIterNext(i) != 0
    
    786
    +        ; ) {
    
    787
    +        if (indexTableIterItem(i)->back_edge) { continue; }
    
    815 788
     
    
    816
    -        ccs1 = pruneCCSTree(i->ccs);
    
    817
    -        if (ccs1 == NULL) {
    
    818
    -            *prev = i->next;
    
    819
    -        } else {
    
    820
    -            prev = &(i->next);
    
    821
    -        }
    
    789
    +        // TODO: @fendor implement pruning
    
    790
    +        // ccs1 = pruneCCSTree(indexTableIterItem(i)->ccs);
    
    791
    +        // if (ccs1 == NULL) {
    
    792
    +        //     *prev = i->next;
    
    793
    +        // } else {
    
    794
    +        //     prev = &(i->next);
    
    795
    +        // }
    
    822 796
         }
    
    823 797
     
    
    824 798
         if ( (RtsFlags.CcFlags.doCostCentres >= COST_CENTRES_ALL
    
    ... ... @@ -833,59 +807,62 @@ pruneCCSTree (CostCentreStack *ccs)
    833 807
         }
    
    834 808
     }
    
    835 809
     
    
    836
    -static IndexTable*
    
    837
    -insertIndexTableInSortedList(IndexTable* tbl, IndexTable* sortedList)
    
    838
    -{
    
    839
    -    StgWord tbl_ticks = tbl->ccs->scc_count;
    
    840
    -    char*   tbl_label = tbl->ccs->cc->label;
    
    841
    -
    
    842
    -    IndexTable *prev   = NULL;
    
    843
    -    IndexTable *cursor = sortedList;
    
    844
    -
    
    845
    -    while (cursor != NULL) {
    
    846
    -        StgWord cursor_ticks = cursor->ccs->scc_count;
    
    847
    -        char*   cursor_label = cursor->ccs->cc->label;
    
    848
    -
    
    849
    -        if (tbl_ticks > cursor_ticks ||
    
    850
    -                (tbl_ticks == cursor_ticks && strcmp(tbl_label, cursor_label) < 0)) {
    
    851
    -            if (prev == NULL) {
    
    852
    -                tbl->next = sortedList;
    
    853
    -                return tbl;
    
    854
    -            } else {
    
    855
    -                prev->next = tbl;
    
    856
    -                tbl->next = cursor;
    
    857
    -                return sortedList;
    
    858
    -            }
    
    859
    -        } else {
    
    860
    -            prev   = cursor;
    
    861
    -            cursor = cursor->next;
    
    862
    -        }
    
    863
    -    }
    
    864
    -
    
    865
    -    prev->next = tbl;
    
    866
    -    return sortedList;
    
    867
    -}
    
    810
    +// static IndexTable*
    
    811
    +// insertIndexTableInSortedList(IndexTable* tbl, IndexTable* sortedList)
    
    812
    +// {
    
    813
    +//     StgWord tbl_ticks = tbl->ccs->scc_count;
    
    814
    +//     char*   tbl_label = tbl->ccs->cc->label;
    
    815
    +
    
    816
    +//     IndexTable *prev   = NULL;
    
    817
    +//     IndexTable *cursor = sortedList;
    
    818
    +
    
    819
    +//     while (cursor != NULL) {
    
    820
    +//         StgWord cursor_ticks = cursor->ccs->scc_count;
    
    821
    +//         char*   cursor_label = cursor->ccs->cc->label;
    
    822
    +
    
    823
    +//         if (tbl_ticks > cursor_ticks ||
    
    824
    +//                 (tbl_ticks == cursor_ticks && strcmp(tbl_label, cursor_label) < 0)) {
    
    825
    +//             if (prev == NULL) {
    
    826
    +//                 tbl->next = sortedList;
    
    827
    +//                 return tbl;
    
    828
    +//             } else {
    
    829
    +//                 prev->next = tbl;
    
    830
    +//                 tbl->next = cursor;
    
    831
    +//                 return sortedList;
    
    832
    +//             }
    
    833
    +//         } else {
    
    834
    +//             prev   = cursor;
    
    835
    +//             cursor = cursor->next;
    
    836
    +//         }
    
    837
    +//     }
    
    838
    +
    
    839
    +//     prev->next = tbl;
    
    840
    +//     return sortedList;
    
    841
    +// }
    
    868 842
     
    
    869 843
     static void
    
    870 844
     sortCCSTree(CostCentreStack *ccs)
    
    871 845
     {
    
    872 846
         if (ccs->indexTable == NULL) return;
    
    873 847
     
    
    874
    -    for (IndexTable *tbl = ccs->indexTable; tbl != NULL; tbl = tbl->next)
    
    875
    -        if (!tbl->back_edge)
    
    876
    -            sortCCSTree(tbl->ccs);
    
    848
    +    for ( IndexTableIter *iter = indexTableIterator(ccs->indexTable)
    
    849
    +        ; indexTableIterNext(iter) != 0
    
    850
    +        ; )
    
    851
    +        if (!indexTableIterItem(iter)->back_edge)
    
    852
    +            sortCCSTree(indexTableIterItem(iter)->ccs);
    
    877 853
     
    
    878 854
         IndexTable *sortedList    = ccs->indexTable;
    
    879
    -    IndexTable *nonSortedList = sortedList->next;
    
    880
    -    sortedList->next = NULL;
    
    881
    -
    
    882
    -    while (nonSortedList != NULL)
    
    883
    -    {
    
    884
    -        IndexTable *nonSortedTail = nonSortedList->next;
    
    885
    -        nonSortedList->next = NULL;
    
    886
    -        sortedList = insertIndexTableInSortedList(nonSortedList, sortedList);
    
    887
    -        nonSortedList = nonSortedTail;
    
    888
    -    }
    
    855
    +    // TODO @fendor: reimplement sorting
    
    856
    +    // IndexTable *nonSortedList = sortedList->next;
    
    857
    +    // sortedList->next = NULL;
    
    858
    +
    
    859
    +    // while (nonSortedList != NULL)
    
    860
    +    // {
    
    861
    +    //     IndexTable *nonSortedTail = nonSortedList->next;
    
    862
    +    //     nonSortedList->next = NULL;
    
    863
    +    //     sortedList = insertIndexTableInSortedList(nonSortedList, sortedList);
    
    864
    +    //     nonSortedList = nonSortedTail;
    
    865
    +    // }
    
    889 866
     
    
    890 867
         ccs->indexTable = sortedList;
    
    891 868
     }
    

  • rts/Profiling.h
    ... ... @@ -11,9 +11,9 @@
    11 11
     #include <stdio.h>
    
    12 12
     
    
    13 13
     #include "Rts.h"
    
    14
    -#if defined(DEBUG)
    
    14
    +// #if defined(DEBUG)
    
    15 15
     #include "Arena.h"
    
    16
    -#endif
    
    16
    +// #endif
    
    17 17
     
    
    18 18
     #include "BeginPrivate.h"
    
    19 19
     
    
    ... ... @@ -49,9 +49,9 @@ void fprintCCS_stderr (CostCentreStack *ccs, StgClosure *exception, StgTSO *tso)
    49 49
     bool ignoreCCS (CostCentreStack const *ccs);
    
    50 50
     bool ignoreCC (CostCentre const *cc);
    
    51 51
     
    
    52
    -#if defined(DEBUG)
    
    53 52
     extern Arena *prof_arena;
    
    54 53
     
    
    54
    +#if defined(DEBUG)
    
    55 55
     void debugCCS( CostCentreStack *ccs );
    
    56 56
     #endif
    
    57 57
     
    

  • rts/StaticPtrTable.c
    ... ... @@ -24,7 +24,7 @@ static Mutex spt_lock;
    24 24
     STATIC_INLINE int hashFingerprint(const HashTable *table, StgWord key) {
    
    25 25
       const StgWord64* ptr = (StgWord64*) key;
    
    26 26
       // Take half of the key to compute the hash.
    
    27
    -  return hashWord(table, *(ptr + 1));
    
    27
    +  return hashAddress(table, *(ptr + 1));
    
    28 28
     }
    
    29 29
     
    
    30 30
     /// Comparison function for the SPT.
    

  • rts/include/Rts.h
    ... ... @@ -231,6 +231,7 @@ void _warnFail(const char *filename, unsigned int linenum);
    231 231
     
    
    232 232
     /* Profiling information */
    
    233 233
     #include "rts/prof/CCS.h"
    
    234
    +#include "rts/prof/IndexTable.h"
    
    234 235
     #include "rts/prof/Heap.h"
    
    235 236
     #include "rts/prof/LDV.h"
    
    236 237
     
    

  • rts/include/rts/prof/CCS.h
    ... ... @@ -99,27 +99,6 @@ void startProfTimer ( void );
    99 99
     /* Constants used to set is_caf flag on CostCentres */
    
    100 100
     #define CC_IS_CAF      true
    
    101 101
     #define CC_NOT_CAF     false
    
    102
    -/* -----------------------------------------------------------------------------
    
    103
    - * Data Structures
    
    104
    - * ---------------------------------------------------------------------------*/
    
    105
    -
    
    106
    -// IndexTable is the list of children of a CCS. (Alternatively it is a
    
    107
    -// cache of the results of pushing onto a CCS, so that the second and
    
    108
    -// subsequent times we push a certain CC on a CCS we get the same
    
    109
    -// result).
    
    110
    -
    
    111
    -typedef struct IndexTable_ {
    
    112
    -    // Just a linked list of (cc, ccs) pairs, where the `ccs` is the result of
    
    113
    -    // pushing `cc` to the owner of the index table (another CostCentreStack).
    
    114
    -    CostCentre *cc;
    
    115
    -    CostCentreStack *ccs;
    
    116
    -    struct IndexTable_ *next;
    
    117
    -    // back_edge is true when `cc` is already in the stack, so pushing it
    
    118
    -    // truncates or drops (see RECURSION_DROPS and RECURSION_TRUNCATES in
    
    119
    -    // Profiling.c).
    
    120
    -    bool back_edge;
    
    121
    -} IndexTable;
    
    122
    -
    
    123 102
     
    
    124 103
     /* -----------------------------------------------------------------------------
    
    125 104
        Pre-defined cost centres and cost centre stacks
    

  • rts/include/rts/prof/IndexTable.h
    1
    +#pragma once
    
    2
    +
    
    3
    +/* -----------------------------------------------------------------------------
    
    4
    + * Data Structures
    
    5
    + * ---------------------------------------------------------------------------*/
    
    6
    +
    
    7
    +// IndexTable is the list of children of a CCS. (Alternatively it is a
    
    8
    +// cache of the results of pushing onto a CCS, so that the second and
    
    9
    +// subsequent times we push a certain CC on a CCS we get the same
    
    10
    +// result).
    
    11
    +
    
    12
    +typedef struct IndexTableNode_ {
    
    13
    +    // Just a linked list of (cc, ccs) pairs, where the `ccs` is the result of
    
    14
    +    // pushing `cc` to the owner of the index table (another CostCentreStack).
    
    15
    +    CostCentre *cc;
    
    16
    +    CostCentreStack *ccs;
    
    17
    +    // back_edge is true when `cc` is already in the stack, so pushing it
    
    18
    +    // truncates or drops (see RECURSION_DROPS and RECURSION_TRUNCATES in
    
    19
    +    // Profiling.c).
    
    20
    +    bool back_edge;
    
    21
    +} IndexTableNode;
    
    22
    +
    
    23
    +typedef struct IndexTableNode_ IndexTableNode;
    
    24
    +
    
    25
    +typedef struct IndexTable_ {
    
    26
    +    // IndexTableNode *node;
    
    27
    +    // // Just a linked list of (cc, ccs) pairs, where the `ccs` is the result of
    
    28
    +    // // pushing `cc` to the owner of the index table (another CostCentreStack).
    
    29
    +    // CostCentre *cc;
    
    30
    +    // CostCentreStack *ccs;
    
    31
    +    // // back_edge is true when `cc` is already in the stack, so pushing it
    
    32
    +    // // truncates or drops (see RECURSION_DROPS and RECURSION_TRUNCATES in
    
    33
    +    // // Profiling.c).
    
    34
    +    // bool back_edge;
    
    35
    +    struct hashtable *children;
    
    36
    +} IndexTable;
    
    37
    +
    
    38
    +typedef struct IndexTable_ IndexTable;
    
    39
    +
    
    40
    +IndexTable *      allocateIndexTable( void );
    
    41
    +void              freeIndexTable( IndexTable * );
    
    42
    +CostCentreStack * isInIndexTable  ( IndexTable *, CostCentre * );
    
    43
    +IndexTable *      addToIndexTable ( IndexTable *, CostCentreStack *,
    
    44
    +                                    CostCentre *, bool );
    
    45
    +
    
    46
    +typedef struct IndexTableIter_ IndexTableIter;
    
    47
    +
    
    48
    +
    
    49
    +IndexTableIter* indexTableIterator ( IndexTable * );
    
    50
    +int             indexTableIterNext ( IndexTableIter * );
    
    51
    +IndexTableNode* indexTableIterItem ( IndexTableIter * );

  • rts/rts.cabal
    ... ... @@ -322,6 +322,7 @@ library
    322 322
                             rts/Utils.h
    
    323 323
                             rts/prof/CCS.h
    
    324 324
                             rts/prof/Heap.h
    
    325
    +                        rts/prof/IndexTable.h
    
    325 326
                             rts/prof/LDV.h
    
    326 327
                             rts/storage/Block.h
    
    327 328
                             rts/storage/ClosureMacros.h
    
    ... ... @@ -436,6 +437,7 @@ library
    436 437
                      ProfilerReport.c
    
    437 438
                      ProfilerReportJson.c
    
    438 439
                      Profiling.c
    
    440
    +                 IndexTable.c
    
    439 441
                      IPE.c
    
    440 442
                      Proftimer.c
    
    441 443
                      RaiseAsync.c
    

  • testsuite/tests/perf/should_run/T26147.stdout
    1
    -Test value: 0
    
    2
    -Test value: 1
    
    3
    -Test value: 2
    
    4
    -Test value: 3
    
    5
    -Test value: 4
    
    6
    -Test value: 5
    
    7
    -Test value: 6
    
    8
    -Test value: 7
    
    9
    -Test value: 8
    
    10
    -Test value: 9
    
    11
    -Test value: 10
    
    12
    -Test value: 11
    
    13
    -Test value: 12
    
    14
    -Test value: 13
    
    15
    -Test value: 14
    
    16
    -Test value: 15
    
    17
    -Test value: 16
    
    18
    -Test value: 17
    
    19
    -Test value: 18
    
    20
    -Test value: 19
    
    21
    -Test value: 20
    
    22
    -Test value: 21
    
    23
    -Test value: 22
    
    24
    -Test value: 23
    
    25
    -Test value: 24
    
    26
    -Test value: 25
    
    27
    -Test value: 26
    
    28
    -Test value: 27
    
    29
    -Test value: 28
    
    30
    -Test value: 29
    
    31
    -Test value: 30
    
    32
    -Test value: 31
    
    33
    -Test value: 32
    
    34
    -Test value: 33
    
    35
    -Test value: 34
    
    36
    -Test value: 35
    
    37
    -Test value: 36
    
    38
    -Test value: 37
    
    39
    -Test value: 38
    
    40
    -Test value: 39
    
    41
    -Test value: 40
    
    42
    -Test value: 41
    
    43
    -Test value: 42
    
    44
    -Test value: 43
    
    45
    -Test value: 44
    
    46
    -Test value: 45
    
    47
    -Test value: 46
    
    48
    -Test value: 47
    
    49
    -Test value: 48
    
    50
    -Test value: 49
    
    51
    -Test value: 50
    
    52
    -Test value: 51
    
    53
    -Test value: 52
    
    54
    -Test value: 53
    
    55
    -Test value: 54
    
    56
    -Test value: 55
    
    57
    -Test value: 56
    
    58
    -Test value: 57
    
    59
    -Test value: 58
    
    60
    -Test value: 59
    
    61
    -Test value: 60
    
    62
    -Test value: 61
    
    63
    -Test value: 62
    
    64
    -Test value: 63
    
    65
    -Test value: 64
    
    66
    -Test value: 65
    
    67
    -Test value: 66
    
    68
    -Test value: 67
    
    69
    -Test value: 68
    
    70
    -Test value: 69
    
    71
    -Test value: 70
    
    72
    -Test value: 71
    
    73
    -Test value: 72
    
    74
    -Test value: 73
    
    75
    -Test value: 74
    
    76
    -Test value: 75
    
    77
    -Test value: 76
    
    78
    -Test value: 77
    
    79
    -Test value: 78
    
    80
    -Test value: 79
    
    81
    -Test value: 80
    
    82
    -Test value: 81
    
    83
    -Test value: 82
    
    84
    -Test value: 83
    
    85
    -Test value: 84
    
    86
    -Test value: 85
    
    87
    -Test value: 86
    
    88
    -Test value: 87
    
    89
    -Test value: 88
    
    90
    -Test value: 89
    
    91
    -Test value: 90
    
    92
    -Test value: 91
    
    93
    -Test value: 92
    
    94
    -Test value: 93
    
    95
    -Test value: 94
    
    96
    -Test value: 95
    
    97
    -Test value: 96
    
    98
    -Test value: 97
    
    99
    -Test value: 98
    
    100
    -Test value: 99
    
    101
    -Test value: 100
    
    102
    -Test value: 101
    
    103
    -Test value: 102
    
    104
    -Test value: 103
    
    105
    -Test value: 104
    
    106
    -Test value: 105
    
    107
    -Test value: 106
    
    108
    -Test value: 107
    
    109
    -Test value: 108
    
    110
    -Test value: 109
    
    111
    -Test value: 110
    
    112
    -Test value: 111
    
    113
    -Test value: 112
    
    114
    -Test value: 113
    
    115
    -Test value: 114
    
    116
    -Test value: 115
    
    117
    -Test value: 116
    
    118
    -Test value: 117
    
    119
    -Test value: 118
    
    120
    -Test value: 119
    
    121
    -Test value: 120
    
    122
    -Test value: 121
    
    123
    -Test value: 122
    
    124
    -Test value: 123
    
    125
    -Test value: 124
    
    126
    -Test value: 125
    
    127
    -Test value: 126
    
    128
    -Test value: 127
    
    129
    -Test value: 128
    
    130
    -Test value: 129
    
    131
    -Test value: 130
    
    132
    -Test value: 131
    
    133
    -Test value: 132
    
    134
    -Test value: 133
    
    135
    -Test value: 134
    
    136
    -Test value: 135
    
    137
    -Test value: 136
    
    138
    -Test value: 137
    
    139
    -Test value: 138
    
    140
    -Test value: 139
    
    141
    -Test value: 140
    
    142
    -Test value: 141
    
    143
    -Test value: 142
    
    144
    -Test value: 143
    
    145
    -Test value: 144
    
    146
    -Test value: 145
    
    147
    -Test value: 146
    
    148
    -Test value: 147
    
    149
    -Test value: 148
    
    150
    -Test value: 149
    
    151
    -Test value: 150
    
    152
    -Test value: 151
    
    153
    -Test value: 152
    
    154
    -Test value: 153
    
    155
    -Test value: 154
    
    156
    -Test value: 155
    
    157
    -Test value: 156
    
    158
    -Test value: 157
    
    159
    -Test value: 158
    
    160
    -Test value: 159
    
    161
    -Test value: 160
    
    162
    -Test value: 161
    
    163
    -Test value: 162
    
    164
    -Test value: 163
    
    165
    -Test value: 164
    
    166
    -Test value: 165
    
    167
    -Test value: 166
    
    168
    -Test value: 167
    
    169
    -Test value: 168
    
    170
    -Test value: 169
    
    171
    -Test value: 170
    
    172
    -Test value: 171
    
    173
    -Test value: 172
    
    174
    -Test value: 173
    
    175
    -Test value: 174
    
    176
    -Test value: 175
    
    177
    -Test value: 176
    
    178
    -Test value: 177
    
    179
    -Test value: 178
    
    180
    -Test value: 179
    
    181
    -Test value: 180
    
    182
    -Test value: 181
    
    183
    -Test value: 182
    
    184
    -Test value: 183
    
    185
    -Test value: 184
    
    186
    -Test value: 185
    
    187
    -Test value: 186
    
    188
    -Test value: 187
    
    189
    -Test value: 188
    
    190
    -Test value: 189
    
    191
    -Test value: 190
    
    192
    -Test value: 191
    
    193
    -Test value: 192
    
    194
    -Test value: 193
    
    195
    -Test value: 194
    
    196
    -Test value: 195
    
    197
    -Test value: 196
    
    198
    -Test value: 197
    
    199
    -Test value: 198
    
    200
    -Test value: 199
    
    201
    -Test value: 200
    
    202
    -Test value: 201
    
    203
    -Test value: 202
    
    204
    -Test value: 203
    
    205
    -Test value: 204
    
    206
    -Test value: 205
    
    207
    -Test value: 206
    
    208
    -Test value: 207
    
    209
    -Test value: 208
    
    210
    -Test value: 209
    
    211
    -Test value: 210
    
    212
    -Test value: 211
    
    213
    -Test value: 212
    
    214
    -Test value: 213
    
    215
    -Test value: 214
    
    216
    -Test value: 215
    
    217
    -Test value: 216
    
    218
    -Test value: 217
    
    219
    -Test value: 218
    
    220
    -Test value: 219
    
    221
    -Test value: 220
    
    222
    -Test value: 221
    
    223
    -Test value: 222
    
    224
    -Test value: 223
    
    225
    -Test value: 224
    
    226
    -Test value: 225
    
    227
    -Test value: 226
    
    228
    -Test value: 227
    
    229
    -Test value: 228
    
    230
    -Test value: 229
    
    231
    -Test value: 230
    
    232
    -Test value: 231
    
    233
    -Test value: 232
    
    234
    -Test value: 233
    
    235
    -Test value: 234
    
    236
    -Test value: 235
    
    237
    -Test value: 236
    
    238
    -Test value: 237
    
    239
    -Test value: 238
    
    240
    -Test value: 239
    
    241
    -Test value: 240
    
    242
    -Test value: 241
    
    243
    -Test value: 242
    
    244
    -Test value: 243
    
    245
    -Test value: 244
    
    246
    -Test value: 245
    
    247
    -Test value: 246
    
    248
    -Test value: 247
    
    249
    -Test value: 248
    
    250
    -Test value: 249
    
    251
    -Test value: 250
    
    252
    -Test value: 251
    
    253
    -Test value: 252
    
    254
    -Test value: 253
    
    255
    -Test value: 254
    
    256
    -Test value: 255
    
    257
    -Test value: 256
    
    258
    -Test value: 257
    
    259
    -Test value: 258
    
    260
    -Test value: 259
    
    261
    -Test value: 260
    
    262
    -Test value: 261
    
    263
    -Test value: 262
    
    264
    -Test value: 263
    
    265
    -Test value: 264
    
    266
    -Test value: 265
    
    267
    -Test value: 266
    
    268
    -Test value: 267
    
    269
    -Test value: 268
    
    270
    -Test value: 269
    
    271
    -Test value: 270
    
    272
    -Test value: 271
    
    273
    -Test value: 272
    
    274
    -Test value: 273
    
    275
    -Test value: 274
    
    276
    -Test value: 275
    
    277
    -Test value: 276
    
    278
    -Test value: 277
    
    279
    -Test value: 278
    
    280
    -Test value: 279
    
    281
    -Test value: 280
    
    282
    -Test value: 281
    
    283
    -Test value: 282
    
    284
    -Test value: 283
    
    285
    -Test value: 284
    
    286
    -Test value: 285
    
    287
    -Test value: 286
    
    288
    -Test value: 287
    
    289
    -Test value: 288
    
    290
    -Test value: 289
    
    291
    -Test value: 290
    
    292
    -Test value: 291
    
    293
    -Test value: 292
    
    294
    -Test value: 293
    
    295
    -Test value: 294
    
    296
    -Test value: 295
    
    297
    -Test value: 296
    
    298
    -Test value: 297
    
    299
    -Test value: 298
    
    300
    -Test value: 299
    
    301
    -Test value: 300
    
    302
    -Test value: 301
    
    303
    -Test value: 302
    
    304
    -Test value: 303
    
    305
    -Test value: 304
    
    306
    -Test value: 305
    
    307
    -Test value: 306
    
    308
    -Test value: 307
    
    309
    -Test value: 308
    
    310
    -Test value: 309
    
    311
    -Test value: 310
    
    312
    -Test value: 311
    
    313
    -Test value: 312
    
    314
    -Test value: 313
    
    315
    -Test value: 314
    
    316
    -Test value: 315
    
    317
    -Test value: 316
    
    318
    -Test value: 317
    
    319
    -Test value: 318
    
    320
    -Test value: 319
    
    321
    -Test value: 320
    
    322
    -Test value: 321
    
    323
    -Test value: 322
    
    324
    -Test value: 323
    
    325
    -Test value: 324
    
    326
    -Test value: 325
    
    327
    -Test value: 326
    
    328
    -Test value: 327
    
    329
    -Test value: 328
    
    330
    -Test value: 329
    
    331
    -Test value: 330
    
    332
    -Test value: 331
    
    333
    -Test value: 332
    
    334
    -Test value: 333
    
    335
    -Test value: 334
    
    336
    -Test value: 335
    
    337
    -Test value: 336
    
    338
    -Test value: 337
    
    339
    -Test value: 338
    
    340
    -Test value: 339
    
    341
    -Test value: 340
    
    342
    -Test value: 341
    
    343
    -Test value: 342
    
    344
    -Test value: 343
    
    345
    -Test value: 344
    
    346
    -Test value: 345
    
    347
    -Test value: 346
    
    348
    -Test value: 347
    
    349
    -Test value: 348
    
    350
    -Test value: 349
    
    351
    -Test value: 350
    
    352
    -Test value: 351
    
    353
    -Test value: 352
    
    354
    -Test value: 353
    
    355
    -Test value: 354
    
    356
    -Test value: 355
    
    357
    -Test value: 356
    
    358
    -Test value: 357
    
    359
    -Test value: 358
    
    360
    -Test value: 359
    
    361
    -Test value: 360
    
    362
    -Test value: 361
    
    363
    -Test value: 362
    
    364
    -Test value: 363
    
    365
    -Test value: 364
    
    366
    -Test value: 365
    
    367
    -Test value: 366
    
    368
    -Test value: 367
    
    369
    -Test value: 368
    
    370
    -Test value: 369
    
    371
    -Test value: 370
    
    372
    -Test value: 371
    
    373
    -Test value: 372
    
    374
    -Test value: 373
    
    375
    -Test value: 374
    
    376
    -Test value: 375
    
    377
    -Test value: 376
    
    378
    -Test value: 377
    
    379
    -Test value: 378
    
    380
    -Test value: 379
    
    381
    -Test value: 380
    
    382
    -Test value: 381
    
    383
    -Test value: 382
    
    384
    -Test value: 383
    
    385
    -Test value: 384
    
    386
    -Test value: 385
    
    387
    -Test value: 386
    
    388
    -Test value: 387
    
    389
    -Test value: 388
    
    390
    -Test value: 389
    
    391
    -Test value: 390
    
    392
    -Test value: 391
    
    393
    -Test value: 392
    
    394
    -Test value: 393
    
    395
    -Test value: 394
    
    396
    -Test value: 395
    
    397
    -Test value: 396
    
    398
    -Test value: 397
    
    399
    -Test value: 398
    
    400
    -Test value: 399
    
    401
    -Test value: 400
    
    402
    -Test value: 401
    
    403
    -Test value: 402
    
    404
    -Test value: 403
    
    405
    -Test value: 404
    
    406
    -Test value: 405
    
    407
    -Test value: 406
    
    408
    -Test value: 407
    
    409
    -Test value: 408
    
    410
    -Test value: 409
    
    411
    -Test value: 410
    
    412
    -Test value: 411
    
    413
    -Test value: 412
    
    414
    -Test value: 413
    
    415
    -Test value: 414
    
    416
    -Test value: 415
    
    417
    -Test value: 416
    
    418
    -Test value: 417
    
    419
    -Test value: 418
    
    420
    -Test value: 419
    
    421
    -Test value: 420
    
    422
    -Test value: 421
    
    423
    -Test value: 422
    
    424
    -Test value: 423
    
    425
    -Test value: 424
    
    426
    -Test value: 425
    
    427
    -Test value: 426
    
    428
    -Test value: 427
    
    429
    -Test value: 428
    
    430
    -Test value: 429
    
    431
    -Test value: 430
    
    432
    -Test value: 431
    
    433
    -Test value: 432
    
    434
    -Test value: 433
    
    435
    -Test value: 434
    
    436
    -Test value: 435
    
    437
    -Test value: 436
    
    438
    -Test value: 437
    
    439
    -Test value: 438
    
    440
    -Test value: 439
    
    441
    -Test value: 440
    
    442
    -Test value: 441
    
    443
    -Test value: 442
    
    444
    -Test value: 443
    
    445
    -Test value: 444
    
    446
    -Test value: 445
    
    447
    -Test value: 446
    
    448
    -Test value: 447
    
    449
    -Test value: 448
    
    450
    -Test value: 449
    
    451
    -Test value: 450
    
    452
    -Test value: 451
    
    453
    -Test value: 452
    
    454
    -Test value: 453
    
    455
    -Test value: 454
    
    456
    -Test value: 455
    
    457
    -Test value: 456
    
    458
    -Test value: 457
    
    459
    -Test value: 458
    
    460
    -Test value: 459
    
    461
    -Test value: 460
    
    462
    -Test value: 461
    
    463
    -Test value: 462
    
    464
    -Test value: 463
    
    465
    -Test value: 464
    
    466
    -Test value: 465
    
    467
    -Test value: 466
    
    468
    -Test value: 467
    
    469
    -Test value: 468
    
    470
    -Test value: 469
    
    471
    -Test value: 470
    
    472
    -Test value: 471
    
    473
    -Test value: 472
    
    474
    -Test value: 473
    
    475
    -Test value: 474
    
    476
    -Test value: 475
    
    477
    -Test value: 476
    
    478
    -Test value: 477
    
    479
    -Test value: 478
    
    480
    -Test value: 479
    
    481
    -Test value: 480
    
    482
    -Test value: 481
    
    483
    -Test value: 482
    
    484
    -Test value: 483
    
    485
    -Test value: 484
    
    486
    -Test value: 485
    
    487
    -Test value: 486
    
    488
    -Test value: 487
    
    489
    -Test value: 488
    
    490
    -Test value: 489
    
    491
    -Test value: 490
    
    492
    -Test value: 491
    
    493
    -Test value: 492
    
    494
    -Test value: 493
    
    495
    -Test value: 494
    
    496
    -Test value: 495
    
    497
    -Test value: 496
    
    498
    -Test value: 497
    
    499
    -Test value: 498
    
    500
    -Test value: 499
    
    501
    -Test value: 500
    
    502
    -Test value: 501
    
    503
    -Test value: 502
    
    504
    -Test value: 503
    
    505
    -Test value: 504
    
    506
    -Test value: 505
    
    507
    -Test value: 506
    
    508
    -Test value: 507
    
    509
    -Test value: 508
    
    510
    -Test value: 509
    
    511
    -Test value: 510
    
    512
    -Test value: 511
    
    513
    -Test value: 512
    
    514
    -Test value: 513
    
    515
    -Test value: 514
    
    516
    -Test value: 515
    
    517
    -Test value: 516
    
    518
    -Test value: 517
    
    519
    -Test value: 518
    
    520
    -Test value: 519
    
    521
    -Test value: 520
    
    522
    -Test value: 521
    
    523
    -Test value: 522
    
    524
    -Test value: 523
    
    525
    -Test value: 524
    
    526
    -Test value: 525
    
    527
    -Test value: 526
    
    528
    -Test value: 527
    
    529
    -Test value: 528
    
    530
    -Test value: 529
    
    531
    -Test value: 530
    
    532
    -Test value: 531
    
    533
    -Test value: 532
    
    534
    -Test value: 533
    
    535
    -Test value: 534
    
    536
    -Test value: 535
    
    537
    -Test value: 536
    
    538
    -Test value: 537
    
    539
    -Test value: 538
    
    540
    -Test value: 539
    
    541
    -Test value: 540
    
    542
    -Test value: 541
    
    543
    -Test value: 542
    
    544
    -Test value: 543
    
    545
    -Test value: 544
    
    546
    -Test value: 545
    
    547
    -Test value: 546
    
    548
    -Test value: 547
    
    549
    -Test value: 548
    
    550
    -Test value: 549
    
    551
    -Test value: 550
    
    552
    -Test value: 551
    
    553
    -Test value: 552
    
    554
    -Test value: 553
    
    555
    -Test value: 554
    
    556
    -Test value: 555
    
    557
    -Test value: 556
    
    558
    -Test value: 557
    
    559
    -Test value: 558
    
    560
    -Test value: 559
    
    561
    -Test value: 560
    
    562
    -Test value: 561
    
    563
    -Test value: 562
    
    564
    -Test value: 563
    
    565
    -Test value: 564
    
    566
    -Test value: 565
    
    567
    -Test value: 566
    
    568
    -Test value: 567
    
    569
    -Test value: 568
    
    570
    -Test value: 569
    
    571
    -Test value: 570
    
    572
    -Test value: 571
    
    573
    -Test value: 572
    
    574
    -Test value: 573
    
    575
    -Test value: 574
    
    576
    -Test value: 575
    
    577
    -Test value: 576
    
    578
    -Test value: 577
    
    579
    -Test value: 578
    
    580
    -Test value: 579
    
    581
    -Test value: 580
    
    582
    -Test value: 581
    
    583
    -Test value: 582
    
    584
    -Test value: 583
    
    585
    -Test value: 584
    
    586
    -Test value: 585
    
    587
    -Test value: 586
    
    588
    -Test value: 587
    
    589
    -Test value: 588
    
    590
    -Test value: 589
    
    591
    -Test value: 590
    
    592
    -Test value: 591
    
    593
    -Test value: 592
    
    594
    -Test value: 593
    
    595
    -Test value: 594
    
    596
    -Test value: 595
    
    597
    -Test value: 596
    
    598
    -Test value: 597
    
    599
    -Test value: 598
    
    600
    -Test value: 599
    
    601
    -Test value: 600
    
    602
    -Test value: 601
    
    603
    -Test value: 602
    
    604
    -Test value: 603
    
    605
    -Test value: 604
    
    606
    -Test value: 605
    
    607
    -Test value: 606
    
    608
    -Test value: 607
    
    609
    -Test value: 608
    
    610
    -Test value: 609
    
    611
    -Test value: 610
    
    612
    -Test value: 611
    
    613
    -Test value: 612
    
    614
    -Test value: 613
    
    615
    -Test value: 614
    
    616
    -Test value: 615
    
    617
    -Test value: 616
    
    618
    -Test value: 617
    
    619
    -Test value: 618
    
    620
    -Test value: 619
    
    621
    -Test value: 620
    
    622
    -Test value: 621
    
    623
    -Test value: 622
    
    624
    -Test value: 623
    
    625
    -Test value: 624
    
    626
    -Test value: 625
    
    627
    -Test value: 626
    
    628
    -Test value: 627
    
    629
    -Test value: 628
    
    630
    -Test value: 629
    
    631
    -Test value: 630
    
    632
    -Test value: 631
    
    633
    -Test value: 632
    
    634
    -Test value: 633
    
    635
    -Test value: 634
    
    636
    -Test value: 635
    
    637
    -Test value: 636
    
    638
    -Test value: 637
    
    639
    -Test value: 638
    
    640
    -Test value: 639
    
    641
    -Test value: 640
    
    642
    -Test value: 641
    
    643
    -Test value: 642
    
    644
    -Test value: 643
    
    645
    -Test value: 644
    
    646
    -Test value: 645
    
    647
    -Test value: 646
    
    648
    -Test value: 647
    
    649
    -Test value: 648
    
    650
    -Test value: 649
    
    651
    -Test value: 650
    
    652
    -Test value: 651
    
    653
    -Test value: 652
    
    654
    -Test value: 653
    
    655
    -Test value: 654
    
    656
    -Test value: 655
    
    657
    -Test value: 656
    
    658
    -Test value: 657
    
    659
    -Test value: 658
    
    660
    -Test value: 659
    
    661
    -Test value: 660
    
    662
    -Test value: 661
    
    663
    -Test value: 662
    
    664
    -Test value: 663
    
    665
    -Test value: 664
    
    666
    -Test value: 665
    
    667
    -Test value: 666
    
    668
    -Test value: 667
    
    669
    -Test value: 668
    
    670
    -Test value: 669
    
    671
    -Test value: 670
    
    672
    -Test value: 671
    
    673
    -Test value: 672
    
    674
    -Test value: 673
    
    675
    -Test value: 674
    
    676
    -Test value: 675
    
    677
    -Test value: 676
    
    678
    -Test value: 677
    
    679
    -Test value: 678
    
    680
    -Test value: 679
    
    681
    -Test value: 680
    
    682
    -Test value: 681
    
    683
    -Test value: 682
    
    684
    -Test value: 683
    
    685
    -Test value: 684
    
    686
    -Test value: 685
    
    687
    -Test value: 686
    
    688
    -Test value: 687
    
    689
    -Test value: 688
    
    690
    -Test value: 689
    
    691
    -Test value: 690
    
    692
    -Test value: 691
    
    693
    -Test value: 692
    
    694
    -Test value: 693
    
    695
    -Test value: 694
    
    696
    -Test value: 695
    
    697
    -Test value: 696
    
    698
    -Test value: 697
    
    699
    -Test value: 698
    
    700
    -Test value: 699
    
    701
    -Test value: 700
    
    702
    -Test value: 701
    
    703
    -Test value: 702
    
    704
    -Test value: 703
    
    705
    -Test value: 704
    
    706
    -Test value: 705
    
    707
    -Test value: 706
    
    708
    -Test value: 707
    
    709
    -Test value: 708
    
    710
    -Test value: 709
    
    711
    -Test value: 710
    
    712
    -Test value: 711
    
    713
    -Test value: 712
    
    714
    -Test value: 713
    
    715
    -Test value: 714
    
    716
    -Test value: 715
    
    717
    -Test value: 716
    
    718
    -Test value: 717
    
    719
    -Test value: 718
    
    720
    -Test value: 719
    
    721
    -Test value: 720
    
    722
    -Test value: 721
    
    723
    -Test value: 722
    
    724
    -Test value: 723
    
    725
    -Test value: 724
    
    726
    -Test value: 725
    
    727
    -Test value: 726
    
    728
    -Test value: 727
    
    729
    -Test value: 728
    
    730
    -Test value: 729
    
    731
    -Test value: 730
    
    732
    -Test value: 731
    
    733
    -Test value: 732
    
    734
    -Test value: 733
    
    735
    -Test value: 734
    
    736
    -Test value: 735
    
    737
    -Test value: 736
    
    738
    -Test value: 737
    
    739
    -Test value: 738
    
    740
    -Test value: 739
    
    741
    -Test value: 740
    
    742
    -Test value: 741
    
    743
    -Test value: 742
    
    744
    -Test value: 743
    
    745
    -Test value: 744
    
    746
    -Test value: 745
    
    747
    -Test value: 746
    
    748
    -Test value: 747
    
    749
    -Test value: 748
    
    750
    -Test value: 749
    
    751
    -Test value: 750
    
    752
    -Test value: 751
    
    753
    -Test value: 752
    
    754
    -Test value: 753
    
    755
    -Test value: 754
    
    756
    -Test value: 755
    
    757
    -Test value: 756
    
    758
    -Test value: 757
    
    759
    -Test value: 758
    
    760
    -Test value: 759
    
    761
    -Test value: 760
    
    762
    -Test value: 761
    
    763
    -Test value: 762
    
    764
    -Test value: 763
    
    765
    -Test value: 764
    
    766
    -Test value: 765
    
    767
    -Test value: 766
    
    768
    -Test value: 767
    
    769
    -Test value: 768
    
    770
    -Test value: 769
    
    771
    -Test value: 770
    
    772
    -Test value: 771
    
    773
    -Test value: 772
    
    774
    -Test value: 773
    
    775
    -Test value: 774
    
    776
    -Test value: 775
    
    777
    -Test value: 776
    
    778
    -Test value: 777
    
    779
    -Test value: 778
    
    780
    -Test value: 779
    
    781
    -Test value: 780
    
    782
    -Test value: 781
    
    783
    -Test value: 782
    
    784
    -Test value: 783
    
    785
    -Test value: 784
    
    786
    -Test value: 785
    
    787
    -Test value: 786
    
    788
    -Test value: 787
    
    789
    -Test value: 788
    
    790
    -Test value: 789
    
    791
    -Test value: 790
    
    792
    -Test value: 791
    
    793
    -Test value: 792
    
    794
    -Test value: 793
    
    795
    -Test value: 794
    
    796
    -Test value: 795
    
    797
    -Test value: 796
    
    798
    -Test value: 797
    
    799
    -Test value: 798
    
    800
    -Test value: 799
    
    801
    -Test value: 800
    
    802
    -Test value: 801
    
    803
    -Test value: 802
    
    804
    -Test value: 803
    
    805
    -Test value: 804
    
    806
    -Test value: 805
    
    807
    -Test value: 806
    
    808
    -Test value: 807
    
    809
    -Test value: 808
    
    810
    -Test value: 809
    
    811
    -Test value: 810
    
    812
    -Test value: 811
    
    813
    -Test value: 812
    
    814
    -Test value: 813
    
    815
    -Test value: 814
    
    816
    -Test value: 815
    
    817
    -Test value: 816
    
    818
    -Test value: 817
    
    819
    -Test value: 818
    
    820
    -Test value: 819
    
    821
    -Test value: 820
    
    822
    -Test value: 821
    
    823
    -Test value: 822
    
    824
    -Test value: 823
    
    825
    -Test value: 824
    
    826
    -Test value: 825
    
    827
    -Test value: 826
    
    828
    -Test value: 827
    
    829
    -Test value: 828
    
    830
    -Test value: 829
    
    831
    -Test value: 830
    
    832
    -Test value: 831
    
    833
    -Test value: 832
    
    834
    -Test value: 833
    
    835
    -Test value: 834
    
    836
    -Test value: 835
    
    837
    -Test value: 836
    
    838
    -Test value: 837
    
    839
    -Test value: 838
    
    840
    -Test value: 839
    
    841
    -Test value: 840
    
    842
    -Test value: 841
    
    843
    -Test value: 842
    
    844
    -Test value: 843
    
    845
    -Test value: 844
    
    846
    -Test value: 845
    
    847
    -Test value: 846
    
    848
    -Test value: 847
    
    849
    -Test value: 848
    
    850
    -Test value: 849
    
    851
    -Test value: 850
    
    852
    -Test value: 851
    
    853
    -Test value: 852
    
    854
    -Test value: 853
    
    855
    -Test value: 854
    
    856
    -Test value: 855
    
    857
    -Test value: 856
    
    858
    -Test value: 857
    
    859
    -Test value: 858
    
    860
    -Test value: 859
    
    861
    -Test value: 860
    
    862
    -Test value: 861
    
    863
    -Test value: 862
    
    864
    -Test value: 863
    
    865
    -Test value: 864
    
    866
    -Test value: 865
    
    867
    -Test value: 866
    
    868
    -Test value: 867
    
    869
    -Test value: 868
    
    870
    -Test value: 869
    
    871
    -Test value: 870
    
    872
    -Test value: 871
    
    873
    -Test value: 872
    
    874
    -Test value: 873
    
    875
    -Test value: 874
    
    876
    -Test value: 875
    
    877
    -Test value: 876
    
    878
    -Test value: 877
    
    879
    -Test value: 878
    
    880
    -Test value: 879
    
    881
    -Test value: 880
    
    882
    -Test value: 881
    
    883
    -Test value: 882
    
    884
    -Test value: 883
    
    885
    -Test value: 884
    
    886
    -Test value: 885
    
    887
    -Test value: 886
    
    888
    -Test value: 887
    
    889
    -Test value: 888
    
    890
    -Test value: 889
    
    891
    -Test value: 890
    
    892
    -Test value: 891
    
    893
    -Test value: 892
    
    894
    -Test value: 893
    
    895
    -Test value: 894
    
    896
    -Test value: 895
    
    897
    -Test value: 896
    
    898
    -Test value: 897
    
    899
    -Test value: 898
    
    900
    -Test value: 899
    
    901
    -Test value: 900
    
    902
    -Test value: 901
    
    903
    -Test value: 902
    
    904
    -Test value: 903
    
    905
    -Test value: 904
    
    906
    -Test value: 905
    
    907
    -Test value: 906
    
    908
    -Test value: 907
    
    909
    -Test value: 908
    
    910
    -Test value: 909
    
    911
    -Test value: 910
    
    912
    -Test value: 911
    
    913
    -Test value: 912
    
    914
    -Test value: 913
    
    915
    -Test value: 914
    
    916
    -Test value: 915
    
    917
    -Test value: 916
    
    918
    -Test value: 917
    
    919
    -Test value: 918
    
    920
    -Test value: 919
    
    921
    -Test value: 920
    
    922
    -Test value: 921
    
    923
    -Test value: 922
    
    924
    -Test value: 923
    
    925
    -Test value: 924
    
    926
    -Test value: 925
    
    927
    -Test value: 926
    
    928
    -Test value: 927
    
    929
    -Test value: 928
    
    930
    -Test value: 929
    
    931
    -Test value: 930
    
    932
    -Test value: 931
    
    933
    -Test value: 932
    
    934
    -Test value: 933
    
    935
    -Test value: 934
    
    936
    -Test value: 935
    
    937
    -Test value: 936
    
    938
    -Test value: 937
    
    939
    -Test value: 938
    
    940
    -Test value: 939
    
    941
    -Test value: 940
    
    942
    -Test value: 941
    
    943
    -Test value: 942
    
    944
    -Test value: 943
    
    945
    -Test value: 944
    
    946
    -Test value: 945
    
    947
    -Test value: 946
    
    948
    -Test value: 947
    
    949
    -Test value: 948
    
    950
    -Test value: 949
    
    951
    -Test value: 950
    
    952
    -Test value: 951
    
    953
    -Test value: 952
    
    954
    -Test value: 953
    
    955
    -Test value: 954
    
    956
    -Test value: 955
    
    957
    -Test value: 956
    
    958
    -Test value: 957
    
    959
    -Test value: 958
    
    960
    -Test value: 959
    
    961
    -Test value: 960
    
    962
    -Test value: 961
    
    963
    -Test value: 962
    
    964
    -Test value: 963
    
    965
    -Test value: 964
    
    966
    -Test value: 965
    
    967
    -Test value: 966
    
    968
    -Test value: 967
    
    969
    -Test value: 968
    
    970
    -Test value: 969
    
    971
    -Test value: 970
    
    972
    -Test value: 971
    
    973
    -Test value: 972
    
    974
    -Test value: 973
    
    975
    -Test value: 974
    
    976
    -Test value: 975
    
    977
    -Test value: 976
    
    978
    -Test value: 977
    
    979
    -Test value: 978
    
    980
    -Test value: 979
    
    981
    -Test value: 980
    
    982
    -Test value: 981
    
    983
    -Test value: 982
    
    984
    -Test value: 983
    
    985
    -Test value: 984
    
    986
    -Test value: 985
    
    987
    -Test value: 986
    
    988
    -Test value: 987
    
    989
    -Test value: 988
    
    990
    -Test value: 989
    
    991
    -Test value: 990
    
    992
    -Test value: 991
    
    993
    -Test value: 992
    
    994
    -Test value: 993
    
    995
    -Test value: 994
    
    996
    -Test value: 995
    
    997
    -Test value: 996
    
    998
    -Test value: 997
    
    999
    -Test value: 998
    
    1000
    -Test value: 999
    
    1001
    -Test value: 1000
    1
    +Test value: 30000

  • testsuite/tests/perf/should_run/all.T
    ... ... @@ -446,7 +446,6 @@ test('T26147',
    446 446
          [ collect_stats('all', 5),
    
    447 447
            pre_cmd('./genT26147'),
    
    448 448
            extra_files(['genT26147']),
    
    449
    -       extra_run_opts('+RTS -p'),
    
    450 449
            test_opts_dot_prof,
    
    451 450
          ],
    
    452 451
          compile_and_run,
    

  • testsuite/tests/perf/should_run/genT26147
    ... ... @@ -16,7 +16,6 @@ for i in $(seq $NUMFUN); do
    16 16
     
    
    17 17
     costCenter${i} :: Int -> IO ()
    
    18 18
     costCenter${i} n = do
    
    19
    -  putStrLn $ "Test value: " ++ show n
    
    20 19
       costCenter$((i + 1)) (n+1)
    
    21 20
     EOF
    
    22 21
     done
    
    ... ... @@ -25,5 +24,7 @@ cat >> T26147.hs << EOF
    25 24
     
    
    26 25
     costCenter$((i + 1)) :: Int -> IO ()
    
    27 26
     costCenter$((i + 1)) n = do
    
    28
    -  putStrLn $ "Test value: " ++ show n
    
    27
    +  if n < $NUMFUN * 30
    
    28
    +    then costCenter1 n
    
    29
    +    else putStrLn $ "Test value: " ++ show n
    
    29 30
     EOF