effet-0.3.0.0: An Effect System based on Type Classes
Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Resource

Description

The resource effect allows a computation to allocate resources which are guaranteed to be released after their usage.

Synopsis

Tagged Resource Effect

class Monad m => Resource' tag m where Source #

An effect that allows a computation to allocate resources which are guaranteed to be released after their usage.

Methods

bracket' Source #

Arguments

:: m a

The computation which acquires the resource.

-> (a -> m c)

The computation which releases the resource.

-> (a -> m b)

The computation which uses the resource.

-> m b

The result of the computation which used the resource.

Acquire a resource, use it, and then release the resource after usage.

bracketOnError' Source #

Arguments

:: m a

The computation which acquires the resource.

-> (a -> m c)

The computation which releases the resource.

-> (a -> m b)

The computation which uses the resource.

-> m b

The result of the computation which used the resource.

Like bracket', but only performs the release computation if the usage computation throws an exception.

Instances

Instances details
MonadBaseControl IO m => Resource' (tag :: k) (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

bracket' :: LowerIO m a -> (a -> LowerIO m c) -> (a -> LowerIO m b) -> LowerIO m b Source #

bracketOnError' :: LowerIO m a -> (a -> LowerIO m c) -> (a -> LowerIO m b) -> LowerIO m b Source #

Handle (Resource' tag) t m => Resource' (tag :: k) (EachVia (Resource' tag ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

bracket' :: EachVia (Resource' tag ': effs) t m a -> (a -> EachVia (Resource' tag ': effs) t m c) -> (a -> EachVia (Resource' tag ': effs) t m b) -> EachVia (Resource' tag ': effs) t m b Source #

bracketOnError' :: EachVia (Resource' tag ': effs) t m a -> (a -> EachVia (Resource' tag ': effs) t m c) -> (a -> EachVia (Resource' tag ': effs) t m b) -> EachVia (Resource' tag ': effs) t m b Source #

Find (Resource' tag) effs t m => Resource' (tag :: k) (EachVia (other ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

bracket' :: EachVia (other ': effs) t m a -> (a -> EachVia (other ': effs) t m c) -> (a -> EachVia (other ': effs) t m b) -> EachVia (other ': effs) t m b Source #

bracketOnError' :: EachVia (other ': effs) t m a -> (a -> EachVia (other ': effs) t m c) -> (a -> EachVia (other ': effs) t m b) -> EachVia (other ': effs) t m b Source #

Control (Resource' tag) t m => Resource' (tag :: k) (EachVia ('[] :: [Effect]) t m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

bracket' :: EachVia '[] t m a -> (a -> EachVia '[] t m c) -> (a -> EachVia '[] t m b) -> EachVia '[] t m b Source #

bracketOnError' :: EachVia '[] t m a -> (a -> EachVia '[] t m c) -> (a -> EachVia '[] t m b) -> EachVia '[] t m b Source #

Resource' new m => Resource' (tag :: k2) (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

bracket' :: Tagger tag new m a -> (a -> Tagger tag new m c) -> (a -> Tagger tag new m b) -> Tagger tag new m b Source #

bracketOnError' :: Tagger tag new m a -> (a -> Tagger tag new m c) -> (a -> Tagger tag new m b) -> Tagger tag new m b Source #

Untagged Resource Effect

If you don't require disambiguation of multiple resource effects (i.e., you only have one resource effect in your monadic context), it is recommended to always use the untagged resource effect.

bracket :: Resource m => m a -> (a -> m c) -> (a -> m b) -> m b Source #

bracketOnError :: Resource m => m a -> (a -> m c) -> (a -> m b) -> m b Source #

Convenience Functions

If you don't require disambiguation of multiple resource effects (i.e., you only have one resource effect in your monadic context), it is recommended to always use the untagged functions.

finally' Source #

Arguments

:: forall tag m a b. Resource' tag m 
=> m a

The computation to run.

-> m b

The computation to run afterwards, even if the first computation throws an exception.

-> m a

The result of the first computation.

A simpler version of bracket' where one computation is guaranteed to run after another.

finally :: Resource m => m a -> m b -> m a Source #

The untagged version of finally'.

onException' Source #

Arguments

:: forall tag m a b. Resource' tag m 
=> m a

The computation to run.

-> m b

The computation to run afterwards, only if the first computation throws an exception.

-> m a

The result of the first computation.

A simpler version of bracketOnError' where one computation is guaranteed to run after another in case the first computation throws an exception.

onException :: Resource m => m a -> m b -> m a Source #

The untagged version of onException'.

Interpretations

data LowerIO m a Source #

The IO-based interpreter of the resource effect. This type implements the Resource' 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.

Instances

Instances details
MonadBaseControl IO m => Resource' (tag :: k) (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

bracket' :: LowerIO m a -> (a -> LowerIO m c) -> (a -> LowerIO m b) -> LowerIO m b Source #

bracketOnError' :: LowerIO m a -> (a -> LowerIO m c) -> (a -> LowerIO m b) -> LowerIO m b Source #

MonadBase b m => MonadBase b (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

liftBase :: b α -> LowerIO m α #

MonadBaseControl b m => MonadBaseControl b (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Associated Types

type StM (LowerIO m) a #

Methods

liftBaseWith :: (RunInBase (LowerIO m) b -> b a) -> LowerIO m a #

restoreM :: StM (LowerIO m) a -> LowerIO m a #

MonadTrans (LowerIO :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

lift :: Monad m => m a -> LowerIO m a #

MonadTransControl (LowerIO :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Resource

Associated Types

type StT LowerIO a #

Methods

liftWith :: Monad m => (Run LowerIO -> m a) -> LowerIO m a #

restoreT :: Monad m => m (StT LowerIO a) -> LowerIO m a #

Monad m => Monad (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

(>>=) :: LowerIO m a -> (a -> LowerIO m b) -> LowerIO m b #

(>>) :: LowerIO m a -> LowerIO m b -> LowerIO m b #

return :: a -> LowerIO m a #

Functor m => Functor (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

fmap :: (a -> b) -> LowerIO m a -> LowerIO m b #

(<$) :: a -> LowerIO m b -> LowerIO m a #

Applicative m => Applicative (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

pure :: a -> LowerIO m a #

(<*>) :: LowerIO m (a -> b) -> LowerIO m a -> LowerIO m b #

liftA2 :: (a -> b -> c) -> LowerIO m a -> LowerIO m b -> LowerIO m c #

(*>) :: LowerIO m a -> LowerIO m b -> LowerIO m b #

(<*) :: LowerIO m a -> LowerIO m b -> LowerIO m a #

MonadIO m => MonadIO (LowerIO m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

liftIO :: IO a -> LowerIO m a #

type StT (LowerIO :: (Type -> Type) -> Type -> Type) a Source # 
Instance details

Defined in Control.Effect.Resource

type StT (LowerIO :: (Type -> Type) -> Type -> Type) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type StM (LowerIO m) a Source # 
Instance details

Defined in Control.Effect.Resource

type StM (LowerIO m) a = StM m a

runResourceIO' :: (Resource' tag `Via` LowerIO) m a -> m a Source #

Runs the resource effect using bracket.

runResourceIO :: (Resource `Via` LowerIO) m a -> m a Source #

The untagged version of runResourceIO'.

Tagging and Untagging

Conversion functions between the tagged and untagged resource effect, usually used in combination with type applications, like:

    tagResource' @"newTag" program
    retagResource' @"oldTag" @"newTag" program
    untagResource' @"erasedTag" program

tagResource' :: forall new m a. Via (Resource' G) (Tagger G new) m a -> m a Source #

retagResource' :: forall tag new m a. Via (Resource' tag) (Tagger tag new) m a -> m a Source #

untagResource' :: forall tag m a. Via (Resource' tag) (Tagger tag G) m a -> m a Source #