{-# LANGUAGE ScopedTypeVariables, CPP, ConstraintKinds #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
module Control.Exception.Extra(
module Control.Exception,
Partial,
retry, retryBool,
errorWithoutStackTrace,
showException, stringException,
errorIO,
ignore,
catch_, handle_, try_,
catchJust_, handleJust_, tryJust_,
catchBool, handleBool, tryBool
) where
#if __GLASGOW_HASKELL__ >= 800
import GHC.Stack
#endif
import Control.Exception
import Control.Monad
import Data.List.Extra
import Data.Functor
import Partial
import Prelude
stringException :: String -> IO String
stringException x = do
r <- try_ $ evaluate $ list [] (\x xs -> x `seq` x:xs) x
case r of
Left e -> return "<Exception>"
Right [] -> return []
Right (x:xs) -> (x:) <$> stringException xs
showException :: Show e => e -> IO String
showException = stringException . show
#if __GLASGOW_HASKELL__ < 800
errorWithoutStackTrace :: String -> a
errorWithoutStackTrace = error
#endif
ignore :: IO () -> IO ()
ignore = void . try_
errorIO :: Partial => String -> IO a
errorIO x = withFrozenCallStack $ evaluate $ error x
#if __GLASGOW_HASKELL__ < 800
withFrozenCallStack :: a -> a
withFrozenCallStack = id
#endif
retry :: Int -> IO a -> IO a
retry i x | i <= 0 = error "Control.Exception.Extra.retry: count must be 1 or more"
retry i x = retryBool (\(e :: SomeException) -> True) i x
retryBool :: Exception e => (e -> Bool) -> Int -> IO a -> IO a
retryBool p i x | i <= 0 = error "Control.Exception.Extra.retryBool: count must be 1 or more"
retryBool p 1 x = x
retryBool p i x = do
res <- tryBool p x
case res of
Left _ -> retryBool p (i-1) x
Right v -> return v
catch_ :: IO a -> (SomeException -> IO a) -> IO a
catch_ = Control.Exception.catch
catchJust_ :: (SomeException -> Maybe b) -> IO a -> (b -> IO a) -> IO a
catchJust_ = catchJust
handle_ :: (SomeException -> IO a) -> IO a -> IO a
handle_ = handle
handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO a
handleJust_ = handleJust
try_ :: IO a -> IO (Either SomeException a)
try_ = try
tryJust_ :: (SomeException -> Maybe b) -> IO a -> IO (Either b a)
tryJust_ = tryJust
catchBool :: Exception e => (e -> Bool) -> IO a -> (e -> IO a) -> IO a
catchBool f a b = catchJust (bool f) a b
handleBool :: Exception e => (e -> Bool) -> (e -> IO a) -> IO a -> IO a
handleBool f a b = handleJust (bool f) a b
tryBool :: Exception e => (e -> Bool) -> IO a -> IO (Either e a)
tryBool f a = tryJust (bool f) a
bool :: (e -> Bool) -> (e -> Maybe e)
bool f x = if f x then Just x else Nothing