Copyright | (c) Michael Szvetits 2020 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | typedbyte@qualified.name |
Stability | stable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
The managed effect allows a computation to allocate resources which are
guaranteed to be released after the end of the computation. This effect
provides a monadic interface for managing one or more long-living
resources in a more readable way than nesting bracket
-style
operations of the Control.Effect.Resource effect.
Synopsis
- class MonadIO m => Managed' tag m where
- manage' :: m a -> (a -> m b) -> m a
- type Managed = Managed' G
- manage :: Managed m => m a -> (a -> m b) -> m a
- data Bracket n m a
- runManaged' :: forall tag m a. MonadBaseControl IO m => (Managed' tag `Via` Bracket m) m a -> m a
- runManaged :: MonadBaseControl IO m => (Managed `Via` Bracket m) m a -> m a
- tagManaged' :: forall new m a. (Managed' G `Via` Tagger G new) m a -> m a
- retagManaged' :: forall tag new m a. (Managed' tag `Via` Tagger tag new) m a -> m a
- untagManaged' :: forall tag m a. (Managed' tag `Via` Tagger tag G) m a -> m a
Tagged Managed Effect
class MonadIO m => Managed' tag m where Source #
An effect that allows a computation to allocate resources which are guaranteed to be released after the computation.
Since: 0.4.0.0
:: m a | The computation which acquires the resource. |
-> (a -> m b) | The computation which releases the resource. |
-> m a | The acquired resource. |
Acquire a resource by specifying an acquisition action and a release action to be used for cleanup after the computation.
Since: 0.4.0.0
Instances
(MonadBase IO m, MonadIO m) => Managed' (tag :: k) (Bracket m m) Source # | |
Handle '[MonadIO] (Managed' tag) others t m => Managed' (tag :: k) (EachVia (Managed' tag ': others) t m) Source # | |
Find '[MonadIO] (Managed' tag) other effs t m => Managed' (tag :: k) (EachVia (other ': effs) t m) Source # | |
Control '[MonadIO] (Managed' tag) t m => Managed' (tag :: k) (EachVia ('[] :: [Effect]) t m) Source # | |
Managed' new m => Managed' (tag :: k2) (Tagger tag new m) Source # | |
Untagged Managed Effect
If you don't require disambiguation of multiple managed effects (i.e., you only have one managed effect in your monadic context), it is recommended to always use the untagged managed effect.
Interpretations
The bracket-based interpreter of the managed effect. This type implements
the Managed'
type class by using bracket
, thus requiring IO
at the
bottom of the monad transformer stack.
When interpreting the effect, you usually don't interact with this type directly, but instead use one of its corresponding interpretation functions.
Since: 0.4.0.0
Instances
(MonadBase IO m, MonadIO m) => Managed' (tag :: k) (Bracket m m) Source # | |
MonadBase b m => MonadBase b (Bracket n m) Source # | |
Defined in Control.Effect.Managed | |
MonadBaseControl b m => MonadBaseControl b (Bracket n m) Source # | |
MonadTrans (Bracket n) Source # | |
Defined in Control.Effect.Managed | |
MonadTransControl (Bracket n) Source # | |
Monad m => Monad (Bracket n m) Source # | |
Functor m => Functor (Bracket n m) Source # | |
Applicative m => Applicative (Bracket n m) Source # | |
Defined in Control.Effect.Managed | |
MonadIO m => MonadIO (Bracket n m) Source # | |
Defined in Control.Effect.Managed | |
type StT (Bracket n) a Source # | |
type StM (Bracket n m) a Source # | |
runManaged' :: forall tag m a. MonadBaseControl IO m => (Managed' tag `Via` Bracket m) m a -> m a Source #
Runs the managed effect using bracket
.
Since: 0.4.0.0
runManaged :: MonadBaseControl IO m => (Managed `Via` Bracket m) m a -> m a Source #
The untagged version of runManaged'
.
Since: 0.4.0.0
Tagging and Untagging
Conversion functions between the tagged and untagged managed effect, usually used in combination with type applications, like:
tagManaged'
@"newTag" programretagManaged'
@"oldTag" @"newTag" programuntagManaged'
@"erasedTag" program