[commit: ghc] wip/annotate-core: Some more references and actually export binder type (36b8478)

git at git.haskell.org git at git.haskell.org
Wed Jul 26 22:40:13 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/annotate-core
Link       : http://ghc.haskell.org/trac/ghc/changeset/36b847896360d4e9b7ae86b4b1e664b8af476d2b/ghc

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

commit 36b847896360d4e9b7ae86b4b1e664b8af476d2b
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Wed Jul 26 22:38:52 2017 +0000

    Some more references and actually export binder type
    
    Need to do some refinement about where definition sites are printed but
    this will do for now.


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

36b847896360d4e9b7ae86b4b1e664b8af476d2b
 compiler/coreSyn/PprCore.hs            | 4 ++--
 compiler/utils/OutputableAnnotation.hs | 2 +-
 2 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/compiler/coreSyn/PprCore.hs b/compiler/coreSyn/PprCore.hs
index a77b593..70ae2e1 100644
--- a/compiler/coreSyn/PprCore.hs
+++ b/compiler/coreSyn/PprCore.hs
@@ -158,7 +158,7 @@ ppr_expr :: OutputableBndr b => (SDoc -> SDoc) -> Expr b -> SDoc
 
 ppr_expr add_par (Var name)
  | isJoinId name               = add_par ((text "jump") <+> ppr name)
- | otherwise                   = ppr name
+ | otherwise                   = addAnn (varReference name) (ppr name)
 ppr_expr add_par (Type ty)     = add_par (text "TYPE:" <+> ppr ty)       -- Weird
 ppr_expr add_par (Coercion co) = add_par (text "CO:" <+> ppr co)
 ppr_expr add_par (Lit lit)     = pprLiteral add_par lit
@@ -202,7 +202,7 @@ ppr_expr add_par expr@(App {})
                    _ -> parens (hang fun_doc 2 pp_args)
                    where
                      fun_doc | isJoinId f = text "jump" <+> ppr f
-                             | otherwise  = ppr f
+                             | otherwise  = addAnn (varReference f) (ppr f)
 
         _ -> parens (hang (pprParendExpr fun) 2 pp_args)
     }
diff --git a/compiler/utils/OutputableAnnotation.hs b/compiler/utils/OutputableAnnotation.hs
index 1ad2d83..71b9c69 100644
--- a/compiler/utils/OutputableAnnotation.hs
+++ b/compiler/utils/OutputableAnnotation.hs
@@ -1,5 +1,5 @@
 {-# LANGUAGE GADTs #-}
-module OutputableAnnotation (PExpr(..), BindType, varBinder, varReference) where
+module OutputableAnnotation (PExpr(..), BindType(..), varBinder, varReference) where
 
 import CoreSyn
 import Outputable ( OutputableBndr(..))



More information about the ghc-commits mailing list