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

Safe HaskellSafe
LanguageHaskell98

Streaming.Eversion

Contents

Description

Most 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. In practice, that means lifting functions like throwE and hoistEither a number of times.

Inspired by http://pchiusano.blogspot.com.es/2011/12/programmatic-translation-to-iteratees.html

Synopsis

Stream folds

data Eversible a x Source #

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

Instances

Profunctor Eversible Source # 

Methods

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

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

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

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

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

Functor (Eversible a) Source # 

Methods

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

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

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

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

data EversibleM m a x Source #

Like Eversible, but gives the stream-folding function access to a base monad.

>>> :{
    let consume stream = lift (putStrLn "x") >> S.effects stream
    in  L.foldM (evertM (eversibleM_ consume)) ["a","b","c"]
    :}
x

Note however that control operations can't be lifted through the transformer.

Instances

Profunctor (EversibleM m) Source # 

Methods

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

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

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

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

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

Functor (EversibleM m a) Source # 

Methods

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

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

eversibleM Source #

Arguments

:: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) 
-> EversibleM m a x 

eversibleM_ Source #

Arguments

:: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> t m r) 
-> EversibleM m a () 

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

data EversibleMIO m a x Source #

Like EversibleM, but gives the stream-consuming function the ability to use liftIO.

>>> L.foldM (evertMIO (eversibleMIO_ S.print)) ["a","b","c"]
"a"
"b"
"c"

Instances

Profunctor (EversibleMIO m) Source # 

Methods

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

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

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

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

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

Functor (EversibleMIO m a) Source # 

Methods

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

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

eversibleMIO Source #

Arguments

:: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) 
-> EversibleMIO m a x 

eversibleMIO_ Source #

Arguments

:: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> t m r) 
-> EversibleMIO m a () 

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

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 #

Category * Transvertible Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

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 #

Category * (TransvertibleM m) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat 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 

runTransvertibleM Source #

Arguments

:: TransvertibleM m a b 
-> forall r. Monad m => Stream (Of a) m r -> Stream (Of b) m r 

Recover the stored function, discarding the transformer.

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

Category * (TransvertibleMIO m) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat 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 

runTransvertibleMIO Source #

Arguments

:: TransvertibleMIO m a b 
-> forall r. MonadIO m => Stream (Of a) m r -> Stream (Of b) m r 

transvertMIO Source #

Arguments

:: MonadIO m 
=> TransvertibleMIO m b a 
-> forall x. FoldM m a x -> FoldM m b x