{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ViewPatterns #-}
module Relude.Exception
(
Exception (..)
, SomeException (..)
, Bug (..)
, bug
, pattern Exc
) where
import Control.Exception (Exception (..), SomeException (..))
import Data.List ((++))
import GHC.Show (Show)
import GHC.Stack (CallStack, HasCallStack, callStack, prettyCallStack)
import Relude.Function ((.))
import Relude.Monad (Maybe (..))
import qualified Control.Exception as E (displayException, throw, toException)
data Bug = Bug SomeException CallStack
deriving stock (Int -> Bug -> ShowS
[Bug] -> ShowS
Bug -> String
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) =
forall e. Exception e => e -> String
E.displayException SomeException
e forall a. [a] -> [a] -> [a]
++ String
"\n"
forall a. [a] -> [a] -> [a]
++ CallStack -> String
prettyCallStack CallStack
cStack
impureThrow :: Exception e => e -> a
impureThrow :: forall e a. Exception e => e -> a
impureThrow = forall a e. Exception e => e -> a
E.throw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. Exception e => e -> SomeException
E.toException
bug :: (HasCallStack, Exception e) => e -> a
bug :: forall e a. (HasCallStack, Exception e) => e -> a
bug e
e = forall e a. Exception e => e -> a
impureThrow (SomeException -> CallStack -> Bug
Bug (forall e. Exception e => e -> SomeException
E.toException e
e) HasCallStack => CallStack
callStack)
pattern Exc :: Exception e => e -> SomeException
pattern $bExc :: forall e. Exception e => e -> SomeException
$mExc :: forall {r} {e}.
Exception e =>
SomeException -> (e -> r) -> ((# #) -> r) -> r
Exc e <- (fromException -> Just e)
where
Exc e
e = forall e. Exception e => e -> SomeException
toException e
e