module Util.Exception
(
throwLeft
,
TextException (..)
, DisplayExceptionInShow(..)
, displayUncaughtException
) where
import Control.Exception (throwIO)
import Fmt (Buildable(..), pretty)
import System.Exit (ExitCode(..))
import qualified Text.Show
throwLeft :: (MonadThrow m, Exception e) => m (Either e a) -> m a
throwLeft :: m (Either e a) -> m a
throwLeft =
(m (Either e a) -> (Either e a -> m a) -> m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left e :: e
e -> e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM e
e
Right x :: a
x -> a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x)
data TextException = TextException Text
instance Exception TextException
instance Buildable TextException where
build :: TextException -> Builder
build (TextException desc :: Text
desc) = Text -> Builder
forall p. Buildable p => p -> Builder
build Text
desc
instance Show TextException where
show :: TextException -> String
show = TextException -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty
newtype DisplayExceptionInShow = DisplayExceptionInShow { DisplayExceptionInShow -> SomeException
unDisplayExceptionInShow :: SomeException }
instance Show DisplayExceptionInShow where
show :: DisplayExceptionInShow -> String
show (DisplayExceptionInShow se :: SomeException
se) = SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
se
instance Exception DisplayExceptionInShow
displayUncaughtException :: IO () -> IO ()
displayUncaughtException :: IO () -> IO ()
displayUncaughtException = (SomeException -> SomeException) -> IO () -> IO ()
forall a. (SomeException -> SomeException) -> IO a -> IO a
mapIOExceptions SomeException -> SomeException
wrapUnlessExitCode
where
mapIOExceptions :: (SomeException -> SomeException) -> IO a -> IO a
mapIOExceptions :: (SomeException -> SomeException) -> IO a -> IO a
mapIOExceptions f :: SomeException -> SomeException
f action :: IO a
action = IO a
action IO a -> (SomeException -> IO a) -> IO a
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
`catchAny` (SomeException -> IO a
forall e a. Exception e => e -> IO a
throwIO (SomeException -> IO a)
-> (SomeException -> SomeException) -> SomeException -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> SomeException
f)
wrapUnlessExitCode :: SomeException -> SomeException
wrapUnlessExitCode :: SomeException -> SomeException
wrapUnlessExitCode e :: SomeException
e =
case SomeException -> Maybe ExitCode
forall e. Exception e => SomeException -> Maybe e
fromException @ExitCode SomeException
e of
Just _ -> SomeException
e
Nothing -> DisplayExceptionInShow -> SomeException
forall e. Exception e => e -> SomeException
toException (DisplayExceptionInShow -> SomeException)
-> DisplayExceptionInShow -> SomeException
forall a b. (a -> b) -> a -> b
$ SomeException -> DisplayExceptionInShow
DisplayExceptionInShow SomeException
e