annotated-exception-0.2.0.4: Exceptions, with checkpoints and context.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Annotation

Description

An Annotation is attached to an AnnotatedException. They're essentially a dynamically typed value with a convenient IsString instance.

When integrating into your own application, you will likely want to do more than just have the String you get from showing the Annotation. You can do this by creating a special wrapper type that carries a class constraint. This allows you to also pluck out the Annotations from your library or executable independently and treat them differently from unknonwn annotations.

As an example, here's one that requires a ToJSON constraint on the underlying value. This means that you can convert any annotated value to JSON, and then use that JSON in bug reports or logging.

data JsonAnnotation where
  JsonAnnotation :: (ToJSON a, Typeable a) => a -> JsonAnnotation

instance Show JsonANnotation where
  show (JsonAnnotation a) = concat
     [ "(JsonAnnotation ("
     , show (toJSON a)
     , "))"
     ]

jsonCheckpoint :: (Typeable a, ToJSON a, HasCallStack, MonadCatch m) => a -> m a -> m a
jsonCheckpoint val = withFrozenCallStack checkpoint (JsonAnnotation val)

When handling the [Annotation] carried on the AnnotatedException, you can use tryAnnotations to pick out the JSON annotations.

jsonAnnotations :: [Annotation] -> ([JsonAnnotation], [Annotation])
jsonAnnotations = tryAnnotations

and handle them however you please.

Since: 0.1.0.0

Synopsis

Documentation

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

Constructors

CallStackAnnotation

Deprecated: You can just use CallStack directly now.

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 showing the Annotation if it is otherwise unrecognized.

Since: 0.1.0.0

Constructors

Annotation :: AnnC a => a -> Annotation 

Instances

Instances details
Show Annotation Source #

Since: 0.1.0.0

Instance details

Defined in Data.Annotation

IsString Annotation Source #

Since: 0.1.0.0

Instance details

Defined in Data.Annotation

type AnnC a = (Typeable a, Show a) Source #

The constraints that the value inside an Annotation must have.

We want Typeable so we can do cast and potentially get more useful information out of it.

Since: 0.1.0.0

toAnnotation :: AnnC a => a -> Annotation Source #

Wrap a value in an Annotation.

Since: 0.1.0.0

castAnnotation :: forall a. Typeable a => Annotation -> Maybe a Source #

Attempt to cast the underlying value out of an Annotation.

Since: 0.1.0.0

tryAnnotation :: forall a. Typeable a => Annotation -> Either a Annotation Source #

Attempt to cast the underlying value out of an Annotation. Returns the original Annotation if the cast isn't right.

Since: 0.1.0.0

tryAnnotations :: forall a. Typeable a => [Annotation] -> ([a], [Annotation]) Source #

Attempt to cast list of Annotation into the given type. Any Annotation that is not in that form is left untouched.

Since: 0.1.0.0

annotationTypes :: [Annotation] -> Set TypeRep Source #

Returns the Set of types that are in the given annotations.

Since: 0.1.0.0

mapAnnotation :: (AnnC a, AnnC b) => (a -> b) -> Annotation -> Maybe Annotation Source #

Map a function over the given Annotation. If the types don't match up, then the whole thing returns Nothing.

Since: 0.1.0.0

mapMaybeAnnotation :: (AnnC a, AnnC b) => (a -> b) -> Annotation -> Annotation Source #

Map a function over the Annotation, leaving it unchanged if the types don't match.

Since: 0.1.0.0

callStackAnnotation :: HasCallStack => Annotation Source #

Grab an Annotation corresponding to the CallStack that is currently in scope.

Since: 0.1.0.0

callStackToAnnotation :: CallStack -> Annotation Source #

Stuff a CallStack into an Annotation via the CallStackAnnotation newtype wrapper.

Since: 0.1.0.0

callStackFromAnnotation :: CallStackAnnotation -> CallStack Source #

Deprecated: You can use CallStack directly in annotations as of 0.2.0.0.

Convert the legacy CallStackAnnotation into a CallStack.

Deprecated in 0.2.0.0 since you can use CallStack directly.

Since: 0.1.0.0

callStackInAnnotations :: [Annotation] -> ([CallStack], [Annotation]) Source #

Deprecated: You can just use tryAnnotations directly as of 0.2.0.0.

Extract the CallStacks from the [Annotation]. Any Annotation not corresponding to a CallStack will be in the second element of the tuple.

Since: 0.1.0.0

module Data.Proxy