lazy-async-1.0.0.1: Asynchronous actions that don't start right away
Safe HaskellSafe
LanguageHaskell2010

LazyAsync

Description

What is this — A LazyAsync is an action that doesn't start right away. When it does run, it runs in a separate thread.

How to get one — The lazyAsync function makes a LazyAsync available within a ContT context because it ensures the asynchronous action is cancelled when the continuation ends, to avoid accidentally leaving any unneeded threads running in the background.

How to use it — You can incite a LazyAsync to begin by using 🚀 start, and then you can use ⏸️ wait to block until it completes. There is also 🚀⏸️ startWait, which does both.

If the only thing you ever do with your LazyAsyncs is startWait on them, then you may consider using memoize instead, which does not require interacting with the LazyAsync type at all.

Synopsis

LazyAsync

data LazyAsync a Source #

An asynchronous action that does not start right away

Instances

Instances details
Functor LazyAsync Source # 
Instance details

Defined in LazyAsync.Types.LazyAsync

Methods

fmap :: (a -> b) -> LazyAsync a -> LazyAsync b #

(<$) :: a -> LazyAsync b -> LazyAsync a #

Applicative LazyAsync Source #

🌈 <*> is equivalent to apply

Instance details

Defined in LazyAsync.Orphans

Methods

pure :: a -> LazyAsync a #

(<*>) :: LazyAsync (a -> b) -> LazyAsync a -> LazyAsync b #

liftA2 :: (a -> b -> c) -> LazyAsync a -> LazyAsync b -> LazyAsync c #

(*>) :: LazyAsync a -> LazyAsync b -> LazyAsync b #

(<*) :: LazyAsync a -> LazyAsync b -> LazyAsync a #

Alternative LazyAsync Source #

🌈 <|> is equivalent to choose

Instance details

Defined in LazyAsync.Orphans

Methods

empty :: LazyAsync a #

(<|>) :: LazyAsync a -> LazyAsync a -> LazyAsync a #

some :: LazyAsync a -> LazyAsync [a] #

many :: LazyAsync a -> LazyAsync [a] #

Spawning

lazyAsync Source #

Arguments

:: MonadBaseControl IO m 
=> m a

Action

-> ContT r m (LazyAsync (StM m a)) 

Creates a situation wherein:

  • The action shall begin running only once it is needed (that is, until prompted by start)
  • The action shall run asynchronously (other than where it is waited upon)
  • The action shall run at most once
  • The action shall run only within the continuation (when the continuation ends, the action is stopped)

Getting results

startWait :: (MonadBaseControl base m, MonadIO base) => LazyAsync (StM m a) -> m a Source #

🚀 Starts an asynchronous action, ⏸️ waits for it to complete, and ✅ returns its value

💣 If the action throws an exception, then the exception is re-thrown

🌈 (startWait x) is equivalent to (start x *> wait x)

Combining actions

apply Source #

Arguments

:: LazyAsync (a -> b)

Left part

-> LazyAsync a

Right part

-> LazyAsync b

Conjunction

Conjunctively combines the results of two LazyAsyncs

🚀 start starts both parts immediately

⏸️ wait returns a Success result after both parts complete successfully. As soon as one part fails, the whole conjunction fails immediately (but any Incomplete part keeps running in the background)

🕵️ poll returns Failure if either part has failed; otherwise Incomplete if either part has not finished; otherwise Success

💣 The wait and poll operations disclose the leftmost exception of the parts that have failed so far, which may not be consistent over time

🌈 apply is equivalent to (merge applyStatus)

choose Source #

Arguments

:: LazyAsync a

Left part

-> LazyAsync a

Right part

-> LazyAsync a

Disjunction

Disjunctively combines the results of two LazyAsyncs

🚀 start starts both parts immediately

⏸️ wait returns a Success result after either part completes successfully. As soon as one part succeeds, the whole disjunction succeeds immediately (but any Incomplete part keeps running in the background)

🕵️ poll returns Success if either part has succeeded; otherwise Incomplete if either part has not finished; otherwise Failure

✅ The wait and poll operations disclose the leftmost result of the parts that have succeeded so far, which may not be consistent over time

🌈 choose is equivalent to (merge chooseStatus)

merge Source #

Arguments

:: (Status a -> Status b -> Status c)

Status merge function

-> LazyAsync a -> LazyAsync b -> LazyAsync c 

A combination of two LazyAsyncs, where the Status of the combination is a function of the statuses of each of its parts

🚀 start starts both parts immediately

The behavior of 🕵️ poll and 💣 wait is determined by the status merge function

Catching (Outcome)

startWaitCatch :: (MonadBaseControl base m, MonadIO base) => LazyAsync (StM m a) -> m (Outcome a) Source #

🚀 Starts an asynchronous action, ⏸️ waits for it to complete, and ✅ returns its value

💣 If the action throws an exception, then the exception is returned

🌈 (startWaitCatch x) is equivalent to (start x *> waitCatch x)

data Outcome a Source #

The result of a LazyAsync that is Done running

Obtained using waitCatch

Constructors

Failure SomeException

💣 The LazyAsync action threw an exception

Success a

✅ The LazyAsync action completed normally

Instances

Instances details
Functor Outcome Source # 
Instance details

Defined in LazyAsync.Types.Outcome

Methods

fmap :: (a -> b) -> Outcome a -> Outcome b #

(<$) :: a -> Outcome b -> Outcome a #

Applicative Outcome Source #

🌈 <*> is equivalent to applyOutcome

Instance details

Defined in LazyAsync.Orphans

Methods

pure :: a -> Outcome a #

(<*>) :: Outcome (a -> b) -> Outcome a -> Outcome b #

liftA2 :: (a -> b -> c) -> Outcome a -> Outcome b -> Outcome c #

(*>) :: Outcome a -> Outcome b -> Outcome b #

(<*) :: Outcome a -> Outcome b -> Outcome a #

Foldable Outcome Source # 
Instance details

Defined in LazyAsync.Types.Outcome

Methods

fold :: Monoid m => Outcome m -> m #

foldMap :: Monoid m => (a -> m) -> Outcome a -> m #

foldMap' :: Monoid m => (a -> m) -> Outcome a -> m #

foldr :: (a -> b -> b) -> b -> Outcome a -> b #

foldr' :: (a -> b -> b) -> b -> Outcome a -> b #

foldl :: (b -> a -> b) -> b -> Outcome a -> b #

foldl' :: (b -> a -> b) -> b -> Outcome a -> b #

foldr1 :: (a -> a -> a) -> Outcome a -> a #

foldl1 :: (a -> a -> a) -> Outcome a -> a #

toList :: Outcome a -> [a] #

null :: Outcome a -> Bool #

length :: Outcome a -> Int #

elem :: Eq a => a -> Outcome a -> Bool #

maximum :: Ord a => Outcome a -> a #

minimum :: Ord a => Outcome a -> a #

sum :: Num a => Outcome a -> a #

product :: Num a => Outcome a -> a #

Traversable Outcome Source # 
Instance details

Defined in LazyAsync.Types.Outcome

Methods

traverse :: Applicative f => (a -> f b) -> Outcome a -> f (Outcome b) #

sequenceA :: Applicative f => Outcome (f a) -> f (Outcome a) #

mapM :: Monad m => (a -> m b) -> Outcome a -> m (Outcome b) #

sequence :: Monad m => Outcome (m a) -> m (Outcome a) #

Alternative Outcome Source #

🌈 <|> is equivalent to chooseOutcome

Instance details

Defined in LazyAsync.Orphans

Methods

empty :: Outcome a #

(<|>) :: Outcome a -> Outcome a -> Outcome a #

some :: Outcome a -> Outcome [a] #

many :: Outcome a -> Outcome [a] #

Show a => Show (Outcome a) Source # 
Instance details

Defined in LazyAsync.Types.Outcome

Methods

showsPrec :: Int -> Outcome a -> ShowS #

show :: Outcome a -> String #

showList :: [Outcome a] -> ShowS #

applyOutcome :: Outcome (a -> b) -> Outcome a -> Outcome b Source #

Behaves the same as <*> for Either, halting at the leftmost Failure

chooseOutcome :: Outcome a -> Outcome a -> Outcome a Source #

Behaves the same as <|> for Either, returning the leftmost Success

Polling (Status)

poll :: (MonadBaseControl base m, MonadIO base) => LazyAsync (StM m a) -> m (Status a) Source #

🕵️ Checks whether an asynchronous action has completed yet

🛑 Does not start the action

data Status a Source #

Whether a LazyAsync action has completed yet, and, if so, what it produced

Obtained using poll

Constructors

Incomplete

⏳ The LazyAsync action has not finished (and might not have even started yet)

Done (Outcome a)

⌛ The LazyAsync action has ended, either by ✅ returning normally or by 💣 throwing an exception

Instances

Instances details
Functor Status Source # 
Instance details

Defined in LazyAsync.Types.Status

Methods

fmap :: (a -> b) -> Status a -> Status b #

(<$) :: a -> Status b -> Status a #

Applicative Status Source #

🌈 <*> is equivalent to applyStatus

Instance details

Defined in LazyAsync.Orphans

Methods

pure :: a -> Status a #

(<*>) :: Status (a -> b) -> Status a -> Status b #

liftA2 :: (a -> b -> c) -> Status a -> Status b -> Status c #

(*>) :: Status a -> Status b -> Status b #

(<*) :: Status a -> Status b -> Status a #

Foldable Status Source # 
Instance details

Defined in LazyAsync.Types.Status

Methods

fold :: Monoid m => Status m -> m #

foldMap :: Monoid m => (a -> m) -> Status a -> m #

foldMap' :: Monoid m => (a -> m) -> Status a -> m #

foldr :: (a -> b -> b) -> b -> Status a -> b #

foldr' :: (a -> b -> b) -> b -> Status a -> b #

foldl :: (b -> a -> b) -> b -> Status a -> b #

foldl' :: (b -> a -> b) -> b -> Status a -> b #

foldr1 :: (a -> a -> a) -> Status a -> a #

foldl1 :: (a -> a -> a) -> Status a -> a #

toList :: Status a -> [a] #

null :: Status a -> Bool #

length :: Status a -> Int #

elem :: Eq a => a -> Status a -> Bool #

maximum :: Ord a => Status a -> a #

minimum :: Ord a => Status a -> a #

sum :: Num a => Status a -> a #

product :: Num a => Status a -> a #

Traversable Status Source # 
Instance details

Defined in LazyAsync.Types.Status

Methods

traverse :: Applicative f => (a -> f b) -> Status a -> f (Status b) #

sequenceA :: Applicative f => Status (f a) -> f (Status a) #

mapM :: Monad m => (a -> m b) -> Status a -> m (Status b) #

sequence :: Monad m => Status (m a) -> m (Status a) #

Alternative Status Source #

🌈 <|> is equivalent to chooseStatus

Instance details

Defined in LazyAsync.Orphans

Methods

empty :: Status a #

(<|>) :: Status a -> Status a -> Status a #

some :: Status a -> Status [a] #

many :: Status a -> Status [a] #

Show a => Show (Status a) Source # 
Instance details

Defined in LazyAsync.Types.Status

Methods

showsPrec :: Int -> Status a -> ShowS #

show :: Status a -> String #

showList :: [Status a] -> ShowS #

applyStatus :: Status (a -> b) -> Status a -> Status b Source #

Combines two LazyAsync statuses to produce the status of their conjunction

💣 Returns the leftmost Failure, if there is one

⏳ Otherwise, if any part of a conjunction is Incomplete, then the whole thing evaluates to Incomplete

✅ Only when all parts have completed as Success does the whole succeed

For example, applyStatus Incomplete (Failure e) = Failure e

chooseStatus :: Status a -> Status a -> Status a Source #

Combines two LazyAsync statuses to produce the status of their disjunction

✅ Returns the leftmost Success, if there is one

⏳ Otherwise, if any part of a disjunction is Incomplete, then the whole thing evaluates to Incomplete

💣 Only when all parts have completed as Failure does the whole fail

Starting manually

start :: (MonadBase base m, MonadIO base) => LazyAsync a -> m () Source #

🚀 Starts an asynchronous action, if it has not already been started

wait :: (MonadBaseControl base m, MonadIO base) => LazyAsync (StM m a) -> m a Source #

⏸️ Waits for the action to complete and ✅ returns its value

💣 If the action throws an exception, then the exception is re-thrown

🛑 Does not start the action

waitCatch :: (MonadBaseControl base m, MonadIO base) => LazyAsync (StM m a) -> m (Outcome a) Source #

⏸️ Waits for the action to complete and ✅ returns its value

💣 If the action throws an exception, then the exception is returned

🛑 Does not start the action

Manual cancellation

acquire Source #

Arguments

:: MonadBaseControl IO m 
=> m a

Action

-> m (Resource m (LazyAsync (StM m a))) 

Like lazyAsync, but does not automatically stop the action

The returned Resource includes the desired LazyAsync (the resource), as well as a release action that brings it to a halt. If the action is not yet started, release prevents it from ever starting. If the action is in progress, release throws an async exception to stop it. If the action is completed, release has no effect.

A LazyAsync represents a background thread which may be utilizing time and space. A running thread is not automatically reaped by the garbage collector, so one should take care to eventually release every LazyAsync resource to avoid accidentally leaving unwanted LazyAsyncs running.

data Resource m a Source #

A resource and an action that releases it

A resource is something that can be acquired and then released, where releasing an object once it is no longer needed is important because the supply is exhaustible.

Constructors

Resource 

Fields

Instances

Instances details
Functor (Resource m) Source # 
Instance details

Defined in LazyAsync.Types.Resource

Methods

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

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

Transactions

pollSTM :: LazyAsync a -> STM (Status a) Source #

Akin to poll

startSTM :: LazyAsync a -> STM () Source #

Akin to start

Memoization

memoize Source #

Arguments

:: MonadBaseControl IO m 
=> m a

Action

-> ContT r m (m a)

Memoized action, in a continuation

Creates a situation wherein:

  • The action shall begin running only once the memoized action runs
  • The action shall run at most once
  • The action shall run only within the continuation (when the continuation ends, the action is stopped)

Bulk operations

If you have a list (or other Traversable) of actions, the "many" functions (manyLazyAsyncs and memoizeMany) can create a thread for each action in the list.

If you have a big recordful of actions and feel like getting real fancy, try making your datatype "higher-kinded" and using memoizeRank2 to automatically create a bunch of threads at once. You'll need the rank2classes package; see Rank2 and Rank2.TH.

manyLazyAsyncs :: (MonadBaseControl IO m, Traversable t) => t (m a) -> ContT r m (t (LazyAsync (StM m a))) Source #

🌈 manyLazyAsyncs is equivalent to (traverse lazyAsync)

memoizeMany :: (MonadBaseControl IO m, Traversable t) => t (m a) -> ContT r m (t (m a)) Source #

🌈 memoizeMany is equivalent to (traverse memoize)

memoizeRank2 :: (MonadBaseControl IO m, Traversable t) => t m -> ContT r m (t m) Source #

🌈 memoizeRank2 is equivalent to (traverse memoize)

Notes on monads

Working with ContT — Compose actions within the ContT monadic context, and apply evalContT at the top to run the continuation. You can also apply runContT to a ContT action to convert it to a "continuation-passing style" higher-order function.

Working with MonadBaseControl and StM — Most of the functions in this module are generalized using MonadBaseControl, which allows you to work in monads other than IO (to see an example of this, see the test suite for this package, which creates LazyAsyncs in Hedgehog's PropertyT context). StM is a type family which often "disappears" (that is, StM m a ~ a for many m).

Unlifted variants

If you are uninterested in monad transformers, you may prefer the functions in this section.

  • All of the m type variables are specialized to IO, thus eliminating MonadBase, MonadBaseControl, MonadIO, and StM from the types
  • Async spawning is done with explicit continuation passing instead of ContT actions
  • Traversable-constrained type constructors are specialized to []

withLazyAsyncIO :: IO a -> (LazyAsync a -> IO b) -> IO b Source #

Akin to lazyAsync

pollIO :: LazyAsync a -> IO (Status a) Source #

Akin to poll

startIO :: LazyAsync a -> IO () Source #

Akin to start

waitIO :: LazyAsync a -> IO a Source #

Akin to wait

withLazyAsyncListIO :: [IO a] -> ([LazyAsync a] -> IO b) -> IO b Source #

withMemoizedIO :: IO a -> (IO a -> IO b) -> IO b Source #

Akin to memoize

withMemoizedListIO :: [IO a] -> ([IO a] -> IO b) -> IO b Source #

Akin to memoizeMany

Re-exports

Some key monad lifting concepts from other packages are re-exported from this module.

base (Control.Monad.IO.Class)

transformers (Control.Monad.Trans.Cont)

monad-base (Control.Monad.Base)

monad-control (Control.Monad.Trans.Control)

newtype ContT (r :: k) (m :: k -> Type) a #

The continuation monad transformer. Can be used to add continuation handling to any type constructor: the Monad instance and most of the operations do not require m to be a monad.

ContT is not a functor on the category of monads, and many operations cannot be lifted through it.

Constructors

ContT 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (ContT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ContT r m α #

MonadTrans (ContT r) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

lift :: Monad m => m a -> ContT r m a #

Monad (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

(>>=) :: ContT r m a -> (a -> ContT r m b) -> ContT r m b #

(>>) :: ContT r m a -> ContT r m b -> ContT r m b #

return :: a -> ContT r m a #

Functor (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

fmap :: (a -> b) -> ContT r m a -> ContT r m b #

(<$) :: a -> ContT r m b -> ContT r m a #

MonadFail m => MonadFail (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

fail :: String -> ContT r m a #

Applicative (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

pure :: a -> ContT r m a #

(<*>) :: ContT r m (a -> b) -> ContT r m a -> ContT r m b #

liftA2 :: (a -> b -> c) -> ContT r m a -> ContT r m b -> ContT r m c #

(*>) :: ContT r m a -> ContT r m b -> ContT r m b #

(<*) :: ContT r m a -> ContT r m b -> ContT r m a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a #

evalContT :: Monad m => ContT r m r -> m r #

The result of running a CPS computation with return as the final continuation.

class MonadBase b m => MonadBaseControl (b :: Type -> Type) (m :: Type -> Type) | m -> b where #

Writing instances

The usual way to write a MonadBaseControl instance for a transformer stack over a base monad B is to write an instance MonadBaseControl B B for the base monad, and MonadTransControl T instances for every transformer T. Instances for MonadBaseControl are then simply implemented using ComposeSt, defaultLiftBaseWith, defaultRestoreM.

Associated Types

type StM (m :: Type -> Type) a #

Monadic state that m adds to the base monad b.

For all base (non-transformed) monads, StM m a ~ a:

StM IO         a ~ a
StM Maybe      a ~ a
StM (Either e) a ~ a
StM []         a ~ a
StM ((->) r)   a ~ a
StM Identity   a ~ a
StM STM        a ~ a
StM (ST s)     a ~ a

If m is a transformed monad, m ~ t b, StM is the monadic state of the transformer t (given by its StT from MonadTransControl). For a transformer stack, StM is defined recursively:

StM (IdentityT  m) a ~ ComposeSt IdentityT m a ~ StM m a
StM (MaybeT     m) a ~ ComposeSt MaybeT    m a ~ StM m (Maybe a)
StM (ErrorT e   m) a ~ ComposeSt ErrorT    m a ~ Error e => StM m (Either e a)
StM (ExceptT e  m) a ~ ComposeSt ExceptT   m a ~ StM m (Either e a)
StM (ListT      m) a ~ ComposeSt ListT     m a ~ StM m [a]
StM (ReaderT r  m) a ~ ComposeSt ReaderT   m a ~ StM m a
StM (StateT s   m) a ~ ComposeSt StateT    m a ~ StM m (a, s)
StM (WriterT w  m) a ~ ComposeSt WriterT   m a ~ Monoid w => StM m (a, w)
StM (RWST r w s m) a ~ ComposeSt RWST      m a ~ Monoid w => StM m (a, s, w)

Methods

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

liftBaseWith is similar to liftIO and liftBase in that it lifts a base computation to the constructed monad.

Instances should satisfy similar laws as the MonadIO and MonadBase laws:

liftBaseWith (\_ -> return a) = return a
liftBaseWith (\_ -> m >>= f)  =  liftBaseWith (\_ -> m) >>= (\a -> liftBaseWith (\_ -> f a))

As Li-yao Xia explains, parametricity guarantees that

f $ liftBaseWith q = liftBaseWith $ runInBase -> f $ q runInBase

The difference with liftBase is that before lifting the base computation liftBaseWith captures the state of m. It then provides the base computation with a RunInBase function that allows running m computations in the base monad on the captured state:

withFileLifted :: MonadBaseControl IO m => FilePath -> IOMode -> (Handle -> m a) -> m a
withFileLifted file mode action = liftBaseWith (\runInBase -> withFile file mode (runInBase . action)) >>= restoreM
                             -- = control $ \runInBase -> withFile file mode (runInBase . action)
                             -- = liftBaseOp (withFile file mode) action

liftBaseWith is usually not implemented directly, but using defaultLiftBaseWith.

restoreM :: StM m a -> m a #

Construct a m computation from the monadic state of m that is returned from a RunInBase function.

Instances should satisfy:

liftBaseWith (\runInBase -> runInBase m) >>= restoreM = m

restoreM is usually not implemented directly, but using defaultRestoreM.

Instances

Instances details
MonadBaseControl [] [] 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM [] a #

Methods

liftBaseWith :: (RunInBase [] [] -> [a]) -> [a] #

restoreM :: StM [] a -> [a] #

MonadBaseControl Maybe Maybe 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Maybe a #

MonadBaseControl IO IO 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM IO a #

Methods

liftBaseWith :: (RunInBase IO IO -> IO a) -> IO a #

restoreM :: StM IO a -> IO a #

MonadBaseControl Identity Identity 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Identity a #

MonadBaseControl STM STM 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM STM a #

Methods

liftBaseWith :: (RunInBase STM STM -> STM a) -> STM a #

restoreM :: StM STM a -> STM a #

MonadBaseControl b m => MonadBaseControl b (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (MaybeT m) a #

Methods

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

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

MonadBaseControl b m => MonadBaseControl b (ListT m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ListT m) a #

Methods

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

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

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (WriterT w m) a #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (WriterT w m) a #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (StateT s m) a #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (StateT s m) a #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ReaderT r m) a #

Methods

liftBaseWith :: (RunInBase (ReaderT r m) b -> b a) -> ReaderT r m a #

restoreM :: StM (ReaderT r m) a -> ReaderT r m a #

MonadBaseControl b m => MonadBaseControl b (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (IdentityT m) a #

Methods

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

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

MonadBaseControl b m => MonadBaseControl b (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ExceptT e m) a #

Methods

liftBaseWith :: (RunInBase (ExceptT e m) b -> b a) -> ExceptT e m a #

restoreM :: StM (ExceptT e m) a -> ExceptT e m a #

(Error e, MonadBaseControl b m) => MonadBaseControl b (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ErrorT e m) a #

Methods

liftBaseWith :: (RunInBase (ErrorT e m) b -> b a) -> ErrorT e m a #

restoreM :: StM (ErrorT e m) a -> ErrorT e m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (RWST r w s m) a #

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (RWST r w s m) a #

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

MonadBaseControl (Either e) (Either e) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (Either e) a #

Methods

liftBaseWith :: (RunInBase (Either e) (Either e) -> Either e a) -> Either e a #

restoreM :: StM (Either e) a -> Either e a #

MonadBaseControl (ST s) (ST s) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ST s) a #

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl (ST s) (ST s) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ST s) a #

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl ((->) r :: Type -> Type) ((->) r :: Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM ((->) r) a #

Methods

liftBaseWith :: (RunInBase ((->) r) ((->) r) -> r -> a) -> r -> a #

restoreM :: StM ((->) r) a -> r -> a #

class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase (b :: Type -> Type) (m :: Type -> Type) | m -> b where #

Methods

liftBase :: b α -> m α #

Lift a computation from the base monad

Instances

Instances details
MonadBase [] [] 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: [α] -> [α] #

MonadBase Maybe Maybe 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: Maybe α -> Maybe α #

MonadBase IO IO 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: IO α -> IO α #

MonadBase Identity Identity 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: Identity α -> Identity α #

MonadBase STM STM 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: STM α -> STM α #

MonadBase b m => MonadBase b (MaybeT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> MaybeT m α #

MonadBase b m => MonadBase b (ListT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ListT m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> WriterT w m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> WriterT w m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> WriterT w m α #

MonadBase b m => MonadBase b (StateT s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (StateT s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (SelectT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> SelectT r m α #

MonadBase b m => MonadBase b (ReaderT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ReaderT r m α #

MonadBase b m => MonadBase b (IdentityT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> IdentityT m α #

MonadBase b m => MonadBase b (ExceptT e m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ExceptT e m α #

(Error e, MonadBase b m) => MonadBase b (ErrorT e m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ErrorT e m α #

(Monoid w, MonadBase b m) => MonadBase b (AccumT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> AccumT w m α #

MonadBase b m => MonadBase b (ContT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ContT r m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> RWST r w s m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> RWST r w s m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> RWST r w s m α #

MonadBase (Either e) (Either e) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: Either e α -> Either e α #

MonadBase (ST s) (ST s) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: ST s α -> ST s α #

MonadBase (ST s) (ST s) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: ST s α -> ST s α #

MonadBase ((->) r :: Type -> Type) ((->) r :: Type -> Type) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: (r -> α) -> r -> α #

class Monad m => MonadIO (m :: Type -> Type) where #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, Functor m, MonadIO m) => MonadIO (AccumT w m) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

liftIO :: IO a -> AccumT w m a #

MonadIO m => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (SelectT r m) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

liftIO :: IO a -> SelectT r m a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

MonadIO m => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

liftIO :: IO a -> RWST r w s m a #