cleveland-0.3.0: Testing framework for Morley.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cleveland.Internal.Exceptions.Annotated

Description

This module defines annotated exceptions and machinery to work with them.

Synopsis

Documentation

class (Show ann, Typeable ann) => ExceptionAnnotation ann where Source #

Type class for exception annotations.

Minimal complete definition

displayAnnotation

Methods

displayAnnotation :: ann -> Builder -> Builder Source #

Given an annotation and the error message (as Builder), 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.

newtype AnnotationMap Source #

A map from Key to corresponding annotation.

Instances

Instances details
Show AnnotationMap Source # 
Instance details

Defined in Test.Cleveland.Internal.Exceptions.Annotated

data Key ann where Source #

Constructors

Key :: ExceptionAnnotation a => Key a 

Instances

Instances details
GCompare Key Source # 
Instance details

Defined in Test.Cleveland.Internal.Exceptions.Annotated

Methods

gcompare :: forall (a :: k) (b :: k). Key a -> Key b -> GOrdering a b #

GEq Key Source # 
Instance details

Defined in Test.Cleveland.Internal.Exceptions.Annotated

Methods

geq :: forall (a :: k) (b :: k). Key a -> Key b -> Maybe (a :~: b) #

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.

removeAnnEx' :: forall ann. ExceptionAnnotation ann => AnnotatedException -> AnnotatedException Source #

Remove an annotation of the given type from AnnotatedException.

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.

lookupAnnEx :: forall ann. ExceptionAnnotation ann => SomeException -> Maybe ann Source #

Extract the given annotation type from SomeException if possible.

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 -> Builder Source #

Print all annotations from an AnnotationMap, given the initial message.

Essentially right-fold using displayAnnotation.

lookupAnn :: ExceptionAnnotation t => AnnotationMap -> Maybe t Source #

Try to find the given type t in an AnnotationMap.

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.

removeAnn :: forall t. ExceptionAnnotation t => AnnotationMap -> AnnotationMap Source #

Remove an annotation of a given type t from AnnotationMap.

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.