{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
#ifndef MIN_VERSION_transformers
#define MIN_VERSION_transformers(x,y,z) 1
#endif
#ifndef MIN_VERSION_mtl
#define MIN_VERSION_mtl(x,y,z) 1
#endif
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Control.Monad.Catch (
MonadThrow(..)
, MonadCatch(..)
, MonadMask(..)
, ExitCase(..)
, mask_
, uninterruptibleMask_
, catchAll
, catchIOError
, catchJust
, catchIf
, Handler(..), catches
, handle
, handleAll
, handleIOError
, handleJust
, handleIf
, try
, tryJust
, onException
, onError
, bracket
, bracket_
, finally
, bracketOnError
, Exception(..)
, SomeException(..)
) where
import Control.Exception (Exception(..), SomeException(..))
import qualified Control.Exception as ControlException
import qualified Control.Monad.STM as STM
import qualified Control.Monad.Trans.RWS.Lazy as LazyRWS
import qualified Control.Monad.Trans.RWS.Strict as StrictRWS
import qualified Control.Monad.Trans.State.Lazy as LazyS
import qualified Control.Monad.Trans.State.Strict as StrictS
import qualified Control.Monad.Trans.Writer.Lazy as LazyW
import qualified Control.Monad.Trans.Writer.Strict as StrictW
import Control.Monad.ST (ST)
import Control.Monad.STM (STM)
import Control.Monad.Trans.List (ListT(..), runListT)
import Control.Monad.Trans.Maybe (MaybeT(..), runMaybeT)
import Control.Monad.Trans.Error (ErrorT(..), Error, runErrorT)
import Control.Monad.Trans.Except (ExceptT(..), runExceptT)
import Control.Monad.Trans.Cont (ContT)
import Control.Monad.Trans.Identity
import Control.Monad.Reader as Reader
import Language.Haskell.TH.Syntax (Q)
#if MIN_VERSION_base(4,4,0)
import Control.Monad.ST.Unsafe (unsafeIOToST)
#else
import Control.Monad.ST (unsafeIOToST)
#endif
#if __GLASGOW_HASKELL__ < 706
import Prelude hiding (catch, foldr)
import Data.Foldable
import Data.Monoid
#elif __GLASGOW_HASKELL__ < 710
import Prelude hiding (foldr)
import Data.Foldable
import Data.Monoid
#endif
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
class Monad m => MonadThrow m where
throwM :: Exception e => e -> m a
class MonadThrow m => MonadCatch m where
catch :: Exception e => m a -> (e -> m a) -> m a
class MonadCatch m => MonadMask m where
mask :: ((forall a. m a -> m a) -> m b) -> m b
uninterruptibleMask :: ((forall a. m a -> m a) -> m b) -> m b
generalBracket
:: m a
-> (a -> ExitCase b -> m c)
-> (a -> m b)
-> m (b, c)
data ExitCase a
= ExitCaseSuccess a
| ExitCaseException SomeException
| ExitCaseAbort
deriving Int -> ExitCase a -> ShowS
[ExitCase a] -> ShowS
ExitCase a -> String
(Int -> ExitCase a -> ShowS)
-> (ExitCase a -> String)
-> ([ExitCase a] -> ShowS)
-> Show (ExitCase a)
forall a. Show a => Int -> ExitCase a -> ShowS
forall a. Show a => [ExitCase a] -> ShowS
forall a. Show a => ExitCase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExitCase a] -> ShowS
$cshowList :: forall a. Show a => [ExitCase a] -> ShowS
show :: ExitCase a -> String
$cshow :: forall a. Show a => ExitCase a -> String
showsPrec :: Int -> ExitCase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ExitCase a -> ShowS
External instance of the constraint type Show SomeException
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show a
Show
instance MonadThrow [] where
throwM :: e -> [a]
throwM e
_ = []
instance MonadThrow Maybe where
throwM :: e -> Maybe a
throwM e
_ = Maybe a
forall a. Maybe a
Nothing
instance MonadThrow Q where
throwM :: e -> Q a
throwM = String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type MonadFail Q
fail (String -> Q a) -> (e -> String) -> e -> Q a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> String
forall a. Show a => a -> String
External instance of the constraint type forall e. Exception e => Show e
Evidence bound by a type signature of the constraint type Exception e
show
instance MonadThrow IO where
throwM :: e -> IO a
throwM = e -> IO a
forall e a. Exception e => e -> IO a
Evidence bound by a type signature of the constraint type Exception e
ControlException.throwIO
instance MonadCatch IO where
catch :: IO a -> (e -> IO a) -> IO a
catch = IO a -> (e -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Evidence bound by a type signature of the constraint type Exception e
ControlException.catch
instance MonadMask IO where
mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b
mask = ((forall a. IO a -> IO a) -> IO b) -> IO b
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
ControlException.mask
uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b
uninterruptibleMask = ((forall a. IO a -> IO a) -> IO b) -> IO b
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
ControlException.uninterruptibleMask
generalBracket :: IO a -> (a -> ExitCase b -> IO c) -> (a -> IO b) -> IO (b, c)
generalBracket IO a
acquire a -> ExitCase b -> IO c
release a -> IO b
use = ((forall a. IO a -> IO a) -> IO (b, c)) -> IO (b, c)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Instance of class: MonadMask of the constraint type MonadMask IO
mask (((forall a. IO a -> IO a) -> IO (b, c)) -> IO (b, c))
-> ((forall a. IO a -> IO a) -> IO (b, c)) -> IO (b, c)
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
unmasked -> do
a
resource <- IO a
acquire
b
b <- IO b -> IO b
forall a. IO a -> IO a
unmasked (a -> IO b
use a
resource) IO b -> (SomeException -> IO b) -> IO b
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
External instance of the constraint type Exception SomeException
Instance of class: MonadCatch of the constraint type MonadCatch IO
`catch` \SomeException
e -> do
c
_ <- a -> ExitCase b -> IO c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e)
SomeException -> IO b
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
External instance of the constraint type Exception SomeException
Instance of class: MonadThrow of the constraint type MonadThrow IO
throwM SomeException
e
c
c <- a -> ExitCase b -> IO c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b)
(b, c) -> IO (b, c)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (b
b, c
c)
instance MonadThrow (ST s) where
throwM :: e -> ST s a
throwM = IO a -> ST s a
forall a s. IO a -> ST s a
unsafeIOToST (IO a -> ST s a) -> (e -> IO a) -> e -> ST s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> IO a
forall e a. Exception e => e -> IO a
Evidence bound by a type signature of the constraint type Exception e
ControlException.throwIO
instance MonadThrow STM where
throwM :: e -> STM a
throwM = e -> STM a
forall e a. Exception e => e -> STM a
Evidence bound by a type signature of the constraint type Exception e
STM.throwSTM
instance MonadCatch STM where
catch :: STM a -> (e -> STM a) -> STM a
catch = STM a -> (e -> STM a) -> STM a
forall e a. Exception e => STM a -> (e -> STM a) -> STM a
Evidence bound by a type signature of the constraint type Exception e
STM.catchSTM
instance e ~ SomeException => MonadThrow (Either e) where
throwM :: e -> Either e a
throwM = SomeException -> Either SomeException a
forall a b. a -> Either a b
Left (SomeException -> Either SomeException a)
-> (e -> SomeException) -> e -> Either SomeException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> SomeException
forall e. Exception e => e -> SomeException
Evidence bound by a type signature of the constraint type Exception e
toException
instance e ~ SomeException => MonadCatch (Either e) where
catch :: Either e a -> (e -> Either e a) -> Either e a
catch (Left e
e) e -> Either e a
f =
case SomeException -> Maybe e
forall e. Exception e => SomeException -> Maybe e
Evidence bound by a type signature of the constraint type Exception e
fromException e
SomeException
e of
Maybe e
Nothing -> e -> Either e a
forall a b. a -> Either a b
Left e
e
Just e
e' -> e -> Either e a
f e
e'
catch x :: Either e a
x@(Right a
_) e -> Either e a
_ = Either e a
x
instance e ~ SomeException => MonadMask (Either e) where
mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b
mask (forall a. Either e a -> Either e a) -> Either e b
f = (forall a. Either e a -> Either e a) -> Either e b
f forall a. a -> a
forall a. Either e a -> Either e a
id
uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b
uninterruptibleMask (forall a. Either e a -> Either e a) -> Either e b
f = (forall a. Either e a -> Either e a) -> Either e b
f forall a. a -> a
forall a. Either e a -> Either e a
id
generalBracket :: Either e a
-> (a -> ExitCase b -> Either e c)
-> (a -> Either e b)
-> Either e (b, c)
generalBracket Either e a
acquire a -> ExitCase b -> Either e c
release a -> Either e b
use =
case Either e a
acquire of
Left e
e -> e -> Either e (b, c)
forall a b. a -> Either a b
Left e
e
Right a
resource ->
case a -> Either e b
use a
resource of
Left e
e -> a -> ExitCase b -> Either e c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException e
SomeException
e) Either e c -> Either e (b, c) -> Either e (b, c)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall e. Monad (Either e)
Evidence bound by a type signature of the constraint type e ~ SomeException
>> e -> Either e (b, c)
forall a b. a -> Either a b
Left e
e
Right b
b -> do
c
c <- a -> ExitCase b -> Either e c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b)
(b, c) -> Either e (b, c)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall e. Monad (Either e)
Evidence bound by a type signature of the constraint type e ~ SomeException
return (b
b, c
c)
instance MonadThrow m => MonadThrow (IdentityT m) where
throwM :: e -> IdentityT m a
throwM e
e = m a -> IdentityT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type MonadTrans IdentityT
lift (m a -> IdentityT m a) -> m a -> IdentityT m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance MonadCatch m => MonadCatch (IdentityT m) where
catch :: IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a
catch (IdentityT m a
m) e -> IdentityT m a
f = m a -> IdentityT m a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch m a
m (IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT (IdentityT m a -> m a) -> (e -> IdentityT m a) -> e -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> IdentityT m a
f))
instance MonadMask m => MonadMask (IdentityT m) where
mask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b)
-> IdentityT m b
mask (forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
a = m b -> IdentityT m b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m b -> IdentityT m b) -> m b -> IdentityT m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m b) -> m b
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m b) -> m b)
-> ((forall a. m a -> m a) -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> IdentityT m b -> m b
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
a ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b)
-> (forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
forall a b. (a -> b) -> a -> b
$ (m a -> m a) -> IdentityT m a -> IdentityT m a
forall (m :: * -> *) a.
(m a -> m a) -> IdentityT m a -> IdentityT m a
q m a -> m a
forall a. m a -> m a
u)
where q :: (m a -> m a) -> IdentityT m a -> IdentityT m a
q :: (m a -> m a) -> IdentityT m a -> IdentityT m a
q m a -> m a
u = m a -> IdentityT m a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m a -> IdentityT m a)
-> (IdentityT m a -> m a) -> IdentityT m a -> IdentityT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m a
u (m a -> m a) -> (IdentityT m a -> m a) -> IdentityT m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
uninterruptibleMask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b)
-> IdentityT m b
uninterruptibleMask (forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
a =
m b -> IdentityT m b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m b -> IdentityT m b) -> m b -> IdentityT m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m b) -> m b
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m b) -> m b)
-> ((forall a. m a -> m a) -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> IdentityT m b -> m b
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
a ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b)
-> (forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
forall a b. (a -> b) -> a -> b
$ (m a -> m a) -> IdentityT m a -> IdentityT m a
forall (m :: * -> *) a.
(m a -> m a) -> IdentityT m a -> IdentityT m a
q m a -> m a
forall a. m a -> m a
u)
where q :: (m a -> m a) -> IdentityT m a -> IdentityT m a
q :: (m a -> m a) -> IdentityT m a -> IdentityT m a
q m a -> m a
u = m a -> IdentityT m a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m a -> IdentityT m a)
-> (IdentityT m a -> m a) -> IdentityT m a -> IdentityT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m a
u (m a -> m a) -> (IdentityT m a -> m a) -> IdentityT m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT
generalBracket :: IdentityT m a
-> (a -> ExitCase b -> IdentityT m c)
-> (a -> IdentityT m b)
-> IdentityT m (b, c)
generalBracket IdentityT m a
acquire a -> ExitCase b -> IdentityT m c
release a -> IdentityT m b
use = m (b, c) -> IdentityT m (b, c)
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (m (b, c) -> IdentityT m (b, c)) -> m (b, c) -> IdentityT m (b, c)
forall a b. (a -> b) -> a -> b
$
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(IdentityT m a -> m a
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT IdentityT m a
acquire)
(\a
resource ExitCase b
exitCase -> IdentityT m c -> m c
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT (a -> ExitCase b -> IdentityT m c
release a
resource ExitCase b
exitCase))
(\a
resource -> IdentityT m b -> m b
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT (a -> IdentityT m b
use a
resource))
instance MonadThrow m => MonadThrow (LazyS.StateT s m) where
throwM :: e -> StateT s m a
throwM e
e = m a -> StateT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall s. MonadTrans (StateT s)
lift (m a -> StateT s m a) -> m a -> StateT s m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance MonadCatch m => MonadCatch (LazyS.StateT s m) where
catch :: StateT s m a -> (e -> StateT s m a) -> StateT s m a
catch = Catch e m (a, s)
-> StateT s m a -> (e -> StateT s m a) -> StateT s m a
forall e (m :: * -> *) a s.
Catch e m (a, s) -> Catch e (StateT s m) a
LazyS.liftCatch Catch e m (a, s)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch
instance MonadMask m => MonadMask (LazyS.StateT s m) where
mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> StateT s m b
mask (forall a. StateT s m a -> StateT s m a) -> StateT s m b
a = (s -> m (b, s)) -> StateT s m b
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
LazyS.StateT ((s -> m (b, s)) -> StateT s m b)
-> (s -> m (b, s)) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ \s
s -> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (b, s)) -> m (b, s))
-> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> StateT s m b -> s -> m (b, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT ((forall a. StateT s m a -> StateT s m a) -> StateT s m b
a ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> (forall a. StateT s m a -> StateT s m a) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
forall (m :: * -> *) a s.
(m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
forall a. m a -> m a
u) s
s
where q :: (m (a, s) -> m (a, s)) -> LazyS.StateT s m a -> LazyS.StateT s m a
q :: (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
u (LazyS.StateT s -> m (a, s)
b) = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
LazyS.StateT (m (a, s) -> m (a, s)
u (m (a, s) -> m (a, s)) -> (s -> m (a, s)) -> s -> m (a, s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m (a, s)
b)
uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> StateT s m b
uninterruptibleMask (forall a. StateT s m a -> StateT s m a) -> StateT s m b
a =
(s -> m (b, s)) -> StateT s m b
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
LazyS.StateT ((s -> m (b, s)) -> StateT s m b)
-> (s -> m (b, s)) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ \s
s -> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (b, s)) -> m (b, s))
-> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> StateT s m b -> s -> m (b, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT ((forall a. StateT s m a -> StateT s m a) -> StateT s m b
a ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> (forall a. StateT s m a -> StateT s m a) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
forall (m :: * -> *) a s.
(m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
forall a. m a -> m a
u) s
s
where q :: (m (a, s) -> m (a, s)) -> LazyS.StateT s m a -> LazyS.StateT s m a
q :: (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
u (LazyS.StateT s -> m (a, s)
b) = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
LazyS.StateT (m (a, s) -> m (a, s)
u (m (a, s) -> m (a, s)) -> (s -> m (a, s)) -> s -> m (a, s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m (a, s)
b)
generalBracket :: StateT s m a
-> (a -> ExitCase b -> StateT s m c)
-> (a -> StateT s m b)
-> StateT s m (b, c)
generalBracket StateT s m a
acquire a -> ExitCase b -> StateT s m c
release a -> StateT s m b
use = (s -> m ((b, c), s)) -> StateT s m (b, c)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
LazyS.StateT ((s -> m ((b, c), s)) -> StateT s m (b, c))
-> (s -> m ((b, c), s)) -> StateT s m (b, c)
forall a b. (a -> b) -> a -> b
$ \s
s0 -> do
((b
b, s
_s2), (c
c, s
s3)) <- m (a, s)
-> ((a, s) -> ExitCase (b, s) -> m (c, s))
-> ((a, s) -> m (b, s))
-> m ((b, s), (c, s))
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(StateT s m a -> s -> m (a, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT StateT s m a
acquire s
s0)
(\(a
resource, s
s1) ExitCase (b, s)
exitCase -> case ExitCase (b, s)
exitCase of
ExitCaseSuccess (b
b, s
s2) -> StateT s m c -> s -> m (c, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT (a -> ExitCase b -> StateT s m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b)) s
s2
ExitCaseException SomeException
e -> StateT s m c -> s -> m (c, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT (a -> ExitCase b -> StateT s m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e)) s
s1
ExitCase (b, s)
ExitCaseAbort -> StateT s m c -> s -> m (c, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT (a -> ExitCase b -> StateT s m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort) s
s1)
(\(a
resource, s
s1) -> StateT s m b -> s -> m (b, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
LazyS.runStateT (a -> StateT s m b
use a
resource) s
s1)
((b, c), s) -> m ((b, c), s)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((b
b, c
c), s
s3)
instance MonadThrow m => MonadThrow (StrictS.StateT s m) where
throwM :: e -> StateT s m a
throwM e
e = m a -> StateT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall s. MonadTrans (StateT s)
lift (m a -> StateT s m a) -> m a -> StateT s m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance MonadCatch m => MonadCatch (StrictS.StateT s m) where
catch :: StateT s m a -> (e -> StateT s m a) -> StateT s m a
catch = Catch e m (a, s)
-> StateT s m a -> (e -> StateT s m a) -> StateT s m a
forall e (m :: * -> *) a s.
Catch e m (a, s) -> Catch e (StateT s m) a
StrictS.liftCatch Catch e m (a, s)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch
instance MonadMask m => MonadMask (StrictS.StateT s m) where
mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> StateT s m b
mask (forall a. StateT s m a -> StateT s m a) -> StateT s m b
a = (s -> m (b, s)) -> StateT s m b
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StrictS.StateT ((s -> m (b, s)) -> StateT s m b)
-> (s -> m (b, s)) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ \s
s -> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (b, s)) -> m (b, s))
-> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> StateT s m b -> s -> m (b, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT ((forall a. StateT s m a -> StateT s m a) -> StateT s m b
a ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> (forall a. StateT s m a -> StateT s m a) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
forall (m :: * -> *) a s.
(m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
forall a. m a -> m a
u) s
s
where q :: (m (a, s) -> m (a, s)) -> StrictS.StateT s m a -> StrictS.StateT s m a
q :: (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
u (StrictS.StateT s -> m (a, s)
b) = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StrictS.StateT (m (a, s) -> m (a, s)
u (m (a, s) -> m (a, s)) -> (s -> m (a, s)) -> s -> m (a, s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m (a, s)
b)
uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> StateT s m b
uninterruptibleMask (forall a. StateT s m a -> StateT s m a) -> StateT s m b
a =
(s -> m (b, s)) -> StateT s m b
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StrictS.StateT ((s -> m (b, s)) -> StateT s m b)
-> (s -> m (b, s)) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ \s
s -> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (b, s)) -> m (b, s))
-> ((forall a. m a -> m a) -> m (b, s)) -> m (b, s)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> StateT s m b -> s -> m (b, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT ((forall a. StateT s m a -> StateT s m a) -> StateT s m b
a ((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> (forall a. StateT s m a -> StateT s m a) -> StateT s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
forall (m :: * -> *) a s.
(m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
forall a. m a -> m a
u) s
s
where q :: (m (a, s) -> m (a, s)) -> StrictS.StateT s m a -> StrictS.StateT s m a
q :: (m (a, s) -> m (a, s)) -> StateT s m a -> StateT s m a
q m (a, s) -> m (a, s)
u (StrictS.StateT s -> m (a, s)
b) = (s -> m (a, s)) -> StateT s m a
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StrictS.StateT (m (a, s) -> m (a, s)
u (m (a, s) -> m (a, s)) -> (s -> m (a, s)) -> s -> m (a, s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m (a, s)
b)
generalBracket :: StateT s m a
-> (a -> ExitCase b -> StateT s m c)
-> (a -> StateT s m b)
-> StateT s m (b, c)
generalBracket StateT s m a
acquire a -> ExitCase b -> StateT s m c
release a -> StateT s m b
use = (s -> m ((b, c), s)) -> StateT s m (b, c)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StrictS.StateT ((s -> m ((b, c), s)) -> StateT s m (b, c))
-> (s -> m ((b, c), s)) -> StateT s m (b, c)
forall a b. (a -> b) -> a -> b
$ \s
s0 -> do
((b
b, s
_s2), (c
c, s
s3)) <- m (a, s)
-> ((a, s) -> ExitCase (b, s) -> m (c, s))
-> ((a, s) -> m (b, s))
-> m ((b, s), (c, s))
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(StateT s m a -> s -> m (a, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT StateT s m a
acquire s
s0)
(\(a
resource, s
s1) ExitCase (b, s)
exitCase -> case ExitCase (b, s)
exitCase of
ExitCaseSuccess (b
b, s
s2) -> StateT s m c -> s -> m (c, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT (a -> ExitCase b -> StateT s m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b)) s
s2
ExitCaseException SomeException
e -> StateT s m c -> s -> m (c, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT (a -> ExitCase b -> StateT s m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e)) s
s1
ExitCase (b, s)
ExitCaseAbort -> StateT s m c -> s -> m (c, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT (a -> ExitCase b -> StateT s m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort) s
s1)
(\(a
resource, s
s1) -> StateT s m b -> s -> m (b, s)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StrictS.runStateT (a -> StateT s m b
use a
resource) s
s1)
((b, c), s) -> m ((b, c), s)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((b
b, c
c), s
s3)
instance MonadThrow m => MonadThrow (ReaderT r m) where
throwM :: e -> ReaderT r m a
throwM e
e = m a -> ReaderT r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall r. MonadTrans (ReaderT r)
lift (m a -> ReaderT r m a) -> m a -> ReaderT r m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance MonadCatch m => MonadCatch (ReaderT r m) where
catch :: ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a
catch (ReaderT r -> m a
m) e -> ReaderT r m a
c = (r -> m a) -> ReaderT r m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((r -> m a) -> ReaderT r m a) -> (r -> m a) -> ReaderT r m a
forall a b. (a -> b) -> a -> b
$ \r
r -> r -> m a
m r
r m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
`catch` \e
e -> ReaderT r m a -> r -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (e -> ReaderT r m a
c e
e) r
r
instance MonadMask m => MonadMask (ReaderT r m) where
mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b)
-> ReaderT r m b
mask (forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
a = (r -> m b) -> ReaderT r m b
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((r -> m b) -> ReaderT r m b) -> (r -> m b) -> ReaderT r m b
forall a b. (a -> b) -> a -> b
$ \r
e -> ((forall a. m a -> m a) -> m b) -> m b
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m b) -> m b)
-> ((forall a. m a -> m a) -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> ReaderT r m b -> r -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
a ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b)
-> (forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
forall a b. (a -> b) -> a -> b
$ (m a -> m a) -> ReaderT r m a -> ReaderT r m a
forall (m :: * -> *) a e.
(m a -> m a) -> ReaderT e m a -> ReaderT e m a
q m a -> m a
forall a. m a -> m a
u) r
e
where q :: (m a -> m a) -> ReaderT e m a -> ReaderT e m a
q :: (m a -> m a) -> ReaderT e m a -> ReaderT e m a
q m a -> m a
u (ReaderT e -> m a
b) = (e -> m a) -> ReaderT e m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT (m a -> m a
u (m a -> m a) -> (e -> m a) -> e -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
b)
uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b)
-> ReaderT r m b
uninterruptibleMask (forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
a =
(r -> m b) -> ReaderT r m b
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((r -> m b) -> ReaderT r m b) -> (r -> m b) -> ReaderT r m b
forall a b. (a -> b) -> a -> b
$ \r
e -> ((forall a. m a -> m a) -> m b) -> m b
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m b) -> m b)
-> ((forall a. m a -> m a) -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> ReaderT r m b -> r -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
a ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b)
-> (forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
forall a b. (a -> b) -> a -> b
$ (m a -> m a) -> ReaderT r m a -> ReaderT r m a
forall (m :: * -> *) a e.
(m a -> m a) -> ReaderT e m a -> ReaderT e m a
q m a -> m a
forall a. m a -> m a
u) r
e
where q :: (m a -> m a) -> ReaderT e m a -> ReaderT e m a
q :: (m a -> m a) -> ReaderT e m a -> ReaderT e m a
q m a -> m a
u (ReaderT e -> m a
b) = (e -> m a) -> ReaderT e m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT (m a -> m a
u (m a -> m a) -> (e -> m a) -> e -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
b)
generalBracket :: ReaderT r m a
-> (a -> ExitCase b -> ReaderT r m c)
-> (a -> ReaderT r m b)
-> ReaderT r m (b, c)
generalBracket ReaderT r m a
acquire a -> ExitCase b -> ReaderT r m c
release a -> ReaderT r m b
use = (r -> m (b, c)) -> ReaderT r m (b, c)
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT ((r -> m (b, c)) -> ReaderT r m (b, c))
-> (r -> m (b, c)) -> ReaderT r m (b, c)
forall a b. (a -> b) -> a -> b
$ \r
r ->
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(ReaderT r m a -> r -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT r m a
acquire r
r)
(\a
resource ExitCase b
exitCase -> ReaderT r m c -> r -> m c
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (a -> ExitCase b -> ReaderT r m c
release a
resource ExitCase b
exitCase) r
r)
(\a
resource -> ReaderT r m b -> r -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (a -> ReaderT r m b
use a
resource) r
r)
instance (MonadThrow m, Monoid w) => MonadThrow (StrictW.WriterT w m) where
throwM :: e -> WriterT w m a
throwM e
e = m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall w. Monoid w => MonadTrans (WriterT w)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> WriterT w m a) -> m a -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance (MonadCatch m, Monoid w) => MonadCatch (StrictW.WriterT w m) where
catch :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a
catch (StrictW.WriterT m (a, w)
m) e -> WriterT w m a
h = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
StrictW.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w)
m `catch ` \e
e -> WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT (e -> WriterT w m a
h e
e)
instance (MonadMask m, Monoid w) => MonadMask (StrictW.WriterT w m) where
mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> WriterT w m b
mask (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a = m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
StrictW.WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (b, w)) -> m (b, w))
-> ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
forall (m :: * -> *) a w.
(m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
forall a. m a -> m a
u)
where q :: (m (a, w) -> m (a, w)) -> StrictW.WriterT w m a -> StrictW.WriterT w m a
q :: (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
u WriterT w m a
b = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
StrictW.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w) -> m (a, w)
u (WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT WriterT w m a
b)
uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> WriterT w m b
uninterruptibleMask (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a =
m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
StrictW.WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (b, w)) -> m (b, w))
-> ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
forall (m :: * -> *) a w.
(m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
forall a. m a -> m a
u)
where q :: (m (a, w) -> m (a, w)) -> StrictW.WriterT w m a -> StrictW.WriterT w m a
q :: (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
u WriterT w m a
b = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
StrictW.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w) -> m (a, w)
u (WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT WriterT w m a
b)
generalBracket :: WriterT w m a
-> (a -> ExitCase b -> WriterT w m c)
-> (a -> WriterT w m b)
-> WriterT w m (b, c)
generalBracket WriterT w m a
acquire a -> ExitCase b -> WriterT w m c
release a -> WriterT w m b
use = m ((b, c), w) -> WriterT w m (b, c)
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
StrictW.WriterT (m ((b, c), w) -> WriterT w m (b, c))
-> m ((b, c), w) -> WriterT w m (b, c)
forall a b. (a -> b) -> a -> b
$ do
((b
b, w
_w12), (c
c, w
w123)) <- m (a, w)
-> ((a, w) -> ExitCase (b, w) -> m (c, w))
-> ((a, w) -> m (b, w))
-> m ((b, w), (c, w))
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT WriterT w m a
acquire)
(\(a
resource, w
w1) ExitCase (b, w)
exitCase -> case ExitCase (b, w)
exitCase of
ExitCaseSuccess (b
b, w
w12) -> do
(c
c, w
w3) <- WriterT w m c -> m (c, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT (a -> ExitCase b -> WriterT w m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b))
(c, w) -> m (c, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w12 w
w3)
ExitCaseException SomeException
e -> do
(c
c, w
w3) <- WriterT w m c -> m (c, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT (a -> ExitCase b -> WriterT w m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e))
(c, w) -> m (c, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3)
ExitCase (b, w)
ExitCaseAbort -> do
(c
c, w
w3) <- WriterT w m c -> m (c, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT (a -> ExitCase b -> WriterT w m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort)
(c, w) -> m (c, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3))
(\(a
resource, w
w1) -> do
(b
a, w
w2) <- WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
StrictW.runWriterT (a -> WriterT w m b
use a
resource)
(b, w) -> m (b, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (b
a, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w2))
((b, c), w) -> m ((b, c), w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((b
b, c
c), w
w123)
instance (MonadThrow m, Monoid w) => MonadThrow (LazyW.WriterT w m) where
throwM :: e -> WriterT w m a
throwM e
e = m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall w. Monoid w => MonadTrans (WriterT w)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> WriterT w m a) -> m a -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance (MonadCatch m, Monoid w) => MonadCatch (LazyW.WriterT w m) where
catch :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a
catch (LazyW.WriterT m (a, w)
m) e -> WriterT w m a
h = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
LazyW.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w)
m `catch ` \e
e -> WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT (e -> WriterT w m a
h e
e)
instance (MonadMask m, Monoid w) => MonadMask (LazyW.WriterT w m) where
mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> WriterT w m b
mask (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a = m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
LazyW.WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (b, w)) -> m (b, w))
-> ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
forall (m :: * -> *) a w.
(m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
forall a. m a -> m a
u)
where q :: (m (a, w) -> m (a, w)) -> LazyW.WriterT w m a -> LazyW.WriterT w m a
q :: (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
u WriterT w m a
b = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
LazyW.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w) -> m (a, w)
u (WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT WriterT w m a
b)
uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> WriterT w m b
uninterruptibleMask (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a =
m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
LazyW.WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (b, w)) -> m (b, w))
-> ((forall a. m a -> m a) -> m (b, w)) -> m (b, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
a ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
forall (m :: * -> *) a w.
(m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
forall a. m a -> m a
u)
where q :: (m (a, w) -> m (a, w)) -> LazyW.WriterT w m a -> LazyW.WriterT w m a
q :: (m (a, w) -> m (a, w)) -> WriterT w m a -> WriterT w m a
q m (a, w) -> m (a, w)
u WriterT w m a
b = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
LazyW.WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ m (a, w) -> m (a, w)
u (WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT WriterT w m a
b)
generalBracket :: WriterT w m a
-> (a -> ExitCase b -> WriterT w m c)
-> (a -> WriterT w m b)
-> WriterT w m (b, c)
generalBracket WriterT w m a
acquire a -> ExitCase b -> WriterT w m c
release a -> WriterT w m b
use = m ((b, c), w) -> WriterT w m (b, c)
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
LazyW.WriterT (m ((b, c), w) -> WriterT w m (b, c))
-> m ((b, c), w) -> WriterT w m (b, c)
forall a b. (a -> b) -> a -> b
$ do
((b
b, w
_w12), (c
c, w
w123)) <- m (a, w)
-> ((a, w) -> ExitCase (b, w) -> m (c, w))
-> ((a, w) -> m (b, w))
-> m ((b, w), (c, w))
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT WriterT w m a
acquire)
(\(a
resource, w
w1) ExitCase (b, w)
exitCase -> case ExitCase (b, w)
exitCase of
ExitCaseSuccess (b
b, w
w12) -> do
(c
c, w
w3) <- WriterT w m c -> m (c, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT (a -> ExitCase b -> WriterT w m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b))
(c, w) -> m (c, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w12 w
w3)
ExitCaseException SomeException
e -> do
(c
c, w
w3) <- WriterT w m c -> m (c, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT (a -> ExitCase b -> WriterT w m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e))
(c, w) -> m (c, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3)
ExitCase (b, w)
ExitCaseAbort -> do
(c
c, w
w3) <- WriterT w m c -> m (c, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT (a -> ExitCase b -> WriterT w m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort)
(c, w) -> m (c, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3))
(\(a
resource, w
w1) -> do
(b
a, w
w2) <- WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LazyW.runWriterT (a -> WriterT w m b
use a
resource)
(b, w) -> m (b, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (b
a, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w2))
((b, c), w) -> m ((b, c), w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((b
b, c
c), w
w123)
instance (MonadThrow m, Monoid w) => MonadThrow (LazyRWS.RWST r w s m) where
throwM :: e -> RWST r w s m a
throwM e
e = m a -> RWST r w s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall w r s. Monoid w => MonadTrans (RWST r w s)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> RWST r w s m a) -> m a -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance (MonadCatch m, Monoid w) => MonadCatch (LazyRWS.RWST r w s m) where
catch :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a
catch (LazyRWS.RWST r -> s -> m (a, s, w)
m) e -> RWST r w s m a
h = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
LazyRWS.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> r -> s -> m (a, s, w)
m r
r s
s m (a, s, w) -> (e -> m (a, s, w)) -> m (a, s, w)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
`catch` \e
e -> RWST r w s m a -> r -> s -> m (a, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST (e -> RWST r w s m a
h e
e) r
r s
s
instance (MonadMask m, Monoid w) => MonadMask (LazyRWS.RWST r w s m) where
mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> RWST r w s m b
mask (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a = (r -> s -> m (b, s, w)) -> RWST r w s m b
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
LazyRWS.RWST ((r -> s -> m (b, s, w)) -> RWST r w s m b)
-> (r -> s -> m (b, s, w)) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w))
-> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> RWST r w s m b -> r -> s -> m (b, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
forall (m :: * -> *) a s w r.
(m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
forall a. m a -> m a
u) r
r s
s
where q :: (m (a, s, w) -> m (a, s, w)) -> LazyRWS.RWST r w s m a -> LazyRWS.RWST r w s m a
q :: (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
u (LazyRWS.RWST r -> s -> m (a, s, w)
b) = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
LazyRWS.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \ r
r s
s -> m (a, s, w) -> m (a, s, w)
u (r -> s -> m (a, s, w)
b r
r s
s)
uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> RWST r w s m b
uninterruptibleMask (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a =
(r -> s -> m (b, s, w)) -> RWST r w s m b
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
LazyRWS.RWST ((r -> s -> m (b, s, w)) -> RWST r w s m b)
-> (r -> s -> m (b, s, w)) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w))
-> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> RWST r w s m b -> r -> s -> m (b, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
forall (m :: * -> *) a s w r.
(m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
forall a. m a -> m a
u) r
r s
s
where q :: (m (a, s, w) -> m (a, s, w)) -> LazyRWS.RWST r w s m a -> LazyRWS.RWST r w s m a
q :: (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
u (LazyRWS.RWST r -> s -> m (a, s, w)
b) = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
LazyRWS.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \ r
r s
s -> m (a, s, w) -> m (a, s, w)
u (r -> s -> m (a, s, w)
b r
r s
s)
generalBracket :: RWST r w s m a
-> (a -> ExitCase b -> RWST r w s m c)
-> (a -> RWST r w s m b)
-> RWST r w s m (b, c)
generalBracket RWST r w s m a
acquire a -> ExitCase b -> RWST r w s m c
release a -> RWST r w s m b
use = (r -> s -> m ((b, c), s, w)) -> RWST r w s m (b, c)
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
LazyRWS.RWST ((r -> s -> m ((b, c), s, w)) -> RWST r w s m (b, c))
-> (r -> s -> m ((b, c), s, w)) -> RWST r w s m (b, c)
forall a b. (a -> b) -> a -> b
$ \r
r s
s0 -> do
((b
b, s
_s2, w
_w12), (c
c, s
s3, w
w123)) <- m (a, s, w)
-> ((a, s, w) -> ExitCase (b, s, w) -> m (c, s, w))
-> ((a, s, w) -> m (b, s, w))
-> m ((b, s, w), (c, s, w))
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(RWST r w s m a -> r -> s -> m (a, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST RWST r w s m a
acquire r
r s
s0)
(\(a
resource, s
s1, w
w1) ExitCase (b, s, w)
exitCase -> case ExitCase (b, s, w)
exitCase of
ExitCaseSuccess (b
b, s
s2, w
w12) -> do
(c
c, s
s3, w
w3) <- RWST r w s m c -> r -> s -> m (c, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST (a -> ExitCase b -> RWST r w s m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b)) r
r s
s2
(c, s, w) -> m (c, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, s
s3, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w12 w
w3)
ExitCaseException SomeException
e -> do
(c
c, s
s3, w
w3) <- RWST r w s m c -> r -> s -> m (c, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST (a -> ExitCase b -> RWST r w s m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e)) r
r s
s1
(c, s, w) -> m (c, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, s
s3, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3)
ExitCase (b, s, w)
ExitCaseAbort -> do
(c
c, s
s3, w
w3) <- RWST r w s m c -> r -> s -> m (c, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST (a -> ExitCase b -> RWST r w s m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort) r
r s
s1
(c, s, w) -> m (c, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, s
s3, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3))
(\(a
resource, s
s1, w
w1) -> do
(b
a, s
s2, w
w2) <- RWST r w s m b -> r -> s -> m (b, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
LazyRWS.runRWST (a -> RWST r w s m b
use a
resource) r
r s
s1
(b, s, w) -> m (b, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (b
a, s
s2, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w2))
((b, c), s, w) -> m ((b, c), s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((b
b, c
c), s
s3, w
w123)
instance (MonadThrow m, Monoid w) => MonadThrow (StrictRWS.RWST r w s m) where
throwM :: e -> RWST r w s m a
throwM e
e = m a -> RWST r w s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall w r s. Monoid w => MonadTrans (RWST r w s)
Evidence bound by a type signature of the constraint type Monoid w
lift (m a -> RWST r w s m a) -> m a -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM e
e
instance (MonadCatch m, Monoid w) => MonadCatch (StrictRWS.RWST r w s m) where
catch :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a
catch (StrictRWS.RWST r -> s -> m (a, s, w)
m) e -> RWST r w s m a
h = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
StrictRWS.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> r -> s -> m (a, s, w)
m r
r s
s m (a, s, w) -> (e -> m (a, s, w)) -> m (a, s, w)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
`catch` \e
e -> RWST r w s m a -> r -> s -> m (a, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST (e -> RWST r w s m a
h e
e) r
r s
s
instance (MonadMask m, Monoid w) => MonadMask (StrictRWS.RWST r w s m) where
mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> RWST r w s m b
mask (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a = (r -> s -> m (b, s, w)) -> RWST r w s m b
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
StrictRWS.RWST ((r -> s -> m (b, s, w)) -> RWST r w s m b)
-> (r -> s -> m (b, s, w)) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w))
-> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> RWST r w s m b -> r -> s -> m (b, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
forall (m :: * -> *) a s w r.
(m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
forall a. m a -> m a
u) r
r s
s
where q :: (m (a, s, w) -> m (a, s, w)) -> StrictRWS.RWST r w s m a -> StrictRWS.RWST r w s m a
q :: (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
u (StrictRWS.RWST r -> s -> m (a, s, w)
b) = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
StrictRWS.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \ r
r s
s -> m (a, s, w) -> m (a, s, w)
u (r -> s -> m (a, s, w)
b r
r s
s)
uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> RWST r w s m b
uninterruptibleMask (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a =
(r -> s -> m (b, s, w)) -> RWST r w s m b
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
StrictRWS.RWST ((r -> s -> m (b, s, w)) -> RWST r w s m b)
-> (r -> s -> m (b, s, w)) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ \r
r s
s -> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w))
-> ((forall a. m a -> m a) -> m (b, s, w)) -> m (b, s, w)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> RWST r w s m b -> r -> s -> m (b, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
a ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
forall a b. (a -> b) -> a -> b
$ (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
forall (m :: * -> *) a s w r.
(m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
forall a. m a -> m a
u) r
r s
s
where q :: (m (a, s, w) -> m (a, s, w)) -> StrictRWS.RWST r w s m a -> StrictRWS.RWST r w s m a
q :: (m (a, s, w) -> m (a, s, w)) -> RWST r w s m a -> RWST r w s m a
q m (a, s, w) -> m (a, s, w)
u (StrictRWS.RWST r -> s -> m (a, s, w)
b) = (r -> s -> m (a, s, w)) -> RWST r w s m a
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
StrictRWS.RWST ((r -> s -> m (a, s, w)) -> RWST r w s m a)
-> (r -> s -> m (a, s, w)) -> RWST r w s m a
forall a b. (a -> b) -> a -> b
$ \ r
r s
s -> m (a, s, w) -> m (a, s, w)
u (r -> s -> m (a, s, w)
b r
r s
s)
generalBracket :: RWST r w s m a
-> (a -> ExitCase b -> RWST r w s m c)
-> (a -> RWST r w s m b)
-> RWST r w s m (b, c)
generalBracket RWST r w s m a
acquire a -> ExitCase b -> RWST r w s m c
release a -> RWST r w s m b
use = (r -> s -> m ((b, c), s, w)) -> RWST r w s m (b, c)
forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
StrictRWS.RWST ((r -> s -> m ((b, c), s, w)) -> RWST r w s m (b, c))
-> (r -> s -> m ((b, c), s, w)) -> RWST r w s m (b, c)
forall a b. (a -> b) -> a -> b
$ \r
r s
s0 -> do
((b
b, s
_s2, w
_w12), (c
c, s
s3, w
w123)) <- m (a, s, w)
-> ((a, s, w) -> ExitCase (b, s, w) -> m (c, s, w))
-> ((a, s, w) -> m (b, s, w))
-> m ((b, s, w), (c, s, w))
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(RWST r w s m a -> r -> s -> m (a, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST RWST r w s m a
acquire r
r s
s0)
(\(a
resource, s
s1, w
w1) ExitCase (b, s, w)
exitCase -> case ExitCase (b, s, w)
exitCase of
ExitCaseSuccess (b
b, s
s2, w
w12) -> do
(c
c, s
s3, w
w3) <- RWST r w s m c -> r -> s -> m (c, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST (a -> ExitCase b -> RWST r w s m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b)) r
r s
s2
(c, s, w) -> m (c, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, s
s3, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w12 w
w3)
ExitCaseException SomeException
e -> do
(c
c, s
s3, w
w3) <- RWST r w s m c -> r -> s -> m (c, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST (a -> ExitCase b -> RWST r w s m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e)) r
r s
s1
(c, s, w) -> m (c, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, s
s3, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3)
ExitCase (b, s, w)
ExitCaseAbort -> do
(c
c, s
s3, w
w3) <- RWST r w s m c -> r -> s -> m (c, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST (a -> ExitCase b -> RWST r w s m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort) r
r s
s1
(c, s, w) -> m (c, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (c
c, s
s3, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w3))
(\(a
resource, s
s1, w
w1) -> do
(b
a, s
s2, w
w2) <- RWST r w s m b -> r -> s -> m (b, s, w)
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
StrictRWS.runRWST (a -> RWST r w s m b
use a
resource) r
r s
s1
(b, s, w) -> m (b, s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (b
a, s
s2, w -> w -> w
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid w
mappend w
w1 w
w2))
((b, c), s, w) -> m ((b, c), s, w)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((b
b, c
c), s
s3, w
w123)
instance MonadThrow m => MonadThrow (ListT m) where
throwM :: e -> ListT m a
throwM = m a -> ListT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type MonadTrans ListT
lift (m a -> ListT m a) -> (e -> m a) -> e -> ListT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM
instance MonadCatch m => MonadCatch (ListT m) where
catch :: ListT m a -> (e -> ListT m a) -> ListT m a
catch (ListT m [a]
m) e -> ListT m a
f = m [a] -> ListT m a
forall (m :: * -> *) a. m [a] -> ListT m a
ListT (m [a] -> ListT m a) -> m [a] -> ListT m a
forall a b. (a -> b) -> a -> b
$ m [a] -> (e -> m [a]) -> m [a]
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch m [a]
m (ListT m a -> m [a]
forall (m :: * -> *) a. ListT m a -> m [a]
runListT (ListT m a -> m [a]) -> (e -> ListT m a) -> e -> m [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ListT m a
f)
instance MonadThrow m => MonadThrow (MaybeT m) where
throwM :: e -> MaybeT m a
throwM = m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type MonadTrans MaybeT
lift (m a -> MaybeT m a) -> (e -> m a) -> e -> MaybeT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM
instance MonadCatch m => MonadCatch (MaybeT m) where
catch :: MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a
catch (MaybeT m (Maybe a)
m) e -> MaybeT m a
f = m (Maybe a) -> MaybeT m a
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe a) -> MaybeT m a) -> m (Maybe a) -> MaybeT m a
forall a b. (a -> b) -> a -> b
$ m (Maybe a) -> (e -> m (Maybe a)) -> m (Maybe a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch m (Maybe a)
m (MaybeT m a -> m (Maybe a)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m a -> m (Maybe a))
-> (e -> MaybeT m a) -> e -> m (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> MaybeT m a
f)
instance MonadMask m => MonadMask (MaybeT m) where
mask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b
mask (forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b
f = m (Maybe b) -> MaybeT m b
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe b) -> MaybeT m b) -> m (Maybe b) -> MaybeT m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (Maybe b)) -> m (Maybe b)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (Maybe b)) -> m (Maybe b))
-> ((forall a. m a -> m a) -> m (Maybe b)) -> m (Maybe b)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> MaybeT m b -> m (Maybe b)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m b -> m (Maybe b)) -> MaybeT m b -> m (Maybe b)
forall a b. (a -> b) -> a -> b
$ (forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b
f ((m (Maybe a) -> m (Maybe a)) -> MaybeT m a -> MaybeT m a
forall (m :: * -> *) a.
(m (Maybe a) -> m (Maybe a)) -> MaybeT m a -> MaybeT m a
q m (Maybe a) -> m (Maybe a)
forall a. m a -> m a
u)
where
q :: (m (Maybe a) -> m (Maybe a))
-> MaybeT m a -> MaybeT m a
q :: (m (Maybe a) -> m (Maybe a)) -> MaybeT m a -> MaybeT m a
q m (Maybe a) -> m (Maybe a)
u (MaybeT m (Maybe a)
b) = m (Maybe a) -> MaybeT m a
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe a) -> m (Maybe a)
u m (Maybe a)
b)
uninterruptibleMask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b
uninterruptibleMask (forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b
f = m (Maybe b) -> MaybeT m b
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe b) -> MaybeT m b) -> m (Maybe b) -> MaybeT m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (Maybe b)) -> m (Maybe b)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (Maybe b)) -> m (Maybe b))
-> ((forall a. m a -> m a) -> m (Maybe b)) -> m (Maybe b)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> MaybeT m b -> m (Maybe b)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m b -> m (Maybe b)) -> MaybeT m b -> m (Maybe b)
forall a b. (a -> b) -> a -> b
$ (forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b
f ((m (Maybe a) -> m (Maybe a)) -> MaybeT m a -> MaybeT m a
forall (m :: * -> *) a.
(m (Maybe a) -> m (Maybe a)) -> MaybeT m a -> MaybeT m a
q m (Maybe a) -> m (Maybe a)
forall a. m a -> m a
u)
where
q :: (m (Maybe a) -> m (Maybe a))
-> MaybeT m a -> MaybeT m a
q :: (m (Maybe a) -> m (Maybe a)) -> MaybeT m a -> MaybeT m a
q m (Maybe a) -> m (Maybe a)
u (MaybeT m (Maybe a)
b) = m (Maybe a) -> MaybeT m a
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe a) -> m (Maybe a)
u m (Maybe a)
b)
generalBracket :: MaybeT m a
-> (a -> ExitCase b -> MaybeT m c)
-> (a -> MaybeT m b)
-> MaybeT m (b, c)
generalBracket MaybeT m a
acquire a -> ExitCase b -> MaybeT m c
release a -> MaybeT m b
use = m (Maybe (b, c)) -> MaybeT m (b, c)
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (b, c)) -> MaybeT m (b, c))
-> m (Maybe (b, c)) -> MaybeT m (b, c)
forall a b. (a -> b) -> a -> b
$ do
(Maybe b
eb, Maybe c
ec) <- m (Maybe a)
-> (Maybe a -> ExitCase (Maybe b) -> m (Maybe c))
-> (Maybe a -> m (Maybe b))
-> m (Maybe b, Maybe c)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(MaybeT m a -> m (Maybe a)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT MaybeT m a
acquire)
(\Maybe a
resourceMay ExitCase (Maybe b)
exitCase -> case Maybe a
resourceMay of
Maybe a
Nothing -> Maybe c -> m (Maybe c)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return Maybe c
forall a. Maybe a
Nothing
Just a
resource -> case ExitCase (Maybe b)
exitCase of
ExitCaseSuccess (Just b
b) -> MaybeT m c -> m (Maybe c)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (a -> ExitCase b -> MaybeT m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b))
ExitCaseException SomeException
e -> MaybeT m c -> m (Maybe c)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (a -> ExitCase b -> MaybeT m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e))
ExitCase (Maybe b)
_ -> MaybeT m c -> m (Maybe c)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (a -> ExitCase b -> MaybeT m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort))
(\Maybe a
resourceMay -> case Maybe a
resourceMay of
Maybe a
Nothing -> Maybe b -> m (Maybe b)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return Maybe b
forall a. Maybe a
Nothing
Just a
resource -> MaybeT m b -> m (Maybe b)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (a -> MaybeT m b
use a
resource))
Maybe (b, c) -> m (Maybe (b, c))
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ((,) (b -> c -> (b, c)) -> Maybe b -> Maybe (c -> (b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$> Maybe b
eb Maybe (c -> (b, c)) -> Maybe c -> Maybe (b, c)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Maybe
<*> Maybe c
ec)
instance (Error e, MonadThrow m) => MonadThrow (ErrorT e m) where
throwM :: e -> ErrorT e m a
throwM = m a -> ErrorT e m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall e. MonadTrans (ErrorT e)
lift (m a -> ErrorT e m a) -> (e -> m a) -> e -> ErrorT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM
instance (Error e, MonadCatch m) => MonadCatch (ErrorT e m) where
catch :: ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a
catch (ErrorT m (Either e a)
m) e -> ErrorT e m a
f = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ m (Either e a) -> (e -> m (Either e a)) -> m (Either e a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch m (Either e a)
m (ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (ErrorT e m a -> m (Either e a))
-> (e -> ErrorT e m a) -> e -> m (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ErrorT e m a
f)
instance (Error e, MonadMask m) => MonadMask (ErrorT e m) where
mask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b)
-> ErrorT e m b
mask (forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b
f = m (Either e b) -> ErrorT e m b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e b) -> ErrorT e m b) -> m (Either e b) -> ErrorT e m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b))
-> ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> ErrorT e m b -> m (Either e b)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (ErrorT e m b -> m (Either e b)) -> ErrorT e m b -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ (forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b
f ((m (Either e a) -> m (Either e a)) -> ErrorT e m a -> ErrorT e m a
forall (m :: * -> *) e a.
(m (Either e a) -> m (Either e a)) -> ErrorT e m a -> ErrorT e m a
q m (Either e a) -> m (Either e a)
forall a. m a -> m a
u)
where
q :: (m (Either e a) -> m (Either e a))
-> ErrorT e m a -> ErrorT e m a
q :: (m (Either e a) -> m (Either e a)) -> ErrorT e m a -> ErrorT e m a
q m (Either e a) -> m (Either e a)
u (ErrorT m (Either e a)
b) = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> m (Either e a)
u m (Either e a)
b)
uninterruptibleMask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b)
-> ErrorT e m b
uninterruptibleMask (forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b
f = m (Either e b) -> ErrorT e m b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e b) -> ErrorT e m b) -> m (Either e b) -> ErrorT e m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b))
-> ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> ErrorT e m b -> m (Either e b)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (ErrorT e m b -> m (Either e b)) -> ErrorT e m b -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ (forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b
f ((m (Either e a) -> m (Either e a)) -> ErrorT e m a -> ErrorT e m a
forall (m :: * -> *) e a.
(m (Either e a) -> m (Either e a)) -> ErrorT e m a -> ErrorT e m a
q m (Either e a) -> m (Either e a)
forall a. m a -> m a
u)
where
q :: (m (Either e a) -> m (Either e a))
-> ErrorT e m a -> ErrorT e m a
q :: (m (Either e a) -> m (Either e a)) -> ErrorT e m a -> ErrorT e m a
q m (Either e a) -> m (Either e a)
u (ErrorT m (Either e a)
b) = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> m (Either e a)
u m (Either e a)
b)
generalBracket :: ErrorT e m a
-> (a -> ExitCase b -> ErrorT e m c)
-> (a -> ErrorT e m b)
-> ErrorT e m (b, c)
generalBracket ErrorT e m a
acquire a -> ExitCase b -> ErrorT e m c
release a -> ErrorT e m b
use = m (Either e (b, c)) -> ErrorT e m (b, c)
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e (b, c)) -> ErrorT e m (b, c))
-> m (Either e (b, c)) -> ErrorT e m (b, c)
forall a b. (a -> b) -> a -> b
$ do
(Either e b
eb, Either e c
ec) <- m (Either e a)
-> (Either e a -> ExitCase (Either e b) -> m (Either e c))
-> (Either e a -> m (Either e b))
-> m (Either e b, Either e c)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
acquire)
(\Either e a
eresource ExitCase (Either e b)
exitCase -> case Either e a
eresource of
Left e
e -> Either e c -> m (Either e c)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (e -> Either e c
forall a b. a -> Either a b
Left e
e)
Right a
resource -> case ExitCase (Either e b)
exitCase of
ExitCaseSuccess (Right b
b) -> ErrorT e m c -> m (Either e c)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (a -> ExitCase b -> ErrorT e m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b))
ExitCaseException SomeException
e -> ErrorT e m c -> m (Either e c)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (a -> ExitCase b -> ErrorT e m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e))
ExitCase (Either e b)
_ -> ErrorT e m c -> m (Either e c)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (a -> ExitCase b -> ErrorT e m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort))
((e -> m (Either e b))
-> (a -> m (Either e b)) -> Either e a -> m (Either e b)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (Either e b -> m (Either e b))
-> (e -> Either e b) -> e -> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e b
forall a b. a -> Either a b
Left) (ErrorT e m b -> m (Either e b)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (ErrorT e m b -> m (Either e b))
-> (a -> ErrorT e m b) -> a -> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ErrorT e m b
use))
Either e (b, c) -> m (Either e (b, c))
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (Either e (b, c) -> m (Either e (b, c)))
-> Either e (b, c) -> m (Either e (b, c))
forall a b. (a -> b) -> a -> b
$ do
c
c <- Either e c
ec
b
b <- Either e b
eb
(b, c) -> Either e (b, c)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall e. Monad (Either e)
return (b
b, c
c)
instance MonadThrow m => MonadThrow (ExceptT e m) where
throwM :: e -> ExceptT e m a
throwM = m a -> ExceptT e m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall e. MonadTrans (ExceptT e)
lift (m a -> ExceptT e m a) -> (e -> m a) -> e -> ExceptT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM
instance MonadCatch m => MonadCatch (ExceptT e m) where
catch :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a
catch (ExceptT m (Either e a)
m) e -> ExceptT e m a
f = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT e m a
forall a b. (a -> b) -> a -> b
$ m (Either e a) -> (e -> m (Either e a)) -> m (Either e a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch m (Either e a)
m (ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT e m a -> m (Either e a))
-> (e -> ExceptT e m a) -> e -> m (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ExceptT e m a
f)
instance MonadMask m => MonadMask (ExceptT e m) where
mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b)
-> ExceptT e m b
mask (forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b
f = m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> m (Either e b) -> ExceptT e m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b))
-> ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> ExceptT e m b -> m (Either e b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT e m b -> m (Either e b))
-> ExceptT e m b -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ (forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b
f ((m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
forall (m :: * -> *) e a.
(m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
q m (Either e a) -> m (Either e a)
forall a. m a -> m a
u)
where
q :: (m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
q :: (m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
q m (Either e a) -> m (Either e a)
u (ExceptT m (Either e a)
b) = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> m (Either e a)
u m (Either e a)
b)
uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b)
-> ExceptT e m b
uninterruptibleMask (forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b
f = m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> m (Either e b) -> ExceptT e m b
forall a b. (a -> b) -> a -> b
$ ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b))
-> ((forall a. m a -> m a) -> m (Either e b)) -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
u -> ExceptT e m b -> m (Either e b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT e m b -> m (Either e b))
-> ExceptT e m b -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ (forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b
f ((m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
forall (m :: * -> *) e a.
(m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
q m (Either e a) -> m (Either e a)
forall a. m a -> m a
u)
where
q :: (m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
q :: (m (Either e a) -> m (Either e a))
-> ExceptT e m a -> ExceptT e m a
q m (Either e a) -> m (Either e a)
u (ExceptT m (Either e a)
b) = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> m (Either e a)
u m (Either e a)
b)
generalBracket :: ExceptT e m a
-> (a -> ExitCase b -> ExceptT e m c)
-> (a -> ExceptT e m b)
-> ExceptT e m (b, c)
generalBracket ExceptT e m a
acquire a -> ExitCase b -> ExceptT e m c
release a -> ExceptT e m b
use = m (Either e (b, c)) -> ExceptT e m (b, c)
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e (b, c)) -> ExceptT e m (b, c))
-> m (Either e (b, c)) -> ExceptT e m (b, c)
forall a b. (a -> b) -> a -> b
$ do
(Either e b
eb, Either e c
ec) <- m (Either e a)
-> (Either e a -> ExitCase (Either e b) -> m (Either e c))
-> (Either e a -> m (Either e b))
-> m (Either e b, Either e c)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
(ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT e m a
acquire)
(\Either e a
eresource ExitCase (Either e b)
exitCase -> case Either e a
eresource of
Left e
e -> Either e c -> m (Either e c)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (e -> Either e c
forall a b. a -> Either a b
Left e
e)
Right a
resource -> case ExitCase (Either e b)
exitCase of
ExitCaseSuccess (Right b
b) -> ExceptT e m c -> m (Either e c)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (a -> ExitCase b -> ExceptT e m c
release a
resource (b -> ExitCase b
forall a. a -> ExitCase a
ExitCaseSuccess b
b))
ExitCaseException SomeException
e -> ExceptT e m c -> m (Either e c)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (a -> ExitCase b -> ExceptT e m c
release a
resource (SomeException -> ExitCase b
forall a. SomeException -> ExitCase a
ExitCaseException SomeException
e))
ExitCase (Either e b)
_ -> ExceptT e m c -> m (Either e c)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (a -> ExitCase b -> ExceptT e m c
release a
resource ExitCase b
forall a. ExitCase a
ExitCaseAbort))
((e -> m (Either e b))
-> (a -> m (Either e b)) -> Either e a -> m (Either e b)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (Either e b -> m (Either e b))
-> (e -> Either e b) -> e -> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e b
forall a b. a -> Either a b
Left) (ExceptT e m b -> m (Either e b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT e m b -> m (Either e b))
-> (a -> ExceptT e m b) -> a -> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ExceptT e m b
use))
Either e (b, c) -> m (Either e (b, c))
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return (Either e (b, c) -> m (Either e (b, c)))
-> Either e (b, c) -> m (Either e (b, c))
forall a b. (a -> b) -> a -> b
$ do
c
c <- Either e c
ec
b
b <- Either e b
eb
(b, c) -> Either e (b, c)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall e. Monad (Either e)
return (b
b, c
c)
instance MonadThrow m => MonadThrow (ContT r m) where
throwM :: e -> ContT r m a
throwM = m a -> ContT r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall r. MonadTrans (ContT r)
lift (m a -> ContT r m a) -> (e -> m a) -> e -> ContT r m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadThrow m
throwM
mask_ :: MonadMask m => m a -> m a
mask_ :: m a -> m a
mask_ m a
io = ((forall a. m a -> m a) -> m a) -> m a
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
mask (((forall a. m a -> m a) -> m a) -> m a)
-> ((forall a. m a -> m a) -> m a) -> m a
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
_ -> m a
io
uninterruptibleMask_ :: MonadMask m => m a -> m a
uninterruptibleMask_ :: m a -> m a
uninterruptibleMask_ m a
io = ((forall a. m a -> m a) -> m a) -> m a
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
uninterruptibleMask (((forall a. m a -> m a) -> m a) -> m a)
-> ((forall a. m a -> m a) -> m a) -> m a
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
_ -> m a
io
catchAll :: MonadCatch m => m a -> (SomeException -> m a) -> m a
catchAll :: m a -> (SomeException -> m a) -> m a
catchAll = m a -> (SomeException -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
External instance of the constraint type Exception SomeException
Evidence bound by a type signature of the constraint type MonadCatch m
catch
catchIOError :: MonadCatch m => m a -> (IOError -> m a) -> m a
catchIOError :: m a -> (IOError -> m a) -> m a
catchIOError = m a -> (IOError -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
External instance of the constraint type Exception IOError
Evidence bound by a type signature of the constraint type MonadCatch m
catch
catchIf :: (MonadCatch m, Exception e) =>
(e -> Bool) -> m a -> (e -> m a) -> m a
catchIf :: (e -> Bool) -> m a -> (e -> m a) -> m a
catchIf e -> Bool
f m a
a e -> m a
b = m a
a m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
`catch` \e
e -> if e -> Bool
f e
e then e -> m a
b e
e else e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
throwM e
e
catchJust :: (MonadCatch m, Exception e) =>
(e -> Maybe b) -> m a -> (b -> m a) -> m a
catchJust :: (e -> Maybe b) -> m a -> (b -> m a) -> m a
catchJust e -> Maybe b
f m a
a b -> m a
b = m a
a m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
`catch` \e
e -> m a -> (b -> m a) -> Maybe b -> m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
throwM e
e) b -> m a
b (Maybe b -> m a) -> Maybe b -> m a
forall a b. (a -> b) -> a -> b
$ e -> Maybe b
f e
e
handle :: (MonadCatch m, Exception e) => (e -> m a) -> m a -> m a
handle :: (e -> m a) -> m a -> m a
handle = (m a -> (e -> m a) -> m a) -> (e -> m a) -> m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch
{-# INLINE handle #-}
handleIOError :: MonadCatch m => (IOError -> m a) -> m a -> m a
handleIOError :: (IOError -> m a) -> m a -> m a
handleIOError = (IOError -> m a) -> m a -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
External instance of the constraint type Exception IOError
Evidence bound by a type signature of the constraint type MonadCatch m
handle
handleAll :: MonadCatch m => (SomeException -> m a) -> m a -> m a
handleAll :: (SomeException -> m a) -> m a -> m a
handleAll = (SomeException -> m a) -> m a -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
External instance of the constraint type Exception SomeException
Evidence bound by a type signature of the constraint type MonadCatch m
handle
handleIf :: (MonadCatch m, Exception e) => (e -> Bool) -> (e -> m a) -> m a -> m a
handleIf :: (e -> Bool) -> (e -> m a) -> m a -> m a
handleIf e -> Bool
f = (m a -> (e -> m a) -> m a) -> (e -> m a) -> m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((e -> Bool) -> m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> Bool) -> m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catchIf e -> Bool
f)
handleJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a
handleJust :: (e -> Maybe b) -> (b -> m a) -> m a -> m a
handleJust e -> Maybe b
f = (m a -> (b -> m a) -> m a) -> (b -> m a) -> m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((e -> Maybe b) -> m a -> (b -> m a) -> m a
forall (m :: * -> *) e b a.
(MonadCatch m, Exception e) =>
(e -> Maybe b) -> m a -> (b -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catchJust e -> Maybe b
f)
{-# INLINE handleJust #-}
try :: (MonadCatch m, Exception e) => m a -> m (Either e a)
try :: m a -> m (Either e a)
try m a
a = m (Either e a) -> (e -> m (Either e a)) -> m (Either e a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch (a -> Either e a
forall a b. b -> Either a b
Right (a -> Either e a) -> m a -> m (Either e a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
`liftM` m a
a) (Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
return (Either e a -> m (Either e a))
-> (e -> Either e a) -> e -> m (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e a
forall a b. a -> Either a b
Left)
tryJust :: (MonadCatch m, Exception e) =>
(e -> Maybe b) -> m a -> m (Either b a)
tryJust :: (e -> Maybe b) -> m a -> m (Either b a)
tryJust e -> Maybe b
f m a
a = m (Either b a) -> (e -> m (Either b a)) -> m (Either b a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a type signature of the constraint type MonadCatch m
catch (a -> Either b a
forall a b. b -> Either a b
Right (a -> Either b a) -> m a -> m (Either b a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
`liftM` m a
a) (\e
e -> m (Either b a)
-> (b -> m (Either b a)) -> Maybe b -> m (Either b a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (e -> m (Either b a)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
throwM e
e) (Either b a -> m (Either b a)
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
return (Either b a -> m (Either b a))
-> (b -> Either b a) -> b -> m (Either b a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Either b a
forall a b. a -> Either a b
Left) (e -> Maybe b
f e
e))
data Handler m a = forall e . ControlException.Exception e => Handler (e -> m a)
instance Monad m => Functor (Handler m) where
fmap :: (a -> b) -> Handler m a -> Handler m b
fmap a -> b
f (Handler e -> m a
h) = (e -> m b) -> Handler m b
forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Evidence bound by a pattern of the constraint type Exception e
Handler ((a -> b) -> m a -> m b
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Evidence bound by a type signature of the constraint type Monad m
liftM a -> b
f (m a -> m b) -> (e -> m a) -> e -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
h)
catches :: (Foldable f, MonadCatch m) => m a -> f (Handler m a) -> m a
catches :: m a -> f (Handler m a) -> m a
catches m a
a f (Handler m a)
hs = m a
a m a -> (SomeException -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
External instance of the constraint type Exception SomeException
Evidence bound by a type signature of the constraint type MonadCatch m
`catch` SomeException -> m a
handler
where
handler :: SomeException -> m a
handler SomeException
e = (Handler m a -> m a -> m a) -> m a -> f (Handler m a) -> m a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Evidence bound by a type signature of the constraint type Foldable f
foldr Handler m a -> m a -> m a
probe (SomeException -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
External instance of the constraint type Exception SomeException
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
throwM SomeException
e) f (Handler m a)
hs
where
probe :: Handler m a -> m a -> m a
probe (Handler e -> m a
h) m a
xs = m a -> (e -> m a) -> Maybe e -> m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m a
xs e -> m a
h (SomeException -> Maybe e
forall e. Exception e => SomeException -> Maybe e
Evidence bound by a pattern of the constraint type Exception e
ControlException.fromException SomeException
e)
onException :: MonadCatch m => m a -> m b -> m a
onException :: m a -> m b -> m a
onException m a
action m b
handler = m a
action m a -> (SomeException -> m a) -> m a
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
Evidence bound by a type signature of the constraint type MonadCatch m
`catchAll` \SomeException
e -> m b
handler m b -> m a -> m a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
>> SomeException -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
External instance of the constraint type Exception SomeException
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
throwM SomeException
e
onError :: MonadMask m => m a -> m b -> m a
onError :: m a -> m b -> m a
onError m a
action m b
handler = m () -> (() -> m b) -> (() -> m a) -> m a
forall (m :: * -> *) a c b.
MonadMask m =>
m a -> (a -> m c) -> (a -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
bracketOnError (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ()) (m b -> () -> m b
forall a b. a -> b -> a
const m b
handler) (m a -> () -> m a
forall a b. a -> b -> a
const m a
action)
bracket :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b
bracket :: m a -> (a -> m c) -> (a -> m b) -> m b
bracket m a
acquire a -> m c
release = ((b, c) -> b) -> m (b, c) -> m b
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
liftM (b, c) -> b
forall a b. (a, b) -> a
fst (m (b, c) -> m b) -> ((a -> m b) -> m (b, c)) -> (a -> m b) -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
m a
acquire
(\a
a ExitCase b
_exitCase -> a -> m c
release a
a)
bracket_ :: MonadMask m => m a -> m c -> m b -> m b
bracket_ :: m a -> m c -> m b -> m b
bracket_ m a
before m c
after m b
action = m a -> (a -> m c) -> (a -> m b) -> m b
forall (m :: * -> *) a c b.
MonadMask m =>
m a -> (a -> m c) -> (a -> m b) -> m b
Evidence bound by a type signature of the constraint type MonadMask m
bracket m a
before (m c -> a -> m c
forall a b. a -> b -> a
const m c
after) (m b -> a -> m b
forall a b. a -> b -> a
const m b
action)
finally :: MonadMask m => m a -> m b -> m a
finally :: m a -> m b -> m a
finally m a
action m b
finalizer = m () -> m b -> m a -> m a
forall (m :: * -> *) a c b. MonadMask m => m a -> m c -> m b -> m b
Evidence bound by a type signature of the constraint type MonadMask m
bracket_ (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ()) m b
finalizer m a
action
bracketOnError :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b
bracketOnError :: m a -> (a -> m c) -> (a -> m b) -> m b
bracketOnError m a
acquire a -> m c
release = ((b, ()) -> b) -> m (b, ()) -> m b
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
liftM (b, ()) -> b
forall a b. (a, b) -> a
fst (m (b, ()) -> m b)
-> ((a -> m b) -> m (b, ())) -> (a -> m b) -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> (a -> ExitCase b -> m ()) -> (a -> m b) -> m (b, ())
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
Evidence bound by a type signature of the constraint type MonadMask m
generalBracket
m a
acquire
(\a
a ExitCase b
exitCase -> case ExitCase b
exitCase of
ExitCaseSuccess b
_ -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ()
ExitCase b
_ -> do
c
_ <- a -> m c
release a
a
() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a superclass of: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a superclass of: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a superclass of: MonadMask of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
return ())