#if __GLASGOW_HASKELL__ >= 708
#endif
module Control.Exception.Safe.Checked
(
Throws
, ThrowsImpure
, throw
, impureThrow
, catch
, catchDeep
, handle
, handleDeep
, try
, tryDeep
, uncheck
, uncheckImpure
, Exception
, MonadIO
, MonadCatch
, MonadMask
, MonadThrow
, NFData
) where
import Control.DeepSeq (NFData)
import Control.Exception (Exception(..))
import Control.Exception.Safe (MonadCatch, MonadMask, MonadThrow)
import Control.Monad.IO.Class (MonadIO)
import Data.Proxy (Proxy(Proxy))
import qualified Control.Exception.Safe as Safe
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce (coerce)
#else
import Unsafe.Coerce (unsafeCoerce)
#endif
throw :: (MonadThrow m, Exception e, Throws e) => e -> m a
throw = Safe.throw
impureThrow :: (Exception e, ThrowsImpure e) => e -> a
impureThrow = Safe.impureThrow
catch :: (MonadCatch m, Exception e) => (Throws e => m a) -> (e -> m a) -> m a
catch = catch_
where
catch_
:: forall a e m. (MonadCatch m, Exception e)
=> (Throws e => m a) -> (e -> m a) -> m a
catch_ m = Safe.catch (uncheck (Proxy :: Proxy e) m)
catchDeep
:: (MonadCatch m, MonadIO m, Exception e, NFData a)
=> (ThrowsImpure e => m a) -> (e -> m a) -> m a
catchDeep = catchDeep_
where
catchDeep_ :: forall a e m. (MonadCatch m, MonadIO m, Exception e, NFData a)
=> (ThrowsImpure e => m a) -> (e -> m a) -> m a
catchDeep_ m = Safe.catchDeep (uncheckImpure (Proxy :: Proxy e) m)
handle :: (MonadCatch m, Exception e) => (e -> m a) -> (Throws e => m a) -> m a
handle f g = catch g f
handleDeep
:: (MonadCatch m, MonadIO m, Exception e, NFData a)
=> (e -> m a) -> (ThrowsImpure e => m a) -> m a
handleDeep f g = catchDeep g f
try
:: (MonadCatch m, Exception e)
=> (Throws e => m a) -> m (Either e a)
try = try_
where
try_
:: forall a e m.
(MonadCatch m, Exception e)
=> (Throws e => m a) -> m (Either e a)
try_ m = Safe.try (uncheck (Proxy :: Proxy e) m)
tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a)
=> (ThrowsImpure e => m a) -> m (Either e a)
tryDeep = tryDeep_
where
tryDeep_ :: forall a e m. (MonadCatch m, MonadIO m, Exception e, NFData a)
=> (ThrowsImpure e => m a) -> m (Either e a)
tryDeep_ m = Safe.tryDeep (uncheckImpure (Proxy :: Proxy e) m)
class X e
class X e => Throws e
class X e => ThrowsImpure e
#if __GLASGOW_HASKELL__ >= 708
type role X representational
type role Throws representational
type role ThrowsImpure representational
#endif
newtype Wrap e a = Wrap { unWrap :: Throws e => a }
newtype WrapImpure e a = WrapImpure { unWrapImpure :: ThrowsImpure e => a }
newtype Catch a = Catch a
instance X (Catch a)
instance Throws (Catch a)
instance ThrowsImpure (Catch a)
coerceWrap :: Wrap e a -> Wrap (Catch e) a
#if __GLASGOW_HASKELL__ >= 708
coerceWrap = coerce
#else
coerceWrap = unsafeCoerce
#endif
coerceWrapImpure :: WrapImpure e a -> WrapImpure (Catch e) a
#if __GLASGOW_HASKELL__ >= 708
coerceWrapImpure = coerce
#else
coerceWrapImpure = unsafeCoerce
#endif
uncheck :: forall a e proxy. proxy e -> (Throws e => a) -> a
uncheck _ m = unWrap (coerceWrap (Wrap m :: Wrap e a))
uncheckImpure :: forall a e proxy. proxy e -> (ThrowsImpure e => a) -> a
uncheckImpure _ m = unWrapImpure (coerceWrapImpure (WrapImpure m :: WrapImpure e a))