Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : local-gc

http://hackage.haskell.org/trac/ghc/changeset/e684cb6c41a494048c50d3fe109b42437d25b5c3

>---------------------------------------------------------------

commit e684cb6c41a494048c50d3fe109b42437d25b5c3
Merge: f0e9125... 1fb3844...
Author: Simon Marlow <[email protected]>
Date:   Sun Jun 5 14:31:30 2011 +0100

    merge

 compiler/main/SysTools.lhs |    2 +-
 rts/Capability.c           |    3 +--
 rts/Stats.c                |   16 ++++++++--------
 rts/Task.c                 |    4 ++--
 rts/sm/GC.c                |    1 +
 utils/ghc-pkg/ghc.mk       |    6 ++++--
 6 files changed, 17 insertions(+), 15 deletions(-)

diff --cc rts/Stats.c
index 5f18a56,159a909..1162d2b
--- a/rts/Stats.c
+++ b/rts/Stats.c
@@@ -165,13 -165,13 +165,13 @@@ initStats1 (void
        statsPrintf("    Alloc    Copied     Live    GC    GC     TOT     TOT  
Page Flts\n");
        statsPrintf("    bytes     bytes     bytes  user  elap    user    
elap\n");
      }
--    GC_coll_cpu = 
--      (Ticks *)stgMallocBytes(
 -            sizeof(Ticks)*RtsFlags.GcFlags.generations,
++    GC_coll_cpu =
++        (Ticks *)stgMallocBytes(
 +          sizeof(Ticks)*total_generations,
            "initStats");
--    GC_coll_elapsed = 
--      (Ticks *)stgMallocBytes(
 -          sizeof(Ticks)*RtsFlags.GcFlags.generations,
++    GC_coll_elapsed =
++        (Ticks *)stgMallocBytes(
 +          sizeof(Ticks)*total_generations,
            "initStats");
      GC_coll_max_pause =
        (Ticks *)stgMallocBytes(
@@@ -332,46 -326,29 +332,46 @@@ stat_endGC (gc_thread *gct
  
          taskDoneGC(gct->cap->running_task, thread_gc_cpu, gc_elapsed);
  
 -        if (RtsFlags.GcFlags.giveStats == VERBOSE_GC_STATS) {
 -          nat faults = getPageFaults();
 +        if (gct->gc_type == GC_LOCAL) {
 +            gen_ix = gct->index;
 +        } else {
 +            gen_ix = old_generations[gct->collect_gen].ix;
 +        }
 +
 +      if (RtsFlags.GcFlags.giveStats == VERBOSE_GC_STATS) {
-           nat faults = getPageFaults();
++            nat faults = getPageFaults();
            
            statsPrintf("%9ld %9ld %9ld",
                    alloc*sizeof(W_), copied*sizeof(W_), 
                        live*sizeof(W_));
-           statsPrintf(" %5.2f %5.2f %7.2f %7.2f %4ld %4ld  ", 
 -            statsPrintf(" %5.2f %5.2f %7.2f %7.2f %4ld %4ld  (Gen: %2d)\n",
 -                    TICK_TO_DBL(gc_cpu),
++            statsPrintf(" %5.2f %5.2f %7.2f %7.2f %4ld %4ld  ",
 +                  TICK_TO_DBL(gc_cpu),
                    TICK_TO_DBL(gc_elapsed),
                    TICK_TO_DBL(cpu),
                    TICK_TO_DBL(elapsed - start_init_elapsed),
                    faults - gct->gc_start_faults,
 -                        gct->gc_start_faults - GC_end_faults,
 -                    gen);
 -
 -            GC_end_faults = faults;
 -          statsFlush();
 +                        gct->gc_start_faults - GC_end_faults);
 +
 +            switch (gct->gc_type) {
 +            case GC_LOCAL:
 +                statsPrintf("(G0.%d, loc)", gct->index);
 +                break;
 +            case GC_PAR:
 +                statsPrintf("(G%d, par)", gct->collect_gen);
 +                break;
 +            case GC_SEQ:
 +                statsPrintf("(G%d)", gct->collect_gen);
 +                break;
 +            }
 +            statsPrintf("\n");
 +          GC_end_faults = faults;
-           statsFlush();
++            statsFlush();
        }
  
-       GC_coll_cpu[gen_ix] += gc_cpu;
 -        GC_coll_cpu[gen] += gc_cpu;
 -        GC_coll_elapsed[gen] += gc_elapsed;
 -        if (GC_coll_max_pause[gen] < gc_elapsed) {
 -            GC_coll_max_pause[gen] = gc_elapsed;
++        GC_coll_cpu[gen_ix] += gc_cpu;
 +      GC_coll_elapsed[gen_ix] += gc_elapsed;
 +        if (GC_coll_max_pause[gen_ix] < gc_elapsed) {
 +            GC_coll_max_pause[gen_ix] = gc_elapsed;
          }
  
        GC_tot_copied += (StgWord64) copied;
@@@ -570,17 -542,12 +570,17 @@@ stat_exit(int alloc
            statsPrintf(" %5.2f %5.2f\n\n", 0.0, 0.0);
        }
  
 -        for (i = 0; i < RtsFlags.GcFlags.generations; i++) {
 -            gc_cpu     += GC_coll_cpu[i];
 -            gc_elapsed += GC_coll_elapsed[i];
 +        for (i = 0; i < total_generations; i++) {
 +            if (all_generations[i].is_local) {
 +                gc_local_cpu     += GC_coll_cpu[i];
 +                gc_local_elapsed += GC_coll_elapsed[i];
 +            } else {
 +                gc_global_cpu     += GC_coll_cpu[i];
 +                gc_global_elapsed += GC_coll_elapsed[i];
 +            }
          }
  
--      if (RtsFlags.GcFlags.giveStats >= SUMMARY_GC_STATS) {
++        if (RtsFlags.GcFlags.giveStats >= SUMMARY_GC_STATS) {
            showStgWord64(GC_tot_alloc*sizeof(W_), 
                                 temp, rtsTrue/*commas*/);
            statsPrintf("%16s bytes allocated in the heap\n", temp);
@@@ -589,17 -556,9 +589,17 @@@
                                 temp, rtsTrue/*commas*/);
            statsPrintf("%16s bytes copied during GC\n", temp);
  
 -            if ( residency_samples > 0 ) {
 +            for (i = 0; i < n_capabilities; i++) {
 +                globalised += gc_threads[i]->globalised;
 +            }
 +
 +          showStgWord64(globalised * sizeof(W_), 
 +                               temp, rtsTrue/*commas*/);
 +          statsPrintf("%16s bytes globalised\n", temp);
 +
 +          if ( residency_samples > 0 ) {
                showStgWord64(max_residency*sizeof(W_), 
--                                   temp, rtsTrue/*commas*/);
++                                     temp, rtsTrue/*commas*/);
                statsPrintf("%16s bytes maximum residency (%ld sample(s))\n",
                        temp, residency_samples);
            }
diff --cc rts/Task.c
index aa17749,e77a030..5f2ec5b
--- a/rts/Task.c
+++ b/rts/Task.c
@@@ -323,10 -323,10 +323,10 @@@ taskTimeStamp (Task *task USED_IF_THREA
      currentUserTime = getThreadCPUTime();
      currentElapsedTime = getProcessElapsedTime();
  
-     task->mut_time = 
-       currentUserTime - task->muttimestart - task->gc_time;
+     task->mut_time =
 -      currentUserTime - task->muttimestart - task->gc_time;
++        currentUserTime - task->muttimestart - task->gc_time;
      task->mut_etime = 
-       currentElapsedTime - task->elapsedtimestart - task->gc_etime;
+         currentElapsedTime - task->elapsedtimestart - task->gc_etime;
  
      if (task->gc_time   < 0) { task->gc_time   = 0; }
      if (task->gc_etime  < 0) { task->gc_etime  = 0; }
diff --cc rts/sm/GC.c
index a642778,d0dd44d..ba4aab2
--- a/rts/sm/GC.c
+++ b/rts/sm/GC.c
@@@ -200,11 -199,9 +200,12 @@@ GarbageCollect (nat N, // generation t
    ASSERT(sizeof(gen_workspace) == 16 * sizeof(StgWord));
    // otherwise adjust the padding in gen_workspace.
  
+   // this is the main thread
    SET_GCT(gc_threads[cap->no]);
  
 +  gct->gc_type = gc_type;
 +  major_gc = (N == RtsFlags.GcFlags.generations-1);
 +
    // tell the stats department that we've started a GC 
    stat_startGC(gct);
  
diff --cc rts/sm/GCThread.h
index dde9fe2,e42a3a1..15e104a
--- a/rts/sm/GCThread.h
+++ b/rts/sm/GCThread.h
@@@ -169,36 -165,9 +169,36 @@@ typedef struct gc_thread_ 
                                     // instead of the to-space
                                     // corresponding to the object
  
--    lnat thunk_selector_depth;     // used to avoid unbounded recursion in 
++    lnat thunk_selector_depth;     // used to avoid unbounded recursion in
                                     // evacuate() for THUNK_SELECTOR
  
 +    nat collect_gen;               // maximum generation (no) to collect
 +
 +    nat gc_type;                   // The gc type (GC_SEQ, GC_PAR, GC_LOCAL)
 +
 +    rtsBool globalise_thunks;      // whether to globalise THUNK objects
 +
 +    StgTSO *resurrected_threads;   // threads found to be unreachable,
 +                                   // linked by ->global_link field.
 +
 +    StgTSO *exception_threads;     // List of blocked threads found to
 +                                   // have pending throwTos
 +
 +    /* Which stage of processing various kinds of weak pointer are we at?
 +     * (see traverse_weak_ptr_list() below for discussion).
 +     */
 +    enum { WeakPtrs, WeakThreads, WeakDone } weak_stage;
 +
 +    StgWeak *old_weak_ptrs;
 +
 +    // --------------------
 +    // The mark stack
 +
 +    bdescr *mark_stack_top_bd; // topmost block in the mark stack
 +    bdescr *mark_stack_bd;     // current block in the mark stack
 +    StgPtr mark_sp;            // pointer to the next unallocated mark
 +                               // stack entry
 +
  #ifdef USE_PAPI
      int papi_events;
  #endif



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to