[commit: ghc] wip/annotate-core: Add reference to ppr_ty for type variables (360cf4c)

git at git.haskell.org git at git.haskell.org
Wed Aug 9 15:27:23 UTC 2017


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

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

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

commit 360cf4c8bc92830d0e6d92cc35d50465a683855d
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Wed Aug 9 15:23:28 2017 +0000

    Add reference to ppr_ty for type variables


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

360cf4c8bc92830d0e6d92cc35d50465a683855d
 compiler/basicTypes/Name.hs-boot            |  2 ++
 compiler/iface/IfaceType.hs                 |  3 ++-
 compiler/utils/OutputableAnnotation.hs      | 10 +++++-----
 compiler/utils/OutputableAnnotation.hs-boot |  6 ++++++
 4 files changed, 15 insertions(+), 6 deletions(-)

diff --git a/compiler/basicTypes/Name.hs-boot b/compiler/basicTypes/Name.hs-boot
index c4eeca4..6c66846 100644
--- a/compiler/basicTypes/Name.hs-boot
+++ b/compiler/basicTypes/Name.hs-boot
@@ -1,3 +1,5 @@
 module Name where
 
 data Name
+
+class NamedThing a
diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs
index 39e3028..20144cb 100644
--- a/compiler/iface/IfaceType.hs
+++ b/compiler/iface/IfaceType.hs
@@ -60,6 +60,7 @@ import Name
 import BasicTypes
 import Binary
 import Outputable
+import {-# SOURCE #-} OutputableAnnotation
 import FastString
 import FastStringEnv
 import Util
@@ -573,7 +574,7 @@ pprPrecIfaceType :: TyPrec -> IfaceType -> SDoc
 pprPrecIfaceType prec ty = eliminateRuntimeRep (ppr_ty prec) ty
 
 ppr_ty :: TyPrec -> IfaceType -> SDoc
-ppr_ty _         (IfaceFreeTyVar tyvar) = ppr tyvar  -- This is the main reson for IfaceFreeTyVar!
+ppr_ty _         (IfaceFreeTyVar tyvar) = addAnn (varReference tyvar) (ppr tyvar)
 ppr_ty _         (IfaceTyVar tyvar)     = ppr tyvar  -- See Note [TcTyVars in IfaceType]
 ppr_ty ctxt_prec (IfaceTyConApp tc tys) = pprTyTcApp ctxt_prec tc tys
 ppr_ty _         (IfaceTupleTy i p tys) = pprTuple i p tys
diff --git a/compiler/utils/OutputableAnnotation.hs b/compiler/utils/OutputableAnnotation.hs
index 12a7bba..fe6a39e 100644
--- a/compiler/utils/OutputableAnnotation.hs
+++ b/compiler/utils/OutputableAnnotation.hs
@@ -6,16 +6,16 @@ import Outputable ( OutputableBndr(..))
 import Name (NamedThing)
 
 data PExpr where
-  PCoreExpr :: (OutputableBndr a, NamedThing a) => Expr a -> PExpr
-  PBind :: (OutputableBndr a, NamedThing a) => Bind a -> PExpr
-  PVar :: (OutputableBndr a, NamedThing a) => BindType -> a -> PExpr
+  PCoreExpr :: NamedThing a => Expr a -> PExpr
+  PBind :: NamedThing a => Bind a -> PExpr
+  PVar :: NamedThing a => BindType -> a -> PExpr
 
 data BindType = Binder | Reference
 
-varBinder :: (OutputableBndr a, NamedThing a) => a -> PExpr
+varBinder :: NamedThing a => a -> PExpr
 varBinder a = PVar Binder a
 
-varReference :: (OutputableBndr a, NamedThing a) => a -> PExpr
+varReference :: NamedThing a => a -> PExpr
 varReference a = PVar Reference a
 
 
diff --git a/compiler/utils/OutputableAnnotation.hs-boot b/compiler/utils/OutputableAnnotation.hs-boot
index d71f632..d7120df 100644
--- a/compiler/utils/OutputableAnnotation.hs-boot
+++ b/compiler/utils/OutputableAnnotation.hs-boot
@@ -1,3 +1,9 @@
 module OutputableAnnotation where
 
+import {-# SOURCE #-} Name (NamedThing)
+
 data PExpr
+
+data BindType
+
+varReference :: NamedThing a => a -> PExpr



More information about the ghc-commits mailing list