Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module defines an exception wrapper AnnotatedException
that
carries a list of Annotation
s, along with some helper methods for
throwing and catching that can make the annotations transparent.
While this library can be used directly, it is recommended that you
define your own types and functions specific to your domain. As an
example, checkpoint
is useful *only* for providing exception
annotation information. However, you probably want to use checkpoint
in concert with other context adding features, like logging.
Likewise, the Annotation
type defined in Data.Annotation is
essentially a wrapper for a dynamically typed value. So you probably
want to define your own checkpoint
that uses a custom type that you
want to enforce throughout your application.
Synopsis
- data AnnotatedException exception = AnnotatedException {
- annotations :: [Annotation]
- exception :: exception
- exceptionWithCallStack :: (Exception e, HasCallStack) => e -> AnnotatedException e
- throw :: (HasCallStack, MonadThrow m, Exception e) => e -> m a
- throwWithCallStack :: (HasCallStack, MonadThrow m, Exception e) => e -> m a
- checkpoint :: (HasCallStack, MonadCatch m) => Annotation -> m a -> m a
- checkpointMany :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a
- checkpointCallStack :: (MonadCatch m, HasCallStack) => m a -> m a
- checkpointCallStackWith :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a
- catch :: (HasCallStack, Exception e, MonadCatch m) => m a -> (e -> m a) -> m a
- catches :: (MonadCatch m, HasCallStack) => m a -> [Handler m a] -> m a
- tryAnnotated :: (Exception e, MonadCatch m) => m a -> m (Either (AnnotatedException e) a)
- try :: (Exception e, MonadCatch m) => m a -> m (Either e a)
- check :: Exception e => AnnotatedException SomeException -> Maybe (AnnotatedException e)
- hide :: Exception e => AnnotatedException e -> AnnotatedException SomeException
- annotatedExceptionCallStack :: AnnotatedException exception -> Maybe CallStack
- addCallStackToException :: CallStack -> AnnotatedException exception -> AnnotatedException exception
- data Annotation where
- Annotation :: AnnC a => a -> Annotation
- newtype CallStackAnnotation = CallStackAnnotation {
- unCallStackAnnotation :: [(String, SrcLoc)]
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- data SomeException = Exception e => SomeException e
- data Handler (m :: Type -> Type) a = Exception e => Handler (e -> m a)
The Main Type
data AnnotatedException exception Source #
The AnnotatedException
type wraps an exception
with
a [
. This can provide a sort of a manual stack trace with
programmer provided data.Annotation
]
Since: 0.1.0.0
AnnotatedException | |
|
Instances
exceptionWithCallStack :: (Exception e, HasCallStack) => e -> AnnotatedException e Source #
Annotate the underlying exception with a CallStack
.
Since: 0.2.0.0
throw :: (HasCallStack, MonadThrow m, Exception e) => e -> m a Source #
Throws an Exception
and annotates it with the current CallStack
.
An alias for throwWithCallStack
.
Since: 0.2.0.0
throwWithCallStack :: (HasCallStack, MonadThrow m, Exception e) => e -> m a Source #
Attaches the CallStack
to the AnnotatedException
that is thrown.
Since: 0.1.0.0
Annotating Exceptions
checkpoint :: (HasCallStack, MonadCatch m) => Annotation -> m a -> m a Source #
Add a single Annotation
to any exceptions thrown in the following
action. The CallStack
present on any AnnotatedException
will also be
updated to include this location.
Example:
main = do checkpoint "Foo" $ do print =<< readFile "I don't exist.markdown"
The exception thrown due to a missing file will now have an Annotation
Foo
.
Since: 0.1.0.0
checkpointMany :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a Source #
Add the list of Annotation
to any exception thrown in the following
action.
Since: 0.1.0.0
checkpointCallStack :: (MonadCatch m, HasCallStack) => m a -> m a Source #
checkpointCallStackWith :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a Source #
Deprecated: As of 0.2.0.0 this is exactly equivalent to checkpointMany
.
Add the current CallStack
to the checkpoint, along with the given
annotations. This function merges CallStack
s together, attempting to
preserve the call site ordering as GHC does it.
As of 0.2.0.0, an alias for checkpointMany
.
Since: 0.1.0.0
Handling Exceptions
catch :: (HasCallStack, Exception e, MonadCatch m) => m a -> (e -> m a) -> m a Source #
Catch an exception. This works just like catch
, but it also
will attempt to catch
. The annotations will be
preserved in the handler, so rethrowing exceptions will retain the
context.AnnotatedException
e
Let's consider a few examples, that share this import and exception type.
import qualified Control.Exception.Safe as Safe import Control.Exception.Annotated data TestException deriving (Show, Exception)
We can throw an exception and catch it as usual.
throw TestException `catch` \TestException -> putStrLn "ok!"
We can throw an exception and catch it with annotations.
throw TestException `catch` \(AnnotatedException anns TestException) -> putStrLn "ok!"
We can throw an exception and catch it as a
.AnnotatedException
SomeException
throw TestException `catch` \(AnnotatedException anns (e :: SomeException) -> putStrLn "ok!"
Since: 0.1.0.0
catches :: (MonadCatch m, HasCallStack) => m a -> [Handler m a] -> m a Source #
Like catches
, but this function enhance the provided Handler
s
to "see through" any AnnotatedException
s.
Since: 0.1.2.0
tryAnnotated :: (Exception e, MonadCatch m) => m a -> m (Either (AnnotatedException e) a) Source #
Like catch
, but always returns a AnnotatedException
.
Since: 0.1.0.0
try :: (Exception e, MonadCatch m) => m a -> m (Either e a) Source #
Like try
, but can also handle an AnnotatedException
or the
underlying value. Useful when you want to try
to catch a type of
exception, but you may not care about the Annotation
s that it may or
may not have.
Example:
Left exn <- try $ throw (AnnotatedException [] TestException) exn == TestException
Left exn <- try $ throw TestException exn == AnnotatedException [] TestException
Since: 0.1.0.1
Manipulating Annotated Exceptions
check :: Exception e => AnnotatedException SomeException -> Maybe (AnnotatedException e) Source #
Call fromException
on the underlying Exception
, attaching the
annotations to the result.
Since: 0.1.0.0
hide :: Exception e => AnnotatedException e -> AnnotatedException SomeException Source #
Call toException
on the underlying Exception
.
Since: 0.1.0.0
annotatedExceptionCallStack :: AnnotatedException exception -> Maybe CallStack Source #
Retrieves the CallStack
from an AnnotatedException
if one is present.
The library maintains an internal check that a single CallStack
is present
in the list, so this only returns the first one found. If you have added
a CallStack
directly to the [
, then this will likely break.Annotation
]
Since: 0.1.0.0
addCallStackToException :: CallStack -> AnnotatedException exception -> AnnotatedException exception Source #
Adds a CallStack
to the given AnnotatedException
. This function will
search through the existing annotations, and it will not add a second
CallStack
to the list. Instead, it will append the contents of the given
CallStack
to the existing one.
This mirrors the behavior of the way HasCallStack
actually works.
Since: 0.1.0.0
Re-exports from Data.Annotation
data Annotation where Source #
An Annotation
is a wrapper around a value that includes a Typeable
constraint so we can later unpack it. It is essentially a Dynamic
, but
we also include Show
so that you can always fall back to simply show
ing
the Annotation
if it is otherwise unrecognized.
Since: 0.1.0.0
Annotation :: AnnC a => a -> Annotation |
Instances
IsString Annotation Source # | Since: 0.1.0.0 |
Defined in Data.Annotation fromString :: String -> Annotation # | |
Show Annotation Source # | Since: 0.1.0.0 |
Defined in Data.Annotation showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # |
newtype CallStackAnnotation Source #
Deprecated: You can just use CallStack
directly now.
A wrapper type for putting a CallStack
into an Annotation
. We need
this because CallStack
does not have an Eq
instance.
Deprecated in 0.2.0.0 since you can just put a CallStack
directly in an
Annotation
now that we have no need for an Eq
constraint on it.
Since: 0.1.0.0
CallStackAnnotation | Deprecated: You can just use |
|
Instances
Show CallStackAnnotation Source # | |
Defined in Data.Annotation showsPrec :: Int -> CallStackAnnotation -> ShowS # show :: CallStackAnnotation -> String # showList :: [CallStackAnnotation] -> ShowS # | |
Eq CallStackAnnotation Source # | |
Defined in Data.Annotation (==) :: CallStackAnnotation -> CallStackAnnotation -> Bool # (/=) :: CallStackAnnotation -> CallStackAnnotation -> Bool # |
Re-exports from Control.Exception.Safe
class (Typeable e, Show e) => Exception e where #
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 instance Exception MyException
The 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 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 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 Show instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Nothing
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
Render this exception value in a human-friendly manner.
Default implementation:
.show
Since: base-4.8.0.0
Instances
data SomeException #
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
Exception e => SomeException e |
Instances
Exception SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type | |
Show SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # |