diff --git a/compiler/rename/RnSplice.hs b/compiler/rename/RnSplice.hs index 522f8dda0081ea800db21792f4f861e775b43e1b..5766080fefbe5bb9f55d4dbec7e0b739dee4dc2a 100644 --- a/compiler/rename/RnSplice.hs +++ b/compiler/rename/RnSplice.hs @@ -378,22 +378,19 @@ mkQuasiQuoteExpr flavour quoter q_span quote rnSplice :: HsSplice GhcPs -> RnM (HsSplice GhcRn, FreeVars) -- Not exported...used for all rnSplice (HsTypedSplice x hasParen splice_name expr) - = do { checkTH expr "Template Haskell typed splice" - ; loc <- getSrcSpanM + = do { loc <- getSrcSpanM ; n' <- newLocalBndrRn (cL loc splice_name) ; (expr', fvs) <- rnLExpr expr ; return (HsTypedSplice x hasParen n' expr', fvs) } rnSplice (HsUntypedSplice x hasParen splice_name expr) - = do { checkTH expr "Template Haskell untyped splice" - ; loc <- getSrcSpanM + = do { loc <- getSrcSpanM ; n' <- newLocalBndrRn (cL loc splice_name) ; (expr', fvs) <- rnLExpr expr ; return (HsUntypedSplice x hasParen n' expr', fvs) } rnSplice (HsQuasiQuote x splice_name quoter q_loc quote) - = do { checkTH quoter "Template Haskell quasi-quote" - ; loc <- getSrcSpanM + = do { loc <- getSrcSpanM ; splice_name' <- newLocalBndrRn (cL loc splice_name) -- Rename the quoter; akin to the HsVar case of rnExpr diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs index 29e4b00c4d31a1603ca37860f4d88efef7a066d2..d2918a263f86985fe70fae9861535604c830eab2 100644 --- a/compiler/simplCore/CoreMonad.hs +++ b/compiler/simplCore/CoreMonad.hs @@ -36,7 +36,6 @@ module CoreMonad ( -- ** Lifting into the monad liftIO, liftIOWithCount, - liftIO1, liftIO2, liftIO3, liftIO4, -- ** Dealing with annotations getAnnotations, getFirstAnnotations, diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index d5c600dda8634ac08def9c1be74c6b00b64bbf5f..85175b227a391ba3bbc0a47b5354090e61cba1ca 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -8,7 +8,7 @@ module TcEvidence ( HsWrapper(..), (<.>), mkWpTyApps, mkWpEvApps, mkWpEvVarApps, mkWpTyLams, mkWpLams, mkWpLet, mkWpCastN, mkWpCastR, collectHsWrapBinders, - mkWpFun, mkWpFuns, idHsWrapper, isIdHsWrapper, isErasableHsWrapper, + mkWpFun, idHsWrapper, isIdHsWrapper, isErasableHsWrapper, pprHsWrapper, -- Evidence bindings @@ -300,21 +300,6 @@ mkWpFun (WpCast co1) WpHole _ t2 _ = WpCast (mkTcFunCo Representational ( mkWpFun (WpCast co1) (WpCast co2) _ _ _ = WpCast (mkTcFunCo Representational (mkTcSymCo co1) co2) mkWpFun co1 co2 t1 _ d = WpFun co1 co2 t1 d --- | @mkWpFuns [(ty1, wrap1), (ty2, wrap2)] ty_res wrap_res@, --- where @wrap1 :: ty1 "->" ty1'@ and @wrap2 :: ty2 "->" ty2'@, --- @wrap3 :: ty3 "->" ty3'@ and @ty_res@ is /either/ @ty3@ or @ty3'@, --- gives a wrapper @(ty1' -> ty2' -> ty3) "->" (ty1 -> ty2 -> ty3')@. --- Notice that the result wrapper goes the other way round to all --- the others. This is a result of sub-typing contravariance. --- The SDoc is a description of what you were doing when you called mkWpFuns. -mkWpFuns :: [(TcType, HsWrapper)] -> TcType -> HsWrapper -> SDoc -> HsWrapper -mkWpFuns args res_ty res_wrap doc = snd $ go args res_ty res_wrap - where - go [] res_ty res_wrap = (res_ty, res_wrap) - go ((arg_ty, arg_wrap) : args) res_ty res_wrap - = let (tail_ty, tail_wrap) = go args res_ty res_wrap in - (arg_ty `mkVisFunTy` tail_ty, mkWpFun arg_wrap tail_wrap arg_ty tail_ty doc) - mkWpCastR :: TcCoercionR -> HsWrapper mkWpCastR co | isTcReflCo co = WpHole diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index 3997f2dc82f1649563aaab13098a6b90bb4127f2..25cf04f1532b3a4854e8ee66c9bd4c89421a8270 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -75,7 +75,6 @@ module TcRnMonad( askNoErrs, discardErrs, tryTcDiscardingErrs, checkNoErrs, whenNoErrs, ifErrsM, failIfErrsM, - checkTH, failTH, -- * Context management for the type checker getErrCtxt, setErrCtxt, addErrCtxt, addErrCtxtM, addLandmarkErrCtxt, @@ -1021,17 +1020,6 @@ failIfErrsM :: TcRn () -- Useful to avoid error cascades failIfErrsM = ifErrsM failM (return ()) -checkTH :: a -> String -> TcRn () -checkTH _ _ = return () -- OK - -failTH :: Outputable a => a -> String -> TcRn x -failTH e what -- Raise an error in a stage-1 compiler - = failWithTc (vcat [ hang (char 'A' <+> text what - <+> text "requires GHC with interpreter support:") - 2 (ppr e) - , text "Perhaps you are using a stage-1 compiler?" ]) - - {- ********************************************************************* * * Context management for the type checker diff --git a/compiler/utils/MonadUtils.hs b/compiler/utils/MonadUtils.hs index 1cfb943464c1f49634551bc511d2f829c52f01bd..5c28aa5f39811997da56eec7a22862ad52befd4e 100644 --- a/compiler/utils/MonadUtils.hs +++ b/compiler/utils/MonadUtils.hs @@ -8,8 +8,6 @@ module MonadUtils , MonadFix(..) , MonadIO(..) - , liftIO1, liftIO2, liftIO3, liftIO4 - , zipWith3M, zipWith3M_, zipWith4M, zipWithAndUnzipM , mapAndUnzipM, mapAndUnzip3M, mapAndUnzip4M, mapAndUnzip5M , mapAccumLM @@ -37,27 +35,6 @@ import Control.Monad.IO.Class import Data.Foldable (sequenceA_) import Data.List (unzip4, unzip5, zipWith4) -------------------------------------------------------------------------------- --- Lift combinators --- These are used throughout the compiler -------------------------------------------------------------------------------- - --- | Lift an 'IO' operation with 1 argument into another monad -liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b -liftIO1 = (.) liftIO - --- | Lift an 'IO' operation with 2 arguments into another monad -liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c -liftIO2 = ((.).(.)) liftIO - --- | Lift an 'IO' operation with 3 arguments into another monad -liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d -liftIO3 = ((.).((.).(.))) liftIO - --- | Lift an 'IO' operation with 4 arguments into another monad -liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e -liftIO4 = (((.).(.)).((.).(.))) liftIO - ------------------------------------------------------------------------------- -- Common functions -- These are used throughout the compiler