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

On branch  : supercompiler

http://hackage.haskell.org/trac/ghc/changeset/5c058a0fe6364c874ee071c912a3f1a61014a2da

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

commit 5c058a0fe6364c874ee071c912a3f1a61014a2da
Author: Max Bolingbroke <batterseapo...@hotmail.com>
Date:   Wed Oct 24 18:43:36 2012 +0100

    Mark module SUPERINLINABLE by default (otherwise SC is almost an identity 
transformation)

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

 compiler/supercompile/Supercompile.hs             |    3 ++-
 compiler/supercompile/Supercompile/StaticFlags.hs |    3 +++
 2 files changed, 5 insertions(+), 1 deletions(-)

diff --git a/compiler/supercompile/Supercompile.hs 
b/compiler/supercompile/Supercompile.hs
index e577c62..2d416f4 100644
--- a/compiler/supercompile/Supercompile.hs
+++ b/compiler/supercompile/Supercompile.hs
@@ -17,6 +17,7 @@ module Supercompile (supercompileProgram, 
supercompileProgramSelective) where
 -- Probably can't/shouldn't do this if the wildcard binder y is used in the 
RHS.
 
 import Supercompile.GHC
+import Supercompile.StaticFlags
 import Supercompile.Utilities
 import qualified Supercompile.Core.Syntax as S
 import qualified Supercompile.Core.FreeVars as S
@@ -263,7 +264,7 @@ supercompile e = -- liftM (termToCoreExpr . snd) $
   where unfs = termUnfoldings e'
         -- NB: ensure we mark any child bindings of bindings marked 
SUPERINLINABLE in *this module* as SUPERINLINABLE,
         -- just like we would if we imported a SUPERINLINABLE binding
-        e' = superinlinableLexically False $ runParseM anfUniqSupply' $ 
coreExprToTerm e
+        e' = superinlinableLexically mODULE_SUPERINLINABLE $ runParseM 
anfUniqSupply' $ coreExprToTerm e
 
 supercompileProgram :: [CoreBind] -> IO [CoreBind]
 supercompileProgram binds = supercompileProgramSelective selector binds
diff --git a/compiler/supercompile/Supercompile/StaticFlags.hs 
b/compiler/supercompile/Supercompile/StaticFlags.hs
index 7e973db..8e6d3c2 100644
--- a/compiler/supercompile/Supercompile/StaticFlags.hs
+++ b/compiler/supercompile/Supercompile/StaticFlags.hs
@@ -161,6 +161,9 @@ pOSITIVE_INFORMATION = lookUp $ fsLit 
"-fsupercompiler-positive-information"
 pREINITALIZE_MEMO_TABLE :: Bool
 pREINITALIZE_MEMO_TABLE = not $ lookUp $ fsLit 
"-fsupercompiler-no-preinitalize"
 
+mODULE_SUPERINLINABLE :: Bool
+mODULE_SUPERINLINABLE = not $ lookUp $ fsLit 
"-fsupercompiler-no-module-superinlinable"
+
 -- FIXME: turning this off is actually broken right now
 uSE_LET_BINDINGS :: Bool
 uSE_LET_BINDINGS = not $ lookUp $ fsLit "-fsupercompiler-no-let-bindings"



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to