monadology-0.3: The best ideas in monad-related classes and types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Ology.Specific.LifecycleT

Synopsis

Documentation

newtype LifecycleT m a Source #

This is for managing the automatic closing of opened resources.

Constructors

MkLifecycleT 

Fields

Instances

Instances details
TransConstraint MonadFail (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadFail m => Dict (MonadFail (LifecycleT m)) Source #

TransConstraint MonadFix (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadFix m => Dict (MonadFix (LifecycleT m)) Source #

TransConstraint MonadIO (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadIO m => Dict (MonadIO (LifecycleT m)) Source #

TransConstraint Applicative (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). Applicative m => Dict (Applicative (LifecycleT m)) Source #

TransConstraint Functor (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). Functor m => Dict (Functor (LifecycleT m)) Source #

TransConstraint Monad (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). Monad m => Dict (Monad (LifecycleT m)) Source #

TransConstraint MonadException (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

MonadCatch e m => MonadCatch e (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

catch :: LifecycleT m a -> (e -> LifecycleT m a) -> LifecycleT m a Source #

MonadThrow e m => MonadThrow e (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

throw :: e -> LifecycleT m a Source #

MonadTransHoist (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hoist :: forall (m1 :: Type -> Type) (m2 :: Type -> Type). (Monad m1, Monad m2) => (m1 --> m2) -> LifecycleT m1 --> LifecycleT m2 Source #

MonadTransTunnel (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Associated Types

type Tunnel LifecycleT :: Type -> Type Source #

Methods

tunnel :: Monad m => ((forall (m1 :: Type -> Type) a. Monad m1 => LifecycleT m1 a -> m1 (Tunnel LifecycleT a)) -> m (Tunnel LifecycleT r)) -> LifecycleT m r Source #

MonadTransUnlift (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

MonadTrans (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

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

TransConstraint (MonadCatch e) (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadCatch e m => Dict (MonadCatch e (LifecycleT m)) Source #

TransConstraint (MonadThrow e) (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadThrow e m => Dict (MonadThrow e (LifecycleT m)) Source #

MonadFail m => MonadFail (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

fail :: String -> LifecycleT m a #

MonadFix m => MonadFix (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

mfix :: (a -> LifecycleT m a) -> LifecycleT m a #

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

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

liftIO :: IO a -> LifecycleT m a #

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

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

pure :: a -> LifecycleT m a #

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

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

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

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

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

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

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

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

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

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

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

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

return :: a -> LifecycleT m a #

MonadException m => MonadException (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Associated Types

type Exc (LifecycleT m) Source #

type Tunnel (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

type Exc (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

type Exc (LifecycleT m) = Exc m

type Lifecycle = LifecycleT IO Source #

This is the expected most common use.

runLifecycle :: forall m. (MonadException m, MonadTunnelIO m) => LifecycleT m --> m Source #

Run the lifecycle, then close all resources in reverse order they were opened.

lifecycleOnCloseIO :: MonadIO m => IO () -> LifecycleT m () Source #

Add a closing action.

lifecycleOnClose :: MonadAskUnliftIO m => m () -> LifecycleT m () Source #

Add a closing action.

lifecycleGetCloser :: forall m a. MonadIO m => LifecycleT m a -> LifecycleT m (a, IO ()) Source #

Runs the given lifecycle, returning a closer. This is how you close things out of order.

The closer is an idempotent action that will close the lifecycle only if it hasn't already been closed. The closer will also be run as the closer of the resulting lifecycle.

forkLifecycle :: MonadUnliftIO m => m () -> LifecycleT m ThreadId Source #

Fork a thread that will complete in this lifecycle. Closing will wait for the thread to finish.

lifecycleMonitor :: MonadIO m => LifecycleT m (IO Bool) Source #

Returned action returns True if still alive, False if closed.

With

type With (m :: k -> Type) (t :: Type) = forall (r :: k). (t -> m r) -> m r Source #

A type synoynm for a common pattern for closing opened resources, e.g. withFile, withBinaryFile, etc.

withLifecycle :: forall m a. (MonadException m, MonadTunnelIO m) => LifecycleT m a -> With m a Source #

Convert a lifecycle to a function that uses the "with" pattern.

lifecycleWith :: (MonadCoroutine m, MonadAskUnliftIO m) => With m t -> LifecycleT m t Source #

Convert a function that uses the "with" pattern to a lifecycle.

LifeState

data LifeState Source #

This represents all the actions that need to be done when closing the lifecycle.

getLifeState :: forall m a. MonadIO m => LifecycleT m a -> m (a, LifeState) Source #

Runs a lifecycle, but instead of running the closing actions, return them as a LifeState.