Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Member (t :: Effect) (r :: EffectRow)
- type family Members (es :: [Effect]) (r :: EffectRow) where ...
- data Sem (r :: EffectRow) a
- send :: forall e (r :: EffectRow) a. Member e r => e (Sem r) a -> Sem r a
- makeSem :: Name -> Q [Dec]
- makeSem_ :: Name -> Q [Dec]
- data Final (m :: Type -> Type) (z :: Type -> Type) a
- runFinal :: Monad m => Sem '[Final m] a -> m a
- data Async (m :: Type -> Type) a
- async :: forall (r :: EffectRow) a. Member Async r => Sem r a -> Sem r (Async (Maybe a))
- await :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r a
- cancel :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r ()
- sequenceConcurrently :: forall t (r :: EffectRow) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a))
- data DataLog a (b :: Type -> Type) c
- data Log (a :: Type -> Type) b
- data LogEntry a
- type Logger = DataLog (LogEntry LogMessage)
- data LogMessage
- data Severity
- dataLog :: forall a (r :: EffectRow). Member (DataLog a) r => a -> Sem r ()
- log :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Severity -> Text -> Sem r ()
- trace :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r ()
- debug :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r ()
- info :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r ()
- warn :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r ()
- error :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r ()
- crit :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r ()
- formatLogEntry :: LogEntry LogMessage -> Text
- parseSeverity :: Text -> Maybe Severity
- setLogLevel :: forall (r :: EffectRow) a. Member (DataLog (LogEntry LogMessage)) r => Maybe Severity -> Sem r a -> Sem r a
- setLogLevelWith :: forall msg (r :: EffectRow) a. Member (DataLog msg) r => (msg -> Severity) -> Maybe Severity -> Sem r a -> Sem r a
- data Embed (m :: Type -> Type) (z :: Type -> Type) a
- embed :: forall m (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a
- embedToFinal :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a
- runEmbedded :: forall m1 m2 (r :: EffectRow) a. Member (Embed m2) r => (forall x. m1 x -> m2 x) -> Sem (Embed m1 ': r) a -> Sem r a
- data Error e (m :: k -> Type) (a :: k)
- throw :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Sem r a
- catch :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> (e -> Sem r a) -> Sem r a
- trap :: forall e a r. (e -> Sem r a) -> Sem (Error e ': r) a -> Sem r a
- trap_ :: forall e a r. Sem r a -> Sem (Error e ': r) a -> Sem r a
- embedRunExceptT :: forall e a r m. Member (Embed m) r => ExceptT e m a -> Sem r (Either e a)
- embedThrowExceptT :: forall e a r m. Member (Error e) r => Member (Embed m) r => ExceptT e m a -> Sem r a
- fromEither :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Either e a -> Sem r a
- fromEitherM :: forall e m (r :: EffectRow) a. (Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed m) r) => m (Either e a) -> Sem r a
- fromException :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => IO a -> Sem r a
- fromExceptionVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => (exc -> err) -> IO a -> Sem r a
- note :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Maybe a -> Sem r a
- try :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r (Either e a)
- tryJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a)
- catchJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> (b -> Sem r a) -> Sem r a
- mapError :: forall e1 e2 (r :: EffectRow) a. Member (Error e2 :: (Type -> Type) -> Type -> Type) r => (e1 -> e2) -> Sem ((Error e1 :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- onLeft :: forall e a m. Monad m => (e -> m a) -> Either e a -> m a
- onNothing :: forall a m. Monad m => m a -> Maybe a -> m a
- onLeftM :: forall e a m. Monad m => (e -> m a) -> m (Either e a) -> m a
- onNothingM :: forall a m. Monad m => m a -> m (Maybe a) -> m a
- runError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a)
- data Reader i (m :: Type -> Type) a
- ask :: forall i (r :: EffectRow). Member (Reader i) r => Sem r i
- asks :: forall i j (r :: EffectRow). Member (Reader i) r => (i -> j) -> Sem r j
- inputToReader :: forall i (r :: EffectRow) a. Member (Reader i) r => Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem (Reader i ': r) a -> Sem r a
- data Resource (m :: Type -> Type) a
- bracket :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b
- bracket_ :: forall (r :: EffectRow) a b c. Member Resource r => Sem r a -> Sem r b -> Sem r c -> Sem r c
- bracketOnError :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b
- finally :: forall (r :: EffectRow) a b. Member Resource r => Sem r a -> Sem r b -> Sem r a
- onException :: forall (r :: EffectRow) a b. Member Resource r => Sem r a -> Sem r b -> Sem r a
- runResource :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Resource ': r) a -> Sem r a
Documentation
class Member (t :: Effect) (r :: EffectRow) #
This class indicates that an effect must be present in the caller's stack. It is the main mechanism by which a program defines its effect dependencies.
membership'
Instances
Member t z => Member t (_1 ': z) | |
Defined in Polysemy.Internal.Union membership' :: ElemOf t (_1 ': z) | |
Member t (t ': z) | |
Defined in Polysemy.Internal.Union membership' :: ElemOf t (t ': z) |
type family Members (es :: [Effect]) (r :: EffectRow) where ... #
Makes constraints of functions that use multiple effects shorter by
translating single list of effects into multiple Member
constraints:
foo ::Members
'[Output
Int ,Output
Bool ,State
String ] r =>Sem
r ()
translates into:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ,Member
(State
String) r ) =>Sem
r ()
Since: polysemy-0.1.2.0
The Sem
monad handles computations of arbitrary extensible effects.
A value of type Sem r
describes a program with the capabilities of
r
. For best results, r
should always be kept polymorphic, but you can
add capabilities via the Member
constraint.
The value of the Sem
monad is that it allows you to write programs
against a set of effects without a predefined meaning, and provide that
meaning later. For example, unlike with mtl, you can decide to interpret an
Error
effect traditionally as an Either
, or instead
as (a significantly faster) IO
Exception
. These
interpretations (and others that you might add) may be used interchangeably
without needing to write any newtypes or Monad
instances. The only
change needed to swap interpretations is to change a call from
runError
to errorToIOFinal
.
The effect stack r
can contain arbitrary other monads inside of it. These
monads are lifted into effects via the Embed
effect. Monadic values can be
lifted into a Sem
via embed
.
Higher-order actions of another monad can be lifted into higher-order actions
of Sem
via the Final
effect, which is more powerful
than Embed
, but also less flexible to interpret.
A Sem
can be interpreted as a pure value (via run
) or as any
traditional Monad
(via runM
or runFinal
).
Each effect E
comes equipped with some interpreters of the form:
runE ::Sem
(E ': r) a ->Sem
r a
which is responsible for removing the effect E
from the effect stack. It
is the order in which you call the interpreters that determines the
monomorphic representation of the r
parameter.
Order of interpreters can be important - it determines behaviour of effects that manipulate state or change control flow. For example, when interpreting this action:
>>>
:{
example :: Members '[State String, Error String] r => Sem r String example = do put "start" let throwing, catching :: Members '[State String, Error String] r => Sem r String throwing = do modify (++"-throw") throw "error" get catching = do modify (++"-catch") get catch @String throwing (\ _ -> catching) :}
when handling Error
first, state is preserved after error
occurs:
>>>
:{
example & runError & fmap (either id id) & evalState "" & runM & (print =<<) :} "start-throw-catch"
while handling State
first discards state in such cases:
>>>
:{
example & evalState "" & runError & fmap (either id id) & runM & (print =<<) :} "start-catch"
A good rule of thumb is to handle effects which should have "global" behaviour over other effects later in the chain.
After all of your effects are handled, you'll be left with either
a
, a Sem
'[] a
, or a Sem
'[ Embed
m ] a
value, which can be consumed respectively by Sem
'[ Final
m ] arun
, runM
, and
runFinal
.
Examples
As an example of keeping r
polymorphic, we can consider the type
Member
(State
String) r =>Sem
r ()
to be a program with access to
get
::Sem
r Stringput
:: String ->Sem
r ()
methods.
By also adding a
Member
(Error
Bool) r
constraint on r
, we gain access to the
throw
:: Bool ->Sem
r acatch
::Sem
r a -> (Bool ->Sem
r a) ->Sem
r a
functions as well.
In this sense, a
constraint is
analogous to mtl's Member
(State
s) r
and should
be thought of as such. However, unlike mtl, a MonadState
s mSem
monad may have
an arbitrary number of the same effect.
For example, we can write a Sem
program which can output either
Int
s or Bool
s:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ) =>Sem
r () foo = dooutput
@Int 5output
True
Notice that we must use -XTypeApplications
to specify that we'd like to
use the (Output
Int
) effect.
Since: polysemy-0.1.2.0
Instances
Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r) | Since: polysemy-1.1.0.0 |
Defined in Polysemy.Internal | |
Member Fixpoint r => MonadFix (Sem r) | |
Defined in Polysemy.Internal | |
Member (Embed IO) r => MonadIO (Sem r) | This instance will only lift |
Defined in Polysemy.Internal | |
Member NonDet r => Alternative (Sem r) | |
Applicative (Sem f) | |
Functor (Sem f) | |
Monad (Sem f) | |
Member NonDet r => MonadPlus (Sem r) | Since: polysemy-0.2.1.0 |
Monoid a => Monoid (Sem f a) | Since: polysemy-1.6.0.0 |
Semigroup a => Semigroup (Sem f a) | Since: polysemy-1.6.0.0 |
send :: forall e (r :: EffectRow) a. Member e r => e (Sem r) a -> Sem r a #
Execute an action of an effect.
This is primarily used to create methods for actions of effects:
data FooBar m a where Foo :: String -> m a -> FooBar m a Bar :: FooBar m Int foo :: Member FooBar r => String -> Sem r a -> Sem r a foo s m = send (Foo s m) bar :: Member FooBar r => Sem r Int bar = send Bar
makeSem
allows you to eliminate this boilerplate.
@since TODO
If T
is a GADT representing an effect algebra, as described in the
module documentation for Polysemy, $(
automatically
generates a smart constructor for every data constructor of makeSem
''T)T
. This also
works for data family instances. Names of smart constructors are created by
changing first letter to lowercase or removing prefix :
in case of
operators. Fixity declaration is preserved for both normal names and
operators.
Since: polysemy-0.1.2.0
Like makeSem
, but does not provide type signatures and fixities. This
can be used to attach Haddock comments to individual arguments for each
generated function.
data Output o m a where Output :: o -> Output o m () makeSem_ ''Output -- | Output the value @o@. output :: forall o r . Member (Output o) r => o -- ^ Value to output. -> Sem r () -- ^ No result.
Because of limitations in Template Haskell, signatures have to follow some rules to work properly:
makeSem_
must be used before the explicit type signatures- signatures have to specify argument of
Sem
representing union of effects asr
(e.g.
)Sem
r () - all arguments in effect's type constructor have to follow naming scheme from data constructor's declaration:
data Foo e m a where FooC1 :: Foo x m () FooC2 :: Foo (Maybe x) m ()
should have x
in type signature of fooC1
:
fooC1 :: forall x r. Member (Foo x) r => Sem r ()
and Maybe x
in signature of fooC2
:
fooC2 :: forall x r. Member (Foo (Maybe x)) r => Sem r ()
- all effect's type variables and
r
have to be explicitly quantified usingforall
(order is not important)
These restrictions may be removed in the future, depending on changes to the compiler.
Change in (TODO(Sandy): version): in case of GADTs, signatures now only use names from data constructor's type and not from type constructor declaration.
Since: polysemy-0.1.2.0
data Final (m :: Type -> Type) (z :: Type -> Type) a #
An effect for embedding higher-order actions in the final target monad of the effect stack.
This is very useful for writing interpreters that interpret higher-order effects in terms of the final monad.
Final
is more powerful than Embed
, but is also less flexible
to interpret (compare runEmbedded
with finalToFinal
).
If you only need the power of embed
, then you should use Embed
instead.
Beware: Final
actions are interpreted as actions of the final monad,
and the effectful state visible to
withWeavingToFinal
/ withStrategicToFinal
/ interpretFinal
is that of all interpreters run in order to produce the final monad.
This means that any interpreter built using Final
will not
respect local/global state semantics based on the order of
interpreters run. You should signal interpreters that make use of
Final
by adding a -
suffix to the names of these.Final
State semantics of effects that are not interpreted in terms of the final monad will always appear local to effects that are interpreted in terms of the final monad.
State semantics between effects that are interpreted in terms of the final monad depend on the final monad. For example, if the final monad is a monad transformer stack, then state semantics will depend on the order monad transformers are stacked.
Since: polysemy-1.2.0.0
runFinal :: Monad m => Sem '[Final m] a -> m a #
Lower a Sem
containing only a single lifted, final Monad
into that
monad.
If you also need to process an
effect, use this together with
Embed
membedToFinal
.
Since: polysemy-1.2.0.0
async :: forall (r :: EffectRow) a. Member Async r => Sem r a -> Sem r (Async (Maybe a)) #
Run the given action asynchronously and return a thread handle.
await :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r a #
Wait for the thread referenced by the given handle to terminate.
cancel :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r () #
Cancel the thread referenced by the given handle.
sequenceConcurrently :: forall t (r :: EffectRow) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a)) #
Perform a sequence of effectful actions concurrently.
Since: polysemy-1.2.2.0
data Log (a :: Type -> Type) b #
The default high-level effect for simple text messages. To be used with the severity constructors:
import qualified Polysemy.Log as Log prog = do Log.debug "debugging…" Log.warn "warning!"
Interpreters should preprocess and relay the message to DataLog
.
Metadata wrapper for a log message.
type Logger = DataLog (LogEntry LogMessage) #
Alias for the logger with the default message type used by Log
.
data LogMessage #
User-specified part of the default logging data, consisting of a severity level like warning, error, debug, and a plain text message.
Instances
Show LogMessage | |
Defined in Polysemy.Log.Data.LogMessage showsPrec :: Int -> LogMessage -> ShowS # show :: LogMessage -> String # showList :: [LogMessage] -> ShowS # | |
Eq LogMessage | |
Defined in Polysemy.Log.Data.LogMessage (==) :: LogMessage -> LogMessage -> Bool # (/=) :: LogMessage -> LogMessage -> Bool # |
A log message's severity, or log level.
Instances
Enum Severity | |
Defined in Polysemy.Log.Data.Severity | |
Show Severity | |
Eq Severity | |
Ord Severity | |
Defined in Polysemy.Log.Data.Severity |
dataLog :: forall a (r :: EffectRow). Member (DataLog a) r => a -> Sem r () #
Schedule an arbitrary value for logging.
log :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Severity -> Text -> Sem r () #
Log a message with the given severity.
Basic Sem
constructor.
trace :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #
Log a message with the Trace
severity.
debug :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #
Log a message with the Debug
severity.
info :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #
Log a message with the Info
severity.
warn :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #
Log a message with the Warn
severity.
error :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #
Log a message with the Error
severity.
crit :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #
Log a message with the Crit
severity.
formatLogEntry :: LogEntry LogMessage -> Text #
Default formatter for the default message type.
setLogLevel :: forall (r :: EffectRow) a. Member (DataLog (LogEntry LogMessage)) r => Maybe Severity -> Sem r a -> Sem r a #
Set the minimum severity for messages to be handled, with Nothing
meaning no messages are logged.
setLogLevelWith :: forall msg (r :: EffectRow) a. Member (DataLog msg) r => (msg -> Severity) -> Maybe Severity -> Sem r a -> Sem r a #
Set the minimum severity for messages to be handled, with Nothing
meaning no messages are logged.
This can be used with arbitrary message types, using the ex
argument to extract the severity from the message.
data Embed (m :: Type -> Type) (z :: Type -> Type) a #
An effect which allows a regular Monad
m
into the Sem
ecosystem. Monadic actions in m
can be lifted into Sem
via
embed
.
For example, you can use this effect to lift IO
actions directly into
Sem
:
embed
(putStrLn "hello") ::Member
(Embed
IO) r =>Sem
r ()
That being said, you lose out on a significant amount of the benefits of
Sem
by using embed
directly in application code; doing
so will tie your application code directly to the underlying monad, and
prevent you from interpreting it differently. For best results, only use
Embed
in your effect interpreters.
Consider using trace
and traceToIO
as
a substitute for using putStrLn
directly.
Since: polysemy-1.0.0.0
embed :: forall m (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a #
Embed a monadic action m
in Sem
.
Since: polysemy-1.0.0.0
embedToFinal :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a #
runEmbedded :: forall m1 m2 (r :: EffectRow) a. Member (Embed m2) r => (forall x. m1 x -> m2 x) -> Sem (Embed m1 ': r) a -> Sem r a #
Given a natural transform from m1
to m2
run a Embed m1
effect by transforming it into a Embed m2
effect.
Since: polysemy-1.0.0.0
data Error e (m :: k -> Type) (a :: k) #
This effect abstracts the throwing and catching of errors, leaving
it up to the interpreter whether to use exceptions or monad transformers
like ExceptT
to perform the short-circuiting mechanism.
throw :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Sem r a #
Short-circuit the current program using the given error value.
catch :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> (e -> Sem r a) -> Sem r a #
Recover from an error that might have been thrown in the higher-order action given by the first argument by passing the error to the handler given by the second argument.
trap_ :: forall e a r. Sem r a -> Sem (Error e ': r) a -> Sem r a Source #
Like trap
, but the error is not passed to the handler.
embedRunExceptT :: forall e a r m. Member (Embed m) r => ExceptT e m a -> Sem r (Either e a) Source #
embedThrowExceptT :: forall e a r m. Member (Error e) r => Member (Embed m) r => ExceptT e m a -> Sem r a Source #
fromEither :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Either e a -> Sem r a #
fromEitherM :: forall e m (r :: EffectRow) a. (Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed m) r) => m (Either e a) -> Sem r a #
A combinator doing embed
and fromEither
at the same time. Useful for
interoperating with IO
.
Since: polysemy-0.5.1.0
fromException :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => IO a -> Sem r a #
fromExceptionVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => (exc -> err) -> IO a -> Sem r a #
Like fromException
, but with the ability to transform the exception
before turning it into an Error
.
note :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Maybe a -> Sem r a #
try :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r (Either e a) #
tryJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a) #
mapError :: forall e1 e2 (r :: EffectRow) a. Member (Error e2 :: (Type -> Type) -> Type -> Type) r => (e1 -> e2) -> Sem ((Error e1 :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Transform one Error
into another. This function can be used to aggregate
multiple errors into a single type.
Since: polysemy-1.0.0.0
onNothingM :: forall a m. Monad m => m a -> m (Maybe a) -> m a Source #
runError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a) #
asks :: forall i j (r :: EffectRow). Member (Reader i) r => (i -> j) -> Sem r j #
Apply a function to the environment and return the result.
inputToReader :: forall i (r :: EffectRow) a. Member (Reader i) r => Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
runReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem (Reader i ': r) a -> Sem r a #
Run a Reader
effect with a constant value.
data Resource (m :: Type -> Type) a #
An effect capable of providing bracket
semantics. Interpreters for this
will successfully run the deallocation action even in the presence of other
short-circuiting effects.
bracket :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #
Allocate a resource, use it, and clean it up afterwards.
bracketOnError :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #
Allocate a resource, use it, and clean it up afterwards if an error occurred.
:: forall (r :: EffectRow) a b. Member Resource r | |
=> Sem r a | computation to run first |
-> Sem r b | computation to run afterward (even if an exception was raised) |
-> Sem r a |
Like bracket
, but for the simple case of one computation to run
afterward.
Since: polysemy-0.4.0.0