ANNOUNCE: pipes-core 0.1.0

I'm pleased to announce the release of version 0.1.0 of pipes-core, a library for efficient, safe and compositional IO, similar in scope to iteratee and conduits. http://hackage.haskell.org/package/pipes-core This release fixes a mistake in the previous version which violated the category laws in certain cases. I have now written a fairly explicit proof of the category laws for the current implementation, which I'll try to keep updated as the library evolves: https://github.com/pcapriotti/pipes-core/wiki/Category-laws-for-pipes --- # CHANGELOG for pipes-core: ## Version 0.1.0 - Significant simplification of the internals. - Removed `ensure` primitive. # CHANGELOG for pipes-extra: ## Version 0.1.0 - Improved naming in Control.Pipe.Coroutine. - Replaced ChunkPipe with PutbackPipe. --- BR, Paolo Capriotti

On 09/04/12 23:49, Paolo Capriotti wrote:
I'm pleased to announce the release of version 0.1.0 of pipes-core, a library for efficient, safe and compositional IO, similar in scope to iteratee and conduits.
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 (+++). 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] 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 A true intersperse analogue would be intersperse x = do y0 <- await yield y0 forever $ do y <- await yield x yield y The function you have defined is something like `yieldNothingBeforeMatching`. Do you have a use case for this function? 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. Twan

On Tue, Apr 10, 2012 at 4:50 PM, Twan van Laarhoven
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

Paolo Capriotti wrote:
I'm pleased to announce the release of version 0.1.0 of pipes-core, a library for efficient, safe and compositional IO, similar in scope to iteratee and conduits.
I like your pipes package. This is very similar to what Mario Blažević wrote about his Coroutines in the Monad.Reader (can't remember which issue; great article, BTW, many thanks Mario for making me understand the iteratee business (and also generators) for the first time). Your pipes-core looks even simpler to use, maybe due to avoiding to make a type distinction between consumer/producer/pipe (except the natural one i.e. through the input/output types), even though the parameterization by a functor (as in Monad.Coroutine) has its own beauty. Two issues: (1) What is the reason for the asymmetry in type Producer b m = Pipe () b m type Consumer a m = Pipe a Void m i.e. why does Producer use () for the input? I would expect it to use Void, like Consumer does for its output. Calling await in a Producer resulting in an immediate 'return ()' as you say is allowed (in the tutorial) strikes me as not very useful. If the idea is simply to flag nonsense like consumer >+> producer with a type error, then it might be a better idea to introduce two different Void types: data NoOutput data NoInput type Producer b m = Pipe NoInput b m type Consumer a m = Pipe a NoOutput m type Pipeline m = Pipe NoInput NoOutput m (and isn't this nicely self-explaining?) (2) The $$ operator is poorly named. I would intuitively expect an operator that looks so similar to the standard $ to have the same direction of data flow (i.e. right to left, like function application and composition) but your is left to right. You could use e.g. >$> instead, which has the additional advantage of allowing a symmetric variant for the other direction i.e. <$<. Cheers Ben

On Mon, Apr 16, 2012 at 10:13 PM, Ben Franksen
I like your pipes package. This is very similar to what Mario Blažević wrote about his Coroutines in the Monad.Reader (can't remember which issue; great article, BTW, many thanks Mario for making me understand the iteratee business (and also generators) for the first time). Your pipes-core looks even simpler to use, maybe due to avoiding to make a type distinction between consumer/producer/pipe (except the natural one i.e. through the input/output types), even though the parameterization by a functor (as in Monad.Coroutine) has its own beauty.
Yes, Mario Blažević's Transducer is the main inspiration for the original pipes package, and consequently pipes-core.
Two issues:
(1) What is the reason for the asymmetry in
type Producer b m = Pipe () b m type Consumer a m = Pipe a Void m
i.e. why does Producer use () for the input? I would expect it to use Void, like Consumer does for its output. Calling await in a Producer resulting in an immediate 'return ()' as you say is allowed (in the tutorial) strikes me as not very useful.
The underlying reason for the asymmetry is the fact that '()' is a terminal object in the category of haskell types and *total* functions, while 'Void' is an initial object. Here's a property that uniquely determines the definitions of 'Producer' above. Let 'X' be the type such that 'Producer b m = Pipe X b m'. For all producers 'p' there should be a unique (total) pipe 'alpha :: forall a r. Pipe a X m r' such that 'alpha >+> p' and 'p' are observationally equal. In other words, since a producer "never uses values of its input type 'a'", there should be a unique way to make it into a pipe which is polymorphic in 'a'. It's easy to see that this property immediately implies that 'X' should be a terminal object, i.e. '()', and 'alpha' is therefore 'pipe (const ())'. Dually, you obtain that 'Consumer a m' is necessarily 'Pipe a Void m', and 'alpha = pipe absurd'.
(2) The $$ operator is poorly named. I would intuitively expect an operator that looks so similar to the standard $ to have the same direction of data flow (i.e. right to left, like function application and composition) but your is left to right. You could use e.g. >$> instead, which has the additional advantage of allowing a symmetric variant for the other direction i.e. <$<.
'$$' is inspired by iteratees. Similarly to its iteratee counterpart, it discards upstream result values and only returns the output of the last pipe. That said, '>$>' looks like a clearer alternative, so I could consider changing it. Thanks for your feedback! Paolo

Paolo Capriotti wrote:
On Mon, Apr 16, 2012 at 10:13 PM, Ben Franksen
wrote: (1) What is the reason for the asymmetry in
type Producer b m = Pipe () b m type Consumer a m = Pipe a Void m
i.e. why does Producer use () for the input? I would expect it to use Void, like Consumer does for its output. Calling await in a Producer resulting in an immediate 'return ()' as you say is allowed (in the tutorial) strikes me as not very useful.
The underlying reason for the asymmetry is the fact that '()' is a terminal object in the category of haskell types and *total* functions, while 'Void' is an initial object.
Here's a property that uniquely determines the definitions of 'Producer' above. Let 'X' be the type such that 'Producer b m = Pipe X b m'. For all producers 'p' there should be a unique (total) pipe 'alpha :: forall a r. Pipe a X m r' such that 'alpha >+> p' and 'p' are observationally equal. In other words, since a producer "never uses values of its input type 'a'", there should be a unique way to make it into a pipe which is polymorphic in 'a'. It's easy to see that this property immediately implies that 'X' should be a terminal object, i.e. '()', and 'alpha' is therefore 'pipe (const ())'.
Dually, you obtain that 'Consumer a m' is necessarily 'Pipe a Void m', and 'alpha = pipe absurd'.
Ok, thanks for the explanation. Makes sense...
(2) The $$ operator is poorly named. I would intuitively expect an operator that looks so similar to the standard $ to have the same direction of data flow (i.e. right to left, like function application and composition) but your is left to right. You could use e.g. >$> instead, which has the additional advantage of allowing a symmetric variant for the other direction i.e. <$<.
'$$' is inspired by iteratees. Similarly to its iteratee counterpart, it discards upstream result values and only returns the output of the last pipe. That said, '>$>' looks like a clearer alternative, so I could consider changing it.
(...or maybe use a plain function instead of an operator...) Cheers Ben

Paolo, This new pipes-core release looks very nice, and I'm happy to see exception and finalizer safety while still retaining the general structure of the original pipes package. One thing that Gabriel and Michael have been talking about, though, that seems to be missing here, is a way for a pipe to indicate that it's finished with its upstream portion, so that upstream finalizers can be immediately run without waiting for the downstream parts of the pipe to complete. Do you have an answer for this? I've been puzzling it out this morning, but it's unclear to me how something like this interacts with type safety and exception handling. -- Chris

On Tue, Apr 17, 2012 at 4:10 PM, Chris Smith
One thing that Gabriel and Michael have been talking about, though, that seems to be missing here, is a way for a pipe to indicate that it's finished with its upstream portion, so that upstream finalizers can be immediately run without waiting for the downstream parts of the pipe to complete.
Yes, that is indeed a limitation of pipes-core, but it's still possible to achieve early finalization when needed, by explicitly returning a "continuation" pipe. The following operator (>!>) :: Monad m => Pipe a b m r -> Pipe b c m (Pipe a c m r) -> Pipe a c m r p1 >!> p2 = do r0 <- (Left <$> p1) >+> (Right <$> p2) case r0 of Left r -> return r Right p' -> p' could be used to compose such a pipe. Alternatively, one can use 'Control.Pipe.Zip.controllable' together with 'loopP' (there's a similar example in pipes-extra/Examples/finalizers/complex.hs). Unfortunately, both approaches are not compositional. They require you to structure the whole pipeline around them. I suspect it might be possible to incorporate these ideas into the Pipe type without losing associativity, but I don't have any motivating examples where this feature would actually be useful. Do you have anything in mind, Chris? BR, Paolo
participants (4)
-
Ben Franksen
-
Chris Smith
-
Paolo Capriotti
-
Twan van Laarhoven