Question

A Pipe can be broken into two parts: the generator part (yield) and the consumer part (await).

If you have a Pipe that only uses it's generator half, and only returns () (or never returns), then it can be represented as a "ListT done right". It turns out that MonadPlus can be used to represent anything like ListT-done-right.

http://www.reddit.com/r/haskell/comments/2bpsh7/a_simple_monadic_stream_library/cj7sqtw?context=3

So my question is this: Is there a dual to ListT and to MonadPlus for the consumer portion of Pipes?

Requirements:

  • A pipe which never uses yield, and only returns () (or never returns), but does use await can be represented as this "dual to ListT".
  • The "dual to ListT" can be generalized to the "dual of MonadPlus"
Was it helpful?

Solution

I think the answer is not to dualize the "generator-like" type-class, but rather to extend it with a simple Category instance equivalent to the await/(>~) category of pipes.

Unfortunately, there is no way to arrange the type variables to make this satisfy all three type classes (MonadPlus, MonadTrans, and Category), so I will define a new type class:

{-# LANGUAGE KindSignatures #-}

import Control.Monad
import Control.Monad.Trans.Class

class Consumer (t :: * -> (* -> *) -> * -> *) where
    await :: t a m a
    (>~)  :: t a m b -> t b m c -> t a m c

The laws for this type class are the category laws:

await >~ f = f

f >~ await = f

(f >~ g) >~ h = f >~ (g >~ h)

Then you can implement both Consumers and Pipes once you have this additional type class:

printer :: (Show a, Monad (t a IO), MonadTrans (t a), Consumer t) => t a IO r
printer = do
    a <- await
    lift (print a)
    printer
{-
printer :: Show a => Consumer a IO r
printer = do
    a <- await
    lift (print a)
    printer
-}

cat :: (MonadPlus (t a m), Consumer t) => t a m a
cat = await `mplus` cat
{-
cat :: Monad m => Pipe a a m r
cat = do
    a <- await
    yield a
    cat
-}

debug :: (Show a, MonadPlus (t a IO), MonadTrans (t a), Consumer t) => t a IO a
debug = do
    a <- await
    lift (print a)
    return a `mplus` debug
{-
debug :: Show a => Pipe a a IO r
debug = do
    a <- await
    lift (print a)
    yield a
    debug
-}

taker :: (Consumer t, MonadPlus (t a m)) => Int -> t a m a
taker 0 = mzero
taker n = do
    a <- await
    return a `mplus` taker (n - 1)
{-
taker :: Monad m => Int -> Pipe a a m ()
taker 0 = return ()
taker n = do
    a <- await
    yield a
    taker (n - 1)
-}

The hard part is figuring out how to do this without adding a new type class to base. I'd prefer to reuse the original Category type class if possible, possibly having await and (>~) just be functions that wrap your type in a newtype, use the Category instance, and then unwrap it, but I'm still working out the specifics of how to do that.

Edit: I found the solution. Just define the following newtype:

{-# LANGUAGE KindSignatures, FlexibleContexts #-}

import Control.Category
import Prelude hiding ((.), id)

newtype Consumer t m a b = Consumer { unConsumer :: t a m b }

await :: Category (Consumer t m) => t a m a
await = unConsumer id

(>~) :: Category (Consumer t m) => t a m b -> t b m c -> t a m c
f >~ g = unConsumer (Consumer f >>> Consumer g)

Then any library can just implement a Category instance for their type wrapped in the Consumer newtype.

Then you would get a constraint like this any time you used await or (>~):

cat :: (MonadPlus (t a m), Category (Consumer t m)) => t a m a
cat = await `mplus` cat
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top