summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2017-05-25 16:07:09 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2017-05-26 12:37:48 +0100
commit226860e786ccb2c5660b64c9cf66e58eaf4dc672 (patch)
tree463cea7ce06c3aca4755ce4d751ded702847bd45
parent8dc6d645fc3384b3b8ded0578939f5c855dd2ed5 (diff)
downloadhaskell-226860e786ccb2c5660b64c9cf66e58eaf4dc672.tar.gz
Shrink a couple of hs-boot files
IfaceType.hs-boot and ToIface.hs-boot were bigger than they needed to be, so I'm shrinking them.
-rw-r--r--compiler/iface/IfaceType.hs-boot29
-rw-r--r--compiler/iface/ToIface.hs-boot5
2 files changed, 8 insertions, 26 deletions
diff --git a/compiler/iface/IfaceType.hs-boot b/compiler/iface/IfaceType.hs-boot
index 2a5331e5c2..4807419903 100644
--- a/compiler/iface/IfaceType.hs-boot
+++ b/compiler/iface/IfaceType.hs-boot
@@ -1,37 +1,20 @@
--- Exists to allow TyCoRep to import pretty-printers
-module IfaceType where
+-- Used only by ToIface.hs-boot
+
+module IfaceType( IfaceType, IfaceTyCon, IfaceForAllBndr
+ , IfaceCoercion, IfaceTyLit, IfaceTcArgs ) where
import Var (TyVarBndr, ArgFlag)
import TyCon (TyConBndrVis)
-import BasicTypes (TyPrec)
-import Outputable (Outputable, SDoc)
import FastString (FastString)
+data IfaceTcArgs
type IfLclName = FastString
type IfaceKind = IfaceType
-type IfacePredType = IfaceType
-data ShowForAllFlag
data IfaceType
data IfaceTyCon
data IfaceTyLit
data IfaceCoercion
-data IfaceTcArgs
-type IfaceTvBndr = (IfLclName, IfaceKind)
+type IfaceTvBndr = (IfLclName, IfaceKind)
type IfaceTyConBinder = TyVarBndr IfaceTvBndr TyConBndrVis
type IfaceForAllBndr = TyVarBndr IfaceTvBndr ArgFlag
-
-instance Outputable IfaceType
-
-pprIfaceType, pprParendIfaceType :: IfaceType -> SDoc
-pprIfaceSigmaType :: ShowForAllFlag -> IfaceType -> SDoc
-pprIfaceTyLit :: IfaceTyLit -> SDoc
-pprIfaceForAll :: [IfaceForAllBndr] -> SDoc
-pprIfaceTvBndr :: Bool -> IfaceTvBndr -> SDoc
-pprUserIfaceForAll :: [IfaceForAllBndr] -> SDoc
-pprIfaceContext :: [IfacePredType] -> SDoc
-pprIfaceContextArr :: [IfacePredType] -> SDoc
-pprIfaceTypeApp :: TyPrec -> IfaceTyCon -> IfaceTcArgs -> SDoc
-pprIfaceCoTcApp :: TyPrec -> IfaceTyCon -> [IfaceCoercion] -> SDoc
-pprTyTcApp :: TyPrec -> IfaceTyCon -> IfaceTcArgs -> SDoc
-pprIfacePrefixApp :: TyPrec -> SDoc -> [SDoc] -> SDoc
diff --git a/compiler/iface/ToIface.hs-boot b/compiler/iface/ToIface.hs-boot
index 04ceab673f..f3614272af 100644
--- a/compiler/iface/ToIface.hs-boot
+++ b/compiler/iface/ToIface.hs-boot
@@ -1,17 +1,16 @@
module ToIface where
import {-# SOURCE #-} TyCoRep
-import {-# SOURCE #-} IfaceType
+import {-# SOURCE #-} IfaceType( IfaceType, IfaceTyCon, IfaceForAllBndr
+ , IfaceCoercion, IfaceTyLit, IfaceTcArgs )
import Var ( TyVar, TyVarBinder )
import TyCon ( TyCon )
import VarSet( VarSet )
-- For TyCoRep
-toIfaceType :: Type -> IfaceType
toIfaceTypeX :: VarSet -> Type -> IfaceType
toIfaceTyLit :: TyLit -> IfaceTyLit
toIfaceForAllBndr :: TyVarBinder -> IfaceForAllBndr
-toIfaceTvBndr :: TyVar -> IfaceTvBndr
toIfaceTyCon :: TyCon -> IfaceTyCon
toIfaceTcArgs :: TyCon -> [Type] -> IfaceTcArgs
toIfaceCoercion :: Coercion -> IfaceCoercion