| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
Streaming.Eversion.Pipes
Description
Like Streaming.Eversion, but for Producer folds and transformations.
- pipeEvertible :: (forall m r. Monad m => Producer a m r -> m (x, r)) -> Evertible a x
- evert :: Evertible a x -> Fold a x
- pipeEvertibleM :: (forall t r. (MonadTrans t, Monad (t m)) => Producer a (t m) r -> t m (x, r)) -> EvertibleM m a x
- evertM :: Monad m => EvertibleM m a x -> FoldM m a x
- pipeEvertibleMIO :: (forall t r. (MonadTrans t, MonadIO (t m)) => Producer a (t m) r -> t m (x, r)) -> EvertibleMIO m a x
- evertMIO :: MonadIO m => EvertibleMIO m a x -> FoldM m a x
- pipeTransvertible :: (forall m r. Monad m => Producer a m r -> Producer b m r) -> Transvertible a b
- transvert :: Transvertible b a -> forall x. Fold a x -> Fold b x
- pipeTransvertibleM :: (forall t r. (MonadTrans t, Monad (t m)) => Producer a (t m) r -> Producer 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
- pipeTransvertibleMIO :: (forall t r. (MonadTrans t, MonadIO (t m)) => Producer a (t m) r -> Producer 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
- pipeLeftoversE :: (MonadTrans t, Monad m, Monad (t (ExceptT bytes m))) => Producer text (t (ExceptT bytes m)) (Producer bytes (t (ExceptT bytes m)) r) -> Producer text (t (ExceptT bytes m)) r
- pipeTransE :: (MonadTrans t, Monad m, Monad (t (ExceptT e m))) => Producer a (t (ExceptT e m)) (Either e r) -> Producer a (t (ExceptT e m)) r
Evertible Producer folds
Arguments
| :: (forall t r. (MonadTrans t, Monad (t m)) => Producer a (t m) r -> t m (x, r)) | |
| -> EvertibleM m a x |
Arguments
| :: (forall t r. (MonadTrans t, MonadIO (t m)) => Producer a (t m) r -> t m (x, r)) | |
| -> EvertibleMIO m a x |
Transvertible Producer transformations
Arguments
| :: (forall m r. Monad m => Producer a m r -> Producer b m r) | |
| -> Transvertible a b |
Arguments
| :: (forall t r. (MonadTrans t, Monad (t m)) => Producer a (t m) r -> Producer 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 #
Arguments
| :: (forall t r. (MonadTrans t, MonadIO (t m)) => Producer a (t m) r -> Producer 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 bytes m))) | |
| => Producer text (t (ExceptT bytes m)) (Producer bytes (t (ExceptT bytes m)) r) | |
| -> Producer text (t (ExceptT bytes m)) r |
Allows you to plug any of the "non-lens decoding functions" from Pipes.Text.Encoding into pipeTransvertibleM. Just
compose the decoder with this function before passing it to pipeTransvertibleM.
The result will be a TransvertibleM that works in ExceptT.
>>>:{let adapted = transvertM (pipeTransvertibleM (pipeLeftoversE . TE.decodeUtf8)) (L.generalize L.mconcat) in runExceptT $ L.foldM adapted ["decode","this"] :} Right "decodethis"
If any undecodable bytes are found, the computation halts with the undecoded bytes as the error.
>>>:{let adapted = transvertM (pipeTransvertibleM (pipeLeftoversE . TE.decodeUtf8)) (L.generalize L.mconcat) in runExceptT $ L.foldM adapted ["invalid \xc3\x28","sequence"] :} Left "\195("
Arguments
| :: (MonadTrans t, Monad m, Monad (t (ExceptT e m))) | |
| => Producer a (t (ExceptT e m)) (Either e r) | |
| -> Producer a (t (ExceptT e m)) r |
If your producer-transforming computation can fail early returning a Left,
compose it with this function before passing it to transvertibleM.
The result will be an TransvertibleM that works on ExceptT.