Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch : supercompiler
http://hackage.haskell.org/trac/ghc/changeset/8cf2d732f72bf50256cf3d50679136c0d60459a8 >--------------------------------------------------------------- commit 8cf2d732f72bf50256cf3d50679136c0d60459a8 Author: Max Bolingbroke <batterseapo...@hotmail.com> Date: Wed Mar 21 14:33:58 2012 +0000 Use localiseId when manufacturing Id for positive information This prevents us creating some local bindings with external names, which messes up later simplifier runs >--------------------------------------------------------------- compiler/supercompile/Supercompile.hs | 7 ++----- compiler/supercompile/Supercompile/Drive/Split.hs | 6 ++++-- 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/compiler/supercompile/Supercompile.hs b/compiler/supercompile/Supercompile.hs index 338c7e2..a378516 100644 --- a/compiler/supercompile/Supercompile.hs +++ b/compiler/supercompile/Supercompile.hs @@ -32,8 +32,6 @@ import MkCore (mkWildValBinder) import Coercion (isCoVar, mkCoVarCo, mkAxInstCo) import DataCon (dataConAllTyVars, dataConRepArgTys, dataConTyCon, dataConWorkId) import VarSet -import Name (localiseName) -import Var (Var, varName, setVarName) import Id import MkId (realWorldPrimId) import FastString (fsLit) @@ -117,7 +115,8 @@ coreBindsToCoreTerm should_sc binds -- unique and b) the internality of these names will be carried down on the next simplifier run, so this works. -- The ice is thin, though! sc_xs = zappedBindersOfBinds sc_binds - internal_sc_binds = map (first localiseInternaliseId) sc_binds + -- NB: if we don't mark these Ids as not exported then we get lots of residual top-level bindings of the form x = y + internal_sc_binds = map (first localiseId) sc_binds -- Decide which things we should export from the supercompiled term using a Church tuple. -- We need to export to the top level of the module those bindings that are *any* of: -- 1. Are exported by the module itself @@ -130,8 +129,6 @@ coreBindsToCoreTerm should_sc binds exported_xs' = unionVarSets (map (S.idFreeVars . fst) exported') sc_xs_internal_xs = uncurry (go []) (partition (\(x, _) -> isExportedId x || x `elemVarSet` dont_sc_binds_fvs) (sc_xs `zip` zappedBindersOfBinds internal_sc_binds)) sc_internal_xs = map snd sc_xs_internal_xs - localiseInternaliseId x = setIdNotExported (x `setVarName` localiseName (varName x)) - -- If we don't mark these Ids as not exported then we get lots of residual top-level bindings of the form x = y -- NB: I can't see any GHC code that prevents nullary unboxed tuples, but I'm not actually sure they work diff --git a/compiler/supercompile/Supercompile/Drive/Split.hs b/compiler/supercompile/Supercompile/Drive/Split.hs index 21b4735..d356388 100644 --- a/compiler/supercompile/Supercompile/Drive/Split.hs +++ b/compiler/supercompile/Supercompile/Drive/Split.hs @@ -24,7 +24,7 @@ import Supercompile.StaticFlags import Supercompile.Utilities hiding (tails) import CoreUtils (filterAlts) -import Id (idUnique, idType, isDeadBinder, zapIdOccInfo) +import Id (idUnique, idType, isDeadBinder, zapIdOccInfo, localiseId) import Var (varUnique) import PrelNames (undefinedName, wildCardKey) import Type (splitTyConApp_maybe) @@ -1120,7 +1120,9 @@ splitStackFrame ctxt_ids ids kf scruts bracketed_hole Just scrut_v <- [altConToValue (idType x') (alt_rn, alt_con)] let in_scrut_e@(_, scrut_e) = renamedTerm (fmap Value scrut_v) scrut <- scruts' - return (scrut, HB (howToBindCheap scrut_e) (Right in_scrut_e))) + -- Localise the Id just in case this is the occurrence of a lambda-bound variable. + -- We don't really want a Let-bound external name in the output! + return (localiseId scrut, HB (howToBindCheap scrut_e) (Right in_scrut_e))) `M.union` M.fromList [(x, lambdaBound) | x <- x':alt_bvs]) -- NB: x' might be in scruts and union is left-biased alt_rns alt_cons alt_bvss -- NB: don't need to grab deeds for these just yet, due to the funny contract for transitiveInline alt_bvss = map altConBoundVars alt_cons' _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc