conduino-0.2.1.0: Lightweight composable continuation-based stream processors

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Conduino.Lift

Contents

Description

Working with underlying monad transformers and Pipe.

There is no "general abstraction" for dealing with each monad transformer, but we can translate the semantics that each monad transformer provides into meaningful Pipe operations.

For example, a Pipe i o u (State s) a is a pipe working over stateful effects --- it can pull information and modify an underlying state to do its job. It takes in i and outputs o, using an underlying state s.

However, such a pipe is similar to s -> Pipe i o u Identity (a, s). Giving some starting state, it takes in i and outputs o, and when it completes, it returns an a and an s, the final state after all its processing is done.

The general idea is that:

  • A pipe over a monad transformer shares that monadic context over every pipe in a composition.

For example, if p, q, and r are all pipes over StateT, the p .| q .| r will all share a common global state.

If p, q, and r are all pipes over ExceptT, then p .| q .| r will all short-circult fail each other: if q fails, then they all fail, etc.

If p, q, and r are all pipes over WriterT then p .| q .| r will all accumulate to a shared global log.

If p, q, and r are all pipes over ReaderT then p .| q .| r will use the same identical environment.

  • Using the runX family of functions (runStateP, runExceptP, etc.) lets you isolate out the common context within a composition of pipes.

For example, if p is a pipe over StateT, then a .| void (runStateP s0 p) .| b, a and b will not be able to use the state of p.

If p is a pipe over ExceptT, then in a .| void (runExceptP p) .| b, a failure in p will not cause all the others to fail.

Both of these representations have different advantages and disadvantages, that are separate and unique for each individual monad transformer on a case-by-case basis. This module provides functions on such a case-by-case basis as you need them.

Since: 0.2.1.0

Synopsis

State

Lazy

stateP :: Monad m => (s -> Pipe i o u m (a, s)) -> Pipe i o u (StateT s m) a Source #

Turn a "state-modifying Pipe" into a Pipe that runs over StateT, so you can chain it with other StateT pipes.

Note that this will overwrite whatever state exists with the s that it gets when it terminates. If any other pipe in this chain modifies or uses state, all modifications will be overwritten when the (a, s)-producing pipe terminates.

Since: 0.2.1.0

runStateP :: Monad m => s -> Pipe i o u (StateT s m) a -> Pipe i o u m (a, s) Source #

Turn a Pipe that runs over StateT into a "state-modifying Pipe", that returns the final state when it terminates.

The main usage of this is to "isolate" the state from other pipes in the same chain. For example, of p, q, and r are all pipes under StateT, then:

    p
 .| q
 .| r

will all share underlying state, and each can modify the state that they all three share. We essentially have global state.

However, if you use runStateP, you can all have them use different encapsulated states.

    void (runStateP s0 p)
 .| void (runStateP s1 q)
 .| runStateP s2 r

In this case, each of those three chained pipes will use their own internal states, without sharing.

This is also useful if you want to chain a pipe over StateT with pipes that don't use state at all: for example if a and b are "non-stateful" pipes (not over StateT), you can do:

    a
 .| void (runStateP s1 q)
 .| b

And a and b will be none the wiser to the fact that q uses StateT internally.

Note to avoid the usage of void, evalStateP might be more useful.

Since: 0.2.1.0

evalStateP :: Monad m => s -> Pipe i o u (StateT s m) a -> Pipe i o u m a Source #

Takes a Pipe over StateT and "hides" the state from the outside world. Give an initial state --- the pipe behaves the same way, but to the external user it is abstracted away. See runStateP for more information.

This can be cleaner than runStateP because if a is (), you don't have to sprinkle in void everywhere. However, it's only really useful if you don't need to get the final state upon termination.

Since: 0.2.1.0

execStateP :: Monad m => s -> Pipe i o u (StateT s m) a -> Pipe i o u m s Source #

Like runStateP, but ignoring the final result. It returns the final state after the pipe succesfuly terminates.

Since: 0.2.1.0

Strict

statePS :: Monad m => (s -> Pipe i o u m (a, s)) -> Pipe i o u (StateT s m) a Source #

runStatePS :: Monad m => s -> Pipe i o u (StateT s m) a -> Pipe i o u m (a, s) Source #

evalStatePS :: Monad m => s -> Pipe i o u (StateT s m) a -> Pipe i o u m a Source #

execStatePS :: Monad m => s -> Pipe i o u (StateT s m) a -> Pipe i o u m s Source #

Except

exceptP :: Monad m => Pipe i o u m (Either e a) -> Pipe i o u (ExceptT e m) a Source #

Turn a "failable-result" Pipe into a pipe over ExceptT.

Note that a throwE failure will only ever happen when the input pipe "succesfully" terminates with Left. It would never happen before the pipe terminates, since you don't get the Either e a until the pipe succesfully terminates.

Since: 0.2.1.0

runExceptP :: Monad m => Pipe i o u (ExceptT e m) a -> Pipe i o u m (Either e a) Source #

Turn a Pipe that runs over ExceptT into an "early-terminating Pipe" that "succesfully" returns Left or Right.

The main usage of this is to "isolate" the short-circuiting failure of ExceptT to only happen within one component of a chain. For example, of p, q, and r are all pipes under ExceptT, then:

    p
 .| q
 .| r

will short-circuit fail if any of p, q, or r fail. We have global failure only.

However, if you use runExceptP, we isolate the short-circuiting failure to only a single type.

    void (runExceptP p)
 .| void (runExceptP q)
 .| runExceptP r

In this case, if (for example) q fails, it won't cause the whole thing to fail: it will just be the same as if q succesfully terminates normally.

This is also useful if you want to chain a pipe over ExceptT with pipes that don't have ExceptT at all: for example if a and b are "non-erroring" pipes (not over ExceptT), you can do:

    a
 .| void (runExceptP q)
 .| b

And a and b will be none the wiser to the fact that q uses ExceptT internally.

Note to avoid the usage of void, runExceptP_ might be more useful.

Since: 0.2.1.0

runExceptP_ :: Monad m => Pipe i o u (ExceptT e m) a -> Pipe i o u m () Source #

A handy version of runExceptP that discards its output, so it can be easier to chain using .|. It's useful if you are using runExceptP to "isolate" failures from the rest of a chain.

Since: 0.2.1.0

Reader

readerP :: Monad m => (r -> Pipe i o u m a) -> Pipe i o u (ReaderT r m) a Source #

Turn a "parameterized Pipe" into a Pipe that runs over ReaderT, so you can chain it with other ReaderT pipes.

Essentially, instead of directly providing the r in an r -> Pipe i o u m a, the r instead comes from the globally shared environment.

Since: 0.2.1.0

runReaderP :: Monad m => r -> Pipe i o u (ReaderT r m) a -> Pipe i o u m a Source #

Turn a pipe over ReaderT into a directly parameterized pipe. Instead of getting the parameter from the globally shared ReaderT environment, give it directly instead.

It can be useful to "ignore" a globally shared environment and just give the r directly and immediately.

Since: 0.2.1.0

Writer

Lazy

writerP :: (Monad m, Monoid w) => Pipe i o u m (a, w) -> Pipe i o u (WriterT w m) a Source #

Turn a pipe returning an (a, w) tuple upon termination into a pipe returning a, logging the w in an underlying WriterT context.

This can be useful for composing your pipe with other WriterT pipes, aggregating all to a common global log.

However, be aware that this only ever tells when the pipe succesfuly terminates. It doesn't do "streaming logging" -- it only makes one log payload at the point of succesful termination. To do streaming logging (logging things as you get them), you should probably just directly use WriterT instead, with repeatM or iterM or something similar.

Since: 0.2.1.0

runWriterP :: (Monad m, Monoid w) => Pipe i o u (WriterT w m) a -> Pipe i o u m (a, w) Source #

Turn a Pipe that runs over WriterT into a Pipe that returns the final log when it terminates.

The main usage of this is to "isolate" the log from other pipes in the same chain. For example, of p, q, and r are all pipes under WriterT, then:

    p
 .| q
 .| r

will all share underlying log, and all logging from any of them will accumulate together in an interleaved way. It is essentially a global log.

However, if you use runWriterP, you can all have them use different encapsulated logs.

    void (runWriterP p)
 .| void (runWriterP q)
 .| runWriterP r

In this case, each of those three chained pipes will use their own internal logs, without sharing.

This is also useful if you want to chain a pipe over WriterT with pipes that don't use state at all: for example if a and b are "non-logging" pipes (not over WriterT), you can do:

    a
 .| void (runWriterP q)
 .| b

And a and b will be none the wiser to the fact that q uses WriterT internally.

Since: 0.2.1.0

execWriterP :: (Monad m, Monoid w) => Pipe i o u (WriterT w m) a -> Pipe i o u m w Source #

runWriterP, but only returning the final log after succesful termination.

Since: 0.2.1.0

Strict

writerPS :: (Monad m, Monoid w) => Pipe i o u m (a, w) -> Pipe i o u (WriterT w m) a Source #

runWriterPS :: (Monad m, Monoid w) => Pipe i o u (WriterT w m) a -> Pipe i o u m (a, w) Source #

execWriterPS :: (Monad m, Monoid w) => Pipe i o u (WriterT w m) a -> Pipe i o u m w Source #

RWS

Lazy

rwsP :: (Monad m, Monoid w) => (r -> s -> Pipe i o u m (a, s, w)) -> Pipe i o u (RWST r w s m) a Source #

Turn a parameterized, state-transforming, log-producing Pipe into a Pipe over RWST, which can be useful for chaining it with other RWST pipes.

See stateP and writerP for more details on caveats, including:

  • Logging only happens when the (a,s,w)-returning pipe terminates. There is no "streaming logging" --- the resulting w is logged all at once.
  • When the (a,s,w)-returning pipe terminates, whatever state in the RWST is overwritten with the s returned. If other pipes in the chain modify the s, their modifications will be overwritten.

Since: 0.2.1.0

runRWSP :: (Monad m, Monoid w) => r -> s -> Pipe i o u (RWST r w s m) a -> Pipe i o u m (a, s, w) Source #

Turn a Pipe that runs over RWST into a state-modifying, environment-using, log-accumulating Pipe. See runStateP, runWriterP, and runReaderP for the uses and semantics.

Since: 0.2.1.0

evalRWSP :: (Monad m, Monoid w) => r -> s -> Pipe i o u (RWST r w s m) a -> Pipe i o u m (a, w) Source #

runRWSP, but ignoring the final state.

Since: 0.2.1.0

execRWSP :: (Monad m, Monoid w) => r -> s -> Pipe i o u (RWST r w s m) a -> Pipe i o u m (s, w) Source #

runRWSP, but ignoring the result value.

Since: 0.2.1.0

Strict

rwsPS :: (Monad m, Monoid w) => (r -> s -> Pipe i o u m (a, s, w)) -> Pipe i o u (RWST r w s m) a Source #

rwsP, but for Control.Monad.Trans.RWS.Strict.

Since: 0.2.1.0

runRWSPS :: (Monad m, Monoid w) => r -> s -> Pipe i o u (RWST r w s m) a -> Pipe i o u m (a, s, w) Source #

evalRWSPS :: (Monad m, Monoid w) => r -> s -> Pipe i o u (RWST r w s m) a -> Pipe i o u m (a, w) Source #

execRWSPS :: (Monad m, Monoid w) => r -> s -> Pipe i o u (RWST r w s m) a -> Pipe i o u m (s, w) Source #

Catch

catchP :: Monad m => Pipe i o u m (Either SomeException a) -> Pipe i o u (CatchT m) a Source #

Like exceptP, but for CatchT. See exceptP for usage details and caveats. In general, can be useful for chaining with other CatchT pipes.

Note that a throwM failure will only ever happen when the input pipe "succesfully" terminates with Left. It would never happen before the pipe terminates, since you don't get the Either SomeException a until the pipe succesfully terminates.

Since: 0.2.1.0

runCatchP :: Monad m => Pipe i o u (CatchT m) a -> Pipe i o u m (Either SomeException a) Source #

Like runExceptP, but for CatchT. See runExceptP for usage details. In general, can be useful for "isolating" a CatchT pipe from the rest of its chain.

Since: 0.2.1.0