[Haskell-cafe] ANNOUNCE: pipes-core 0.1.0

Paolo Capriotti p.capriotti at gmail.com
Tue Apr 10 18:56:04 CEST 2012


On Tue, Apr 10, 2012 at 4:50 PM, Twan van Laarhoven <twanvl at gmail.com> wrote:
> I have some issues with the function names used
>
>    firstP :: Monad m => Pipe a b m r
>              -> Pipe (Either a c) (Either b c) m r
>    secondP :: Monad m => Pipe a b m r
>              -> Pipe (Either c a) (Either c b) m r
>
> Why are firstP and secondP not called leftP and rightP? Those are the
> corresponding functions in Arrow. Similarly (***) should be called (+++).

firstP and secondP are the two components of the morphism function of
the binoidal functor 'Either' on the Pipe category.

I'm following the terminology of the 'categories' package here, as you
can see from the newtype wrappers in Control.Pipe.Category.

Since (pre-)monoidal categories are a generalization of Arrow, I think
it's reasonable to extend the meaning of 'first' and 'second', instead
of reusing the ArrowChoice method names, which are just another
specialization of the same general concept.

> I also don't like `intersperse`, which does something completely different
> from its Data.List counterpart.
>
>    intersperse :: Monad m => (a -> Bool) -> Pipe a (Maybe a) m r
>    Data.List.intersperse :: a -> [a] -> [a]

You're right. It was meant as a generalization of that, but I agree it
needs a better name.

> The documentation is also a bit misleading "Yield Nothing when an input
> satisfying the predicate is received." To me this suggests that could behave
> like some kind of filter,
>
>    intersperse p = pipe $ \x -> if p x then Nothing else Just x

Yes, that is indeed confusing.

> A true intersperse analogue would be
>
>    intersperse x = do
>        y0 <- await
>        yield y0
>        forever $ do
>           y <- await
>           yield x
>           yield y

You can define this using the current intersperse:

intersperse' x = intersperse (const True)
             >+> (await >> pipe (fromMaybe x))

That's why I feel it's a generalization.

> The function you have defined is something like
> `yieldNothingBeforeMatching`. Do you have a use case for this function?

Well, I wrote it for a project of mine, and then decided it was
general enough to be included in Combinators. Maybe that wasn't such a
good idea.

> Perhaps an interesting combinator would be
>
>    -- | Run the first pipe until it yields a value, then run the second pipe
> until it yields, the the first pipe again, etc.
>    alternate :: Pipe a b m r -> Pipe a b m r -> Pipe a b m r
>
>    intersperse x = alternate idP (forever (yield x))
>
> Although I have no idea if it is actually useful in practice.

Neither do I. I think I'll just remove intersperse for the next release.

Thanks a lot for your feedback!

Paolo



More information about the Haskell-Cafe mailing list