{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ViewPatterns #-}
module Universum.Exception
( module Control.Exception.Safe
, Bug (..)
, bug
, pattern Exc
, note
) where
import Control.Exception.Safe (Exception (..), MonadCatch, MonadMask (..), MonadThrow,
SomeException (..), bracket, bracketOnError, bracket_, catch,
catchAny, displayException, finally, handleAny, onException, throwM,
try, tryAny)
import Control.Monad.Except (MonadError, throwError)
import Universum.Applicative (Applicative (pure))
import Universum.Monad (Maybe (..), maybe)
import Data.List ((++))
import GHC.Show (Show)
import GHC.Stack (CallStack, HasCallStack, callStack, prettyCallStack)
import qualified Control.Exception.Safe as Safe (displayException, impureThrow, toException)
data Bug = Bug SomeException CallStack
deriving stock (Int -> Bug -> ShowS
[Bug] -> ShowS
Bug -> String
(Int -> Bug -> ShowS)
-> (Bug -> String) -> ([Bug] -> ShowS) -> Show Bug
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bug] -> ShowS
$cshowList :: [Bug] -> ShowS
show :: Bug -> String
$cshow :: Bug -> String
showsPrec :: Int -> Bug -> ShowS
$cshowsPrec :: Int -> Bug -> ShowS
Show)
instance Exception Bug where
displayException :: Bug -> String
displayException (Bug SomeException
e CallStack
cStack) = SomeException -> String
forall e. Exception e => e -> String
Safe.displayException SomeException
e String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ CallStack -> String
prettyCallStack CallStack
cStack
bug :: (HasCallStack, Exception e) => e -> a
bug :: e -> a
bug e
e = Bug -> a
forall e a. Exception e => e -> a
Safe.impureThrow (SomeException -> CallStack -> Bug
Bug (e -> SomeException
forall e. Exception e => e -> SomeException
Safe.toException e
e) CallStack
HasCallStack => CallStack
callStack)
note :: (MonadError e m) => e -> Maybe a -> m a
note :: e -> Maybe a -> m a
note e
err = m a -> (a -> m a) -> Maybe a -> m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (e -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError e
err) a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
pattern Exc :: Exception e => e -> SomeException
pattern $bExc :: e -> SomeException
$mExc :: forall r e.
Exception e =>
SomeException -> (e -> r) -> (Void# -> r) -> r
Exc e <- (fromException -> Just e)
where
Exc e
e = e -> SomeException
forall e. Exception e => e -> SomeException
toException e
e