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

On branch  : supercompiler

http://hackage.haskell.org/trac/ghc/changeset/27195a3a7caca0228b75e7e5760a937963ecd61c

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

commit 27195a3a7caca0228b75e7e5760a937963ecd61c
Author: Max Bolingbroke <batterseapo...@hotmail.com>
Date:   Fri Oct 19 16:23:01 2012 +0100

    Show those binders which are SUPERINLINABLE

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

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

diff --git a/compiler/supercompile/Supercompile/Core/Syntax.hs 
b/compiler/supercompile/Supercompile/Core/Syntax.hs
index cc4732f..1bc8fcb 100644
--- a/compiler/supercompile/Supercompile/Core/Syntax.hs
+++ b/compiler/supercompile/Supercompile/Core/Syntax.hs
@@ -16,7 +16,7 @@ import DataCon  (DataCon, dataConWorkId)
 import Var      (TyVar, Var, varName, isTyVar, varType)
 import Name     (Name, nameOccName)
 import OccName  (occNameString)
-import Id       (Id, idType)
+import Id       (Id, isId, idType, idInlinePragma)
 import PrimOp   (primOpType)
 import Literal  (Literal, literalType)
 import Type     (Type, mkTyVarTy, applyTy, applyTys, mkForAllTy, mkFunTy, 
splitFunTy_maybe, eqType)
@@ -70,10 +70,11 @@ pprPrecDefault prec e = pPrintPrecLam prec xs 
(PrettyFunction ppr_prec)
 
 -- NB: don't use GHC's pprBndr because its way too noisy, printing unfoldings 
etc
 pPrintBndr :: BindingSite -> Var -> SDoc
-pPrintBndr bs x = prettyParen needs_parens $ ppr x <+> text "::" <+> ppr 
(varType x)
+pPrintBndr bs x = prettyParen needs_parens $ ppr x <+> superinlinable <+> text 
"::" <+> ppr (varType x)
   where needs_parens = case bs of LambdaBind -> True
                                   CaseBind   -> True
                                   LetBind    -> False
+        superinlinable = if isId x then ppr (idInlinePragma x) else empty
 
 data AltCon = DataAlt DataCon [TyVar] [CoVar] [Id] | LiteralAlt Literal | 
DefaultAlt
             deriving (Eq, Show)



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

Reply via email to