{-# LANGUAGE CPP #-}
module Effectful.Exception
(
throwIO
#if MIN_VERSION_base(4,21,0)
, rethrowIO
#endif
, catch
#if MIN_VERSION_base(4,21,0)
, catchNoPropagate
#endif
, catchDeep
, catchJust
, catchIf
, catchIO
, catchSync
, catchSyncDeep
, handle
, handleDeep
, handleJust
, handleIf
, handleIO
, handleSync
, handleSyncDeep
, try
#if MIN_VERSION_base(4,21,0)
, tryWithContext
#endif
, tryDeep
, tryJust
, tryIf
, tryIO
, trySync
, trySyncDeep
, C.Handler(..)
, catches
, catchesDeep
, bracket
, bracket_
, bracketOnError
, generalBracket
, C.ExitCase(..)
, finally
, onException
, evaluate
, evaluateDeep
#if MIN_VERSION_base(4,20,0)
, annotateIO
#endif
, isSyncException
, isAsyncException
, mask
, mask_
, uninterruptibleMask
, uninterruptibleMask_
, E.MaskingState(..)
, getMaskingState
, interruptible
, allowInterrupt
, E.SomeException(..)
, E.Exception(..)
, E.mapException
#if MIN_VERSION_base(4,20,0)
, E.addExceptionContext
, E.someExceptionContext
, E.ExceptionWithContext(..)
#if MIN_VERSION_base(4,21,0)
, E.WhileHandling(..)
#endif
, E.ExceptionContext(..)
, E.emptyExceptionContext
, E.addExceptionAnnotation
, E.getExceptionAnnotations
, E.getAllExceptionAnnotations
, E.displayExceptionContext
, E.SomeExceptionAnnotation(..)
, E.ExceptionAnnotation(..)
#endif
, E.IOException
, E.ArithException(..)
, E.ArrayException(..)
, E.AssertionFailed(..)
, E.NoMethodError(..)
, E.PatternMatchFail(..)
, E.RecConError(..)
, E.RecSelError(..)
, E.RecUpdError(..)
, E.ErrorCall(..)
, E.TypeError(..)
, E.SomeAsyncException(..)
, E.AsyncException(..)
, E.asyncExceptionToException
, E.asyncExceptionFromException
, E.NonTermination(..)
, E.NestedAtomically(..)
, E.BlockedIndefinitelyOnMVar(..)
, E.BlockedIndefinitelyOnSTM(..)
, E.AllocationLimitExceeded(..)
, E.CompactionFailed(..)
, E.Deadlock(..)
, E.assert
) where
#if MIN_VERSION_base(4,20,0)
import Control.Exception.Annotation qualified as E
import Control.Exception.Context qualified as E
#endif
import Control.DeepSeq
import Control.Exception qualified as E
import Control.Monad.Catch qualified as C
import GHC.Stack (withFrozenCallStack)
import Effectful
import Effectful.Dispatch.Static
import Effectful.Dispatch.Static.Unsafe
throwIO
:: (HasCallStack, E.Exception e)
=> e
-> Eff es a
throwIO :: forall e (es :: [Effect]) a.
(HasCallStack, Exception e) =>
e -> Eff es a
throwIO = IO a -> Eff es a
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO a -> Eff es a) -> (e -> IO a) -> e -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HasCallStack => e -> IO a) -> e -> IO a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack e -> IO a
HasCallStack => e -> IO a
forall e a. Exception e => e -> IO a
E.throwIO
#if MIN_VERSION_base(4,21,0)
rethrowIO
:: E.Exception e
=> E.ExceptionWithContext e
-> Eff es a
rethrowIO = unsafeEff_ . E.rethrowIO
#endif
catch
:: E.Exception e
=> Eff es a
-> (e -> Eff es a)
-> Eff es a
catch :: forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> (e -> Eff es a) -> Eff es a
catch Eff es a
action e -> Eff es a
handler = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> (e -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action) (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> (e -> Eff es a) -> e -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Eff es a
handler)
catchDeep
:: (E.Exception e, NFData a)
=> Eff es a
-> (e -> Eff es a)
-> Eff es a
catchDeep :: forall e a (es :: [Effect]).
(Exception e, NFData a) =>
Eff es a -> (e -> Eff es a) -> Eff es a
catchDeep Eff es a
action = Eff es a -> (e -> Eff es a) -> Eff es a
forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> (e -> Eff es a) -> Eff es a
catch (a -> Eff es a
forall a (es :: [Effect]). NFData a => a -> Eff es a
evaluateDeep (a -> Eff es a) -> Eff es a -> Eff es a
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Eff es a
action)
#if MIN_VERSION_base(4,21,0)
catchNoPropagate
:: E.Exception e
=> Eff es a
-> (E.ExceptionWithContext e -> Eff es a)
-> Eff es a
catchNoPropagate action handler = reallyUnsafeUnliftIO $ \unlift -> do
E.catchNoPropagate (unlift action) (unlift . handler)
#endif
catchJust
:: E.Exception e
=> (e -> Maybe b)
-> Eff es a
-> (b -> Eff es a)
-> Eff es a
catchJust :: forall e b (es :: [Effect]) a.
Exception e =>
(e -> Maybe b) -> Eff es a -> (b -> Eff es a) -> Eff es a
catchJust e -> Maybe b
f Eff es a
action b -> Eff es a
handler = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
(e -> Maybe b) -> IO a -> (b -> IO a) -> IO a
forall e b a.
Exception e =>
(e -> Maybe b) -> IO a -> (b -> IO a) -> IO a
E.catchJust e -> Maybe b
f (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action) (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> (b -> Eff es a) -> b -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Eff es a
handler)
catchIf
:: E.Exception e
=> (e -> Bool)
-> Eff es a
-> (e -> Eff es a)
-> Eff es a
catchIf :: forall e (es :: [Effect]) a.
Exception e =>
(e -> Bool) -> Eff es a -> (e -> Eff es a) -> Eff es a
catchIf e -> Bool
p = (e -> Maybe e) -> Eff es a -> (e -> Eff es a) -> Eff es a
forall e b (es :: [Effect]) a.
Exception e =>
(e -> Maybe b) -> Eff es a -> (b -> Eff es a) -> Eff es a
catchJust (\e
e -> if e -> Bool
p e
e then e -> Maybe e
forall a. a -> Maybe a
Just e
e else Maybe e
forall a. Maybe a
Nothing)
catchIO
:: Eff es a
-> (E.IOException -> Eff es a)
-> Eff es a
catchIO :: forall (es :: [Effect]) a.
Eff es a -> (IOException -> Eff es a) -> Eff es a
catchIO = Eff es a -> (IOException -> Eff es a) -> Eff es a
forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> (e -> Eff es a) -> Eff es a
catch
catchSync
:: Eff es a
-> (E.SomeException -> Eff es a)
-> Eff es a
catchSync :: forall (es :: [Effect]) a.
Eff es a -> (SomeException -> Eff es a) -> Eff es a
catchSync = forall e (es :: [Effect]) a.
Exception e =>
(e -> Bool) -> Eff es a -> (e -> Eff es a) -> Eff es a
catchIf @E.SomeException SomeException -> Bool
forall e. Exception e => e -> Bool
isSyncException
catchSyncDeep
:: NFData a
=> Eff es a
-> (E.SomeException -> Eff es a)
-> Eff es a
catchSyncDeep :: forall a (es :: [Effect]).
NFData a =>
Eff es a -> (SomeException -> Eff es a) -> Eff es a
catchSyncDeep Eff es a
action = Eff es a -> (SomeException -> Eff es a) -> Eff es a
forall (es :: [Effect]) a.
Eff es a -> (SomeException -> Eff es a) -> Eff es a
catchSync (a -> Eff es a
forall a (es :: [Effect]). NFData a => a -> Eff es a
evaluateDeep (a -> Eff es a) -> Eff es a -> Eff es a
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Eff es a
action)
handle
:: E.Exception e
=> (e -> Eff es a)
-> Eff es a
-> Eff es a
handle :: forall e (es :: [Effect]) a.
Exception e =>
(e -> Eff es a) -> Eff es a -> Eff es a
handle = (Eff es a -> (e -> Eff es a) -> Eff es a)
-> (e -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Eff es a -> (e -> Eff es a) -> Eff es a
forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> (e -> Eff es a) -> Eff es a
catch
handleDeep
:: (E.Exception e, NFData a)
=> (e -> Eff es a)
-> Eff es a
-> Eff es a
handleDeep :: forall e a (es :: [Effect]).
(Exception e, NFData a) =>
(e -> Eff es a) -> Eff es a -> Eff es a
handleDeep = (Eff es a -> (e -> Eff es a) -> Eff es a)
-> (e -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Eff es a -> (e -> Eff es a) -> Eff es a
forall e a (es :: [Effect]).
(Exception e, NFData a) =>
Eff es a -> (e -> Eff es a) -> Eff es a
catchDeep
handleJust
:: (HasCallStack, E.Exception e)
=> (e -> Maybe b)
-> (b -> Eff es a)
-> Eff es a
-> Eff es a
handleJust :: forall e b (es :: [Effect]) a.
(HasCallStack, Exception e) =>
(e -> Maybe b) -> (b -> Eff es a) -> Eff es a -> Eff es a
handleJust e -> Maybe b
f = (Eff es a -> (b -> Eff es a) -> Eff es a)
-> (b -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((e -> Maybe b) -> Eff es a -> (b -> Eff es a) -> Eff es a
forall e b (es :: [Effect]) a.
Exception e =>
(e -> Maybe b) -> Eff es a -> (b -> Eff es a) -> Eff es a
catchJust e -> Maybe b
f)
handleIf
:: E.Exception e
=> (e -> Bool)
-> (e -> Eff es a)
-> Eff es a
-> Eff es a
handleIf :: forall e (es :: [Effect]) a.
Exception e =>
(e -> Bool) -> (e -> Eff es a) -> Eff es a -> Eff es a
handleIf e -> Bool
p = (Eff es a -> (e -> Eff es a) -> Eff es a)
-> (e -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((e -> Bool) -> Eff es a -> (e -> Eff es a) -> Eff es a
forall e (es :: [Effect]) a.
Exception e =>
(e -> Bool) -> Eff es a -> (e -> Eff es a) -> Eff es a
catchIf e -> Bool
p)
handleIO
:: (E.IOException -> Eff es a)
-> Eff es a
-> Eff es a
handleIO :: forall (es :: [Effect]) a.
(IOException -> Eff es a) -> Eff es a -> Eff es a
handleIO = (Eff es a -> (IOException -> Eff es a) -> Eff es a)
-> (IOException -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Eff es a -> (IOException -> Eff es a) -> Eff es a
forall (es :: [Effect]) a.
Eff es a -> (IOException -> Eff es a) -> Eff es a
catchIO
handleSync
:: (E.SomeException -> Eff es a)
-> Eff es a
-> Eff es a
handleSync :: forall (es :: [Effect]) a.
(SomeException -> Eff es a) -> Eff es a -> Eff es a
handleSync = (Eff es a -> (SomeException -> Eff es a) -> Eff es a)
-> (SomeException -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Eff es a -> (SomeException -> Eff es a) -> Eff es a
forall (es :: [Effect]) a.
Eff es a -> (SomeException -> Eff es a) -> Eff es a
catchSync
handleSyncDeep
:: NFData a
=> (E.SomeException -> Eff es a)
-> Eff es a
-> Eff es a
handleSyncDeep :: forall a (es :: [Effect]).
NFData a =>
(SomeException -> Eff es a) -> Eff es a -> Eff es a
handleSyncDeep = (Eff es a -> (SomeException -> Eff es a) -> Eff es a)
-> (SomeException -> Eff es a) -> Eff es a -> Eff es a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Eff es a -> (SomeException -> Eff es a) -> Eff es a
forall a (es :: [Effect]).
NFData a =>
Eff es a -> (SomeException -> Eff es a) -> Eff es a
catchSyncDeep
try
:: E.Exception e
=> Eff es a
-> Eff es (Either e a)
try :: forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> Eff es (Either e a)
try Eff es a
action = ((forall r. Eff es r -> IO r) -> IO (Either e a))
-> Eff es (Either e a)
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO (Either e a))
-> Eff es (Either e a))
-> ((forall r. Eff es r -> IO r) -> IO (Either e a))
-> Eff es (Either e a)
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO (Either e a)
forall e a. Exception e => IO a -> IO (Either e a)
E.try (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action)
#if MIN_VERSION_base(4,21,0)
tryWithContext
:: E.Exception e
=> Eff es a
-> Eff es (Either (E.ExceptionWithContext e) a)
tryWithContext action = reallyUnsafeUnliftIO $ \unlift -> do
E.tryWithContext (unlift action)
#endif
tryDeep
:: (E.Exception e, NFData a)
=> Eff es a
-> Eff es (Either e a)
tryDeep :: forall e a (es :: [Effect]).
(Exception e, NFData a) =>
Eff es a -> Eff es (Either e a)
tryDeep Eff es a
action = Eff es a -> Eff es (Either e a)
forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> Eff es (Either e a)
try (a -> Eff es a
forall a (es :: [Effect]). NFData a => a -> Eff es a
evaluateDeep (a -> Eff es a) -> Eff es a -> Eff es a
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Eff es a
action)
tryJust
:: E.Exception e
=> (e -> Maybe b)
-> Eff es a
-> Eff es (Either b a)
tryJust :: forall e b (es :: [Effect]) a.
Exception e =>
(e -> Maybe b) -> Eff es a -> Eff es (Either b a)
tryJust e -> Maybe b
f Eff es a
action = ((forall r. Eff es r -> IO r) -> IO (Either b a))
-> Eff es (Either b a)
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO (Either b a))
-> Eff es (Either b a))
-> ((forall r. Eff es r -> IO r) -> IO (Either b a))
-> Eff es (Either b a)
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
(e -> Maybe b) -> IO a -> IO (Either b a)
forall e b a.
Exception e =>
(e -> Maybe b) -> IO a -> IO (Either b a)
E.tryJust e -> Maybe b
f (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action)
tryIf
:: E.Exception e
=> (e -> Bool)
-> Eff es a
-> Eff es (Either e a)
tryIf :: forall e (es :: [Effect]) a.
Exception e =>
(e -> Bool) -> Eff es a -> Eff es (Either e a)
tryIf e -> Bool
p = (e -> Maybe e) -> Eff es a -> Eff es (Either e a)
forall e b (es :: [Effect]) a.
Exception e =>
(e -> Maybe b) -> Eff es a -> Eff es (Either b a)
tryJust (\e
e -> if e -> Bool
p e
e then e -> Maybe e
forall a. a -> Maybe a
Just e
e else Maybe e
forall a. Maybe a
Nothing)
tryIO
:: Eff es a
-> Eff es (Either E.IOException a)
tryIO :: forall (es :: [Effect]) a.
Eff es a -> Eff es (Either IOException a)
tryIO = Eff es a -> Eff es (Either IOException a)
forall e (es :: [Effect]) a.
Exception e =>
Eff es a -> Eff es (Either e a)
try
trySync
:: Eff es a
-> Eff es (Either E.SomeException a)
trySync :: forall (es :: [Effect]) a.
Eff es a -> Eff es (Either SomeException a)
trySync = forall e (es :: [Effect]) a.
Exception e =>
(e -> Bool) -> Eff es a -> Eff es (Either e a)
tryIf @E.SomeException SomeException -> Bool
forall e. Exception e => e -> Bool
isSyncException
trySyncDeep
:: NFData a
=> Eff es a
-> Eff es (Either E.SomeException a)
trySyncDeep :: forall a (es :: [Effect]).
NFData a =>
Eff es a -> Eff es (Either SomeException a)
trySyncDeep Eff es a
action = Eff es a -> Eff es (Either SomeException a)
forall (es :: [Effect]) a.
Eff es a -> Eff es (Either SomeException a)
trySync (a -> Eff es a
forall a (es :: [Effect]). NFData a => a -> Eff es a
evaluateDeep (a -> Eff es a) -> Eff es a -> Eff es a
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Eff es a
action)
catches
:: Eff es a
-> [C.Handler (Eff es) a]
-> Eff es a
catches :: forall (es :: [Effect]) a.
Eff es a -> [Handler (Eff es) a] -> Eff es a
catches Eff es a
action [Handler (Eff es) a]
handlers = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
let unliftHandler :: Handler (Eff es) a -> Handler a
unliftHandler (C.Handler e -> Eff es a
handler) = (e -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
E.Handler (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> (e -> Eff es a) -> e -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Eff es a
handler)
IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
E.catches (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action) ((Handler (Eff es) a -> Handler a)
-> [Handler (Eff es) a] -> [Handler a]
forall a b. (a -> b) -> [a] -> [b]
map Handler (Eff es) a -> Handler a
unliftHandler [Handler (Eff es) a]
handlers)
catchesDeep
:: NFData a
=> Eff es a
-> [C.Handler (Eff es) a]
-> Eff es a
catchesDeep :: forall a (es :: [Effect]).
NFData a =>
Eff es a -> [Handler (Eff es) a] -> Eff es a
catchesDeep Eff es a
action = Eff es a -> [Handler (Eff es) a] -> Eff es a
forall (es :: [Effect]) a.
Eff es a -> [Handler (Eff es) a] -> Eff es a
catches (a -> Eff es a
forall a (es :: [Effect]). NFData a => a -> Eff es a
evaluateDeep (a -> Eff es a) -> Eff es a -> Eff es a
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Eff es a
action)
bracket
:: Eff es a
-> (a -> Eff es b)
-> (a -> Eff es c)
-> Eff es c
bracket :: forall (es :: [Effect]) a b c.
Eff es a -> (a -> Eff es b) -> (a -> Eff es c) -> Eff es c
bracket Eff es a
before a -> Eff es b
after a -> Eff es c
action = ((forall r. Eff es r -> IO r) -> IO c) -> Eff es c
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO c) -> Eff es c)
-> ((forall r. Eff es r -> IO r) -> IO c) -> Eff es c
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> (a -> IO b) -> (a -> IO c) -> IO c
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
E.bracket (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
before) (Eff es b -> IO b
forall r. Eff es r -> IO r
unlift (Eff es b -> IO b) -> (a -> Eff es b) -> a -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Eff es b
after) (Eff es c -> IO c
forall r. Eff es r -> IO r
unlift (Eff es c -> IO c) -> (a -> Eff es c) -> a -> IO c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Eff es c
action)
bracket_
:: Eff es a
-> Eff es b
-> Eff es c
-> Eff es c
bracket_ :: forall (es :: [Effect]) a b c.
Eff es a -> Eff es b -> Eff es c -> Eff es c
bracket_ Eff es a
before Eff es b
after Eff es c
action = ((forall r. Eff es r -> IO r) -> IO c) -> Eff es c
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO c) -> Eff es c)
-> ((forall r. Eff es r -> IO r) -> IO c) -> Eff es c
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO b -> IO c -> IO c
forall a b c. IO a -> IO b -> IO c -> IO c
E.bracket_ (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
before) (Eff es b -> IO b
forall r. Eff es r -> IO r
unlift Eff es b
after) (Eff es c -> IO c
forall r. Eff es r -> IO r
unlift Eff es c
action)
bracketOnError
:: Eff es a
-> (a -> Eff es b)
-> (a -> Eff es c)
-> Eff es c
bracketOnError :: forall (es :: [Effect]) a b c.
Eff es a -> (a -> Eff es b) -> (a -> Eff es c) -> Eff es c
bracketOnError Eff es a
before a -> Eff es b
after a -> Eff es c
action = ((forall r. Eff es r -> IO r) -> IO c) -> Eff es c
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO c) -> Eff es c)
-> ((forall r. Eff es r -> IO r) -> IO c) -> Eff es c
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> (a -> IO b) -> (a -> IO c) -> IO c
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
E.bracketOnError (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
before) (Eff es b -> IO b
forall r. Eff es r -> IO r
unlift (Eff es b -> IO b) -> (a -> Eff es b) -> a -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Eff es b
after) (Eff es c -> IO c
forall r. Eff es r -> IO r
unlift (Eff es c -> IO c) -> (a -> Eff es c) -> a -> IO c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Eff es c
action)
generalBracket
:: Eff es a
-> (a -> C.ExitCase c -> Eff es b)
-> (a -> Eff es c)
-> Eff es (c, b)
generalBracket :: forall (es :: [Effect]) a c b.
Eff es a
-> (a -> ExitCase c -> Eff es b)
-> (a -> Eff es c)
-> Eff es (c, b)
generalBracket = Eff es a
-> (a -> ExitCase c -> Eff es b)
-> (a -> Eff es c)
-> Eff es (c, b)
forall a b c.
HasCallStack =>
Eff es a
-> (a -> ExitCase b -> Eff es c)
-> (a -> Eff es b)
-> Eff es (b, c)
forall (m :: Type -> Type) a b c.
(MonadMask m, HasCallStack) =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
C.generalBracket
finally
:: Eff es a
-> Eff es b
-> Eff es a
finally :: forall (es :: [Effect]) a b. Eff es a -> Eff es b -> Eff es a
finally Eff es a
action Eff es b
handler = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO b -> IO a
forall a b. IO a -> IO b -> IO a
E.finally (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action) (Eff es b -> IO b
forall r. Eff es r -> IO r
unlift Eff es b
handler)
onException
:: Eff es a
-> Eff es b
-> Eff es a
onException :: forall (es :: [Effect]) a b. Eff es a -> Eff es b -> Eff es a
onException Eff es a
action Eff es b
handler = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO b -> IO a
forall a b. IO a -> IO b -> IO a
E.onException (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action) (Eff es b -> IO b
forall r. Eff es r -> IO r
unlift Eff es b
handler)
evaluate :: a -> Eff es a
evaluate :: forall a (es :: [Effect]). a -> Eff es a
evaluate = IO a -> Eff es a
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO a -> Eff es a) -> (a -> IO a) -> a -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO a
forall a. a -> IO a
E.evaluate
evaluateDeep :: NFData a => a -> Eff es a
evaluateDeep :: forall a (es :: [Effect]). NFData a => a -> Eff es a
evaluateDeep = IO a -> Eff es a
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO a -> Eff es a) -> (a -> IO a) -> a -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO a
forall a. a -> IO a
E.evaluate (a -> IO a) -> (a -> a) -> a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall a. NFData a => a -> a
force
#if MIN_VERSION_base(4,20,0)
annotateIO :: E.ExceptionAnnotation e => e -> Eff es a -> Eff es a
annotateIO e action = reallyUnsafeUnliftIO $ \unlift -> do
E.annotateIO e (unlift action)
#endif
isSyncException :: E.Exception e => e -> Bool
isSyncException :: forall e. Exception e => e -> Bool
isSyncException e
e = case SomeException -> Maybe SomeAsyncException
forall e. Exception e => SomeException -> Maybe e
E.fromException (e -> SomeException
forall e. Exception e => e -> SomeException
E.toException e
e) of
Just E.SomeAsyncException{} -> Bool
False
Maybe SomeAsyncException
Nothing -> Bool
True
isAsyncException :: E.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
E.fromException (e -> SomeException
forall e. Exception e => e -> SomeException
E.toException e
e) of
Just E.SomeAsyncException{} -> Bool
True
Maybe SomeAsyncException
Nothing -> Bool
False
mask :: ((forall r. Eff es r -> Eff es r) -> Eff es a) -> Eff es a
mask :: forall (es :: [Effect]) a.
((forall r. Eff es r -> Eff es r) -> Eff es a) -> Eff es a
mask (forall r. Eff es r -> Eff es r) -> Eff es a
k = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
((forall a. IO a -> IO a) -> IO a) -> IO a
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
E.mask (((forall a. IO a -> IO a) -> IO a) -> IO a)
-> ((forall a. IO a -> IO a) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
release -> Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> Eff es a -> IO a
forall a b. (a -> b) -> a -> b
$ (forall r. Eff es r -> Eff es r) -> Eff es a
k ((IO r -> IO r) -> Eff es r -> Eff es r
forall a b (es :: [Effect]). (IO a -> IO b) -> Eff es a -> Eff es b
reallyUnsafeLiftMapIO IO r -> IO r
forall a. IO a -> IO a
release)
mask_ :: Eff es a -> Eff es a
mask_ :: forall (es :: [Effect]) a. Eff es a -> Eff es a
mask_ Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO a
forall a. IO a -> IO a
E.mask_ (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action)
uninterruptibleMask :: ((forall r. Eff es r -> Eff es r) -> Eff es a) -> Eff es a
uninterruptibleMask :: forall (es :: [Effect]) a.
((forall r. Eff es r -> Eff es r) -> Eff es a) -> Eff es a
uninterruptibleMask (forall r. Eff es r -> Eff es r) -> Eff es a
k = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
((forall a. IO a -> IO a) -> IO a) -> IO a
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
E.uninterruptibleMask (((forall a. IO a -> IO a) -> IO a) -> IO a)
-> ((forall a. IO a -> IO a) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
release -> Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> Eff es a -> IO a
forall a b. (a -> b) -> a -> b
$ (forall r. Eff es r -> Eff es r) -> Eff es a
k ((IO r -> IO r) -> Eff es r -> Eff es r
forall a b (es :: [Effect]). (IO a -> IO b) -> Eff es a -> Eff es b
reallyUnsafeLiftMapIO IO r -> IO r
forall a. IO a -> IO a
release)
uninterruptibleMask_ :: Eff es a -> Eff es a
uninterruptibleMask_ :: forall (es :: [Effect]) a. Eff es a -> Eff es a
uninterruptibleMask_ Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO a
forall a. IO a -> IO a
E.uninterruptibleMask_ (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action)
getMaskingState :: Eff es E.MaskingState
getMaskingState :: forall (es :: [Effect]). Eff es MaskingState
getMaskingState = IO MaskingState -> Eff es MaskingState
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO MaskingState
E.getMaskingState
interruptible :: Eff es a -> Eff es a
interruptible :: forall (es :: [Effect]) a. Eff es a -> Eff es a
interruptible Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
reallyUnsafeUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
IO a -> IO a
forall a. IO a -> IO a
E.interruptible (Eff es a -> IO a
forall r. Eff es r -> IO r
unlift Eff es a
action)
allowInterrupt :: Eff es ()
allowInterrupt :: forall (es :: [Effect]). Eff es ()
allowInterrupt = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO ()
E.allowInterrupt