| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Exception.Safe.Checked
Description
Lightweight checked exceptions, based on https://www.well-typed.com/blog/2015/07/checked-exceptions/.
- class X e => Throws e
- class X e => ThrowsImpure e
- throw :: (MonadThrow m, Exception e, Throws e) => e -> m a
- impureThrow :: (Exception e, ThrowsImpure e) => e -> a
- catch :: (MonadCatch m, Exception e) => (Throws e => m a) -> (e -> m a) -> m a
- catchDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (ThrowsImpure e => m a) -> (e -> m a) -> m a
- handle :: (MonadCatch m, Exception e) => (e -> m a) -> (Throws e => m a) -> m a
- handleDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (e -> m a) -> (ThrowsImpure e => m a) -> m a
- try :: (MonadCatch m, Exception e) => (Throws e => m a) -> m (Either e a)
- tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (ThrowsImpure e => m a) -> m (Either e a)
- uncheck :: forall a e proxy. proxy e -> (Throws e => a) -> a
- uncheckImpure :: forall a e proxy. proxy e -> (ThrowsImpure e => a) -> a
- class (Typeable * e, Show e) => Exception e
- class Monad m => MonadIO m
- class MonadThrow m => MonadCatch m
- class MonadCatch m => MonadMask m
- class Monad m => MonadThrow m
- class NFData a
Throwing
class X e => ThrowsImpure e Source #
A constraint indicates a computation may throw impure
exception ThrowsImpure ee. Introduce a constraint with impureThrow, and discharge it
with catchDeep.
You may ignore the X superclass; it exists only to prevent additional
ThrowsImpure instances from being created.
throw :: (MonadThrow m, Exception e, Throws e) => e -> m a Source #
Like throw, but for checked exceptions.
Since: 0.1.0
impureThrow :: (Exception e, ThrowsImpure e) => e -> a Source #
Like impureThrow, but for checked exceptions.
Since: 0.1.0
Catching
catch :: (MonadCatch m, Exception e) => (Throws e => m a) -> (e -> m a) -> m a Source #
Like catch, but for checked exceptions.
Since: 0.1.0
catchDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (ThrowsImpure e => m a) -> (e -> m a) -> m a Source #
Like catchDeep, but for checked exceptions.
Since: 0.1.0
handle :: (MonadCatch m, Exception e) => (e -> m a) -> (Throws e => m a) -> m a Source #
Like handle, but for checked exceptions.
Since: 0.1.0
handleDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (e -> m a) -> (ThrowsImpure e => m a) -> m a Source #
Like handleDeep, but for checked exceptions.
Since: 0.1.0
try :: (MonadCatch m, Exception e) => (Throws e => m a) -> m (Either e a) Source #
Like try, but for checked exceptions.
Since: 0.1.0
tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (ThrowsImpure e => m a) -> m (Either e a) Source #
Like tryDeep, but for checked exceptions.
Since: 0.1.0
Unchecking exceptions
uncheckImpure :: forall a e proxy. proxy e -> (ThrowsImpure e => a) -> a Source #
Unchecked a checked, impure exception.
This is exported for completeness, but normally you should discharge a
ThrowsImpure constraint with catchDeep.
Since: 0.1.0
Re-exports
class (Typeable * e, Show e) => Exception e #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException
deriving (Show, Typeable)
instance Exception MyExceptionThe default method definitions in the Exception class do what we need
in this case. You can now throw and catch ThisException and
ThatException as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler
data SomeCompilerException = forall e . Exception e => SomeCompilerException e
deriving Typeable
instance Show SomeCompilerException where
show (SomeCompilerException e) = show e
instance Exception SomeCompilerException
compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException
compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
SomeCompilerException a <- fromException x
cast a
---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler
data SomeFrontendException = forall e . Exception e => SomeFrontendException e
deriving Typeable
instance Show SomeFrontendException where
show (SomeFrontendException e) = show e
instance Exception SomeFrontendException where
toException = compilerExceptionToException
fromException = compilerExceptionFromException
frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException
frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
SomeFrontendException a <- fromException x
cast a
---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception
data MismatchedParentheses = MismatchedParentheses
deriving (Typeable, Show)
instance Exception MismatchedParentheses where
toException = frontendExceptionToException
fromException = frontendExceptionFromExceptionWe can now catch a MismatchedParentheses exception as
MismatchedParentheses, SomeFrontendException or
SomeCompilerException, but not other types, e.g. IOException:
*Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Monads in which IO computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Minimal complete definition
class MonadThrow m => MonadCatch m #
A class for monads which allow exceptions to be caught, in particular
exceptions which were thrown by throwM.
Instances should obey the following law:
catch (throwM e) f = f e
Note that the ability to catch an exception does not guarantee that we can
deal with all possible exit points from a computation. Some monads, such as
continuation-based stacks, allow for more than just a success/failure
strategy, and therefore catch cannot be used by those monads to properly
implement a function such as finally. For more information, see
MonadMask.
Minimal complete definition
Instances
| MonadCatch IO | |
| MonadCatch STM | |
| (~) * e SomeException => MonadCatch (Either e) | Since: 0.8.3 |
| MonadCatch m => MonadCatch (ListT m) | |
| MonadCatch m => MonadCatch (MaybeT m) | Catches exceptions from the base monad. |
| (Error e, MonadCatch m) => MonadCatch (ErrorT e m) | Catches exceptions from the base monad. |
| MonadCatch m => MonadCatch (ExceptT e m) | Catches exceptions from the base monad. |
| MonadCatch m => MonadCatch (StateT s m) | |
| MonadCatch m => MonadCatch (StateT s m) | |
| (MonadCatch m, Monoid w) => MonadCatch (WriterT w m) | |
| (MonadCatch m, Monoid w) => MonadCatch (WriterT w m) | |
| MonadCatch m => MonadCatch (IdentityT * m) | |
| MonadCatch m => MonadCatch (ReaderT * r m) | |
| (MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) | |
| (MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) | |
class MonadCatch m => MonadMask m #
A class for monads which provide for the ability to account for all
possible exit points from a computation, and to mask asynchronous
exceptions. Continuation-based monads, and stacks such as ErrorT e IO
which provide for multiple failure modes, are invalid instances of this
class.
Note that this package does provide a MonadMask instance for CatchT.
This instance is only valid if the base monad provides no ability to
provide multiple exit. For example, IO or Either would be invalid base
monads, but Reader or State would be acceptable.
Instances should ensure that, in the following code:
f `finally` g
The action g is called regardless of what occurs within f, including
async exceptions.
Minimal complete definition
Instances
| MonadMask IO | |
| (~) * e SomeException => MonadMask (Either e) | Since: 0.8.3 |
| MonadMask m => MonadMask (StateT s m) | |
| MonadMask m => MonadMask (StateT s m) | |
| (MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
| (MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
| MonadMask m => MonadMask (IdentityT * m) | |
| MonadMask m => MonadMask (ReaderT * r m) | |
| (MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
| (MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
class Monad m => MonadThrow m #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Minimal complete definition
Instances
| MonadThrow [] | |
| MonadThrow Maybe | |
| MonadThrow IO | |
| MonadThrow Q | |
| MonadThrow STM | |
| (~) * e SomeException => MonadThrow (Either e) | |
| MonadThrow m => MonadThrow (ListT m) | |
| MonadThrow m => MonadThrow (MaybeT m) | Throws exceptions into the base monad. |
| (Error e, MonadThrow m) => MonadThrow (ErrorT e m) | Throws exceptions into the base monad. |
| MonadThrow m => MonadThrow (ExceptT e m) | Throws exceptions into the base monad. |
| MonadThrow m => MonadThrow (StateT s m) | |
| MonadThrow m => MonadThrow (StateT s m) | |
| (MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
| (MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
| MonadThrow m => MonadThrow (IdentityT * m) | |
| MonadThrow m => MonadThrow (ContT * r m) | |
| MonadThrow m => MonadThrow (ReaderT * r m) | |
| (MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
| (MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
A class of types that can be fully evaluated.
Since: 1.1.0.0
Instances
| NFData Bool | |
| NFData Char | |
| NFData Double | |
| NFData Float | |
| NFData Int | |
| NFData Int8 | |
| NFData Int16 | |
| NFData Int32 | |
| NFData Int64 | |
| NFData Integer | |
| NFData Word | |
| NFData Word8 | |
| NFData Word16 | |
| NFData Word32 | |
| NFData Word64 | |
| NFData CallStack | Since: 1.4.2.0 |
| NFData TypeRep | NOTE: Only defined for Since: 1.4.0.0 |
| NFData () | |
| NFData TyCon | NOTE: Only defined for Since: 1.4.0.0 |
| NFData Natural | Since: 1.4.0.0 |
| NFData Void | Since: 1.4.0.0 |
| NFData Version | Since: 1.3.0.0 |
| NFData Unique | Since: 1.4.0.0 |
| NFData ThreadId | Since: 1.4.0.0 |
| NFData ExitCode | Since: 1.4.2.0 |
| NFData CChar | Since: 1.4.0.0 |
| NFData CSChar | Since: 1.4.0.0 |
| NFData CUChar | Since: 1.4.0.0 |
| NFData CShort | Since: 1.4.0.0 |
| NFData CUShort | Since: 1.4.0.0 |
| NFData CInt | Since: 1.4.0.0 |
| NFData CUInt | Since: 1.4.0.0 |
| NFData CLong | Since: 1.4.0.0 |
| NFData CULong | Since: 1.4.0.0 |
| NFData CLLong | Since: 1.4.0.0 |
| NFData CULLong | Since: 1.4.0.0 |
| NFData CFloat | Since: 1.4.0.0 |
| NFData CDouble | Since: 1.4.0.0 |
| NFData CPtrdiff | Since: 1.4.0.0 |
| NFData CSize | Since: 1.4.0.0 |
| NFData CWchar | Since: 1.4.0.0 |
| NFData CSigAtomic | Since: 1.4.0.0 |
| NFData CClock | Since: 1.4.0.0 |
| NFData CTime | Since: 1.4.0.0 |
| NFData CUSeconds | Since: 1.4.0.0 |
| NFData CSUSeconds | Since: 1.4.0.0 |
| NFData CFile | Since: 1.4.0.0 |
| NFData CFpos | Since: 1.4.0.0 |
| NFData CJmpBuf | Since: 1.4.0.0 |
| NFData CIntPtr | Since: 1.4.0.0 |
| NFData CUIntPtr | Since: 1.4.0.0 |
| NFData CIntMax | Since: 1.4.0.0 |
| NFData CUIntMax | Since: 1.4.0.0 |
| NFData All | Since: 1.4.0.0 |
| NFData Any | Since: 1.4.0.0 |
| NFData Fingerprint | Since: 1.4.0.0 |
| NFData SrcLoc | Since: 1.4.2.0 |
| NFData a => NFData [a] | |
| NFData a => NFData (Maybe a) | |
| NFData a => NFData (Ratio a) | |
| NFData (Ptr a) | Since: 1.4.2.0 |
| NFData (FunPtr a) | Since: 1.4.2.0 |
| NFData a => NFData (Identity a) | Since: 1.4.0.0 |
| NFData a => NFData (Min a) | Since: 1.4.2.0 |
| NFData a => NFData (Max a) | Since: 1.4.2.0 |
| NFData a => NFData (First a) | Since: 1.4.2.0 |
| NFData a => NFData (Last a) | Since: 1.4.2.0 |
| NFData m => NFData (WrappedMonoid m) | Since: 1.4.2.0 |
| NFData a => NFData (Option a) | Since: 1.4.2.0 |
| NFData a => NFData (NonEmpty a) | Since: 1.4.2.0 |
| NFData (Fixed a) | Since: 1.3.0.0 |
| NFData a => NFData (Complex a) | |
| NFData (StableName a) | Since: 1.4.0.0 |
| NFData a => NFData (ZipList a) | Since: 1.4.0.0 |
| NFData a => NFData (Dual a) | Since: 1.4.0.0 |
| NFData a => NFData (Sum a) | Since: 1.4.0.0 |
| NFData a => NFData (Product a) | Since: 1.4.0.0 |
| NFData a => NFData (First a) | Since: 1.4.0.0 |
| NFData a => NFData (Last a) | Since: 1.4.0.0 |
| NFData (IORef a) | NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| NFData a => NFData (Down a) | Since: 1.4.0.0 |
| NFData (MVar a) | NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| NFData (a -> b) | This instance is for convenience and consistency with Since: 1.3.0.0 |
| (NFData a, NFData b) => NFData (Either a b) | |
| (NFData a, NFData b) => NFData (a, b) | |
| (NFData a, NFData b) => NFData (Array a b) | |
| (NFData a, NFData b) => NFData (Arg a b) | Since: 1.4.2.0 |
| NFData (Proxy k a) | Since: 1.4.0.0 |
| NFData (STRef s a) | NOTE: Only strict in the reference and not the referenced value. Since: 1.4.2.0 |
| (NFData a, NFData b, NFData c) => NFData (a, b, c) | |
| NFData a => NFData (Const k a b) | Since: 1.4.0.0 |
| (NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) | |
| (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) | |