| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
Streaming.Eversion
Description
The pull-to-push transformations in this module require functions that are polymorphic over a monad transformer.
Because of this, some of the type signatures look scary, but actually many
(suitably polymorphic) operations on Streams will unify with them.
To get "interruptible" operations that can exit early with an error, put a
ExceptT transformer just below the polymorphic monad transformer. See
foldE.
Inspired by http://pchiusano.blogspot.com.es/2011/12/programmatic-translation-to-iteratees.html
- data Evertible a x
- evertible :: (forall m r. Monad m => Stream (Of a) m r -> m (Of x r)) -> Evertible a x
- evert :: Evertible a x -> Fold a x
- data EvertibleM m a x
- evertibleM :: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) -> EvertibleM m a x
- evertM :: Monad m => EvertibleM m a x -> FoldM m a x
- data EvertibleMIO m a x
- evertibleMIO :: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) -> EvertibleMIO m a x
- evertMIO :: MonadIO m => EvertibleMIO m a x -> FoldM m a x
- data Transvertible a b
- transvertible :: (forall m r. Monad m => Stream (Of a) m r -> Stream (Of b) m r) -> Transvertible a b
- transvert :: Transvertible b a -> forall x. Fold a x -> Fold b x
- data TransvertibleM m a b
- transvertibleM :: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> Stream (Of b) (t m) r) -> TransvertibleM m a b
- transvertM :: Monad m => TransvertibleM m b a -> forall x. FoldM m a x -> FoldM m b x
- data TransvertibleMIO m a b
- transvertibleMIO :: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> Stream (Of b) (t m) r) -> TransvertibleMIO m a b
- transvertMIO :: MonadIO m => TransvertibleMIO m b a -> forall x. FoldM m a x -> FoldM m b x
- foldE :: (MonadTrans t, Monad m, Monad (t (ExceptT e m))) => t (ExceptT e m) (Either e r) -> t (ExceptT e m) r
Evertible Stream folds
A stream-consuming function that can be turned into a pure, push-based fold.
data EvertibleM m a x Source #
Like Evertible, but gives the stream-consuming function access to a base monad.
>>>:{let f stream = fmap ((:>) ()) (lift (putStrLn "x") >> S.effects stream) in L.foldM (evertM (evertibleM f)) ["a","b","c"] :} x
Note however that control operations can't be lifted through the transformer.
Instances
| Profunctor (EvertibleM m) Source # | |
| Functor (EvertibleM m a) Source # | |
Arguments
| :: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) | |
| -> EvertibleM m a x |
data EvertibleMIO m a x Source #
Like EvertibleM, but gives the stream-consuming function the ability to use liftIO.
>>>L.foldM (evertMIO (evertibleMIO (\stream -> fmap ((:>) ()) (S.print stream)))) ["a","b","c"]"a" "b" "c"
Instances
| Profunctor (EvertibleMIO m) Source # | |
| Functor (EvertibleMIO m a) Source # | |
Arguments
| :: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) | |
| -> EvertibleMIO m a x |
Transvertible Stream transformations
data Transvertible a b Source #
A stream-transforming function that can be turned into fold-transforming function.
Instances
data TransvertibleM m a b Source #
Like Transvertible, but gives the stream-transforming function access to a base monad.
Note however that control operations can't be lifted through the transformer.
Instances
| Profunctor (TransvertibleM m) Source # | |
| Functor (TransvertibleM m a) Source # | |
Arguments
| :: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> Stream (Of b) (t m) r) | |
| -> TransvertibleM m a b |
transvertM :: Monad m => TransvertibleM m b a -> forall x. FoldM m a x -> FoldM m b x Source #
data TransvertibleMIO m a b Source #
Like TransvertibleM, but gives the stream-consuming function the ability to use liftIO.
Instances
| Profunctor (TransvertibleMIO m) Source # | |
| Functor (TransvertibleMIO m a) Source # | |
Arguments
| :: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> Stream (Of b) (t m) r) | |
| -> TransvertibleMIO m a b |
transvertMIO :: MonadIO m => TransvertibleMIO m b a -> forall x. FoldM m a x -> FoldM m b x Source #
Auxiliary functions
Arguments
| :: (MonadTrans t, Monad m, Monad (t (ExceptT e m))) | |
| => t (ExceptT e m) (Either e r) | |
| -> t (ExceptT e m) r |
If your stream-folding computation can fail early returning a Left,
compose it with this function before passing it to evertibleM.
The result will be an EvertibleM that works on ExceptT.
>>>runExceptT $ L.foldM (evertM (evertibleM (foldE . (\_ -> return (Left ()))))) [1..10]Left ()