Remove all .hi-boot-6 files
authorIan Lynagh <igloo@earth.li>
Tue, 8 Jul 2008 15:00:59 +0000 (15:00 +0000)
committerIan Lynagh <igloo@earth.li>
Tue, 8 Jul 2008 15:00:59 +0000 (15:00 +0000)
From 6.4 onwards we use .(l)hs-boot instead.
Spotted by Max Bolingbroke.

27 files changed:
compiler/basicTypes/DataCon.hi-boot-6 [deleted file]
compiler/basicTypes/IdInfo.hi-boot-6 [deleted file]
compiler/basicTypes/MkId.hi-boot-6 [deleted file]
compiler/basicTypes/Module.hi-boot-6 [deleted file]
compiler/basicTypes/Name.hi-boot-6 [deleted file]
compiler/basicTypes/OccName.hi-boot-6 [deleted file]
compiler/codeGen/CgBindery.hi-boot-6 [deleted file]
compiler/codeGen/CgExpr.hi-boot-6 [deleted file]
compiler/codeGen/ClosureInfo.hi-boot-6 [deleted file]
compiler/coreSyn/CoreSyn.hi-boot-6 [deleted file]
compiler/deSugar/DsExpr.hi-boot-6 [deleted file]
compiler/deSugar/Match.hi-boot-6 [deleted file]
compiler/hsSyn/HsExpr.hi-boot-6 [deleted file]
compiler/hsSyn/HsPat.hi-boot-6 [deleted file]
compiler/iface/TcIface.hi-boot-6 [deleted file]
compiler/main/ErrUtils.hi-boot-6 [deleted file]
compiler/main/HscTypes.hi-boot-6 [deleted file]
compiler/main/Packages.hi-boot-6 [deleted file]
compiler/parser/HaddockLex.hi-boot-6 [deleted file]
compiler/rename/RnExpr.hi-boot-6 [deleted file]
compiler/typecheck/TcExpr.hi-boot-6 [deleted file]
compiler/typecheck/TcMatches.hi-boot-6 [deleted file]
compiler/typecheck/TcSplice.hi-boot-6 [deleted file]
compiler/typecheck/TcType.hi-boot-6 [deleted file]
compiler/typecheck/TcUnify.hi-boot-6 [deleted file]
compiler/types/TyCon.hi-boot-6 [deleted file]
compiler/types/TypeRep.hi-boot-6 [deleted file]

diff --git a/compiler/basicTypes/DataCon.hi-boot-6 b/compiler/basicTypes/DataCon.hi-boot-6
deleted file mode 100644 (file)
index 7882469..0000000
+++ /dev/null
@@ -1,5 +0,0 @@
-module DataCon where
-
-data DataCon
-dataConName :: DataCon -> Name.Name
-isVanillaDataCon :: DataCon -> GHC.Base.Bool
diff --git a/compiler/basicTypes/IdInfo.hi-boot-6 b/compiler/basicTypes/IdInfo.hi-boot-6
deleted file mode 100644 (file)
index e090800..0000000
+++ /dev/null
@@ -1,8 +0,0 @@
-module IdInfo where
-
-data IdInfo
-data GlobalIdDetails
-
-notGlobalId :: GlobalIdDetails
-seqIdInfo :: IdInfo -> ()
-vanillaIdInfo :: IdInfo
diff --git a/compiler/basicTypes/MkId.hi-boot-6 b/compiler/basicTypes/MkId.hi-boot-6
deleted file mode 100644 (file)
index d3f2252..0000000
+++ /dev/null
@@ -1,5 +0,0 @@
-module MkId where
-
-mkDataConIds :: Name.Name -> Name.Name -> DataCon.DataCon -> DataCon.DataConIds
-
-
diff --git a/compiler/basicTypes/Module.hi-boot-6 b/compiler/basicTypes/Module.hi-boot-6
deleted file mode 100644 (file)
index c3019f8..0000000
+++ /dev/null
@@ -1,7 +0,0 @@
-module Module where
-data Module
-data ModuleName
-data PackageId
-moduleName :: Module -> ModuleName
-modulePackageId :: Module -> PackageId
-packageIdString :: PackageId -> GHC.Base.String
diff --git a/compiler/basicTypes/Name.hi-boot-6 b/compiler/basicTypes/Name.hi-boot-6
deleted file mode 100644 (file)
index c4eeca4..0000000
+++ /dev/null
@@ -1,3 +0,0 @@
-module Name where
-
-data Name
diff --git a/compiler/basicTypes/OccName.hi-boot-6 b/compiler/basicTypes/OccName.hi-boot-6
deleted file mode 100644 (file)
index 705f9b1..0000000
+++ /dev/null
@@ -1,4 +0,0 @@
-module OccName where
-
-data OccName
-
diff --git a/compiler/codeGen/CgBindery.hi-boot-6 b/compiler/codeGen/CgBindery.hi-boot-6
deleted file mode 100644 (file)
index 7d1f300..0000000
+++ /dev/null
@@ -1,8 +0,0 @@
-module CgBindery where
-
-type CgBindings = VarEnv.IdEnv CgIdInfo
-data CgIdInfo
-data VolatileLoc
-data StableLoc
-
-nukeVolatileBinds :: CgBindings -> CgBindings
diff --git a/compiler/codeGen/CgExpr.hi-boot-6 b/compiler/codeGen/CgExpr.hi-boot-6
deleted file mode 100644 (file)
index dc2d75c..0000000
+++ /dev/null
@@ -1,3 +0,0 @@
-module CgExpr where
-
-cgExpr :: StgSyn.StgExpr -> CgMonad.Code
diff --git a/compiler/codeGen/ClosureInfo.hi-boot-6 b/compiler/codeGen/ClosureInfo.hi-boot-6
deleted file mode 100644 (file)
index d313ccd..0000000
+++ /dev/null
@@ -1,4 +0,0 @@
-module ClosureInfo where
-
-data LambdaFormInfo
-data ClosureInfo
diff --git a/compiler/coreSyn/CoreSyn.hi-boot-6 b/compiler/coreSyn/CoreSyn.hi-boot-6
deleted file mode 100644 (file)
index 38dc8c7..0000000
+++ /dev/null
@@ -1,5 +0,0 @@
-module CoreSyn where
-
--- Needed by Var.lhs
-data Expr b
-type CoreExpr = Expr Var.Var
diff --git a/compiler/deSugar/DsExpr.hi-boot-6 b/compiler/deSugar/DsExpr.hi-boot-6
deleted file mode 100644 (file)
index c7ddb2d..0000000
+++ /dev/null
@@ -1,6 +0,0 @@
-module DsExpr where
-
-dsExpr :: HsExpr.HsExpr Var.Id -> DsMonad.DsM CoreSyn.CoreExpr
-dsLExpr :: HsExpr.LHsExpr Var.Id -> DsMonad.DsM CoreSyn.CoreExpr
-dsLocalBinds :: HsBinds.HsLocalBinds Var.Id -> CoreSyn.CoreExpr -> DsMonad.DsM CoreSyn.CoreExpr
-dsValBinds   :: HsBinds.HsValBinds Var.Id   -> CoreSyn.CoreExpr -> DsMonad.DsM CoreSyn.CoreExpr
diff --git a/compiler/deSugar/Match.hi-boot-6 b/compiler/deSugar/Match.hi-boot-6
deleted file mode 100644 (file)
index df806ec..0000000
+++ /dev/null
@@ -1,27 +0,0 @@
-module Match where
-
-match  :: [Var.Id]
-        -> TcType.TcType
-       -> [DsMonad.EquationInfo]
-       -> DsMonad.DsM DsMonad.MatchResult
-
-matchWrapper
-       :: HsExpr.HsMatchContext Name.Name
-        -> HsExpr.MatchGroup Var.Id
-       -> DsMonad.DsM ([Var.Id], CoreSyn.CoreExpr)
-
-matchSimply
-       :: CoreSyn.CoreExpr
-       -> HsExpr.HsMatchContext Name.Name
-       -> HsPat.LPat Var.Id
-       -> CoreSyn.CoreExpr
-       -> CoreSyn.CoreExpr
-       -> DsMonad.DsM CoreSyn.CoreExpr
-
-matchSinglePat
-       :: CoreSyn.CoreExpr
-       -> HsExpr.HsMatchContext Name.Name
-       -> HsPat.LPat Var.Id
-        -> TcType.TcType
-       -> DsMonad.MatchResult
-       -> DsMonad.DsM DsMonad.MatchResult
diff --git a/compiler/hsSyn/HsExpr.hi-boot-6 b/compiler/hsSyn/HsExpr.hi-boot-6
deleted file mode 100644 (file)
index 62b1306..0000000
+++ /dev/null
@@ -1,25 +0,0 @@
-module HsExpr where
-
-data HsExpr i
-data HsSplice i
-data MatchGroup a
-data GRHSs a
-
-type LHsExpr a = SrcLoc.Located (HsExpr a)
-type SyntaxExpr a = HsExpr a
-type PostTcExpr = HsExpr Var.Id
-
-pprLExpr :: (Outputable.OutputableBndr i) => 
-       LHsExpr i -> Outputable.SDoc
-
-pprExpr :: (Outputable.OutputableBndr i) => 
-       HsExpr.HsExpr i -> Outputable.SDoc
-
-pprSplice :: (Outputable.OutputableBndr i) => 
-       HsExpr.HsSplice i -> Outputable.SDoc
-
-pprPatBind :: (Outputable.OutputableBndr b, Outputable.OutputableBndr i) => 
-       HsPat.LPat b -> HsExpr.GRHSs i -> Outputable.SDoc
-
-pprFunBind :: (Outputable.OutputableBndr idL, Outputable.OutputableBndr idR) => 
-       idL -> GHC.Base.Bool -> HsExpr.MatchGroup idR -> Outputable.SDoc
diff --git a/compiler/hsSyn/HsPat.hi-boot-6 b/compiler/hsSyn/HsPat.hi-boot-6
deleted file mode 100644 (file)
index dfa7777..0000000
+++ /dev/null
@@ -1,6 +0,0 @@
-module HsPat where
-
-data HsQuasiQuote i = HsQuasiQuote i i SrcSpan FastString
-
-data Pat i
-type LPat i = SrcLoc.Located (Pat i)
diff --git a/compiler/iface/TcIface.hi-boot-6 b/compiler/iface/TcIface.hi-boot-6
deleted file mode 100644 (file)
index fff8a9b..0000000
+++ /dev/null
@@ -1,9 +0,0 @@
-module TcIface where
-
-tcIfaceDecl  :: GHC.Base.Bool -> IfaceSyn.IfaceDecl -> TcRnTypes.IfL TypeRep.TyThing
-tcIfaceInst  :: IfaceSyn.IfaceInst -> TcRnTypes.IfL InstEnv.Instance
-tcIfaceRules :: GHC.Base.Bool -> [IfaceSyn.IfaceRule] -> TcRnTypes.IfL [CoreSyn.CoreRule]
-tcIfaceVectInfo :: Module.Module -> HscTypes.TypeEnv -> HscTypes.IfaceVectInfo -> TcRnTypes.IfL HscTypes.VectInfo
-tcIfaceFamInst :: IfaceSyn.IfaceFamInst -> TcRnTypes.IfL FamInstEnv.FamInst
-
-
diff --git a/compiler/main/ErrUtils.hi-boot-6 b/compiler/main/ErrUtils.hi-boot-6
deleted file mode 100644 (file)
index fd98ca3..0000000
+++ /dev/null
@@ -1,11 +0,0 @@
-module ErrUtils where
-
-data Severity
-  = SevInfo
-  | SevWarning
-  | SevError
-  | SevFatal
-
-type Message = Outputable.SDoc
-
-mkLocMessage :: SrcLoc.SrcSpan -> Message -> Message
diff --git a/compiler/main/HscTypes.hi-boot-6 b/compiler/main/HscTypes.hi-boot-6
deleted file mode 100644 (file)
index 7b4a7d1..0000000
+++ /dev/null
@@ -1,3 +0,0 @@
-module HscTypes where
-
-data Session
diff --git a/compiler/main/Packages.hi-boot-6 b/compiler/main/Packages.hi-boot-6
deleted file mode 100644 (file)
index 6b12f14..0000000
+++ /dev/null
@@ -1,2 +0,0 @@
-module Packages where
-data PackageState
diff --git a/compiler/parser/HaddockLex.hi-boot-6 b/compiler/parser/HaddockLex.hi-boot-6
deleted file mode 100644 (file)
index 902003f..0000000
+++ /dev/null
@@ -1,18 +0,0 @@
-module HaddockLex where
-
-tokenise :: GHC.Base.String -> [Token]
-
-data Token
-  = TokPara
-  | TokNumber
-  | TokBullet
-  | TokDefStart
-  | TokDefEnd
-  | TokSpecial GHC.Base.Char
-  | TokIdent [RdrName.RdrName]
-  | TokString GHC.Base.String
-  | TokURL GHC.Base.String
-  | TokPic GHC.Base.String
-  | TokEmphasis GHC.Base.String
-  | TokAName GHC.Base.String
-  | TokBirdTrack GHC.Base.String
diff --git a/compiler/rename/RnExpr.hi-boot-6 b/compiler/rename/RnExpr.hi-boot-6
deleted file mode 100644 (file)
index 8f6c7f1..0000000
+++ /dev/null
@@ -1,11 +0,0 @@
-module RnExpr where\r
-\r
-rnLExpr :: HsExpr.LHsExpr RdrName.RdrName\r
-       -> TcRnTypes.RnM (HsExpr.LHsExpr Name.Name, NameSet.FreeVars)\r
-\r
-rnStmts :: forall thing.\r
-          HsExpr.HsStmtContext Name.Name -> [HsExpr.LStmt RdrName.RdrName] \r
-       -> TcRnTypes.RnM (thing, NameSet.FreeVars)\r
-       -> TcRnTypes.RnM (([HsExpr.LStmt Name.Name], thing), NameSet.FreeVars)\r
-\r
-\r
diff --git a/compiler/typecheck/TcExpr.hi-boot-6 b/compiler/typecheck/TcExpr.hi-boot-6
deleted file mode 100644 (file)
index 5a0fa8c..0000000
+++ /dev/null
@@ -1,21 +0,0 @@
-module TcExpr where
-
-tcPolyExpr :: 
-         HsExpr.LHsExpr Name.Name
-       -> TcType.BoxySigmaType
-       -> TcRnTypes.TcM (HsExpr.LHsExpr Var.Id)
-
-tcMonoExpr :: 
-         HsExpr.LHsExpr Name.Name
-       -> TcType.BoxyRhoType
-       -> TcRnTypes.TcM (HsExpr.LHsExpr Var.Id)
-
-tcInferRho :: 
-         HsExpr.LHsExpr Name.Name
-       -> TcRnTypes.TcM (HsExpr.LHsExpr Var.Id, TcType.TcType)
-
-tcSyntaxOp :: 
-         TcRnTypes.InstOrigin
-       -> HsExpr.HsExpr Name.Name
-       -> TcType.TcType
-       -> TcRnTypes.TcM (HsExpr.HsExpr Var.Id)
diff --git a/compiler/typecheck/TcMatches.hi-boot-6 b/compiler/typecheck/TcMatches.hi-boot-6
deleted file mode 100644 (file)
index 3a4865a..0000000
+++ /dev/null
@@ -1,11 +0,0 @@
-module TcMatches where
-
-tcGRHSsPat    :: HsExpr.GRHSs Name.Name
-             -> TcType.BoxyRhoType
-             -> TcRnTypes.TcM (HsExpr.GRHSs TcRnTypes.TcId)
-
-tcMatchesFun :: Name.Name
-             -> GHC.Base.Bool
-            -> HsExpr.MatchGroup Name.Name
-            -> TcType.BoxyRhoType
-            -> TcRnTypes.TcM (HsBinds.HsWrapper, HsExpr.MatchGroup TcRnTypes.TcId)
diff --git a/compiler/typecheck/TcSplice.hi-boot-6 b/compiler/typecheck/TcSplice.hi-boot-6
deleted file mode 100644 (file)
index c33439e..0000000
+++ /dev/null
@@ -1,17 +0,0 @@
-module TcSplice where
-
-tcSpliceExpr :: HsExpr.HsSplice Name.Name
-            -> TcType.BoxyRhoType
-            -> TcRnTypes.TcM (HsExpr.HsExpr Var.Id)
-
-kcSpliceType :: HsExpr.HsSplice Name.Name
-            -> TcRnTypes.TcM (HsTypes.HsType Name.Name, TcType.TcKind)
-
-tcBracket :: HsExpr.HsBracket Name.Name 
-         -> TcType.BoxyRhoType
-         -> TcRnTypes.TcM (HsExpr.LHsExpr Var.Id)
-
-tcSpliceDecls :: HsExpr.LHsExpr Name.Name
-
-runQuasiQuoteExpr :: HsQuasiQuote Name.Name -> TcM (LHsExpr RdrName)
-runQuasiQuotePat  :: HsQuasiQuote Name -> TcM (LPat RdrName)
diff --git a/compiler/typecheck/TcType.hi-boot-6 b/compiler/typecheck/TcType.hi-boot-6
deleted file mode 100644 (file)
index d1fc721..0000000
+++ /dev/null
@@ -1,5 +0,0 @@
-module TcType where
-
-data TcTyVarDetails 
-
-pprTcTyVarDetails :: TcTyVarDetails -> Outputable.SDoc
\ No newline at end of file
diff --git a/compiler/typecheck/TcUnify.hi-boot-6 b/compiler/typecheck/TcUnify.hi-boot-6
deleted file mode 100644 (file)
index e906914..0000000
+++ /dev/null
@@ -1,8 +0,0 @@
-module TcUnify where
-
--- This boot file exists only to tie the knot between
---             TcUnify and TcSimplify
-
-unifyType :: TcType.TcTauType -> TcType.TcTauType -> TcRnTypes.TcM Coercion.CoercionI
-zapToMonotype :: TcType.BoxyType -> TcRnTypes.TcM TcType.TcTauType
-boxyUnify :: TcType.BoxyType -> TcType.BoxyType -> TcRnTypes.TcM Coercion.CoercionI
diff --git a/compiler/types/TyCon.hi-boot-6 b/compiler/types/TyCon.hi-boot-6
deleted file mode 100644 (file)
index 0897562..0000000
+++ /dev/null
@@ -1,7 +0,0 @@
-module TyCon where
-
-data TyCon
-
-isTupleTyCon :: TyCon -> GHC.Base.Bool
-isUnboxedTupleTyCon :: TyCon -> GHC.Base.Bool
-isFunTyCon :: TyCon -> GHC.Base.Bool
diff --git a/compiler/types/TypeRep.hi-boot-6 b/compiler/types/TypeRep.hi-boot-6
deleted file mode 100644 (file)
index 59faa59..0000000
+++ /dev/null
@@ -1,8 +0,0 @@
-module TypeRep where
-
-data Type
-data PredType
-data TyThing
-type Kind = Type
-isCoercionKind :: Kind -> GHC.Base.Bool
-