module System.OsString.Internal.Exception where
import Control.Exception ( catch, fromException, toException, throwIO, Exception, SomeAsyncException(..) )
trySafe :: Exception e => IO a -> IO (Either e a)
trySafe :: forall e a. Exception e => IO a -> IO (Either e a)
trySafe IO a
ioA = IO (Either e a) -> (e -> IO (Either e a)) -> IO (Either e a)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch IO (Either e a)
forall {a}. IO (Either a a)
action e -> IO (Either e a)
forall {a} {b}. Exception a => a -> IO (Either a b)
eHandler
where
action :: IO (Either a a)
action = do
v <- IO a
ioA
return (Right v)
eHandler :: a -> IO (Either a b)
eHandler a
e
| a -> Bool
forall e. Exception e => e -> Bool
isAsyncException a
e = a -> IO (Either a b)
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO a
e
| Bool
otherwise = Either a b -> IO (Either a b)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either a b
forall a b. a -> Either a b
Left a
e)
isAsyncException :: Exception e => e -> Bool
isAsyncException :: forall e. Exception e => e -> Bool
isAsyncException e
e =
case SomeException -> Maybe SomeAsyncException
forall e. Exception e => SomeException -> Maybe e
fromException (e -> SomeException
forall e. Exception e => e -> SomeException
toException e
e) of
Just (SomeAsyncException e
_) -> Bool
True
Maybe SomeAsyncException
Nothing -> Bool
False