Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- class MonadTrans t => Interruptible t where
- inEitherTCtx :: a -> RSt (EitherT e) a
- peelEitherTCtx :: RSt (EitherT e) a -> Either e a
- inStateTCtx :: st -> a -> RSt (StateT st) a
- peelStateTCtx :: RSt (StateT st) a -> (a, st)
- inWriterTCtx :: Monoid w => a -> RSt (WriterT w) a
- peelWriterTCtx :: RSt (WriterT w) a -> (a, w)
- inReaderTCtx :: r -> a -> RSt (ReaderT r) a
- peelReaderTCtx :: RSt (ReaderT r) a -> a
- inRWSTCtx :: Monoid w => r -> s -> a -> RSt (RWST r w s) a
- peelRWSTCtx :: RSt (RWST r w s) a -> (a, w, s)
- resume2 :: (Monad m, Interruptible t, Monad (t m), Interruptible u) => (a -> u (t m) b) -> RSt t (RSt u a) -> m (RSt t (RSt u b))
- resume3 :: (Monad m, Interruptible t0, Monad (t0 m), Interruptible t1, Monad (t1 (t0 m)), Interruptible t2) => (a -> t2 (t1 (t0 m)) b) -> RSt t0 (RSt t1 (RSt t2 a)) -> m (RSt t0 (RSt t1 (RSt t2 b)))
- resume4 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2, Interruptible t3, Monad (t0 m), Monad (t1 (t0 m)), Monad (t2 (t1 (t0 m)))) => (a -> t3 (t2 (t1 (t0 m))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 a))) -> m (RSt t0 (RSt t1 (RSt t2 (RSt t3 b))))
- resume5 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2, Interruptible t3, Interruptible t4, Monad (t0 m), Monad (t1 (t0 m)), Monad (t2 (t1 (t0 m))), Monad (t3 (t2 (t1 (t0 m))))) => (a -> t4 (t3 (t2 (t1 (t0 m)))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 (RSt t4 a)))) -> m (RSt t0 (RSt t1 (RSt t2 (RSt t3 (RSt t4 b)))))
- intercalateWith :: Monad m => ((a -> t a) -> rsta -> m rsta) -> (b -> a -> t a) -> [b] -> [rsta] -> m [rsta]
Documentation
class MonadTrans t => Interruptible t where Source
Interruptible monad transformers.
A monad transformer can be interrupted if it returns its final context from its type creator, and if it is possible to hoist this context again into the monad at the begining of its execution.
For example, StateT
can be interrupted because
runStateT
returns its final state, and because its state
can be set at the type creation. Error can not be hoisted,
thus is can not be interrupted.
Interruptible transformers can be stacked so that their
execution is resumed by composition of their resume
functions, and their data by the composition of their data
constructors at the inverse order. That is, in the stack:
(Monad m, Interruptible i, Interruptible j) => i j m
Both i and j can be resumed by the function resume . resume
,
and given initI :: a -> RSt i a
and initJ :: a -> RSt j a
,
the total context is given by initJ . initI
.
The context data constructors vary with each Interruptible, as well as its signature.
resume :: Monad m => (a -> t m b) -> RSt t a -> m (RSt t b) Source
Resumes the execution of an interruptible transformer
Interruptible (EitherT e) Source | |
Interruptible (ReaderT r) Source | |
Interruptible (StateT st) Source | |
Monoid w => Interruptible (WriterT w) Source | |
Monoid w => Interruptible (RWST r w s) Source |
Instance accessors
inEitherTCtx :: a -> RSt (EitherT e) a Source
Cretes an interrupted EitherT context
peelEitherTCtx :: RSt (EitherT e) a -> Either e a Source
Unwraps an interrupted EitherT context
inStateTCtx :: st -> a -> RSt (StateT st) a Source
Creates an interrupted StateT context
peelStateTCtx :: RSt (StateT st) a -> (a, st) Source
Unwraps an interrupted StateT context
inWriterTCtx :: Monoid w => a -> RSt (WriterT w) a Source
Creates an interrupted WriterT context
peelWriterTCtx :: RSt (WriterT w) a -> (a, w) Source
Unwraps an interrupted WriterT context
inReaderTCtx :: r -> a -> RSt (ReaderT r) a Source
Creates an interrupted ReaderT context
peelReaderTCtx :: RSt (ReaderT r) a -> a Source
Unwraps an interrupted WriterT context
inRWSTCtx :: Monoid w => r -> s -> a -> RSt (RWST r w s) a Source
Creates an interrupted RWST context
peelRWSTCtx :: RSt (RWST r w s) a -> (a, w, s) Source
Unwraps an interrupted RWST context
Resumers for stacks of interruptibles
resume2 :: (Monad m, Interruptible t, Monad (t m), Interruptible u) => (a -> u (t m) b) -> RSt t (RSt u a) -> m (RSt t (RSt u b)) Source
resume3 :: (Monad m, Interruptible t0, Monad (t0 m), Interruptible t1, Monad (t1 (t0 m)), Interruptible t2) => (a -> t2 (t1 (t0 m)) b) -> RSt t0 (RSt t1 (RSt t2 a)) -> m (RSt t0 (RSt t1 (RSt t2 b))) Source
resume4 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2, Interruptible t3, Monad (t0 m), Monad (t1 (t0 m)), Monad (t2 (t1 (t0 m)))) => (a -> t3 (t2 (t1 (t0 m))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 a))) -> m (RSt t0 (RSt t1 (RSt t2 (RSt t3 b)))) Source
resume5 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2, Interruptible t3, Interruptible t4, Monad (t0 m), Monad (t1 (t0 m)), Monad (t2 (t1 (t0 m))), Monad (t3 (t2 (t1 (t0 m))))) => (a -> t4 (t3 (t2 (t1 (t0 m)))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 (RSt t4 a)))) -> m (RSt t0 (RSt t1 (RSt t2 (RSt t3 (RSt t4 b))))) Source
Interruptible applications
intercalateWith :: Monad m => ((a -> t a) -> rsta -> m rsta) -> (b -> a -> t a) -> [b] -> [rsta] -> m [rsta] Source
Folds the second list with the function applied to the first, intercalating the evaluation. That is:
intercalateWith resume f [a00, a10, a20] [b1, b2] = do a01 <- resume (f b1) a00 a11 <- resume (f b1) a10 a21 <- resume (f b1) a20 a02 <- resume (f b2) a11 a12 <- resume (f b2) a21 a22 <- resume (f b2) a31 return [a02, a12, a22]
Usefull for consuming lazy sequences.
The resume function is parametric for allowing resuming deeper Interruptible chains, with resume2, resume3, etc.