| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
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
- data Eversible a x
- eversible :: (forall m r. Monad m => Stream (Of a) m r -> m (Of x r)) -> Eversible a x
- evert :: Eversible a x -> Fold a x
- data EversibleM m a x
- eversibleM :: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) -> EversibleM m a x
- eversibleM_ :: (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
- data EversibleMIO m a x
- eversibleMIO :: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> t m (Of x r)) -> EversibleMIO m a x
- eversibleMIO_ :: (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
- 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
- runTransvertibleM :: TransvertibleM m a b -> forall r. Monad m => Stream (Of a) m r -> Stream (Of b) m r
- 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
- runTransvertibleMIO :: TransvertibleMIO m a b -> forall r. MonadIO m => Stream (Of a) m r -> Stream (Of b) m r
- transvertMIO :: MonadIO m => TransvertibleMIO m b a -> forall x. FoldM m a x -> FoldM m b x
Stream folds
A stream-folding function that can be turned into a pure, push-based fold.
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 # | |
| Functor (EversibleM m a) 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 |
Arguments
| :: (forall t r. (MonadTrans t, Monad (t m)) => Stream (Of a) (t m) r -> t m r) | |
| -> EversibleM m a () |
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 # | |
| Functor (EversibleMIO m a) 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 |
Arguments
| :: (forall t r. (MonadTrans t, MonadIO (t m)) => Stream (Of a) (t m) r -> t m r) | |
| -> EversibleMIO m a () |
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 # | |
| Category * (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 |
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 # | |
| Category * (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 |
Arguments
| :: MonadIO m | |
| => TransvertibleMIO m b a | |
| -> forall x. FoldM m a x -> FoldM m b x |