simple-effects-0.13.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Resource

Description

Provides the Bracket effect for handing resource acquisition and safe cleanup.

Synopsis

Documentation

class Unexceptional (t :: (* -> *) -> * -> *) Source #

Class of transformers that don't introduce additional exit points to a computation.

Examples: StateT s, ReaderT e, IdentityT

Counter-examples: ExceptT e, ErrorT e, MaybeT, ListT

Instances
UnexceptionalError t => Unexceptional t Source #

Warn about unknown transformers with a type error.

Instance details

Defined in Control.Effects.Resource

Unexceptional (WriterT s) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (StateT s) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (StateT s) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (WriterT s) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (ReaderT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (RuntimeImplemented e) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (RWST r w s) Source # 
Instance details

Defined in Control.Effects.Resource

Unexceptional (RWST r w s) Source # 
Instance details

Defined in Control.Effects.Resource

newtype Bracket m Source #

Constructors

BracketMethods 

Fields

  • _bracket :: forall resource result cleanupRes. m resource -> (resource -> Maybe result -> m cleanupRes) -> (resource -> m result) -> m result
     
Instances
Effect Bracket Source # 
Instance details

Defined in Control.Effects.Resource

Methods

liftThrough :: (CanLift Bracket t, Monad m, Monad (t m)) => Bracket m -> Bracket (t m) Source #

mergeContext :: Monad m => m (Bracket m) -> Bracket m Source #

MonadEffect Bracket IO Source #

Use bracketing and masking for IO exceptions

Instance details

Defined in Control.Effects.Resource

MonadEffect Bracket Identity Source #

Identity can't throw or acquire in a meaningful way

Instance details

Defined in Control.Effects.Resource

MonadEffect Bracket m => MonadEffect Bracket (MaybeT m) Source # 
Instance details

Defined in Control.Effects.Resource

Methods

effect :: Bracket (MaybeT m) Source #

MonadEffect Bracket m => MonadEffect Bracket (ExceptT e m) Source #

Source: http://hackage.haskell.org/package/exceptions-0.10.0/docs/src/Control-Monad-Catch.html#line-674

Instance details

Defined in Control.Effects.Resource

Methods

effect :: Bracket (ExceptT e m) Source #

type CanLift Bracket t Source # 
Instance details

Defined in Control.Effects.Resource

type ExtraConstraint Bracket m Source # 
Instance details

Defined in Control.Effects.Resource

bracket :: MonadEffect Bracket m => m resource -> (resource -> Maybe result -> m cleanupRes) -> (resource -> m result) -> m result Source #

bracket acq cln use acquires the resource by running acq. If this computation aborts, the exception won't be handled and no cleanup will be performed since the resource wasn't acquired. Then use is called with the resource. Regardless if use threw an exception/aborted or finished normally, cln is called with the resource and possibly with the result of use (if it didn't abort). If there was an exception, it's rethrown: bracket is not meant to be used for exception handling.

An exception in this context is anything from actual IO exceptions for pure ones "thrown" by ExceptT or MaybeT. In case of IO, the resource acquisition and cleanup are masked from async exceptions.

Since this function can be used on almost any transformer stack, care needs to be taken that all the transformers that can throw exceptions get handled. This is why the effect isn't implicitly lifted through unknown transformers, only though ones that are instances of Unexceptional. If your transformer doesn't introduce new exit points, give it an instance of that class. There are no methods to implement.

bracket_ :: MonadEffect Bracket m => m resource -> m cleanupRes -> m result -> m result Source #

A simpler version of bracket that doesn't use the results of the parameters.

type family UnexceptionalError (t :: (* -> *) -> * -> *) :: Constraint where ... Source #

Equations

UnexceptionalError ListT = TypeError ((((Text "ListT is an exceptional transformer since it can produce zero results. The reason why it isn't handled like ExceptT or MaybeT is because it's unclear what the behavior should be:" :$$: Text "Firstly, it might acquire more than one resource. Is that expected?") :$$: Text "More importantly, it may produce more than one result of using a single resource. How many times should the cleanup function be called then?") :$$: Text "Also, should all the resources be acquired at the beginning and released at the end, or should they be processed one by one?") :$$: Text "If you need this instance, please let me know what you think should happen.") 
UnexceptionalError t = TypeError ((((Text "The Bracket effect doesn't know about the transformer " :<>: ShowType t) :$$: Text "While the effect can be used with any transformer that has a RunnableTrans instance, it's dangerous to do so implicitly because the transformer might introduce an additional exit point to the computation (like IO, MaybeT, ExceptT and friends do)") :$$: Text "If you're sure that it doesn't, give it an 'Unexceptional' instance:") :$$: ((Text "instance Unexceptional (" :<>: ShowType t) :<>: Text ")"))