{-# OPTIONS_GHC -fno-warn-deprecations #-}
{-# LANGUAGE ConstraintKinds #-}
module GHC.Utils.Exception
(
module CE,
module GHC.Utils.Exception
)
where
import GHC.Prelude
import Control.Exception as CE
import Control.Monad.IO.Class
import Control.Monad.Catch
catchIO :: IO a -> (IOException -> IO a) -> IO a
catchIO :: forall a. IO a -> (IOException -> IO a) -> IO a
catchIO = forall e a. Exception e => IO a -> (e -> IO a) -> IO a
CE.catch
handleIO :: (IOException -> IO a) -> IO a -> IO a
handleIO :: forall a. (IOException -> IO a) -> IO a -> IO a
handleIO = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. IO a -> (IOException -> IO a) -> IO a
catchIO
tryIO :: IO a -> IO (Either IOException a)
tryIO :: forall a. IO a -> IO (Either IOException a)
tryIO = forall e a. Exception e => IO a -> IO (Either e a)
CE.try
type ExceptionMonad m = (MonadCatch m, MonadThrow m, MonadMask m, MonadIO m)