Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Cleveland.Internal.Exceptions.Annotated
Description
This module defines annotated exceptions and machinery to work with them.
Synopsis
- data Key ann where
- Key :: ExceptionAnnotation a => Key a
- data AnnotatedException = AnnotatedException AnnotationMap SomeException
- newtype AnnotationMap = AnnotationMap {}
- class (Show ann, Typeable ann) => ExceptionAnnotation ann where
- displayAnnotation :: ann -> Doc -> Doc
- annotationPriority :: Int
- fromPossiblyAnnotatedException :: Exception e => SomeException -> Maybe e
- printAnnotations :: Buildable a => AnnotationMap -> a -> Doc
- insertAnnEx' :: (Semigroup ann, ExceptionAnnotation ann) => ann -> AnnotatedException -> AnnotatedException
- insertAnn :: (Semigroup t, ExceptionAnnotation t) => t -> AnnotationMap -> AnnotationMap
- insertAnnEx :: (Semigroup ann, ExceptionAnnotation ann) => ann -> SomeException -> SomeException
- singletonAnn :: ExceptionAnnotation t => t -> AnnotationMap
- removeAnnEx' :: forall ann. ExceptionAnnotation ann => AnnotatedException -> AnnotatedException
- removeAnn :: forall t. ExceptionAnnotation t => AnnotationMap -> AnnotationMap
- removeAnnEx :: forall ann. ExceptionAnnotation ann => SomeException -> SomeException
- lookupAnnEx' :: forall ann. ExceptionAnnotation ann => AnnotatedException -> Maybe ann
- lookupAnn :: ExceptionAnnotation t => AnnotationMap -> Maybe t
- lookupAnnEx :: forall ann. ExceptionAnnotation ann => SomeException -> Maybe ann
- annotateExceptions :: forall m a ann. (MonadCatch m, Semigroup ann, ExceptionAnnotation ann) => ann -> m a -> m a
Documentation
data AnnotatedException Source #
SomeException
augmented with arbitrary annotations.
Constructors
AnnotatedException AnnotationMap SomeException |
Instances
Exception AnnotatedException Source # | |
Defined in Test.Cleveland.Internal.Exceptions.Annotated Methods toException :: AnnotatedException -> SomeException # fromException :: SomeException -> Maybe AnnotatedException # | |
Show AnnotatedException Source # | |
Defined in Test.Cleveland.Internal.Exceptions.Annotated Methods showsPrec :: Int -> AnnotatedException -> ShowS # show :: AnnotatedException -> String # showList :: [AnnotatedException] -> ShowS # |
newtype AnnotationMap Source #
A map from Key
to corresponding annotation.
Constructors
AnnotationMap | |
Fields |
Instances
Show AnnotationMap Source # | |
Defined in Test.Cleveland.Internal.Exceptions.Annotated Methods showsPrec :: Int -> AnnotationMap -> ShowS # show :: AnnotationMap -> String # showList :: [AnnotationMap] -> ShowS # |
class (Show ann, Typeable ann) => ExceptionAnnotation ann where Source #
Type class for exception annotations.
Minimal complete definition
Methods
displayAnnotation :: ann -> Doc -> Doc Source #
Given an annotation and the error message (as Doc
), produce the
text annotated with the annotation.
annotationPriority :: Int Source #
Relative priority for sorting annotations. Annotations with higher
priority will be applied first. Default is 0
.
Instances
ExceptionAnnotation CallStackAnnotation Source # | |
Defined in Test.Cleveland.Internal.Exceptions.CallStack Methods displayAnnotation :: CallStackAnnotation -> Doc -> Doc Source # | |
ExceptionAnnotation ErrorsClarification Source # | |
Defined in Test.Cleveland.Internal.Exceptions.ErrorsClarification Methods displayAnnotation :: ErrorsClarification -> Doc -> Doc Source # | |
ExceptionAnnotation ScenarioBranchName Source # | |
Defined in Test.Cleveland.Internal.Exceptions.ScenarioBranchName Methods displayAnnotation :: ScenarioBranchName -> Doc -> Doc Source # |
fromPossiblyAnnotatedException :: Exception e => SomeException -> Maybe e Source #
Try to extract a given exception type, skipping over annotations. This
essentially makes AnnotatedException
transparent for this function.
This is intended to be used as the default implementation of fromException
for
exception types that are expected to be annotated, as to make
AnnotatedException
transparent for catch
, try
, etc.
For example:
instance Exception GenericTestError where displayException = pretty fromException = fromPossiblyAnnotatedException
Now, when catching GenericTestError
, it'll work even if wrapped in
AnnotatedException
:
>>>
try @_ @GenericTestError (addCallStack $ throwM UnexpectedSuccess)
Left UnexpectedSuccess
When catching exceptions not explicitly set up like this, this trick unfortunately won't work, so using this function explicitly is required:
>>>
data ExceptionToCatch = ExceptionToCatch deriving stock Show
>>>
instance Exception ExceptionToCatch
>>>
action = addCallStack $ throwM ExceptionToCatch
>>>
try @_ @ExceptionToCatch action
*** Exception: AnnotatedException ... ...ExceptionToCatch>>>
:{
action `catch` \(err :: SomeException) -> case fromPossiblyAnnotatedException err of Just (err' :: ExceptionToCatch) -> pass Nothing -> throwM err :}
printAnnotations :: Buildable a => AnnotationMap -> a -> Doc Source #
Print all annotations from an AnnotationMap
, given the initial message.
Essentially right-fold using displayAnnotation
.
insertAnnEx' :: (Semigroup ann, ExceptionAnnotation ann) => ann -> AnnotatedException -> AnnotatedException Source #
Insert a new annotation into AnnotatedException
.
insertAnn :: (Semigroup t, ExceptionAnnotation t) => t -> AnnotationMap -> AnnotationMap Source #
Insert a new annotation into an AnnotationMap
. If an annotation of this
type already exists, merge the annotations using the Semigroup
instance.
insertAnnEx :: (Semigroup ann, ExceptionAnnotation ann) => ann -> SomeException -> SomeException Source #
Insert a new annotation into SomeException
.
If it's already an AnnotatedException
, simply adds a new annotation.
Otherwise, wraps the exception into AnnotatedException
first.
singletonAnn :: ExceptionAnnotation t => t -> AnnotationMap Source #
Construct a singleton AnnotationMap
.
removeAnnEx' :: forall ann. ExceptionAnnotation ann => AnnotatedException -> AnnotatedException Source #
Remove an annotation of the given type from AnnotatedException
.
removeAnn :: forall t. ExceptionAnnotation t => AnnotationMap -> AnnotationMap Source #
Remove an annotation of a given type t
from AnnotationMap
.
removeAnnEx :: forall ann. ExceptionAnnotation ann => SomeException -> SomeException Source #
Remove an annotation of the given type from SomeException
. If it's not an
AnnotatedException
, this is a no-op.
lookupAnnEx' :: forall ann. ExceptionAnnotation ann => AnnotatedException -> Maybe ann Source #
Extract the given annotation type from AnnotatedException
if possible.
lookupAnn :: ExceptionAnnotation t => AnnotationMap -> Maybe t Source #
Try to find the given type t
in an AnnotationMap
.
lookupAnnEx :: forall ann. ExceptionAnnotation ann => SomeException -> Maybe ann Source #
Extract the given annotation type from SomeException
if possible.
annotateExceptions :: forall m a ann. (MonadCatch m, Semigroup ann, ExceptionAnnotation ann) => ann -> m a -> m a Source #
Add an annotation to exceptions thrown by a monadic action.