[Haskell-cafe] Re: Who is afraid of arrows, was Re: ANNOUNCE: Haskell XML Toolbox Version 9.0.0

Heinrich Apfelmus apfelmus at quantentunnel.de
Fri Oct 15 05:44:26 EDT 2010


Uwe Schmidt wrote:
> In HXT, the concept of a filter is the most important one. This
> concept is a natural generalisation of a function (and that's what
> arrows are). A user has to grasp this idea of a filter. And he/she
> can do this even without knowing anything about arrows or monads.
> People knowing a little bit of Unix pipes and filter will become
> easily familiar with the simple parts of this DSL.
>
> [...]
> 
> The intention with HXT was not to build a general purpose languages,
> where you can do any kind of complex things. The intention was to
> build a (rather) simple and and powerful language for processing XML,
> nothing more. You may of course argue, whether we've found the right
> set of combinators, but that's another story. As Sebasiaan wrote in
> this reply, when processing XML, the cases for higher order
> computations are not very frequent. The few combinators available for
> this are, from a "Real World Haskell" point of view, sufficient.
> 
> To sum it up, I think, from an implementers point of view for this
> eDSL, we agree that both ways arrows/monads are possible and rather
> similar. From a users point of view, I prefer a simple and
> specialised DSL, you would prefer a more general one.

The question is indeed whether HXT offers the right set of combinators.
Gregory and I are inclined to assert that monad combinators are most
suitable. Sebastiaan and you prefer the arrow combinators.

But I think that *neither* of these two options satisfies the worthwhile
"simple and specialised DSL" criterion. You already entertain the notion
that this is the case for the monad combinators, so I'll focus on the
arrow case.


The problem with the arrow combinators is that HXT does not use them in
their full generality. Taking chapter 3 of Manuel Ohlendorfs' thesis as
representative example, it is telling that:

* The combinators  first, second, (***) and (&&&) are completely unused,
even though they are the core arrow combinators that can plumb multiple
arguments.
* Multiple arguments are handled with ($<), which is not a general arrow
combinator, but specific to kleisli arrows, i.e. those coming from a monad.

That's why I don't like the slogan "HXT = XML transformations with
arrows": it suggests that the defining property of arrows - not being
able to do currying while still being able to plumb multiple arguments -
is used in an essential way, but this is actually not the case. Like
monads, I think that arrows are not the right abstraction for HXT. (This
reasoning is why I even thought that HXT were poorly designed and that's
why, personally, I avoided using HXT and opted for HaXmL instead.)


Personally, I would be much happier with the slogan "HXT = XML
transformations with filters". Browsing through Manuel's thesis, I
discover that your combinators are quite slick ( >>> , choiceA , when,
guards ), it's just that they are a very specialized subset of the
general arrow combinators. I think that dropping the arrows and
rebranding your nice set of combinators as "filter combinators" would
greatly improve the library. In particular, mastering arrows, like
Manuel does in chapter 2 of this thesis, would become superfluous; an
advantage that is similar to the advantage of not using monads, as you note.


PS:
Interestingly, this whole discussion is caused by just a small technical
restriction of type classes: XMLArrow has to be a newtype because  a ->
[b]  cannot be made an instance of  Arrow . You can make it either an
arrow or a monad, but not both; even though it actually is both.

PSS:
By the way, the reason why I was preferring monad combinators is that
they are a natural extension of lists. For instance, we have

    deep :: (XmlTree -> XmlTree) -> XmlTree -> XmlTree
    deep f xml = [y | x <- children xml, y <- f x `orElse` deep f x]
        where
        [] `orElse` ys = ys
        xs `orElse` _  = xs

which can also be written as

    deep f xml = do
        x <- children xml
        f x `orElse` deep f x


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com






More information about the Haskell-Cafe mailing list