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

On branch  : local-gc

http://hackage.haskell.org/trac/ghc/changeset/8e1f5e35770fa49c51328e7dca168e7614bde5ce

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

commit 8e1f5e35770fa49c51328e7dca168e7614bde5ce
Author: Simon Marlow <[email protected]>
Date:   Sun Jun 5 22:18:39 2011 +0100

    fix merge bugs

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

 compiler/codeGen/CgClosure.lhs |    6 ------
 compiler/codeGen/CgPrimOp.hs   |   14 +++++++++++---
 rts/Stats.c                    |   40 +++++++++++++++++++++-------------------
 rts/sm/GC.c                    |    2 --
 rts/sm/Storage.c               |    2 +-
 5 files changed, 33 insertions(+), 31 deletions(-)

diff --git a/compiler/codeGen/CgClosure.lhs b/compiler/codeGen/CgClosure.lhs
index dfd37e6..8ee47a0 100644
--- a/compiler/codeGen/CgClosure.lhs
+++ b/compiler/codeGen/CgClosure.lhs
@@ -584,12 +584,6 @@ link_caf cl_info _is_upd = do
   where
     bh_cl_info :: ClosureInfo
     bh_cl_info = cafBlackHoleClosureInfo cl_info
-
-    ind_static_info :: CmmExpr
-    ind_static_info = mkLblExpr mkIndStaticInfoLabel
-
-    off_indirectee :: WordOff
-    off_indirectee = fixedHdrSize + oFFSET_StgInd_indirectee*wORD_SIZE
 \end{code}
 
 
diff --git a/compiler/codeGen/CgPrimOp.hs b/compiler/codeGen/CgPrimOp.hs
index c922979..65f3bc1 100644
--- a/compiler/codeGen/CgPrimOp.hs
+++ b/compiler/codeGen/CgPrimOp.hs
@@ -32,6 +32,8 @@ import Constants
 import Outputable
 import FastString
 
+#include "HsVersions.h"
+
 -- ---------------------------------------------------------------------------
 -- Code generation for PrimOps
 
@@ -235,11 +237,11 @@ emitPrimOp [] CopyMutableArrayOp 
[src,src_off,dst,dst_off,n] live =
 emitPrimOp [res] CloneArrayOp [src,src_off,n] live =
     emitCloneArray mkMAP_FROZEN_infoLabel res src src_off n live
 emitPrimOp [res] CloneMutableArrayOp [src,src_off,n] live =
-    emitCloneArray mkMAP_DIRTY_infoLabel res src src_off n live
+    emitCloneArray mkMAP_GLOBAL_infoLabel res src src_off n live
 emitPrimOp [res] FreezeArrayOp [src,src_off,n] live =
     emitCloneArray mkMAP_FROZEN_infoLabel res src src_off n live
 emitPrimOp [res] ThawArrayOp [src,src_off,n] live =
-    emitCloneArray mkMAP_DIRTY_infoLabel res src src_off n live
+    emitCloneArray mkMAP_GLOBAL_infoLabel res src src_off n live
 
 -- Reading/writing pointer arrays
 
@@ -720,6 +722,9 @@ emitCopyArray :: (CmmExpr -> CmmExpr -> CmmExpr -> CmmExpr 
-> CmmExpr
               -> StgLiveVars
               -> Code
 emitCopyArray copy src0 src_off0 dst0 dst_off0 n0 live = do
+    -- XXX need to fix for local GC
+    WARN(True, text "emitCopyArray: needs fixing for local GC") return ()
+
     -- Assign the arguments to temporaries so the code generator can
     -- calculate liveness for us.
     src <- assignTemp_ src0
@@ -729,7 +734,7 @@ emitCopyArray copy src0 src_off0 dst0 dst_off0 n0 live = do
     n <- assignTemp_ n0
 
     -- Set the dirty bit in the header.
-    stmtC (setInfo dst (CmmLit (CmmLabel mkMAP_DIRTY_infoLabel)))
+    stmtC (setInfo dst (CmmLit (CmmLabel mkMAP_GLOBAL_infoLabel)))
 
     dst_elems_p <- assignTemp $ cmmOffsetB dst arrPtrsHdrSize
     dst_p <- assignTemp $ cmmOffsetExprW dst_elems_p dst_off
@@ -750,6 +755,9 @@ emitCopyArray copy src0 src_off0 dst0 dst_off0 n0 live = do
 emitCloneArray :: CLabel -> CmmFormal -> CmmExpr -> CmmExpr -> CmmExpr
                -> StgLiveVars -> Code
 emitCloneArray info_p res_r src0 src_off0 n0 live = do
+    -- XXX need to fix for local GC
+    WARN(True, text "emitCloneArray: needs fixing for local GC") return ()
+
     -- Assign the arguments to temporaries so the code generator can
     -- calculate liveness for us.
     src <- assignTemp_ src0
diff --git a/rts/Stats.c b/rts/Stats.c
index 6e1eaa4..4ca127b 100644
--- a/rts/Stats.c
+++ b/rts/Stats.c
@@ -589,19 +589,8 @@ stat_exit(int alloc)
         exit_cpu     = end_exit_cpu - start_exit_cpu;
         exit_elapsed = end_exit_elapsed - start_exit_elapsed;
 
-        if (RtsFlags.ParFlags.nNodes == 1)
-        {
-            // In single-threaded mode, we can separate out the
-            // local GC time from the MUT time, and report the
-            // total GC time separately.
-
-            mut_elapsed = start_exit_elapsed - end_init_elapsed - gc_elapsed;
-
-            mut_cpu = start_exit_cpu - end_init_cpu
-                - gc_local_cpu - gc_global_cpu
-                - PROF_VAL(RP_tot_time + HC_tot_time);
-        }
-        else
+#if defined(THREADED_RTS)
+        if (RtsFlags.ParFlags.nNodes != 1)
         {
             // In multi-threaded mode, we have to include the
             // local GC time in the MUT time, because each thread
@@ -615,6 +604,19 @@ stat_exit(int alloc)
                 - gc_global_cpu
                 - PROF_VAL(RP_tot_time + HC_tot_time);
         }
+        else
+#endif
+        {
+            // In single-threaded mode, we can separate out the
+            // local GC time from the MUT time, and report the
+            // total GC time separately.
+
+            mut_elapsed = start_exit_elapsed - end_init_elapsed - gc_elapsed;
+
+            mut_cpu = start_exit_cpu - end_init_cpu
+                - gc_local_cpu - gc_global_cpu
+                - PROF_VAL(RP_tot_time + HC_tot_time);
+        }
 
         if (mut_cpu < 0) { mut_cpu = 0; }
 
@@ -691,7 +693,7 @@ stat_exit(int alloc)
                 statsPrintf("                        MUT time (elapsed)       
GC time  (elapsed)\n");
                for (i = 0, task = all_tasks; 
                     task != NULL; 
-1                    i++, task = task->all_link) {
+                     i++, task = task->all_link) {
                    statsPrintf("  Task %2d %-8s :  %6.2fs    (%6.2fs)     
%6.2fs    (%6.2fs)\n",
                                i,
                                (task->worker) ? "(worker)" : "(bound)",
@@ -870,10 +872,10 @@ void
 statDescribeGens(void)
 {
   nat g, n, i, lge;
-  nat cap_blocks, gen_blocks;
-  nat cap_mut, gen_mut;
-  lnat cap_live, gen_live;
-  lnat slop, tot_live, tot_slop;
+  memcount cap_blocks, gen_blocks;
+  memcount cap_mut, gen_mut;
+  memcount cap_live, gen_live;
+  memcount slop, tot_live, tot_slop;
   bdescr *bd;
   generation *gen;
   
@@ -898,7 +900,7 @@ statDescribeGens(void)
 
       slop = gen_blocks * BLOCK_SIZE_W - gen_live;
 
-      debugBelch("%5d %7d %8d %8d %4s %8s %8d %8ld %8ld\n", 
+      debugBelch("%5d %7ld %8d %8ld %4s %8s %8ld %8ld %8ld\n",
                  g, gen->max_blocks, lge, gen->n_prim_blocks, "", "", 
gen_blocks, 
                  gen_live*sizeof(W_), slop*sizeof(W_));
 
diff --git a/rts/sm/GC.c b/rts/sm/GC.c
index 9da6aaa..febd272 100644
--- a/rts/sm/GC.c
+++ b/rts/sm/GC.c
@@ -648,8 +648,6 @@ GarbageCollect (nat N, // generation to collect
   // update the max size of older generations after a major GC
   resize_generations();
   
-  }
-
   // Free the mark stack, leaving one block.
   freeMarkStack();
       
diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c
index 4cb22f5..3a8c0fa 100644
--- a/rts/sm/Storage.c
+++ b/rts/sm/Storage.c
@@ -950,7 +950,7 @@ calcAllocatedCap (Capability *cap, rtsBool include_nursery)
   nat allocated = 0;
 
   if (include_nursery) {
-      allocated += countOccupied(nurseries[i].blocks);
+      allocated += countOccupied(nurseries[cap->no].blocks);
   }
 
   allocated += cap->r.rG0->n_new_large_words;



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

Reply via email to