streaming-eversion-0.1.0.0: Translate pull-based stream folds into push-based iteratees.

Safe HaskellSafe
LanguageHaskell98

Streaming.Eversion

Contents

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

Synopsis

Evertible Stream folds

data Evertible a x Source #

A stream-consuming function that can be turned into a pure, push-based fold.

Instances

Profunctor Evertible Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Evertible b c -> Evertible a d #

lmap :: (a -> b) -> Evertible b c -> Evertible a c #

rmap :: (b -> c) -> Evertible a b -> Evertible a c #

(#.) :: Coercible * c b => (b -> c) -> Evertible a b -> Evertible a c #

(.#) :: Coercible * b a => Evertible b c -> (a -> b) -> Evertible a c #

Functor (Evertible a) Source # 

Methods

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

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

evertible :: (forall m r. Monad m => Stream (Of a) m r -> m (Of x r)) -> Evertible a x Source #

evert :: Evertible a x -> Fold a x Source #

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 # 

Methods

dimap :: (a -> b) -> (c -> d) -> EvertibleM m b c -> EvertibleM m a d #

lmap :: (a -> b) -> EvertibleM m b c -> EvertibleM m a c #

rmap :: (b -> c) -> EvertibleM m a b -> EvertibleM m a c #

(#.) :: Coercible * c b => (b -> c) -> EvertibleM m a b -> EvertibleM m a c #

(.#) :: Coercible * b a => EvertibleM m b c -> (a -> b) -> EvertibleM m a c #

Functor (EvertibleM m a) Source # 

Methods

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

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

evertibleM 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 

evertM :: Monad m => EvertibleM m a x -> FoldM m a x Source #

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 # 

Methods

dimap :: (a -> b) -> (c -> d) -> EvertibleMIO m b c -> EvertibleMIO m a d #

lmap :: (a -> b) -> EvertibleMIO m b c -> EvertibleMIO m a c #

rmap :: (b -> c) -> EvertibleMIO m a b -> EvertibleMIO m a c #

(#.) :: Coercible * c b => (b -> c) -> EvertibleMIO m a b -> EvertibleMIO m a c #

(.#) :: Coercible * b a => EvertibleMIO m b c -> (a -> b) -> EvertibleMIO m a c #

Functor (EvertibleMIO m a) Source # 

Methods

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

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

evertibleMIO 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 

evertMIO :: MonadIO m => EvertibleMIO m a x -> FoldM m a x Source #

Transvertible Stream transformations

data Transvertible a b Source #

A stream-transforming function that can be turned into fold-transforming function.

Instances

Profunctor Transvertible Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Transvertible b c -> Transvertible a d #

lmap :: (a -> b) -> Transvertible b c -> Transvertible a c #

rmap :: (b -> c) -> Transvertible a b -> Transvertible a c #

(#.) :: Coercible * c b => (b -> c) -> Transvertible a b -> Transvertible a c #

(.#) :: Coercible * b a => Transvertible b c -> (a -> b) -> Transvertible a c #

Functor (Transvertible a) Source # 

Methods

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

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

transvertible Source #

Arguments

:: (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 Source #

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 # 

Methods

dimap :: (a -> b) -> (c -> d) -> TransvertibleM m b c -> TransvertibleM m a d #

lmap :: (a -> b) -> TransvertibleM m b c -> TransvertibleM m a c #

rmap :: (b -> c) -> TransvertibleM m a b -> TransvertibleM m a c #

(#.) :: Coercible * c b => (b -> c) -> TransvertibleM m a b -> TransvertibleM m a c #

(.#) :: Coercible * b a => TransvertibleM m b c -> (a -> b) -> TransvertibleM m a c #

Functor (TransvertibleM m a) Source # 

Methods

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

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

transvertibleM 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 # 

Methods

dimap :: (a -> b) -> (c -> d) -> TransvertibleMIO m b c -> TransvertibleMIO m a d #

lmap :: (a -> b) -> TransvertibleMIO m b c -> TransvertibleMIO m a c #

rmap :: (b -> c) -> TransvertibleMIO m a b -> TransvertibleMIO m a c #

(#.) :: Coercible * c b => (b -> c) -> TransvertibleMIO m a b -> TransvertibleMIO m a c #

(.#) :: Coercible * b a => TransvertibleMIO m b c -> (a -> b) -> TransvertibleMIO m a c #

Functor (TransvertibleMIO m a) Source # 

Methods

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

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

transvertibleMIO 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

foldE Source #

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 ()