diff --git a/compiler/GHC/Cmm/DebugBlock.hs b/compiler/GHC/Cmm/DebugBlock.hs index 8eee5843aa24e47711d40692c0c681741e914bfb..a889f4c796ce1522ccee73726151b254eb55edd3 100644 --- a/compiler/GHC/Cmm/DebugBlock.hs +++ b/compiler/GHC/Cmm/DebugBlock.hs @@ -119,9 +119,6 @@ cmmDebugGen modLoc decls = map (blocksForScope Nothing) topScopes -- recover by copying ticks below. scp' | SubScope _ scp' <- scp = scp' | CombinedScope scp' _ <- scp = scp' -#if __GLASGOW_HASKELL__ < 901 - | otherwise = panic "findP impossible" -#endif scopeMap = foldl' (\acc (key, scope) -> insertMulti key scope acc) Map.empty childScopes diff --git a/compiler/GHC/CmmToAsm/BlockLayout.hs b/compiler/GHC/CmmToAsm/BlockLayout.hs index ebbbf5bbd3c1b68a96e3e87a0ca133990a4456b3..94680637ae1556216d0631f8dbe170eb93d779a0 100644 --- a/compiler/GHC/CmmToAsm/BlockLayout.hs +++ b/compiler/GHC/CmmToAsm/BlockLayout.hs @@ -738,10 +738,6 @@ sequenceChain info weights blocks@((BasicBlock entry _):_) = = [masterChain] | (rest,entry) <- breakChainAt entry masterChain = [entry,rest] -#if __GLASGOW_HASKELL__ <= 810 - | otherwise = pprPanic "Entry point eliminated" $ - ppr masterChain -#endif blockList = assert (noDups [masterChain]) diff --git a/compiler/GHC/CmmToAsm/Reg/Graph.hs b/compiler/GHC/CmmToAsm/Reg/Graph.hs index 40508d39f10b47f55b49d297ea82c2dd4f859580..51b5b045ec80a752b1819834e18c64fb4d3e3d95 100644 --- a/compiler/GHC/CmmToAsm/Reg/Graph.hs +++ b/compiler/GHC/CmmToAsm/Reg/Graph.hs @@ -385,11 +385,6 @@ graphAddCoalesce (r1, r2) graph , RegReal _ <- r2 = graph -#if __GLASGOW_HASKELL__ <= 810 - | otherwise - = panic "graphAddCoalesce" -#endif - -- | Patch registers in code using the reg -> reg mapping in this graph. patchRegsFromGraph diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs index cb13e62137bc6524c045a67517e2cefe48b8d9ff..6a1abd75370f0e3d3c2156c8948359ec8947e898 100644 --- a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs +++ b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs @@ -399,12 +399,6 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs -#if __GLASGOW_HASKELL__ <= 810 - -- some other instruction - | otherwise - = cleanBackward liveSlotsOnEntry noReloads (li : acc) instrs -#endif - -- | Combine the associations from all the inward control flow edges. -- diff --git a/compiler/GHC/CmmToLlvm/CodeGen.hs b/compiler/GHC/CmmToLlvm/CodeGen.hs index cf871ecd0110832ac0ac9baebe0fa902cf77d02b..b362b8a975af3c79d5347ea599af9609105cff60 100644 --- a/compiler/GHC/CmmToLlvm/CodeGen.hs +++ b/compiler/GHC/CmmToLlvm/CodeGen.hs @@ -1684,11 +1684,6 @@ genMachOp_slow opt op [x, y] = case op of MO_AlignmentCheck {} -> panicOp -#if __GLASGOW_HASKELL__ < 811 - MO_VF_Extract {} -> panicOp - MO_V_Extract {} -> panicOp -#endif - where binLlvmOp ty binOp allow_y_cast = do platform <- getPlatform diff --git a/compiler/GHC/Core/Coercion/Opt.hs b/compiler/GHC/Core/Coercion/Opt.hs index 3ffbcecda4de78a2b6b54447779bbc9b0fa5fdf6..3cc6a1638df1f9c8d05b98c50115bdb6d2a72a7f 100644 --- a/compiler/GHC/Core/Coercion/Opt.hs +++ b/compiler/GHC/Core/Coercion/Opt.hs @@ -624,10 +624,6 @@ opt_univ env sym prov role oty1 oty2 where prov' = case prov of -#if __GLASGOW_HASKELL__ < 901 --- This alt is redundant with the first match of the FunDef - PhantomProv kco -> PhantomProv $ opt_co4_wrap env sym False Nominal kco -#endif ProofIrrelProv kco -> ProofIrrelProv $ opt_co4_wrap env sym False Nominal kco PluginProv _ -> prov diff --git a/compiler/GHC/Core/Opt/Simplify.hs b/compiler/GHC/Core/Opt/Simplify.hs index 7b7b439e33dc3e46f5f2b6a6004946b817795370..9387e1489f07d79b2dd10eaf015623676e55d81c 100644 --- a/compiler/GHC/Core/Opt/Simplify.hs +++ b/compiler/GHC/Core/Opt/Simplify.hs @@ -43,10 +43,6 @@ import GHC.Types.Unique.FM import Control.Monad import Data.Foldable ( for_ ) -#if __GLASGOW_HASKELL__ <= 810 -import GHC.Utils.Panic ( panic ) -#endif - {- ************************************************************************ * * @@ -285,9 +281,6 @@ simplifyPgm logger unit_env name_ppr_ctx opts -- Loop do_iteration (iteration_no + 1) (counts1:counts_so_far) binds2 rules1 } } -#if __GLASGOW_HASKELL__ <= 810 - | otherwise = panic "do_iteration" -#endif where -- Remember the counts_so_far are reversed totalise :: [SimplCount] -> SimplCount diff --git a/compiler/GHC/Data/FastString.hs b/compiler/GHC/Data/FastString.hs index 36d6a2d820b89d949710cf156c84c1e520ed80b7..8bd11082e10bfc7c5c9c870075afc5584e94e276 100644 --- a/compiler/GHC/Data/FastString.hs +++ b/compiler/GHC/Data/FastString.hs @@ -146,9 +146,6 @@ import Foreign import GHC.Conc.Sync (sharedCAF) #endif -#if __GLASGOW_HASKELL__ < 811 -import GHC.Base (unpackCString#,unpackNBytes#) -#endif import GHC.Exts import GHC.IO @@ -583,11 +580,7 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- DO NOT move this let binding! indexCharOffAddr# reads from the -- pointer so we need to evaluate this based on the length check -- above. Not doing this right caused #17909. -#if __GLASGOW_HASKELL__ >= 901 !c = int8ToInt# (indexInt8Array# ba# n) -#else - !c = indexInt8Array# ba# n -#endif !h2 = (h *# 16777619#) `xorI#` c in loop h2 (n +# 1#) diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs index 9165de9c247430b36a7275810983258521c6b227..1551de3df052983d4ea8713d92e27cfaabe63b09 100644 --- a/compiler/GHC/Driver/Pipeline.hs +++ b/compiler/GHC/Driver/Pipeline.hs @@ -617,9 +617,6 @@ compileForeign hsc_env lang stub_c = do LangObjcxx -> viaCPipeline Cobjcxx LangAsm -> \pe hsc_env ml fp -> asPipeline True pe hsc_env ml fp LangJs -> \pe hsc_env ml fp -> Just <$> foreignJsPipeline pe hsc_env ml fp -#if __GLASGOW_HASKELL__ < 811 - RawObject -> panic "compileForeign: should be unreachable" -#endif pipe_env = mkPipeEnv NoStop stub_c Nothing (Temporary TFL_GhcSession) res <- runPipeline (hsc_hooks hsc_env) (pipeline pipe_env hsc_env Nothing stub_c) case res of diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs index 41977c86886e0a2a71ad9b0ce335a10d70dc25e3..9671facf9ae2a319bf5757bfa3f56a4eb38c2549 100644 --- a/compiler/GHC/Hs/Binds.hs +++ b/compiler/GHC/Hs/Binds.hs @@ -545,10 +545,6 @@ ppr_monobind (FunBind { fun_id = fun, ppr_monobind (PatSynBind _ psb) = ppr psb ppr_monobind (XHsBindsLR b) = case ghcPass @idL of -#if __GLASGOW_HASKELL__ <= 900 - GhcPs -> dataConCantHappen b - GhcRn -> dataConCantHappen b -#endif GhcTc -> ppr_absbinds b where ppr_absbinds (AbsBinds { abs_tvs = tyvars, abs_ev_vars = dictvars diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs index 2420d6c1517e5a0abb7f15a720d0d6f06bc3d3b4..ce856e160ed2a5d78dc6438aad8fcd20e587ce71 100644 --- a/compiler/GHC/Hs/Expr.hs +++ b/compiler/GHC/Hs/Expr.hs @@ -712,9 +712,6 @@ ppr_expr (HsEmbTy _ _ ty) = hsep [text "type", ppr ty] ppr_expr (XExpr x) = case ghcPass @p of -#if __GLASGOW_HASKELL__ < 811 - GhcPs -> ppr x -#endif GhcRn -> ppr x GhcTc -> ppr x @@ -749,9 +746,6 @@ ppr_infix_expr (HsVar _ (L _ v)) = Just (pprInfixOcc v) ppr_infix_expr (HsRecSel _ f) = Just (pprInfixOcc f) ppr_infix_expr (HsUnboundVar _ occ) = Just (pprInfixOcc occ) ppr_infix_expr (XExpr x) = case ghcPass @p of -#if __GLASGOW_HASKELL__ < 901 - GhcPs -> Nothing -#endif GhcRn -> ppr_infix_expr_rn x GhcTc -> ppr_infix_expr_tc x ppr_infix_expr _ = Nothing @@ -856,9 +850,6 @@ hsExprNeedsParens prec = go go (XExpr x) = case ghcPass @p of GhcTc -> go_x_tc x GhcRn -> go_x_rn x -#if __GLASGOW_HASKELL__ <= 900 - GhcPs -> True -#endif go_x_tc :: XXExprGhcTc -> Bool go_x_tc (WrapExpr (HsWrap _ e)) = hsExprNeedsParens prec e @@ -1302,10 +1293,6 @@ ppr_cmd (HsCmdArrForm _ (L _ op) ps_fix rn_fix args) = fall_through ppr_cmd (XCmd x) = case ghcPass @p of -#if __GLASGOW_HASKELL__ < 811 - GhcPs -> ppr x - GhcRn -> ppr x -#endif GhcTc -> case x of HsWrap w cmd -> pprHsWrapper w (\_ -> parens (ppr_cmd cmd)) @@ -1874,10 +1861,6 @@ instance OutputableBndrId p pprHsQuote (VarBr _ False n) = text "''" <> pprPrefixOcc (unLoc n) pprHsQuote (XQuote b) = case ghcPass @p of -#if __GLASGOW_HASKELL__ <= 900 - GhcPs -> dataConCantHappen b - GhcRn -> dataConCantHappen b -#endif GhcTc -> pprPanic "pprHsQuote: `HsQuote GhcTc` shouldn't exist" (ppr b) -- See Note [The life cycle of a TH quotation] diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs index 304c9f56e8a70795f0ffa762b55f7070cf1ab864..d0a15eccbb93f6d1387b802c515ead8df9d9669f 100644 --- a/compiler/GHC/Hs/Pat.hs +++ b/compiler/GHC/Hs/Pat.hs @@ -383,9 +383,6 @@ pprPat (ConPat { pat_con = con pprPat (EmbTyPat _ toktype tp) = ppr toktype <+> ppr tp pprPat (XPat ext) = case ghcPass @p of -#if __GLASGOW_HASKELL__ < 811 - GhcPs -> dataConCantHappen ext -#endif GhcRn -> case ext of HsPatExpanded orig _ -> pprPat orig GhcTc -> case ext of @@ -593,9 +590,6 @@ isIrrefutableHsPat is_strict = goL go (EmbTyPat {}) = True go (XPat ext) = case ghcPass @p of -#if __GLASGOW_HASKELL__ < 811 - GhcPs -> dataConCantHappen ext -#endif GhcRn -> case ext of HsPatExpanded _ pat -> go pat GhcTc -> case ext of @@ -759,9 +753,6 @@ patNeedsParens p = go @p go (ViewPat {}) = True go (EmbTyPat {}) = True go (XPat ext) = case ghcPass @q of -#if __GLASGOW_HASKELL__ < 901 - GhcPs -> dataConCantHappen ext -#endif GhcRn -> case ext of HsPatExpanded orig _ -> go orig GhcTc -> case ext of diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs index 26d3578b0fb669617d0f57dab91836e03d32e06e..3558277b20ededd66ff2b2c981faaa843a316545 100644 --- a/compiler/GHC/Iface/Ext/Ast.hs +++ b/compiler/GHC/Iface/Ext/Ast.hs @@ -850,9 +850,6 @@ instance HiePass p => ToHie (BindContext (LocatedA (HsBind (GhcPass p)))) where [ toHie expr ] XHsBindsLR ext -> case hiePass @p of -#if __GLASGOW_HASKELL__ < 811 - HieRn -> dataConCantHappen ext -#endif HieTc | AbsBinds{ abs_exports = xs, abs_binds = binds , abs_ev_binds = ev_binds diff --git a/compiler/GHC/Rename/Expr.hs b/compiler/GHC/Rename/Expr.hs index bd2f0278be463e8c2486e18d546871b64eec36ac..e51a515c511cab0b2a3ea1d6f456b10e1a3dbb34 100644 --- a/compiler/GHC/Rename/Expr.hs +++ b/compiler/GHC/Rename/Expr.hs @@ -2311,9 +2311,6 @@ isStrictPattern (L loc pat) = EmbTyPat{} -> False XPat ext -> case ghcPass @p of -#if __GLASGOW_HASKELL__ < 811 - GhcPs -> dataConCantHappen ext -#endif GhcRn | HsPatExpanded _ p <- ext -> isStrictPattern (L loc p) diff --git a/compiler/GHC/Runtime/Eval.hs b/compiler/GHC/Runtime/Eval.hs index 6f32c07f4662a9c1b84e49601bfafe33f5ab0934..1802b98f565dd937a70a7f172bc90aa58f9e7538 100644 --- a/compiler/GHC/Runtime/Eval.hs +++ b/compiler/GHC/Runtime/Eval.hs @@ -396,11 +396,6 @@ handleRunStatus step expr bindings final_ids status history | EvalComplete alloc (EvalException e) <- status = return (ExecComplete (Left (fromSerializableException e)) alloc) -#if __GLASGOW_HASKELL__ <= 810 - | otherwise - = panic "not_tracing" -- actually exhaustive, but GHC can't tell -#endif - resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int -> m ExecResult diff --git a/compiler/GHC/Tc/Errors/Hole.hs b/compiler/GHC/Tc/Errors/Hole.hs index 08907f048add713d775e23b955b917c887c72627..8d0c0fa9a9c39160d71f6faa87cbb9562eb5827b 100644 --- a/compiler/GHC/Tc/Errors/Hole.hs +++ b/compiler/GHC/Tc/Errors/Hole.hs @@ -836,9 +836,6 @@ tcFilterHoleFits limit typed_hole ht@(hole_ty, _) candidates = Just (dataConWrapId con, dataConNonlinearType con) _ -> Nothing } where name = case hfc of -#if __GLASGOW_HASKELL__ < 901 - IdHFCand id -> idName id -#endif GreHFCand gre -> greName gre NameHFCand name -> name discard_it = go subs seen maxleft ty elts diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs index 5293a86371994b514da370709701ea2afe37d9cb..2f80fb6ea6fba2067df59c14427c3d34e8c89633 100644 --- a/compiler/GHC/Tc/Module.hs +++ b/compiler/GHC/Tc/Module.hs @@ -792,10 +792,6 @@ checkHiBootIface tcg_env boot_info -- TODO: Maybe setGlobalTypeEnv should be strict. setGlobalTypeEnv tcg_env_w_binds type_env' } -#if __GLASGOW_HASKELL__ <= 810 - | otherwise = panic "checkHiBootIface: unreachable code" -#endif - {- Note [DFun impedance matching] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We return a list of "impedance-matching" bindings for the dfuns diff --git a/compiler/GHC/Tc/Solver/Equality.hs b/compiler/GHC/Tc/Solver/Equality.hs index 515f42c104d819e3bf50ec95b5136cb0b0464802..d0f32e2f28d2476ddb1a9097f8da7ad159f824b4 100644 --- a/compiler/GHC/Tc/Solver/Equality.hs +++ b/compiler/GHC/Tc/Solver/Equality.hs @@ -2546,10 +2546,6 @@ rewriteEqEvidence new_rewriters old_ev swapped (Reduction lhs_co nlhs) (Reductio , ppr new_rewriters ]) ; return new_ev } -#if __GLASGOW_HASKELL__ <= 810 - | otherwise - = panic "rewriteEvidence" -#endif where new_pred = mkTcEqPredLikeEv old_ev nlhs nrhs loc = ctEvLoc old_ev diff --git a/compiler/GHC/Tc/TyCl.hs b/compiler/GHC/Tc/TyCl.hs index b66fd243a0a923566c1ef3f0989649307240d369..6a359a68b903d48c801a6d237515d14462fbb0c8 100644 --- a/compiler/GHC/Tc/TyCl.hs +++ b/compiler/GHC/Tc/TyCl.hs @@ -2981,10 +2981,6 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info -- overlap done by dropDominatedAxioms ; return fam_tc } } -#if __GLASGOW_HASKELL__ <= 810 - | otherwise = panic "tcFamInst1" -- Silence pattern-exhaustiveness checker -#endif - -- | Maybe return a list of Bools that say whether a type family was declared -- injective in the corresponding type arguments. Length of the list is equal to -- the number of arguments (including implicit kind/coercion arguments). diff --git a/compiler/GHC/Tc/TyCl/PatSyn.hs b/compiler/GHC/Tc/TyCl/PatSyn.hs index 6e65c7eaa83d89720b7f15463fd79fd81323c05b..baa3effe07bf10f5f082a1c7eb96e9e241afcb8a 100644 --- a/compiler/GHC/Tc/TyCl/PatSyn.hs +++ b/compiler/GHC/Tc/TyCl/PatSyn.hs @@ -933,9 +933,6 @@ tcPatSynBuilderBind prag_fn (PSB { psb_id = ps_lname@(L loc ps_name) ; traceTc "tcPatSynBuilderBind }" $ ppr builder_binds ; return builder_binds } } } -#if __GLASGOW_HASKELL__ <= 810 - | otherwise = panic "tcPatSynBuilderBind" -- Both cases dealt with -#endif where mb_match_group = case dir of diff --git a/compiler/GHC/Utils/Binary.hs b/compiler/GHC/Utils/Binary.hs index 03f13b1124dd16098d113e66d70171cda8bec32b..f65efa8191766844dc32e596d3fc5b7fdcf427cd 100644 --- a/compiler/GHC/Utils/Binary.hs +++ b/compiler/GHC/Utils/Binary.hs @@ -10,9 +10,6 @@ {-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} -#if MIN_VERSION_base(4,16,0) -#define HAS_TYPELITCHAR -#endif -- We always optimise this, otherwise performance of a non-optimised -- compiler is severely affected diff --git a/compiler/GHC/Utils/Binary/Typeable.hs b/compiler/GHC/Utils/Binary/Typeable.hs index 5734905ebd6e79c082f5d5a24f328846392e7de8..6b28f98c3b2fa946958b0de26b79cb59db2b5dfd 100644 --- a/compiler/GHC/Utils/Binary/Typeable.hs +++ b/compiler/GHC/Utils/Binary/Typeable.hs @@ -4,9 +4,6 @@ {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} {-# OPTIONS_GHC -Wno-orphans -Wincomplete-patterns #-} -#if MIN_VERSION_base(4,16,0) -#define HAS_TYPELITCHAR -#endif -- | Orphan Binary instances for Data.Typeable stuff module GHC.Utils.Binary.Typeable @@ -19,9 +16,7 @@ import GHC.Prelude import GHC.Utils.Binary import GHC.Exts (RuntimeRep(..), VecCount(..), VecElem(..)) -#if __GLASGOW_HASKELL__ >= 901 import GHC.Exts (Levity(Lifted, Unlifted)) -#endif import GHC.Serialized import Foreign @@ -102,13 +97,8 @@ instance Binary RuntimeRep where put_ bh (VecRep a b) = putByte bh 0 >> put_ bh a >> put_ bh b put_ bh (TupleRep reps) = putByte bh 1 >> put_ bh reps put_ bh (SumRep reps) = putByte bh 2 >> put_ bh reps -#if __GLASGOW_HASKELL__ >= 901 put_ bh (BoxedRep Lifted) = putByte bh 3 put_ bh (BoxedRep Unlifted) = putByte bh 4 -#else - put_ bh LiftedRep = putByte bh 3 - put_ bh UnliftedRep = putByte bh 4 -#endif put_ bh IntRep = putByte bh 5 put_ bh WordRep = putByte bh 6 put_ bh Int64Rep = putByte bh 7 @@ -129,13 +119,8 @@ instance Binary RuntimeRep where 0 -> VecRep <$> get bh <*> get bh 1 -> TupleRep <$> get bh 2 -> SumRep <$> get bh -#if __GLASGOW_HASKELL__ >= 901 3 -> pure (BoxedRep Lifted) 4 -> pure (BoxedRep Unlifted) -#else - 3 -> pure LiftedRep - 4 -> pure UnliftedRep -#endif 5 -> pure IntRep 6 -> pure WordRep 7 -> pure Int64Rep @@ -173,17 +158,13 @@ instance Binary KindRep where instance Binary TypeLitSort where put_ bh TypeLitSymbol = putByte bh 0 put_ bh TypeLitNat = putByte bh 1 -#if defined(HAS_TYPELITCHAR) put_ bh TypeLitChar = putByte bh 2 -#endif get bh = do tag <- getByte bh case tag of 0 -> pure TypeLitSymbol 1 -> pure TypeLitNat -#if defined(HAS_TYPELITCHAR) 2 -> pure TypeLitChar -#endif _ -> fail "Binary.putTypeLitSort: invalid tag" putTypeRep :: BinHandle -> TypeRep a -> IO () @@ -198,12 +179,6 @@ putTypeRep bh (App f x) = do put_ bh (2 :: Word8) putTypeRep bh f putTypeRep bh x -#if __GLASGOW_HASKELL__ < 903 -putTypeRep bh (Fun arg res) = do - put_ bh (3 :: Word8) - putTypeRep bh arg - putTypeRep bh res -#endif instance Binary Serialized where put_ bh (Serialized the_type bytes) = do diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 6315c211c88ca0c2f62476e8fec05b7cda2b3322..95f1b7fa171c38f78505e6a869c94fdc54ee024f 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -57,7 +57,7 @@ import Data.Ratio import GHC.CString ( unpackCString# ) import GHC.Generics ( Generic ) import GHC.Types ( Int(..), Word(..), Char(..), Double(..), Float(..), - TYPE, RuntimeRep(..), Multiplicity (..) ) + TYPE, RuntimeRep(..), Levity(..), Multiplicity (..) ) import qualified Data.Kind as Kind (Type) import GHC.Prim ( Int#, Word#, Char#, Double#, Float#, Addr# ) import GHC.Ptr ( Ptr, plusPtr ) @@ -70,11 +70,6 @@ import Foreign.ForeignPtr import Foreign.C.String import Foreign.C.Types -#if __GLASGOW_HASKELL__ >= 901 -import GHC.Types ( Levity(..) ) -#endif - -#if __GLASGOW_HASKELL__ >= 903 import Data.Array.Byte (ByteArray(..)) import GHC.Exts ( ByteArray#, unsafeFreezeByteArray#, copyAddrToByteArray#, newByteArray# @@ -82,7 +77,6 @@ import GHC.Exts , copyByteArray#, newPinnedByteArray#) import GHC.ForeignPtr (ForeignPtr(..), ForeignPtrContents(..)) import GHC.ST (ST(..), runST) -#endif ----------------------------------------------------- -- @@ -1014,11 +1008,7 @@ class Lift (t :: TYPE r) where -- | Turn a value into a Template Haskell expression, suitable for use in -- a splice. lift :: Quote m => t -> m Exp -#if __GLASGOW_HASKELL__ >= 901 default lift :: (r ~ ('BoxedRep 'Lifted), Quote m) => t -> m Exp -#else - default lift :: (r ~ 'LiftedRep, Quote m) => t -> m Exp -#endif lift = unTypeCode . liftTyped -- | Turn a value into a Template Haskell typed expression, suitable for use @@ -1141,8 +1131,6 @@ instance Lift Addr# where lift x = return (LitE (StringPrimL (map (fromIntegral . ord) (unpackCString# x)))) -#if __GLASGOW_HASKELL__ >= 903 - -- | -- @since 2.19.0.0 instance Lift ByteArray where @@ -1174,8 +1162,6 @@ addrToByteArray (I# len) addr = runST $ ST $ s'' -> case unsafeFreezeByteArray# mb s'' of (# s''', ret #) -> (# s''', ByteArray ret #) -#endif - instance Lift a => Lift (Maybe a) where liftTyped x = unsafeCodeCoerce (lift x)