module Foundation.Monad.Exception
( MonadThrow(..)
, MonadCatch(..)
, MonadBracket(..)
) where
import Basement.Compat.Base
import Basement.Compat.AMP
import qualified Control.Exception as E
class AMPMonad m => MonadThrow m where
throw :: Exception e => e -> m a
class MonadThrow m => MonadCatch m where
catch :: Exception e => m a -> (e -> m a) -> m a
class MonadCatch m => MonadBracket m where
generalBracket
:: m a
-> (a -> b -> m ignored1)
-> (a -> E.SomeException -> m ignored2)
-> (a -> m b)
-> m b
instance MonadThrow IO where
throw = E.throwIO
instance MonadCatch IO where
catch = E.catch
instance MonadBracket IO where
generalBracket acquire onSuccess onException inner = E.mask $ \restore -> do
x <- acquire
res1 <- E.try $ restore $ inner x
case res1 of
Left (e1 :: E.SomeException) -> do
E.uninterruptibleMask_ $ fmap (const ()) (onException x e1) `E.catch`
(\(_ :: E.SomeException) -> return ())
E.throwIO e1
Right y -> do
_ <- onSuccess x y
return y