{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
module Control.Exception.Annotated
(
AnnotatedException(..)
, exceptionWithCallStack
, throw
, throwWithCallStack
, checkpoint
, checkpointMany
, checkpointCallStack
, checkpointCallStackWith
, catch
, catches
, tryAnnotated
, try
, check
, hide
, annotatedExceptionCallStack
, addCallStackToException
, Annotation(..)
, CallStackAnnotation(..)
, Exception(..)
, Safe.SomeException(..)
, Handler (..)
) where
import Control.Applicative ((<|>))
import Control.Exception.Safe
(Exception, Handler(..), MonadCatch, MonadThrow, SomeException(..))
import qualified Control.Exception.Safe as Safe
import Data.Annotation
import Data.Maybe
import qualified Data.Set as Set
import Data.Typeable
import GHC.Stack
data AnnotatedException exception
= AnnotatedException
{ forall exception. AnnotatedException exception -> [Annotation]
annotations :: [Annotation]
, forall exception. AnnotatedException exception -> exception
exception :: exception
}
deriving ((forall a b.
(a -> b) -> AnnotatedException a -> AnnotatedException b)
-> (forall a b. a -> AnnotatedException b -> AnnotatedException a)
-> Functor AnnotatedException
forall a b. a -> AnnotatedException b -> AnnotatedException a
forall a b.
(a -> b) -> AnnotatedException a -> AnnotatedException b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> AnnotatedException a -> AnnotatedException b
fmap :: forall a b.
(a -> b) -> AnnotatedException a -> AnnotatedException b
$c<$ :: forall a b. a -> AnnotatedException b -> AnnotatedException a
<$ :: forall a b. a -> AnnotatedException b -> AnnotatedException a
Functor, (forall m. Monoid m => AnnotatedException m -> m)
-> (forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m)
-> (forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m)
-> (forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b)
-> (forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b)
-> (forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b)
-> (forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b)
-> (forall a. (a -> a -> a) -> AnnotatedException a -> a)
-> (forall a. (a -> a -> a) -> AnnotatedException a -> a)
-> (forall a. AnnotatedException a -> [a])
-> (forall a. AnnotatedException a -> Bool)
-> (forall a. AnnotatedException a -> Int)
-> (forall a. Eq a => a -> AnnotatedException a -> Bool)
-> (forall a. Ord a => AnnotatedException a -> a)
-> (forall a. Ord a => AnnotatedException a -> a)
-> (forall a. Num a => AnnotatedException a -> a)
-> (forall a. Num a => AnnotatedException a -> a)
-> Foldable AnnotatedException
forall a. Eq a => a -> AnnotatedException a -> Bool
forall a. Num a => AnnotatedException a -> a
forall a. Ord a => AnnotatedException a -> a
forall m. Monoid m => AnnotatedException m -> m
forall a. AnnotatedException a -> Bool
forall a. AnnotatedException a -> Int
forall a. AnnotatedException a -> [a]
forall a. (a -> a -> a) -> AnnotatedException a -> a
forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m
forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b
forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => AnnotatedException m -> m
fold :: forall m. Monoid m => AnnotatedException m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> AnnotatedException a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AnnotatedException a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> AnnotatedException a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> AnnotatedException a -> a
foldr1 :: forall a. (a -> a -> a) -> AnnotatedException a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> AnnotatedException a -> a
foldl1 :: forall a. (a -> a -> a) -> AnnotatedException a -> a
$ctoList :: forall a. AnnotatedException a -> [a]
toList :: forall a. AnnotatedException a -> [a]
$cnull :: forall a. AnnotatedException a -> Bool
null :: forall a. AnnotatedException a -> Bool
$clength :: forall a. AnnotatedException a -> Int
length :: forall a. AnnotatedException a -> Int
$celem :: forall a. Eq a => a -> AnnotatedException a -> Bool
elem :: forall a. Eq a => a -> AnnotatedException a -> Bool
$cmaximum :: forall a. Ord a => AnnotatedException a -> a
maximum :: forall a. Ord a => AnnotatedException a -> a
$cminimum :: forall a. Ord a => AnnotatedException a -> a
minimum :: forall a. Ord a => AnnotatedException a -> a
$csum :: forall a. Num a => AnnotatedException a -> a
sum :: forall a. Num a => AnnotatedException a -> a
$cproduct :: forall a. Num a => AnnotatedException a -> a
product :: forall a. Num a => AnnotatedException a -> a
Foldable, Functor AnnotatedException
Foldable AnnotatedException
(Functor AnnotatedException, Foldable AnnotatedException) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AnnotatedException a -> f (AnnotatedException b))
-> (forall (f :: * -> *) a.
Applicative f =>
AnnotatedException (f a) -> f (AnnotatedException a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AnnotatedException a -> m (AnnotatedException b))
-> (forall (m :: * -> *) a.
Monad m =>
AnnotatedException (m a) -> m (AnnotatedException a))
-> Traversable AnnotatedException
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AnnotatedException (m a) -> m (AnnotatedException a)
forall (f :: * -> *) a.
Applicative f =>
AnnotatedException (f a) -> f (AnnotatedException a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AnnotatedException a -> m (AnnotatedException b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AnnotatedException a -> f (AnnotatedException b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AnnotatedException a -> f (AnnotatedException b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AnnotatedException a -> f (AnnotatedException b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
AnnotatedException (f a) -> f (AnnotatedException a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AnnotatedException (f a) -> f (AnnotatedException a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AnnotatedException a -> m (AnnotatedException b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AnnotatedException a -> m (AnnotatedException b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
AnnotatedException (m a) -> m (AnnotatedException a)
sequence :: forall (m :: * -> *) a.
Monad m =>
AnnotatedException (m a) -> m (AnnotatedException a)
Traversable)
instance (Exception exception) => Show (AnnotatedException exception) where
show :: AnnotatedException exception -> [Char]
show = AnnotatedException exception -> [Char]
forall e. Exception e => e -> [Char]
Safe.displayException
instance Applicative AnnotatedException where
pure :: forall a. a -> AnnotatedException a
pure =
[Annotation] -> a -> AnnotatedException a
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException []
AnnotatedException [Annotation]
anns0 a -> b
f <*> :: forall a b.
AnnotatedException (a -> b)
-> AnnotatedException a -> AnnotatedException b
<*> AnnotatedException [Annotation]
anns1 a
a =
[Annotation] -> b -> AnnotatedException b
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException ([Annotation]
anns0 [Annotation] -> [Annotation] -> [Annotation]
forall a. Semigroup a => a -> a -> a
<> [Annotation]
anns1) (a -> b
f a
a)
instance (Exception exception) => Exception (AnnotatedException exception) where
toException :: AnnotatedException exception -> SomeException
toException AnnotatedException exception
loc =
SomeException -> SomeException
tryFlatten (SomeException -> SomeException) -> SomeException -> SomeException
forall a b. (a -> b) -> a -> b
$ AnnotatedException SomeException -> SomeException
forall e. Exception e => e -> SomeException
SomeException (AnnotatedException SomeException -> SomeException)
-> AnnotatedException SomeException -> SomeException
forall a b. (a -> b) -> a -> b
$ AnnotatedException exception -> AnnotatedException SomeException
forall e.
Exception e =>
AnnotatedException e -> AnnotatedException SomeException
hide AnnotatedException exception
loc
fromException :: SomeException -> Maybe (AnnotatedException exception)
fromException (SomeException e
exn)
| Just AnnotatedException exception
x <- e -> Maybe (AnnotatedException exception)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
exn
=
AnnotatedException exception
-> Maybe (AnnotatedException exception)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AnnotatedException exception
x
| Just (AnnotatedException [Annotation]
ann (SomeException
e :: SomeException)) <- e -> Maybe (AnnotatedException SomeException)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
exn
, Just exception
a <- SomeException -> Maybe exception
forall e. Exception e => SomeException -> Maybe e
Safe.fromException SomeException
e
=
AnnotatedException exception
-> Maybe (AnnotatedException exception)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnnotatedException exception
-> Maybe (AnnotatedException exception))
-> AnnotatedException exception
-> Maybe (AnnotatedException exception)
forall a b. (a -> b) -> a -> b
$ [Annotation] -> exception -> AnnotatedException exception
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException [Annotation]
ann exception
a
fromException SomeException
exn
| Just (exception
e :: exception) <- SomeException -> Maybe exception
forall e. Exception e => SomeException -> Maybe e
Safe.fromException SomeException
exn
=
AnnotatedException exception
-> Maybe (AnnotatedException exception)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnnotatedException exception
-> Maybe (AnnotatedException exception))
-> AnnotatedException exception
-> Maybe (AnnotatedException exception)
forall a b. (a -> b) -> a -> b
$ exception -> AnnotatedException exception
forall a. a -> AnnotatedException a
forall (f :: * -> *) a. Applicative f => a -> f a
pure exception
e
| Bool
otherwise
=
Maybe (AnnotatedException exception)
forall a. Maybe a
Nothing
displayException :: AnnotatedException exception -> [Char]
displayException (AnnotatedException {exception
[Annotation]
annotations :: forall exception. AnnotatedException exception -> [Annotation]
exception :: forall exception. AnnotatedException exception -> exception
annotations :: [Annotation]
exception :: exception
..}) =
[[Char]] -> [Char]
unlines
[ [Char]
"! AnnotatedException !"
, [Char]
"Underlying exception type: " [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> TypeRep -> [Char]
forall a. Show a => a -> [Char]
show TypeRep
exceptionType
, [Char]
""
, [Char]
"show:"
, [Char]
"\t" [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> exception -> [Char]
forall a. Show a => a -> [Char]
show exception
exception
, [Char]
""
, [Char]
"displayException:"
, [Char]
"\t" [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> exception -> [Char]
forall e. Exception e => e -> [Char]
Safe.displayException exception
exception
]
[Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Char]
annotationsMessage
[Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Char]
callStackMessage
where
exceptionType :: TypeRep
exceptionType =
case exception -> SomeException
forall e. Exception e => e -> SomeException
Safe.toException exception
exception of
SomeException e
innerException ->
e -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf e
innerException
([CallStack]
callStacks, [Annotation]
otherAnnotations) = forall a. Typeable a => [Annotation] -> ([a], [Annotation])
tryAnnotations @CallStack [Annotation]
annotations
callStackMessage :: [Char]
callStackMessage =
case [CallStack] -> Maybe CallStack
forall a. [a] -> Maybe a
listToMaybe [CallStack]
callStacks of
Maybe CallStack
Nothing ->
[Char]
"(no callstack available)"
Just CallStack
cs ->
CallStack -> [Char]
prettyCallStack CallStack
cs
annotationsMessage :: [Char]
annotationsMessage =
case [Annotation]
otherAnnotations of
[] ->
[Char]
"\n"
[Annotation]
anns ->
[Char]
"Annotations:\n"
[Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> [[Char]] -> [Char]
unlines ((Annotation -> [Char]) -> [Annotation] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (\Annotation
ann -> [Char]
"\t * " [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> Annotation -> [Char]
forall a. Show a => a -> [Char]
show Annotation
ann) [Annotation]
anns)
exceptionWithCallStack :: (Exception e, HasCallStack) => e -> AnnotatedException e
exceptionWithCallStack :: forall e. (Exception e, HasCallStack) => e -> AnnotatedException e
exceptionWithCallStack =
[Annotation] -> e -> AnnotatedException e
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException [Annotation
HasCallStack => Annotation
callStackAnnotation]
annotate :: [Annotation] -> AnnotatedException e -> AnnotatedException e
annotate :: forall e.
[Annotation] -> AnnotatedException e -> AnnotatedException e
annotate [Annotation]
newAnnotations (AnnotatedException [Annotation]
oldAnnotations e
e) =
let
([CallStack]
callStacks, [Annotation]
other) =
[Annotation] -> ([CallStack], [Annotation])
forall a. Typeable a => [Annotation] -> ([a], [Annotation])
tryAnnotations ([Annotation]
newAnnotations [Annotation] -> [Annotation] -> [Annotation]
forall a. Semigroup a => a -> a -> a
<> [Annotation]
oldAnnotations)
in
(CallStack -> AnnotatedException e -> AnnotatedException e)
-> AnnotatedException e -> [CallStack] -> AnnotatedException e
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr CallStack -> AnnotatedException e -> AnnotatedException e
forall exception.
CallStack
-> AnnotatedException exception -> AnnotatedException exception
addCallStackToException ([Annotation] -> e -> AnnotatedException e
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException [Annotation]
other e
e) [CallStack]
callStacks
hide :: Exception e => AnnotatedException e -> AnnotatedException SomeException
hide :: forall e.
Exception e =>
AnnotatedException e -> AnnotatedException SomeException
hide = (e -> SomeException)
-> AnnotatedException e -> AnnotatedException SomeException
forall a b.
(a -> b) -> AnnotatedException a -> AnnotatedException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> SomeException
forall e. Exception e => e -> SomeException
Safe.toException
check :: Exception e => AnnotatedException SomeException -> Maybe (AnnotatedException e)
check :: forall e.
Exception e =>
AnnotatedException SomeException -> Maybe (AnnotatedException e)
check = (SomeException -> Maybe e)
-> AnnotatedException SomeException -> Maybe (AnnotatedException e)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AnnotatedException a -> f (AnnotatedException b)
traverse SomeException -> Maybe e
forall e. Exception e => SomeException -> Maybe e
Safe.fromException
catch :: (HasCallStack, Exception e, MonadCatch m) => m a -> (e -> m a) -> m a
catch :: forall e (m :: * -> *) a.
(HasCallStack, Exception e, MonadCatch m) =>
m a -> (e -> m a) -> m a
catch m a
action e -> m a
handler =
(HasCallStack => m a -> [Handler m a] -> m a)
-> m a -> [Handler m a] -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack m a -> [Handler m a] -> m a
HasCallStack => m a -> [Handler m a] -> m a
forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
m a -> [Handler m a] -> m a
catches m a
action [(e -> m a) -> Handler m a
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler e -> m a
handler]
catches :: (MonadCatch m, HasCallStack) => m a -> [Handler m a] -> m a
catches :: forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
m a -> [Handler m a] -> m a
catches m a
action [Handler m a]
handlers =
m a -> [Handler m a] -> m a
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m, MonadThrow m) =>
m a -> [Handler m a] -> m a
Safe.catches m a
action ((HasCallStack => [Handler m a] -> [Handler m a])
-> [Handler m a] -> [Handler m a]
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => [Handler m a] -> [Handler m a]
[Handler m a] -> [Handler m a]
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
[Handler m a] -> [Handler m a]
mkAnnotatedHandlers [Handler m a]
handlers)
mkAnnotatedHandlers :: (HasCallStack, MonadCatch m) => [Handler m a] -> [Handler m a]
mkAnnotatedHandlers :: forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
[Handler m a] -> [Handler m a]
mkAnnotatedHandlers [Handler m a]
xs =
[Handler m a]
xs [Handler m a] -> (Handler m a -> [Handler m a]) -> [Handler m a]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(Handler e -> m a
hndlr) ->
[ (e -> m a) -> Handler m a
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler ((e -> m a) -> Handler m a) -> (e -> m a) -> Handler m a
forall a b. (a -> b) -> a -> b
$ \e
e ->
m a -> m a
forall (m :: * -> *) a. (MonadCatch m, HasCallStack) => m a -> m a
checkpointCallStack (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$ e -> m a
hndlr e
e
, (AnnotatedException e -> m a) -> Handler m a
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler ((AnnotatedException e -> m a) -> Handler m a)
-> (AnnotatedException e -> m a) -> Handler m a
forall a b. (a -> b) -> a -> b
$ \(AnnotatedException [Annotation]
anns e
e) ->
[Annotation] -> m a -> m a
forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
[Annotation] -> m a -> m a
checkpointMany [Annotation]
anns (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$ e -> m a
hndlr e
e
]
tryAnnotated :: (Exception e, MonadCatch m) => m a -> m (Either (AnnotatedException e) a)
tryAnnotated :: forall e (m :: * -> *) a.
(Exception e, MonadCatch m) =>
m a -> m (Either (AnnotatedException e) a)
tryAnnotated m a
action =
(a -> Either (AnnotatedException e) a
forall a b. b -> Either a b
Right (a -> Either (AnnotatedException e) a)
-> m a -> m (Either (AnnotatedException e) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m a
action) m (Either (AnnotatedException e) a)
-> (AnnotatedException e -> m (Either (AnnotatedException e) a))
-> m (Either (AnnotatedException e) a)
forall e (m :: * -> *) a.
(HasCallStack, Exception e, MonadCatch m) =>
m a -> (e -> m a) -> m a
`catch` (Either (AnnotatedException e) a
-> m (Either (AnnotatedException e) a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (AnnotatedException e) a
-> m (Either (AnnotatedException e) a))
-> (AnnotatedException e -> Either (AnnotatedException e) a)
-> AnnotatedException e
-> m (Either (AnnotatedException e) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnotatedException e -> Either (AnnotatedException e) a
forall a b. a -> Either a b
Left)
try :: (Exception e, MonadCatch m) => m a -> m (Either e a)
try :: forall e (m :: * -> *) a.
(Exception e, MonadCatch m) =>
m a -> m (Either e a)
try m a
action =
(a -> Either e a
forall a b. b -> Either a b
Right (a -> Either e a) -> m a -> m (Either e a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m a
action)
m (Either e a) -> (e -> m (Either e a)) -> m (Either e a)
forall e (m :: * -> *) a.
(HasCallStack, Exception e, MonadCatch m) =>
m a -> (e -> m a) -> m a
`catch`
(\e
exn -> Either e a -> m (Either e a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either e a -> m (Either e a)) -> Either e a -> m (Either e a)
forall a b. (a -> b) -> a -> b
$ e -> Either e a
forall a b. a -> Either a b
Left e
exn)
throw :: (HasCallStack, MonadThrow m, Exception e) => e -> m a
throw :: forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throw = (HasCallStack => e -> m a) -> e -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack e -> m a
HasCallStack => e -> m a
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwWithCallStack
throwWithCallStack
:: (HasCallStack, MonadThrow m, Exception e)
=> e -> m a
throwWithCallStack :: forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwWithCallStack e
e =
(HasCallStack => m a) -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => m a) -> m a) -> (HasCallStack => m a) -> m a
forall a b. (a -> b) -> a -> b
$
AnnotatedException e -> m a
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
Safe.throw ([Annotation] -> e -> AnnotatedException e
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException [Annotation
HasCallStack => Annotation
callStackAnnotation] e
e)
flatten :: AnnotatedException (AnnotatedException e) -> AnnotatedException e
flatten :: forall e.
AnnotatedException (AnnotatedException e) -> AnnotatedException e
flatten (AnnotatedException [Annotation]
a (AnnotatedException [Annotation]
b e
c)) = [Annotation] -> e -> AnnotatedException e
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException (Maybe CallStack -> [Annotation] -> [Annotation] -> [Annotation]
go Maybe CallStack
forall a. Maybe a
Nothing [Annotation]
a [Annotation]
b) e
c
where
go :: Maybe CallStack -> [Annotation] -> [Annotation] -> [Annotation]
go :: Maybe CallStack -> [Annotation] -> [Annotation] -> [Annotation]
go Maybe CallStack
mcallstack [] [Annotation]
bs =
case Maybe CallStack
mcallstack of
Just CallStack
cs ->
CallStack -> [Annotation] -> [Annotation]
addCallStackToAnnotations CallStack
cs [Annotation]
bs
Maybe CallStack
Nothing ->
[Annotation]
bs
go Maybe CallStack
mcallstack (Annotation
ann : [Annotation]
anns) [Annotation]
bs =
case Annotation -> Maybe CallStack
forall a. Typeable a => Annotation -> Maybe a
castAnnotation Annotation
ann of
Just CallStack
cs ->
let newAcc :: Maybe CallStack
newAcc = (CallStack -> CallStack) -> Maybe CallStack -> Maybe CallStack
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CallStack -> CallStack -> CallStack
mergeCallStack CallStack
cs) Maybe CallStack
mcallstack Maybe CallStack -> Maybe CallStack -> Maybe CallStack
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> CallStack -> Maybe CallStack
forall a. a -> Maybe a
Just CallStack
cs
in Maybe CallStack -> [Annotation] -> [Annotation] -> [Annotation]
go Maybe CallStack
newAcc [Annotation]
anns [Annotation]
bs
Maybe CallStack
Nothing ->
Annotation
ann Annotation -> [Annotation] -> [Annotation]
forall a. a -> [a] -> [a]
: Maybe CallStack -> [Annotation] -> [Annotation] -> [Annotation]
go Maybe CallStack
mcallstack [Annotation]
anns [Annotation]
bs
tryFlatten :: SomeException -> SomeException
tryFlatten :: SomeException -> SomeException
tryFlatten SomeException
exn =
case SomeException
-> Maybe (AnnotatedException (AnnotatedException SomeException))
forall e. Exception e => SomeException -> Maybe e
Safe.fromException SomeException
exn of
Just (AnnotatedException (AnnotatedException SomeException)
a :: AnnotatedException (AnnotatedException SomeException)) ->
AnnotatedException SomeException -> SomeException
forall e. Exception e => e -> SomeException
SomeException (AnnotatedException SomeException -> SomeException)
-> AnnotatedException SomeException -> SomeException
forall a b. (a -> b) -> a -> b
$ AnnotatedException (AnnotatedException SomeException)
-> AnnotatedException SomeException
forall e.
AnnotatedException (AnnotatedException e) -> AnnotatedException e
flatten AnnotatedException (AnnotatedException SomeException)
a
Maybe (AnnotatedException (AnnotatedException SomeException))
Nothing ->
SomeException
exn
checkpoint :: (HasCallStack, MonadCatch m) => Annotation -> m a -> m a
checkpoint :: forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
Annotation -> m a -> m a
checkpoint Annotation
ann = (HasCallStack => m a -> m a) -> m a -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ([Annotation] -> m a -> m a
forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
[Annotation] -> m a -> m a
checkpointMany [Annotation
ann])
checkpointCallStackWith
:: (MonadCatch m, HasCallStack)
=> [Annotation]
-> m a
-> m a
checkpointCallStackWith :: forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
[Annotation] -> m a -> m a
checkpointCallStackWith [Annotation]
anns =
(HasCallStack => m a -> m a) -> m a -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ([Annotation] -> m a -> m a
forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
[Annotation] -> m a -> m a
checkpointMany [Annotation]
anns)
{-# DEPRECATED checkpointCallStackWith "As of 0.2.0.0 this is exactly equivalent to `checkpointMany`." #-}
checkpointCallStack
:: (MonadCatch m, HasCallStack)
=> m a
-> m a
checkpointCallStack :: forall (m :: * -> *) a. (MonadCatch m, HasCallStack) => m a -> m a
checkpointCallStack =
(HasCallStack => m a -> m a) -> m a -> m a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Annotation -> m a -> m a
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
Annotation -> m a -> m a
checkpoint (CallStack -> Annotation
forall a. AnnC a => a -> Annotation
Annotation CallStack
HasCallStack => CallStack
callStack))
checkpointMany :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a
checkpointMany :: forall (m :: * -> *) a.
(MonadCatch m, HasCallStack) =>
[Annotation] -> m a -> m a
checkpointMany [Annotation]
anns m a
action =
m a
action m a -> (SomeException -> m a) -> m a
forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`Safe.catch` \(SomeException
exn :: SomeException) ->
AnnotatedException SomeException -> m a
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
Safe.throw
(AnnotatedException SomeException -> m a)
-> (AnnotatedException SomeException
-> AnnotatedException SomeException)
-> AnnotatedException SomeException
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallStack
-> AnnotatedException SomeException
-> AnnotatedException SomeException
forall exception.
CallStack
-> AnnotatedException exception -> AnnotatedException exception
addCallStackToException CallStack
HasCallStack => CallStack
callStack
(AnnotatedException SomeException
-> AnnotatedException SomeException)
-> (AnnotatedException SomeException
-> AnnotatedException SomeException)
-> AnnotatedException SomeException
-> AnnotatedException SomeException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Annotation]
-> AnnotatedException SomeException
-> AnnotatedException SomeException
forall e.
[Annotation] -> AnnotatedException e -> AnnotatedException e
annotate [Annotation]
anns
(AnnotatedException SomeException -> m a)
-> AnnotatedException SomeException -> m a
forall a b. (a -> b) -> a -> b
$ case SomeException -> Maybe (AnnotatedException SomeException)
forall e. Exception e => SomeException -> Maybe e
Safe.fromException SomeException
exn of
Just (AnnotatedException SomeException
e' :: AnnotatedException SomeException) ->
AnnotatedException SomeException
e'
Maybe (AnnotatedException SomeException)
Nothing -> do
SomeException -> AnnotatedException SomeException
forall a. a -> AnnotatedException a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SomeException
exn
annotatedExceptionCallStack :: AnnotatedException exception -> Maybe CallStack
annotatedExceptionCallStack :: forall exception. AnnotatedException exception -> Maybe CallStack
annotatedExceptionCallStack AnnotatedException exception
exn =
let ([CallStack]
stacks, [Annotation]
_rest) = [Annotation] -> ([CallStack], [Annotation])
forall a. Typeable a => [Annotation] -> ([a], [Annotation])
tryAnnotations (AnnotatedException exception -> [Annotation]
forall exception. AnnotatedException exception -> [Annotation]
annotations AnnotatedException exception
exn)
in [CallStack] -> Maybe CallStack
forall a. [a] -> Maybe a
listToMaybe [CallStack]
stacks
addCallStackToException
:: CallStack
-> AnnotatedException exception
-> AnnotatedException exception
addCallStackToException :: forall exception.
CallStack
-> AnnotatedException exception -> AnnotatedException exception
addCallStackToException CallStack
cs (AnnotatedException [Annotation]
anns exception
e) =
[Annotation] -> exception -> AnnotatedException exception
forall exception.
[Annotation] -> exception -> AnnotatedException exception
AnnotatedException (CallStack -> [Annotation] -> [Annotation]
addCallStackToAnnotations CallStack
cs [Annotation]
anns) exception
e
addCallStackToAnnotations :: CallStack -> [Annotation] -> [Annotation]
addCallStackToAnnotations :: CallStack -> [Annotation] -> [Annotation]
addCallStackToAnnotations CallStack
cs = [Annotation] -> [Annotation]
go
where
go :: [Annotation] -> [Annotation]
go [] =
[CallStack -> Annotation
forall a. AnnC a => a -> Annotation
Annotation CallStack
cs]
go (Annotation
ann : [Annotation]
anns) =
case Annotation -> Maybe CallStack
forall a. Typeable a => Annotation -> Maybe a
castAnnotation Annotation
ann of
Just CallStack
preexistingCallStack ->
CallStack -> Annotation
forall a. AnnC a => a -> Annotation
Annotation (CallStack -> CallStack -> CallStack
mergeCallStack CallStack
preexistingCallStack CallStack
cs) Annotation -> [Annotation] -> [Annotation]
forall a. a -> [a] -> [a]
: [Annotation]
anns
Maybe CallStack
Nothing ->
Annotation
ann Annotation -> [Annotation] -> [Annotation]
forall a. a -> [a] -> [a]
: [Annotation] -> [Annotation]
go [Annotation]
anns
mergeCallStack :: CallStack -> CallStack -> CallStack
mergeCallStack :: CallStack -> CallStack -> CallStack
mergeCallStack CallStack
pre CallStack
new =
[([Char], SrcLoc)] -> CallStack
fromCallSiteList
([([Char], SrcLoc)] -> CallStack)
-> [([Char], SrcLoc)] -> CallStack
forall a b. (a -> b) -> a -> b
$ (([Char], ([Char], [Char], [Char], Int, Int, Int, Int))
-> ([Char], SrcLoc))
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
-> [([Char], SrcLoc)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((([Char], [Char], [Char], Int, Int, Int, Int) -> SrcLoc)
-> ([Char], ([Char], [Char], [Char], Int, Int, Int, Int))
-> ([Char], SrcLoc)
forall a b. (a -> b) -> ([Char], a) -> ([Char], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Char], [Char], [Char], Int, Int, Int, Int) -> SrcLoc
fromSrcLocOrd)
([([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
-> [([Char], SrcLoc)])
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
-> [([Char], SrcLoc)]
forall a b. (a -> b) -> a -> b
$ [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
forall a. Ord a => [a] -> [a]
ordNub
([([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))])
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
forall a b. (a -> b) -> a -> b
$ (([Char], SrcLoc)
-> ([Char], ([Char], [Char], [Char], Int, Int, Int, Int)))
-> [([Char], SrcLoc)]
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((SrcLoc -> ([Char], [Char], [Char], Int, Int, Int, Int))
-> ([Char], SrcLoc)
-> ([Char], ([Char], [Char], [Char], Int, Int, Int, Int))
forall a b. (a -> b) -> ([Char], a) -> ([Char], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SrcLoc -> ([Char], [Char], [Char], Int, Int, Int, Int)
toSrcLocOrd)
([([Char], SrcLoc)]
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))])
-> [([Char], SrcLoc)]
-> [([Char], ([Char], [Char], [Char], Int, Int, Int, Int))]
forall a b. (a -> b) -> a -> b
$ CallStack -> [([Char], SrcLoc)]
getCallStack CallStack
pre [([Char], SrcLoc)] -> [([Char], SrcLoc)] -> [([Char], SrcLoc)]
forall a. Semigroup a => a -> a -> a
<> CallStack -> [([Char], SrcLoc)]
getCallStack CallStack
new
where
toSrcLocOrd :: SrcLoc -> ([Char], [Char], [Char], Int, Int, Int, Int)
toSrcLocOrd (SrcLoc [Char]
a [Char]
b [Char]
c Int
d Int
e Int
f Int
g) =
([Char]
a, [Char]
b, [Char]
c, Int
d, Int
e, Int
f, Int
g)
fromSrcLocOrd :: ([Char], [Char], [Char], Int, Int, Int, Int) -> SrcLoc
fromSrcLocOrd ([Char]
a, [Char]
b, [Char]
c, Int
d, Int
e, Int
f, Int
g) =
[Char] -> [Char] -> [Char] -> Int -> Int -> Int -> Int -> SrcLoc
SrcLoc [Char]
a [Char]
b [Char]
c Int
d Int
e Int
f Int
g
ordNub :: Ord a => [a] -> [a]
ordNub :: forall a. Ord a => [a] -> [a]
ordNub = Set a -> [a] -> [a]
forall {a}. Ord a => Set a -> [a] -> [a]
go Set a
forall a. Set a
Set.empty
where
go :: Set a -> [a] -> [a]
go Set a
_ [] = []
go Set a
s (a
x:[a]
xs)
| a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member a
x Set a
s = Set a -> [a] -> [a]
go Set a
s [a]
xs
| Bool
otherwise = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: Set a -> [a] -> [a]
go (a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
Set.insert a
x Set a
s) [a]
xs