Skip to content
Snippets Groups Projects
Commit 5c058a0f authored by batterseapower's avatar batterseapower
Browse files

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

parent 680f9313
No related branches found
No related tags found
No related merge requests found
......@@ -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
......
......@@ -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"
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment