summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CgPrimOp.hs
diff options
context:
space:
mode:
authorsimonmar <unknown>2006-01-17 16:13:18 +0000
committersimonmar <unknown>2006-01-17 16:13:18 +0000
commit91b07216be1cb09230b7d1b417899ddea8620ff3 (patch)
tree03ef770091e4483ad049112ccf81cb12ed9844b4 /ghc/compiler/codeGen/CgPrimOp.hs
parentda69fa9c5047c5b0d05bdb05eaddefa1eb5d5a36 (diff)
downloadhaskell-91b07216be1cb09230b7d1b417899ddea8620ff3.tar.gz
[project @ 2006-01-17 16:13:18 by simonmar]
Improve the GC behaviour of IORefs (see Ticket #650). This is a small change to the way IORefs interact with the GC, which should improve GC performance for programs with plenty of IORefs. Previously we had a single closure type for mutable variables, MUT_VAR. Mutable variables were *always* on the mutable list in older generations, and always traversed on every GC. Now, we have two closure types: MUT_VAR_CLEAN and MUT_VAR_DIRTY. The latter is on the mutable list, but the former is not. (NB. this differs from MUT_ARR_PTRS_CLEAN and MUT_ARR_PTRS_DIRTY, both of which are on the mutable list). writeMutVar# now implements a write barrier, by calling dirty_MUT_VAR() in the runtime, that does the necessary modification of MUT_VAR_CLEAN into MUT_VAR_DIRY, and adding to the mutable list if necessary. This results in some pretty dramatic speedups for GHC itself. I've just measureed a 30% overall speedup compiling a 31-module program (anna) with the default heap settings :-D
Diffstat (limited to 'ghc/compiler/codeGen/CgPrimOp.hs')
-rw-r--r--ghc/compiler/codeGen/CgPrimOp.hs13
1 files changed, 11 insertions, 2 deletions
diff --git a/ghc/compiler/codeGen/CgPrimOp.hs b/ghc/compiler/codeGen/CgPrimOp.hs
index 7784efbb2b..91aa3911f8 100644
--- a/ghc/compiler/codeGen/CgPrimOp.hs
+++ b/ghc/compiler/codeGen/CgPrimOp.hs
@@ -10,13 +10,15 @@ module CgPrimOp (
cgPrimOp
) where
+import ForeignCall ( CCallConv(CCallConv) )
import StgSyn ( StgLiveVars, StgArg )
import CgBindery ( getVolatileRegs, getArgAmodes )
import CgMonad
import CgInfoTbls ( getConstrTag )
import CgUtils ( cmmOffsetW, cmmOffsetB, cmmLoadIndexW )
import Cmm
-import CLabel ( mkMAP_FROZEN_infoLabel, mkMAP_DIRTY_infoLabel )
+import CLabel ( mkMAP_FROZEN_infoLabel, mkMAP_DIRTY_infoLabel,
+ mkDirty_MUT_VAR_Label )
import CmmUtils
import MachOp
import SMRep
@@ -113,7 +115,14 @@ emitPrimOp [res] ReadMutVarOp [mutv] live
= stmtC (CmmAssign res (cmmLoadIndexW mutv fixedHdrSize))
emitPrimOp [] WriteMutVarOp [mutv,var] live
- = stmtC (CmmStore (cmmOffsetW mutv fixedHdrSize) var)
+ = do
+ stmtC (CmmStore (cmmOffsetW mutv fixedHdrSize) var)
+ vols <- getVolatileRegs live
+ stmtC (CmmCall (CmmForeignCall (CmmLit (CmmLabel mkDirty_MUT_VAR_Label))
+ CCallConv)
+ [{-no results-}]
+ [(mutv,PtrHint)]
+ (Just vols))
-- #define sizzeofByteArrayzh(r,a) \
-- r = (((StgArrWords *)(a))->words * sizeof(W_))