summaryrefslogtreecommitdiff
path: root/compiler/GHC/Tc
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Tc')
-rw-r--r--compiler/GHC/Tc/Deriv.hs2
-rw-r--r--compiler/GHC/Tc/Deriv/Functor.hs2
-rw-r--r--compiler/GHC/Tc/Deriv/Generate.hs2
-rw-r--r--compiler/GHC/Tc/Deriv/Generics.hs2
-rw-r--r--compiler/GHC/Tc/Deriv/Infer.hs2
-rw-r--r--compiler/GHC/Tc/Errors.hs2
-rw-r--r--compiler/GHC/Tc/Gen/App.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Bind.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Expr.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Foreign.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Head.hs2
-rw-r--r--compiler/GHC/Tc/Gen/HsType.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Match.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Pat.hs2
-rw-r--r--compiler/GHC/Tc/Gen/Sig.hs4
-rw-r--r--compiler/GHC/Tc/Gen/Splice.hs2
-rw-r--r--compiler/GHC/Tc/Instance/Class.hs2
-rw-r--r--compiler/GHC/Tc/Instance/Family.hs2
-rw-r--r--compiler/GHC/Tc/Instance/FunDeps.hs2
-rw-r--r--compiler/GHC/Tc/Instance/Typeable.hs2
-rw-r--r--compiler/GHC/Tc/Module.hs2
-rw-r--r--compiler/GHC/Tc/Solver.hs2
-rw-r--r--compiler/GHC/Tc/Solver/Canonical.hs2
-rw-r--r--compiler/GHC/Tc/Solver/Interact.hs2
-rw-r--r--compiler/GHC/Tc/Solver/Monad.hs2
-rw-r--r--compiler/GHC/Tc/Solver/Rewrite.hs2
-rw-r--r--compiler/GHC/Tc/TyCl.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/Build.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/Class.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/Instance.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/PatSyn.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/Utils.hs2
-rw-r--r--compiler/GHC/Tc/Types.hs2
-rw-r--r--compiler/GHC/Tc/Types/Constraint.hs2
-rw-r--r--compiler/GHC/Tc/Types/Evidence.hs1
-rw-r--r--compiler/GHC/Tc/Types/Origin.hs4
-rw-r--r--compiler/GHC/Tc/Utils/Backpack.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Env.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Instantiate.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Monad.hs2
-rw-r--r--compiler/GHC/Tc/Utils/TcMType.hs4
-rw-r--r--compiler/GHC/Tc/Utils/TcType.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Unify.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Zonk.hs2
-rw-r--r--compiler/GHC/Tc/Validity.hs2
45 files changed, 3 insertions, 92 deletions
diff --git a/compiler/GHC/Tc/Deriv.hs b/compiler/GHC/Tc/Deriv.hs
index fa1a0afb45..ded92fde1e 100644
--- a/compiler/GHC/Tc/Deriv.hs
+++ b/compiler/GHC/Tc/Deriv.hs
@@ -13,8 +13,6 @@
-- | Handles @deriving@ clauses on @data@ declarations.
module GHC.Tc.Deriv ( tcDeriving, DerivInfo(..) ) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
diff --git a/compiler/GHC/Tc/Deriv/Functor.hs b/compiler/GHC/Tc/Deriv/Functor.hs
index d61b7180ef..d9aa90d6b2 100644
--- a/compiler/GHC/Tc/Deriv/Functor.hs
+++ b/compiler/GHC/Tc/Deriv/Functor.hs
@@ -22,8 +22,6 @@ module GHC.Tc.Deriv.Functor
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Data.Bag
diff --git a/compiler/GHC/Tc/Deriv/Generate.hs b/compiler/GHC/Tc/Deriv/Generate.hs
index 69af151327..465651a2ef 100644
--- a/compiler/GHC/Tc/Deriv/Generate.hs
+++ b/compiler/GHC/Tc/Deriv/Generate.hs
@@ -39,8 +39,6 @@ module GHC.Tc.Deriv.Generate (
getPossibleDataCons, tyConInstArgTys
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Tc.Utils.Monad
diff --git a/compiler/GHC/Tc/Deriv/Generics.hs b/compiler/GHC/Tc/Deriv/Generics.hs
index 9e2dbf07df..d2acbd515a 100644
--- a/compiler/GHC/Tc/Deriv/Generics.hs
+++ b/compiler/GHC/Tc/Deriv/Generics.hs
@@ -62,8 +62,6 @@ import Control.Monad (mplus)
import Data.List (zip4, partition)
import Data.Maybe (isJust)
-#include "HsVersions.h"
-
{-
************************************************************************
* *
diff --git a/compiler/GHC/Tc/Deriv/Infer.hs b/compiler/GHC/Tc/Deriv/Infer.hs
index 5caf62e6c0..b09070e653 100644
--- a/compiler/GHC/Tc/Deriv/Infer.hs
+++ b/compiler/GHC/Tc/Deriv/Infer.hs
@@ -14,8 +14,6 @@ module GHC.Tc.Deriv.Infer
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Data.Bag
diff --git a/compiler/GHC/Tc/Errors.hs b/compiler/GHC/Tc/Errors.hs
index 40810ee619..e4a9abb3ee 100644
--- a/compiler/GHC/Tc/Errors.hs
+++ b/compiler/GHC/Tc/Errors.hs
@@ -12,8 +12,6 @@ module GHC.Tc.Errors(
solverDepthErrorTcS
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Tc.Types
diff --git a/compiler/GHC/Tc/Gen/App.hs b/compiler/GHC/Tc/Gen/App.hs
index 1c5876df52..53f13cc645 100644
--- a/compiler/GHC/Tc/Gen/App.hs
+++ b/compiler/GHC/Tc/Gen/App.hs
@@ -54,8 +54,6 @@ import qualified GHC.LanguageExtensions as LangExt
import Control.Monad
import Data.Function
-#include "HsVersions.h"
-
import GHC.Prelude
{- *********************************************************************
diff --git a/compiler/GHC/Tc/Gen/Bind.hs b/compiler/GHC/Tc/Gen/Bind.hs
index 386f1959b6..135cc67f3b 100644
--- a/compiler/GHC/Tc/Gen/Bind.hs
+++ b/compiler/GHC/Tc/Gen/Bind.hs
@@ -79,8 +79,6 @@ import qualified GHC.LanguageExtensions as LangExt
import Control.Monad
import Data.Foldable (find)
-#include "HsVersions.h"
-
{-
************************************************************************
* *
diff --git a/compiler/GHC/Tc/Gen/Expr.hs b/compiler/GHC/Tc/Gen/Expr.hs
index edcd4fc4d5..c9d18bca27 100644
--- a/compiler/GHC/Tc/Gen/Expr.hs
+++ b/compiler/GHC/Tc/Gen/Expr.hs
@@ -26,8 +26,6 @@ module GHC.Tc.Gen.Expr
addAmbiguousNameErr,
getFixedTyVars ) where
-#include "HsVersions.h"
-
import GHC.Prelude
import {-# SOURCE #-} GHC.Tc.Gen.Splice( tcSpliceExpr, tcTypedBracket, tcUntypedBracket )
diff --git a/compiler/GHC/Tc/Gen/Foreign.hs b/compiler/GHC/Tc/Gen/Foreign.hs
index 166f366038..892cb6764e 100644
--- a/compiler/GHC/Tc/Gen/Foreign.hs
+++ b/compiler/GHC/Tc/Gen/Foreign.hs
@@ -35,8 +35,6 @@ module GHC.Tc.Gen.Foreign
, tcCheckFEType
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
diff --git a/compiler/GHC/Tc/Gen/Head.hs b/compiler/GHC/Tc/Gen/Head.hs
index 9767681607..a03f941168 100644
--- a/compiler/GHC/Tc/Gen/Head.hs
+++ b/compiler/GHC/Tc/Gen/Head.hs
@@ -78,8 +78,6 @@ import Control.Monad
import Data.Function
import qualified Data.List.NonEmpty as NE
-#include "HsVersions.h"
-
import GHC.Prelude
diff --git a/compiler/GHC/Tc/Gen/HsType.hs b/compiler/GHC/Tc/Gen/HsType.hs
index 18af6a8ea4..297df294d3 100644
--- a/compiler/GHC/Tc/Gen/HsType.hs
+++ b/compiler/GHC/Tc/Gen/HsType.hs
@@ -74,8 +74,6 @@ module GHC.Tc.Gen.HsType (
funAppCtxt, addTyConFlavCtxt
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
diff --git a/compiler/GHC/Tc/Gen/Match.hs b/compiler/GHC/Tc/Gen/Match.hs
index 2f62d3d712..0605767a47 100644
--- a/compiler/GHC/Tc/Gen/Match.hs
+++ b/compiler/GHC/Tc/Gen/Match.hs
@@ -76,8 +76,6 @@ import GHC.Types.SrcLoc
import Control.Monad
import Control.Arrow ( second )
-#include "HsVersions.h"
-
{-
************************************************************************
* *
diff --git a/compiler/GHC/Tc/Gen/Pat.hs b/compiler/GHC/Tc/Gen/Pat.hs
index f21b5d9593..892aef0a0b 100644
--- a/compiler/GHC/Tc/Gen/Pat.hs
+++ b/compiler/GHC/Tc/Gen/Pat.hs
@@ -25,8 +25,6 @@ module GHC.Tc.Gen.Pat
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import {-# SOURCE #-} GHC.Tc.Gen.Expr( tcSyntaxOp, tcSyntaxOpGen, tcInferRho )
diff --git a/compiler/GHC/Tc/Gen/Sig.hs b/compiler/GHC/Tc/Gen/Sig.hs
index f327d8f9f7..54108bfaa1 100644
--- a/compiler/GHC/Tc/Gen/Sig.hs
+++ b/compiler/GHC/Tc/Gen/Sig.hs
@@ -24,8 +24,6 @@ module GHC.Tc.Gen.Sig(
mkPragEnv, tcSpecPrags, tcSpecWrapper, tcImpPrags, addInlinePrags
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
@@ -577,7 +575,7 @@ mkPragEnv sigs binds
-- add arity only for real INLINE pragmas, not INLINABLE
= case lookupNameEnv ar_env n of
Just ar -> inl_prag { inl_sat = Just ar }
- Nothing -> WARN( True, text "mkPragEnv no arity" <+> ppr n )
+ Nothing -> warnPprTrace True (text "mkPragEnv no arity" <+> ppr n) $
-- There really should be a binding for every INLINE pragma
inl_prag
| otherwise
diff --git a/compiler/GHC/Tc/Gen/Splice.hs b/compiler/GHC/Tc/Gen/Splice.hs
index 8748fd3786..3c0c85f7c4 100644
--- a/compiler/GHC/Tc/Gen/Splice.hs
+++ b/compiler/GHC/Tc/Gen/Splice.hs
@@ -30,8 +30,6 @@ module GHC.Tc.Gen.Splice(
finishTH, runTopSplice
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Driver.Errors
diff --git a/compiler/GHC/Tc/Instance/Class.hs b/compiler/GHC/Tc/Instance/Class.hs
index 84b523eb93..9ba131873b 100644
--- a/compiler/GHC/Tc/Instance/Class.hs
+++ b/compiler/GHC/Tc/Instance/Class.hs
@@ -9,8 +9,6 @@ module GHC.Tc.Instance.Class (
AssocInstInfo(..), isNotAssociated
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Driver.Session
diff --git a/compiler/GHC/Tc/Instance/Family.hs b/compiler/GHC/Tc/Instance/Family.hs
index ffd2f84f80..8e4181d969 100644
--- a/compiler/GHC/Tc/Instance/Family.hs
+++ b/compiler/GHC/Tc/Instance/Family.hs
@@ -62,8 +62,6 @@ import Data.Function ( on )
import qualified GHC.LanguageExtensions as LangExt
-#include "HsVersions.h"
-
{- Note [The type family instance consistency story]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Tc/Instance/FunDeps.hs b/compiler/GHC/Tc/Instance/FunDeps.hs
index c3bf31fed3..f5b5b7b4eb 100644
--- a/compiler/GHC/Tc/Instance/FunDeps.hs
+++ b/compiler/GHC/Tc/Instance/FunDeps.hs
@@ -21,8 +21,6 @@ module GHC.Tc.Instance.FunDeps
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Types.Name
diff --git a/compiler/GHC/Tc/Instance/Typeable.hs b/compiler/GHC/Tc/Instance/Typeable.hs
index 0de6ec4e78..193ee75009 100644
--- a/compiler/GHC/Tc/Instance/Typeable.hs
+++ b/compiler/GHC/Tc/Instance/Typeable.hs
@@ -10,8 +10,6 @@
module GHC.Tc.Instance.Typeable(mkTypeableBinds, tyConIsTypeable) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Platform
diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs
index 72b588a921..5e3f0b3501 100644
--- a/compiler/GHC/Tc/Module.hs
+++ b/compiler/GHC/Tc/Module.hs
@@ -179,8 +179,6 @@ import qualified Data.Set as S
import Control.DeepSeq
import Control.Monad
-#include "HsVersions.h"
-
{-
************************************************************************
* *
diff --git a/compiler/GHC/Tc/Solver.hs b/compiler/GHC/Tc/Solver.hs
index 373483b5d7..31d6eabe41 100644
--- a/compiler/GHC/Tc/Solver.hs
+++ b/compiler/GHC/Tc/Solver.hs
@@ -26,8 +26,6 @@ module GHC.Tc.Solver(
approximateWC, runTcSDeriveds
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Data.Bag
diff --git a/compiler/GHC/Tc/Solver/Canonical.hs b/compiler/GHC/Tc/Solver/Canonical.hs
index 9e47c6ce8d..f0b4e9deb2 100644
--- a/compiler/GHC/Tc/Solver/Canonical.hs
+++ b/compiler/GHC/Tc/Solver/Canonical.hs
@@ -10,8 +10,6 @@ module GHC.Tc.Solver.Canonical(
solveCallStack -- For GHC.Tc.Solver
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Tc.Types.Constraint
diff --git a/compiler/GHC/Tc/Solver/Interact.hs b/compiler/GHC/Tc/Solver/Interact.hs
index 9ccdc5bc60..b28e88412c 100644
--- a/compiler/GHC/Tc/Solver/Interact.hs
+++ b/compiler/GHC/Tc/Solver/Interact.hs
@@ -8,8 +8,6 @@ module GHC.Tc.Solver.Interact (
solveSimpleWanteds, -- Solves Cts
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Types.Basic ( SwapFlag(..),
infinity, IntWithInf, intGtLimit )
diff --git a/compiler/GHC/Tc/Solver/Monad.hs b/compiler/GHC/Tc/Solver/Monad.hs
index cf116996d5..3428e811ad 100644
--- a/compiler/GHC/Tc/Solver/Monad.hs
+++ b/compiler/GHC/Tc/Solver/Monad.hs
@@ -133,8 +133,6 @@ module GHC.Tc.Solver.Monad (
breakTyVarCycle, rewriterView
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Driver.Env
diff --git a/compiler/GHC/Tc/Solver/Rewrite.hs b/compiler/GHC/Tc/Solver/Rewrite.hs
index 2c95f78f6d..b9e6a997bb 100644
--- a/compiler/GHC/Tc/Solver/Rewrite.hs
+++ b/compiler/GHC/Tc/Solver/Rewrite.hs
@@ -9,8 +9,6 @@ module GHC.Tc.Solver.Rewrite(
rewriteType
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Core.TyCo.Ppr ( pprTyVar )
diff --git a/compiler/GHC/Tc/TyCl.hs b/compiler/GHC/Tc/TyCl.hs
index 800e240f4e..6f41870632 100644
--- a/compiler/GHC/Tc/TyCl.hs
+++ b/compiler/GHC/Tc/TyCl.hs
@@ -25,8 +25,6 @@ module GHC.Tc.TyCl (
wrongKindOfFamily
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Driver.Env
diff --git a/compiler/GHC/Tc/TyCl/Build.hs b/compiler/GHC/Tc/TyCl/Build.hs
index 4e877471bb..8c370ce87c 100644
--- a/compiler/GHC/Tc/TyCl/Build.hs
+++ b/compiler/GHC/Tc/TyCl/Build.hs
@@ -15,8 +15,6 @@ module GHC.Tc.TyCl.Build (
newImplicitBinder, newTyConRepName
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Iface.Env
diff --git a/compiler/GHC/Tc/TyCl/Class.hs b/compiler/GHC/Tc/TyCl/Class.hs
index ea09c89ddb..05565c8467 100644
--- a/compiler/GHC/Tc/TyCl/Class.hs
+++ b/compiler/GHC/Tc/TyCl/Class.hs
@@ -27,8 +27,6 @@ module GHC.Tc.TyCl.Class
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
diff --git a/compiler/GHC/Tc/TyCl/Instance.hs b/compiler/GHC/Tc/TyCl/Instance.hs
index 8a80baaa90..5bd1521113 100644
--- a/compiler/GHC/Tc/TyCl/Instance.hs
+++ b/compiler/GHC/Tc/TyCl/Instance.hs
@@ -19,8 +19,6 @@ module GHC.Tc.TyCl.Instance
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
diff --git a/compiler/GHC/Tc/TyCl/PatSyn.hs b/compiler/GHC/Tc/TyCl/PatSyn.hs
index 660b0da6da..400a4d770a 100644
--- a/compiler/GHC/Tc/TyCl/PatSyn.hs
+++ b/compiler/GHC/Tc/TyCl/PatSyn.hs
@@ -65,8 +65,6 @@ import Data.Maybe( mapMaybe )
import Control.Monad ( zipWithM )
import Data.List( partition, mapAccumL )
-#include "HsVersions.h"
-
{-
************************************************************************
* *
diff --git a/compiler/GHC/Tc/TyCl/Utils.hs b/compiler/GHC/Tc/TyCl/Utils.hs
index 02c681926f..4c47d6d706 100644
--- a/compiler/GHC/Tc/TyCl/Utils.hs
+++ b/compiler/GHC/Tc/TyCl/Utils.hs
@@ -27,8 +27,6 @@ module GHC.Tc.TyCl.Utils(
tcRecSelBinds, mkRecSelBinds, mkOneRecordSelector
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Tc.Utils.Monad
diff --git a/compiler/GHC/Tc/Types.hs b/compiler/GHC/Tc/Types.hs
index 3156a581e8..dcaa4509e5 100644
--- a/compiler/GHC/Tc/Types.hs
+++ b/compiler/GHC/Tc/Types.hs
@@ -87,8 +87,6 @@ module GHC.Tc.Types(
TcRnMessage
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Platform
diff --git a/compiler/GHC/Tc/Types/Constraint.hs b/compiler/GHC/Tc/Types/Constraint.hs
index 2cff342eee..76a51f0f5e 100644
--- a/compiler/GHC/Tc/Types/Constraint.hs
+++ b/compiler/GHC/Tc/Types/Constraint.hs
@@ -70,8 +70,6 @@ module GHC.Tc.Types.Constraint (
)
where
-#include "HsVersions.h"
-
import GHC.Prelude
import {-# SOURCE #-} GHC.Tc.Types ( TcLclEnv, setLclEnvTcLevel, getLclEnvTcLevel
diff --git a/compiler/GHC/Tc/Types/Evidence.hs b/compiler/GHC/Tc/Types/Evidence.hs
index a6dfc4e5f8..e851797f7a 100644
--- a/compiler/GHC/Tc/Types/Evidence.hs
+++ b/compiler/GHC/Tc/Types/Evidence.hs
@@ -60,7 +60,6 @@ module GHC.Tc.Types.Evidence (
-- * QuoteWrapper
QuoteWrapper(..), applyQuoteWrapper, quoteWrapperTyVarTy
) where
-#include "HsVersions.h"
import GHC.Prelude
diff --git a/compiler/GHC/Tc/Types/Origin.hs b/compiler/GHC/Tc/Types/Origin.hs
index b386c65a39..a8263d4c2d 100644
--- a/compiler/GHC/Tc/Types/Origin.hs
+++ b/compiler/GHC/Tc/Types/Origin.hs
@@ -22,8 +22,6 @@ module GHC.Tc.Types.Origin (
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Tc.Utils.TcType
@@ -287,7 +285,7 @@ pprSkolInfo RuntimeUnkSkol = text "Unknown type from GHCi runtime"
-- UnkSkol
-- For type variables the others are dealt with by pprSkolTvBinding.
-- For Insts, these cases should not happen
-pprSkolInfo UnkSkol = WARN( True, text "pprSkolInfo: UnkSkol" ) text "UnkSkol"
+pprSkolInfo UnkSkol = warnPprTrace True (text "pprSkolInfo: UnkSkol") $ text "UnkSkol"
pprSigSkolInfo :: UserTypeCtxt -> TcType -> SDoc
-- The type is already tidied
diff --git a/compiler/GHC/Tc/Utils/Backpack.hs b/compiler/GHC/Tc/Utils/Backpack.hs
index 592b3a64ac..ef2f4e3cb5 100644
--- a/compiler/GHC/Tc/Utils/Backpack.hs
+++ b/compiler/GHC/Tc/Utils/Backpack.hs
@@ -89,8 +89,6 @@ import Data.List (find)
import {-# SOURCE #-} GHC.Tc.Module
-#include "HsVersions.h"
-
fixityMisMatch :: TyThing -> Fixity -> Fixity -> SDoc
fixityMisMatch real_thing real_fixity sig_fixity =
vcat [ppr real_thing <+> text "has conflicting fixities in the module",
diff --git a/compiler/GHC/Tc/Utils/Env.hs b/compiler/GHC/Tc/Utils/Env.hs
index cf0f1b706b..7c809a752d 100644
--- a/compiler/GHC/Tc/Utils/Env.hs
+++ b/compiler/GHC/Tc/Utils/Env.hs
@@ -70,8 +70,6 @@ module GHC.Tc.Utils.Env(
mkWrapperName
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Driver.Env
diff --git a/compiler/GHC/Tc/Utils/Instantiate.hs b/compiler/GHC/Tc/Utils/Instantiate.hs
index 7edaab0e42..e3dcd8c5fd 100644
--- a/compiler/GHC/Tc/Utils/Instantiate.hs
+++ b/compiler/GHC/Tc/Utils/Instantiate.hs
@@ -38,8 +38,6 @@ module GHC.Tc.Utils.Instantiate (
tyCoVarsOfCt, tyCoVarsOfCts,
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Driver.Session
diff --git a/compiler/GHC/Tc/Utils/Monad.hs b/compiler/GHC/Tc/Utils/Monad.hs
index aea13efbc0..46dd001960 100644
--- a/compiler/GHC/Tc/Utils/Monad.hs
+++ b/compiler/GHC/Tc/Utils/Monad.hs
@@ -148,8 +148,6 @@ module GHC.Tc.Utils.Monad(
module GHC.Data.IOEnv
) where
-#include "HsVersions.h"
-
import GHC.Prelude
diff --git a/compiler/GHC/Tc/Utils/TcMType.hs b/compiler/GHC/Tc/Utils/TcMType.hs
index 00b16f8380..360ffbc8ba 100644
--- a/compiler/GHC/Tc/Utils/TcMType.hs
+++ b/compiler/GHC/Tc/Utils/TcMType.hs
@@ -96,8 +96,6 @@ module GHC.Tc.Utils.TcMType (
ensureNotLevPoly, checkForLevPoly, checkForLevPolyX, formatLevPolyErr
) where
-#include "HsVersions.h"
-
-- friends:
import GHC.Prelude
@@ -1894,7 +1892,7 @@ skolemiseUnboundMetaTyVar tv
do { cts <- readMetaTyVar tv
; case cts of
Flexi -> return ()
- Indirect ty -> WARN( True, ppr tv $$ ppr ty )
+ Indirect ty -> warnPprTrace True (ppr tv $$ ppr ty) $
return () }
{- Note [Error on unconstrained meta-variables]
diff --git a/compiler/GHC/Tc/Utils/TcType.hs b/compiler/GHC/Tc/Utils/TcType.hs
index bebc370d39..b0b49be7be 100644
--- a/compiler/GHC/Tc/Utils/TcType.hs
+++ b/compiler/GHC/Tc/Utils/TcType.hs
@@ -193,8 +193,6 @@ module GHC.Tc.Utils.TcType (
) where
-#include "HsVersions.h"
-
-- friends:
import GHC.Prelude
diff --git a/compiler/GHC/Tc/Utils/Unify.hs b/compiler/GHC/Tc/Utils/Unify.hs
index 76d0418eef..4e72cbf61d 100644
--- a/compiler/GHC/Tc/Utils/Unify.hs
+++ b/compiler/GHC/Tc/Utils/Unify.hs
@@ -41,8 +41,6 @@ module GHC.Tc.Utils.Unify (
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Hs
diff --git a/compiler/GHC/Tc/Utils/Zonk.hs b/compiler/GHC/Tc/Utils/Zonk.hs
index e2fe09991f..4ff7e175a8 100644
--- a/compiler/GHC/Tc/Utils/Zonk.hs
+++ b/compiler/GHC/Tc/Utils/Zonk.hs
@@ -43,8 +43,6 @@ module GHC.Tc.Utils.Zonk (
lookupTyVarOcc
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Platform
diff --git a/compiler/GHC/Tc/Validity.hs b/compiler/GHC/Tc/Validity.hs
index 0605926d94..25828a7f11 100644
--- a/compiler/GHC/Tc/Validity.hs
+++ b/compiler/GHC/Tc/Validity.hs
@@ -20,8 +20,6 @@ module GHC.Tc.Validity (
allDistinctTyVars
) where
-#include "HsVersions.h"
-
import GHC.Prelude
import GHC.Data.Maybe