[commit: ghc] wip/iface-type-pretty: Progress (48c6355)
git at git.haskell.org
git at git.haskell.org
Wed Jul 20 17:04:02 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/iface-type-pretty
Link : http://ghc.haskell.org/trac/ghc/changeset/48c63554896118310579e66ec9859c9c29c6efc4/ghc
>---------------------------------------------------------------
commit 48c63554896118310579e66ec9859c9c29c6efc4
Author: Ben Gamari <ben at smart-cactus.org>
Date: Tue May 17 23:21:10 2016 +0200
Progress
>---------------------------------------------------------------
48c63554896118310579e66ec9859c9c29c6efc4
compiler/iface/IfaceType.hs | 2 +-
compiler/iface/IfaceType.hs-boot | 28 ++++++++++++++++++++++++++++
compiler/types/TyCoRep.hs | 1 +
compiler/types/TyCoRep.hs-boot | 1 +
4 files changed, 31 insertions(+), 1 deletion(-)
diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs
index 5627d91..0ea7a48 100644
--- a/compiler/iface/IfaceType.hs
+++ b/compiler/iface/IfaceType.hs
@@ -63,7 +63,7 @@ import Coercion
import DataCon ( isTupleDataCon )
import TcType
import DynFlags
-import TyCoRep -- needs to convert core types to iface types
+import {-# SOURCE #-}TyCoRep -- needs to convert core types to iface types
import TyCon hiding ( pprPromotionQuote )
import CoAxiom
import Id
diff --git a/compiler/iface/IfaceType.hs-boot b/compiler/iface/IfaceType.hs-boot
new file mode 100644
index 0000000..12859f6
--- /dev/null
+++ b/compiler/iface/IfaceType.hs-boot
@@ -0,0 +1,28 @@
+-- Exists to allow TyCoRep to import pretty-printers
+module IfaceType where
+
+import Var (TyVar)
+import {-# SOURCE #-} TyCoRep (Type, TyLit, TyBinder)
+import Outputable
+
+data IfaceType
+data IfaceTyLit
+data IfaceForAllBndr
+data IfaceTyConBinder
+data IfaceTvBndr
+
+pprIfaceType, pprParendIfaceType :: IfaceType -> SDoc
+pprIfaceSigmaType :: IfaceType -> SDoc
+pprIfaceTyLit :: IfaceTyLit -> SDoc
+pprIfaceForAll :: [IfaceForAllBndr] -> SDoc
+pprIfaceTvBndr :: Bool -> IfaceTvBndr -> SDoc
+pprUserIfaceForAll :: [IfaceForAllBndr] -> SDoc
+pprIfaceContext :: Outputable a => [a] -> SDoc
+pprIfaceContextArr :: Outputable a => [a] -> SDoc
+
+toIfaceType :: Type -> IfaceType
+toIfaceTyLit :: TyLit -> IfaceTyLit
+
+zipIfaceBinders :: [TyVar] -> [TyBinder] -> [IfaceTyConBinder]
+
+toDegenerateBinders :: [TyBinder] -> [IfaceTyConBinder]
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index ac568cf..766bf8d 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -137,6 +137,7 @@ import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy
import {-# SOURCE #-} Coercion
import {-# SOURCE #-} ConLike ( ConLike(..), conLikeName )
import {-# SOURCE #-} TysWiredIn ( ptrRepLiftedTy )
+import {-# SOURCE #-} IfaceType
-- friends:
import Var
diff --git a/compiler/types/TyCoRep.hs-boot b/compiler/types/TyCoRep.hs-boot
index 0bcd9b3..ef63d2a 100644
--- a/compiler/types/TyCoRep.hs-boot
+++ b/compiler/types/TyCoRep.hs-boot
@@ -10,6 +10,7 @@ data Coercion
data LeftOrRight
data UnivCoProvenance
data TCvSubst
+data TyLit
mkForAllTys :: [TyBinder] -> Type -> Type
More information about the ghc-commits
mailing list