ANNOUNCE: Haskell XML Toolbox Version 9.0.0

Haskell XML Toolbox 9.0.0 I would like to announce a new version of the Haskell XML Toolbox. HXT has grown over the years. Components for XPath, XSLT, validation with RelaxNG, picklers for conversion from/to native Haskell data, lazy parsing with tagsoup, input via curl and native Haskell HTTP and others have been added. This has led to a rather large package with a lot of dependencies. To make the toolbox more modular and to reduce the dependencies on other packages, hxt has been split into various smaller packages since this version. Information about this release, about the new packages, changes and incompatibilities to older versions can be found at HXT home: "http://www.fh-wedel.de/~si/HXmlToolbox/index.html" and on the Haskell wiki page about HXT "http://www.haskell.org/haskellwiki/HXT" The source repo has been moved to GitHub: "http://github.com/UweSchmidt/hxt" Downloads and installation is available from hackage. Please email comments, bugs, etc. to hxmltoolbox@fh-wedel.de or si@fh-wedel.de Uwe -- University of Applied Sciences, Wedel, Germany http://www.fh-wedel.de/~si/index.html

Could you explain to me why HXT uses arrows? I have never been able to figure out what advantage this gives your library over monads. Since your arrows in practice implement ArrowApply, they are really just monads anyway, so it seems to me that using arrows instead of monads only serves to add complexity to the library without adding any benefit. Furthermore, by using arrows instead of monads people cannot use the many standard monad libraries out there, but have to instead write their own generalizations of them to arrows. Is there some benefit that your library gets out of using arrows that I missed which makes these costs worth it? Cheers, Greg On 10/7/10 5:28 AM, Uwe Schmidt wrote:
Haskell XML Toolbox 9.0.0
I would like to announce a new version of the Haskell XML Toolbox.
HXT has grown over the years. Components for XPath, XSLT, validation with RelaxNG, picklers for conversion from/to native Haskell data, lazy parsing with tagsoup, input via curl and native Haskell HTTP and others have been added. This has led to a rather large package with a lot of dependencies.
To make the toolbox more modular and to reduce the dependencies on other packages, hxt has been split into various smaller packages since this version.
Information about this release, about the new packages, changes and incompatibilities to older versions can be found at HXT home:
"http://www.fh-wedel.de/~si/HXmlToolbox/index.html"
and on the Haskell wiki page about HXT
"http://www.haskell.org/haskellwiki/HXT"
The source repo has been moved to GitHub: "http://github.com/UweSchmidt/hxt"
Downloads and installation is available from hackage.
Please email comments, bugs, etc. to hxmltoolbox@fh-wedel.de or si@fh-wedel.de
Uwe
--
University of Applied Sciences, Wedel, Germany http://www.fh-wedel.de/~si/index.html
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Gregory Crosswhite wrote:
Could you explain to me why HXT uses arrows? I have never been able to figure out what advantage this gives your library over monads. Since your arrows in practice implement ArrowApply, they are really just monads anyway, so it seems to me that using arrows instead of monads only serves to add complexity to the library without adding any benefit. Furthermore, by using arrows instead of monads people cannot use the many standard monad libraries out there, but have to instead write their own generalizations of them to arrows.
Is there some benefit that your library gets out of using arrows that I missed which makes these costs worth it?
I have the same question. It looks like the arrows in HXT are typed version of CFilter from Malcolm Wallace, Colin Runciman. Haskell and XML: Generic Combinators or Type-Based Translation? http://www.haskell.org/HaXml/icfp99.html but it appears to me that representing them as type Filter a b = a -> [b] allows the use of the list monad, which would highlight the similarity between list comprehensions and working with XML trees. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Hi Gregory,
Could you explain to me why HXT uses arrows? I have never been able to figure out what advantage this gives your library over monads. Since your arrows in practice implement ArrowApply, they are really just monads anyway, so it seems to me that using arrows instead of monads only serves to add complexity to the library without adding any benefit. Furthermore, by using arrows instead of monads people cannot use the many standard monad libraries out there, but have to instead write their own generalizations of them to arrows.
Is there some benefit that your library gets out of using arrows that I missed which makes these costs worth it?
Hi Heinrich,
I have the same question.
It looks like the arrows in HXT are typed version of CFilter from
Malcolm Wallace, Colin Runciman. Haskell and XML: Generic Combinators or Type-Based Translation? http://www.haskell.org/HaXml/icfp99.html
but it appears to me that representing them as
type Filter a b = a -> [b]
allows the use of the list monad, which would highlight the similarity between list comprehensions and working with XML trees.
I thing, this is not a question of functionality, it's a question of style. Of course everything in hxt could have been done with monads, but does this also mean: Everything must have been done with monads? We all have learned the elegant style of point free programming as described in IFPH and Richard Birds new book gives a lot more valuable examples of this. When these elegant algorithms have to be generalized, e.g. to do some IO, we have to rewrite the whole algorithms in a monadic style. I don't like this. Arrows are a generalisation of functions, so if you know all about working with functions you know (almost) all about working with arrows. When generalizing a pure algorithm, something like "f3 . f2 . f1", or in Unix pipe style "f1 >>> f2 >>> f3", you don't have to rewrite the code, you just generalize function composition. When constructing code, it is of course sometimes simpler to start with a point wise version and then refactor and rewrite it into a more compact point free version. The problem with arrows seems, that the arrow style forces to start with the point free style. And that may be the main hurdle in mind. What we should have done in hxt, is to combine the arrows with arbitrary monads, at the moment the monadic arrows work with a combination of a state and IO. The list gives us the "nondeterminism" and the exception (empty list). You can do a lot of things with this, but it can be generalized. And perhaps we'll do this in the future. I hope this shows a bit of the motivation for taking the arrow approach, Uwe

Uwe, Thank you for your reply. On 10/11/10 6:20 AM, Uwe Schmidt wrote:
I thing, this is not a question of functionality, it's a question of style. Of course everything in hxt could have been done with monads, but does this also mean: Everything must have been done with monads?
No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover situations in which one could not use a monad. When your problem is solved by a monad there is no point in using arrows since an arrow require you to jump through extra hoops to accomplish the same goal.
Arrows are a generalisation of functions, so if you know all about working with functions you know (almost) all about working with arrows. When generalizing a pure algorithm, something like "f3 . f2 . f1", or in Unix pipe style "f1>>> f2>>> f3", you don't have to rewrite the code, you just generalize function composition.
Yes, but the >=> operator lets you do the same thing with monads, and in fact I use it all the time to do point-free programming with monads, so this isn't at all an advantage that arrows have over monads.
When constructing code, it is of course sometimes simpler to start with a point wise version and then refactor and rewrite it into a more compact point free version. The problem with arrows seems, that the arrow style forces to start with the point free style. And that may be the main hurdle in mind.
No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. Second, they place restrictions on how you define the input arguments of the arrow because you can't feed the output of one arrow into to input of the next unless said input is captured in the arrows type. To be more concrete about my second point, suppose you have some monadic action f :: a -> b -> m c How would you structure this same action as an arrow? One thing that you could do is take one of the arguments and turn it into the input of the arrow: f' :: a -> Arrow b c But now you can't feed the output of an arrow into the first argument. Alternatively, you could pack both arguments into the input of the arrow: f'' :: Arrow (a,b) c Great, but now you have made it more awkward to use f'' because you have to always pack the arguments into a tuple, so that for example if one of the arguments is a constant then you can no longer easily use currying. The advantage of f over both alternatives is that you don't have to waste any of your time fitting multiple input arguments into the input type of an arrow. In fact, if the first argument to f'' is usually a constant, then f'' is arguably more awkward to use in a point-free setting than f, because instead of being able to write a >=> f 42 >=> b You have to write something like a >>> (const 42 &&& id) >>> f'' >>> b Of course, if the first argument were *always* a constant then you could use f', but then you lose the ability to ever feed in the output of an arrow into the first argument. So in short, arrows force you to make choices and trade-offs that never come up when using monads. In conclusion, while I greatly appreciate you taking the time to explain your reasoning, it still looks to me like there is nothing you have gained by using arrows except adding extra unnecessary complexity in your library. Cheers, Greg

Gregory Crosswhite schrieb:
In conclusion, while I greatly appreciate you taking the time to explain your reasoning, it still looks to me like there is nothing you have gained by using arrows except adding extra unnecessary complexity in your library.
As a pragmatic question: Would it be possible to split hxt even further into hxt (core) and hxt-arrow, and resurrect hxt-filter? This way people could choose the way they like to process XML. Or is it too tedious to maintain both hxt-arrow and hxt-filter? Is it possible to implement one interface in terms of the other one? It seems that the filter interface is the more general one, such that the arrow interface may be implemented in terms of filters.

Hi, Am Montag, den 11.10.2010, 21:29 +0200 schrieb Henning Thielemann:
Gregory Crosswhite schrieb:
In conclusion, while I greatly appreciate you taking the time to explain your reasoning, it still looks to me like there is nothing you have gained by using arrows except adding extra unnecessary complexity in your library.
As a pragmatic question: Would it be possible to split hxt even further into hxt (core) and hxt-arrow, and resurrect hxt-filter? This way people could choose the way they like to process XML. Or is it too tedious to maintain both hxt-arrow and hxt-filter? Is it possible to implement one interface in terms of the other one? It seems that the filter interface is the more general one, such that the arrow interface may be implemented in terms of filters.
without having something to add about arrows to the discussion, a little side note from your distribution package maintainer: Before you split up stuff even more into little packages, consider keeping one package but offering different modules If it is just about offering alternative APIs (and not really avoiding additional dependencies), this should be sufficient and is less work for us. Thanks, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

Hi Gregory,
... No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover situations in which one could not use a monad. When your problem is solved by a monad there is no point in using arrows since an arrow require you to jump through extra hoops to accomplish the same goal.
As I understood, John Hughes invented the arrows as a generalisation of monads, you say it's a less powerful concept. I'm a bit puzzled with that. Could you explain these different views.
... Yes, but the >=> operator lets you do the same thing with monads, and in fact I use it all the time to do point-free programming with monads, so this isn't at all an advantage that arrows have over monads.
yes, I agree. What about the other combinators (&&&, ***,...)?
... No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. ...
It's rather easy to define some choice combinators. Or am I missing the point?
... Second, they place restrictions on how you define the input arguments of the arrow because you can't feed the output of one arrow into to input of the next unless said input is captured in the arrows type.
To be more concrete about my second point, suppose you have some monadic action
f :: a -> b -> m c
How would you structure this same action as an arrow? One thing that you could do is take one of the arguments and turn it into the input of the arrow:
f' :: a -> Arrow b c
But now you can't feed the output of an arrow into the first argument.
yes, this a common pattern, a function f' with an extra argument of type a, and sometimes you want to call f' with some value, e.g. f' 42, sometimes the extra argument must be computed from the arrow input, let's say with an arrow g. For this case in hxt there is a combinator ($<) with signature ($<) :: (c -> a b d) -> a b c -> a b d With that combinator you can write f' $< g The combinator does the following: The input of the whole arrow is fed into g, g computes some result and this result together with the input is used for evaluating f'. The ($<) is something similar to ($).
Alternatively, you could pack both arguments into the input of the arrow:
f'' :: Arrow (a,b) c
Great, but now you have made it more awkward to use f'' because you have ...
yes, that become rather clumsy.
... In conclusion, while I greatly appreciate you taking the time to explain your reasoning, it still looks to me like there is nothing you have gained by using arrows except adding extra unnecessary complexity in your library.
So, your advice is to throw away the whole arrow stuff in hxt-10 and redefined (or rename) the combinators on the basis of monads? Cheers, Uwe

On Tue, Oct 12, 2010 at 8:56 AM, Uwe Schmidt
No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover situations in which one could not use a monad. When your problem is solved by a monad there is no point in using arrows since an arrow require you to jump through extra hoops to accomplish the same goal.
As I understood, John Hughes invented the arrows as a generalisation of monads, you say it's a less powerful concept. I'm a bit puzzled with that. Could you explain these different views.
These are the same thing, the difference is whether you're talking about how many different concepts are compatible with an abstract structure as opposed to what can be done universally with such a structure. Adding the ability to do more things with a structure necessarily reduces the number of concepts that structure applies to. Perhaps a more familiar example is the relationship Functor > Applicative > Monad. Going left to right adds power, making generic code more expressive but reducing the number of concepts that can be represented as instances; going right to left adds generality, limiting what generic code can do but enabling more instances. That said, I dislike calling arrows a generalization of monads--it's not incorrect as such, but I don't think it aids understanding. It really is much better to think of them as generalized functions, which they explicitly are if you look at the borrowed category theory terminology being used. They're generalized monads only in the sense that functions (a -> m b) form arrows in a category, as far as I can tell.
No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. ...
It's rather easy to define some choice combinators. Or am I missing the point?
The key point is that arrows in full generality--meaning instances of Arrow only, not other type classes--are not higher-order because no internal application operator is provided. The ArrowApply class gives you full higher-order generalized functions, at the cost of giving up some useful limitations (read: static guarantees about code behavior) that make reasoning about arrow-based structures potentially easier. So, a general arrow can perform different actions and produce different output based on input it receives, but it can't take *other arrows* and pick different ones to use depending on its input.
The combinator does the following: The input of the whole arrow is fed into g, g computes some result and this result together with the input is used for evaluating f'. The ($<) is something similar to ($).
There's no shortage of ways to deal with the issue, but they all rely on using combinator *functions*, not arrows. The result is that arrow-based expressions tend to be internally less flexible, following pre-defined paths, similar to how expressions using Applicative can't embed control flow the way ones using Monad can. Which is fine for many purposes, of course. Essentially, arrows lend themselves best to composing first-order computations to create larger computations with a fixed structure. If you find yourself forced to frequently use ArrowApply or other means of eliminating higher-order structure--e.g., anything that results in an arrow with an output type that contains fewer instances of the arrow's own type constructor than does the input type--it may be worth considering if arrows are really what you want to use. Personally, though, I think monads are really overkill in many cases and strongly prefer, where possible, to use Applicative or Arrow. - C.

On Tue, Oct 12, 2010 at 8:56 AM, Uwe Schmidt
wrote: No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover situations in which one could not use a monad.
On Tue, Oct 12, 2010 at 9:49 AM, C. McCann
Essentially, arrows lend themselves best to composing first-order computations to create larger computations with a fixed structure. If you find yourself forced to frequently use ArrowApply or other means of eliminating higher-order structure--e.g., anything that results in an arrow with an output type that contains fewer instances of the arrow's own type constructor than does the input type--it may be worth considering if arrows are really what you want to use.
Personally, though, I think monads are really overkill in many cases and strongly prefer, where possible, to use Applicative or Arrow.
Well I am compelled to add my two cents worth to this conversation. I like to use examples, so that is what I will do. I am going to use a simple one, and you may wonder why I used an arrow to represent this little computation, but the main reason is that it fits the way I think better then if's , guards, cases, in or where clauses. The entirety of a computation is right there in my face. The other thing that I will explain after showing this little example function {arrow under the hood} is that it leads to more thinking of composing into even more higher orderness, until you have a single function definition that can be the entire program. Function splitMiddle: Takes a list and returns a pair consisting of the list split into two equal parts. splitMiddle :: forall a. [a] -> ([a], [a]) splitMiddle = (id &&& (length >>> flip div 2)) >>> (\(xs,a) -> splitAt a xs) usage: splitMiddle [1..10] ([1,2,3,4,5],[6,7,8,9,10]) OKAY here is where the thoughts can come in to play and are a direct result of the pointfree style that is adopted as a direct result of using arrow notation. To split the list of words of a line of text you may do this initially: splitMiddle $ words "Now is the time to come to the aid of our country" (["Now","is","the","time","to","come"],["to","the","aid","of","our","country"]) Then it occurs that well hell, why not move the "words" function into the arrow: (words >>> splitMiddle) "Now is the time to come to the aid of our country" (["Now","is","the","time","to","come"],["to","the","aid","of","our","country"]) That can be turned into a new function with great ease and clarity: splitSentence :: String -> ([String], [String]) splitSentence = words >>> splitMiddle Then maybe I decide, hey, I only want the second half of the sentence: sndHalfSentence :: String -> [String] sndHalfSentence = words >>> splitMiddle >>> snd or if I have defined splitSentence as above: sndHalfSentence :: String -> [String] sndHalfSentence = splitSentence >>> snd doing the function fstHalfSentence is obvious in that the mechanics are right there to see and no variables to muck it up, just change the snd to fst : fstHalfSentence :: String -> [String] fstHalfSentence = splitSentence >>> fst The other nice use of arrow is INSIDE of a monadic structure: "Now is the time to come to the aid of our country" >>= (return >>> words
concat) "Nowisthetimetocometotheaidofourcountry"
which can become the definition of squeeze: squeeze :: [Char] -> [Char] *Big3> let squeeze cs = cs >>= (return >>> words >>> concat) squeeze "Now is the time to come to the aid of our country" "Nowisthetimetocometotheaidofourcountry" and then of course you can do a few sentences instead of only one,if you change the definition with the simple addition of an applicative operator to the mix. squeezeSentenceF :: forall (f :: * -> *). (Functor f) => f [Char] -> f [Char] squeezeSentenceF css = (squeeze <$>) css squeezeSentenceF ["This is how to do a list of sentences", "It makes use of applicatives too"] ["Thisishowtodoalistofsentences","Itmakesuseofapplicativestoo"] notice that this is more general then just mapping as it applies to any functor, of which the Maybe monad has an instance.. so: squeezeSentenceL (Just "This is how to do a Maybe sentence") Just "ThisishowtodoaMaybesentence" works just nicely. I think that the more you mix and match ALL of the tools and do a little experimentation with them, that it then begins to be a situation where your thoughts of how to compose things are not locked down to one way and it opens up your mind to many possibilities. I am a proponent of having and using ALL the available tools in a mix and match way if need be. About the only thing you have to do to use any of the various tools in the same line of code is to remember to use a parenthetic bit of separation between one and the next. metacode" xss >>= ( ((g >>> h) <$>) >>> return) so you are using a monadic bind to shove something of {functor f, monad m} embodied in xss such that f (m x) has the functions g and then h applied to the elements of the monad 'm' inside of the functor f and then have that structure returned as: f (m ((g>>>f) x)). Okay, I am totally done with that.. probably just muddied things up, but maybe make sense if you try using ghci after loading a dummy module that imports Control.Monad, Control.Arrow and Control.Applicative. I just think that one is missing out when not using ALL the computational tools. cheers, gene

On 10/12/10 12:39 PM, Gene A wrote:
splitMiddle :: forall a. [a] -> ([a], [a]) splitMiddle = (id &&& (length >>> flip div 2)) >>> (\(xs,a) -> splitAt a xs)
But is that really easier to understand at a glance then splitMiddle xs = splitAt (length xs `div` 2) xs ? It seems to me that while point-free style is nice and I personally us it extensively, sticking to it religiously can sometimes lead to code that is *less* clear. Also, I don't see why one would prefer >>> over the standard function composition operator, ".". Using this and uncurry you could actually make your point-free style definition much more succinct and arguably easier to read: splitMiddle = uncurry splitAt . ((`div` 2) . length &&& id)
OKAY here is where the thoughts can come in to play and are a direct result of the pointfree style that is adopted as a direct result of using arrow notation. [...]
I completely agree with you that point-free style is nice; I am certainly not arguing against it. However, it can be over-kill, and there is no reason that I can see why using the arrow notation ">>>" in place of the standard function notation "." helps one write function in a point-free style.
The other nice use of arrow is INSIDE of a monadic structure:
"Now is the time to come to the aid of our country" >>= (return >>> words >>> concat) "Nowisthetimetocometotheaidofourcountry" [...]
Your use of a monad here both redundant and obfuscatory; a much simpler version of this code is (concat . words) "Now is the time to come to the aid of our country"
squeezeSentenceF :: forall (f :: * -> *). (Functor f) => f [Char] -> f [Char] squeezeSentenceF css = (squeeze <$>) css squeezeSentenceF ["This is how to do a list of sentences", "It makes use of applicatives too"] ["Thisishowtodoalistofsentences","Itmakesuseofapplicativestoo"] [...]
You aren't really using applicative style here, you are just defining a shorthand for calling "fmap squeeze". Also, your function could be expressed in point-free style as follows: squeezeSentenceF = fmap squeeze
I think that the more you mix and match ALL of the tools and do a little experimentation with them, that it then begins to be a situation where your thoughts of how to compose things are not locked down to one way and it opens up your mind to many possibilities. I am a proponent of having and using ALL the available tools in a mix and match way if need be.
I agree, but what I oppose is the choice of fancy tools because they are fancy rather than because they get the job done better than simple tools, because the fancy tools often carry a price with them over the simpler tools. Cheers, Greg

2010/10/12 Gregory Crosswhite
Also, I don't see why one would prefer >>> over the standard function composition operator, ".".
With "." you have to read right-to-left to follow data's path. For me that reading order isn't natural, and I imagine it is so for most people which don't have a mathematical background. Combined with >>= / >> you have multiple reading direction in the same expression, as in expression ( c . b . a ) `liftM` a1 >>= a2 >>= a3 reading order 6 5 4 1 2 3 So that could be one reason.

David Virebayre wrote:
Gregory Crosswhite wrote:
Also, I don't see why one would prefer >>> over the standard function composition operator, ".".
With "." you have to read right-to-left to follow data's path.
For me that reading order isn't natural, and I imagine it is so for most people which don't have a mathematical background.
Combined with >>= / >> you have multiple reading direction in the same expression, as in
expression ( c . b . a ) `liftM` a1 >>= a2 >>= a3 reading order 6 5 4 1 2 3
So that could be one reason.
That's why I'm usually using =<< instead of >>= . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Wed, Oct 13, 2010 at 3:50 AM, Heinrich Apfelmus
Combined with >>= / >> you have multiple reading direction in the same expression, as in
expression ( c . b . a ) `liftM` a1 >>= a2 >>= a3 reading order 6 5 4 1 2 3
That's why I'm usually using =<< instead of >>= .
Does it bother you that (=<<) is defined to be infixr 1, while (<$>) and (<*>) are infixl 4? Or is that just me? For instance, I might write the above expression as something like: a3 =<< a2 =<< a . b . c <$> a1 But this still seems awkward, because it mixes different fixities and I have to mentally regroup things when reading it. Right associativity here does make a certain amount of sense for monads, but left-associativity is consistent with plain function application and feels more natural to me. - C.

C. McCann wrote:
Heinrich Apfelmus wrote:
Combined with >>= / >> you have multiple reading direction in the same expression, as in
expression ( c . b . a ) `liftM` a1 >>= a2 >>= a3 reading order 6 5 4 1 2 3
That's why I'm usually using =<< instead of >>= .
Does it bother you that (=<<) is defined to be infixr 1, while (<$>) and (<*>) are infixl 4? Or is that just me?
For instance, I might write the above expression as something like:
a3 =<< a2 =<< a . b . c <$> a1
But this still seems awkward, because it mixes different fixities and I have to mentally regroup things when reading it. Right associativity here does make a certain amount of sense for monads, but left-associativity is consistent with plain function application and feels more natural to me.
Well, you can't give (=<<) left fixity because its type doesn't allow it. (a3 =<< a2) =<< a1 -- ill-typed! So, (=<<) is modeled after (:) , not after (<$>) . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

David Virebayre schrieb:
2010/10/12 Gregory Crosswhite
: Also, I don't see why one would prefer >>> over the standard function composition operator, ".".
With "." you have to read right-to-left to follow data's path.
For me that reading order isn't natural, and I imagine it is so for most people which don't have a mathematical background.
Combined with >>= / >> you have multiple reading direction in the same expression, as in
expression ( c . b . a ) `liftM` a1 >>= a2 >>= a3 reading order 6 5 4 1 2 3

2010/10/13 Henning Thielemann
David Virebayre schrieb:
2010/10/12 Gregory Crosswhite
: Also, I don't see why one would prefer >>> over the standard function composition operator, ".".
With "." you have to read right-to-left to follow data's path.
For me that reading order isn't natural, and I imagine it is so for most people which don't have a mathematical background.
Very informative link, thanks. Fortunately the time when I was struggling with all that is gone; Even though right-to-left still isn't "natural" to me, I've now written enough haskell so that isn't a problem anymore. I don't even try to use >>> redefine a left-to-right composition operator in my programs, I'm converted ! My previous post was just me remembering my (past) problems with "." to answer Gregory's question. David.

On 10/12/10 5:56 AM, Uwe Schmidt wrote:
Hi Gregory,
As I understood, John Hughes invented the arrows as a generalisation of monads, you say it's a less powerful concept. I'm a bit puzzled with that. Could you explain these different views.
Consider the following example: f :: Int -> m a f i = monads !! (i *5 `mod` length monads) where monads = [...] :: [m a] In this case, we see that the action chosen by f is a non-trivial function of the input argument. In general, there is no way that we can represent this equivalently as an arrow. The reason why is because, unlike monads, in general arrows do not give you arbitrary freedom to choose the action performed by the arrow. It is true that one can get this freedom back for arrows which are instances of ArrowApply, but that that point what you really have is a monad with different notation. Hughes himself said that when your arrow is an instance of ArrowApply, you are better off just sticking with monads. The reason for the existence of arrows is because allowing the user to arbitrarily choose actions restricts the power that the creator of a library has to do stuff behind the scenes with these actions. To see why, suppose we are chaining together two arrows like so: f :: Arrow a b g :: Arrow b c h :: Arrow a c h = f >>> g When defining the composition operator >>>, the library author has the power to "open up" both of the actions f and g, which gives him lots of power in defining what h should be. By contrast, suppose we are chaining together two monads like this: f :: Monad b g :: b -> Monad c h :: Monad c h = f >>= g When defining the composition operator >>=, the library author can look inside f, but he has no way of knowing which action will be chosen by g, so he cannot use this information to decide what h should be. The motivation Hughes gave for arrows was parsers that have a "static" part in them; he pointed out that using monads we have no way to access and combine these static parts, so we needed to come up with a formalism that let us have a nice combinator framework like monads but which allows us to "break open" components so that we can combine them in interesting ways. So in short, arrows (relative to monads) take away some of the power of the user to choose actions as a function of the input in order to give library authors more power to define how actions are combined. In this sense arrows are "less powerful" from a user perspective than monads, except in the case where an arrow is an instance of ArrowApply in which case they are
... Yes, but the>=> operator lets you do the same thing with monads, and in fact I use it all the time to do point-free programming with monads, so this isn't at all an advantage that arrows have over monads. yes, I agree. What about the other combinators (&&&, ***,...)?
A couple of points in response. First, though it is less convenient, you can use those combinators if you wrap your arrow inside the Kleisli newtype wrapper, which is something I have occasionally done. Second, while I see your point that there are some combinators that arrows have that are not defined for monads, there are not that many of them, and it would be trivial to write special instances of them for monads; it seems to me that the price of making versions of these operators for monads is less than the price of having to re-implement all of the existing monad combinators and libraries using arrow notation just to not have to redefined monad versions of &&&, etc.
... No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. ... It's rather easy to define some choice combinators. Or am I missing the point?
No, in general arrows do not allow you to define choice combinators. Having said that, you *can* give the user some power to choose between fixed choices action in exchange for possibly losing power from your perspective a library author. If your arrow is an instance of ArrowChoice, then you give your user the ability to choose between a fixed set of predefined actions. However, the user is not able to compute an arbitrary action in response to an input. To get this power, you need to make your arrow an instance of ArrowApply, in which case you really aren't getting any benefit from the perspective of either a user *or* a library author over using a monad.
yes, this a common pattern, a function f' with an extra argument of type a, and sometimes you want to call f' with some value, e.g. f' 42, sometimes the extra argument must be computed from the arrow input, let's say with an arrow g.
For this case in hxt there is a combinator ($<) with signature
($<) :: (c -> a b d) -> a b c -> a b d
With that combinator you can write
f' $< g
The combinator does the following: The input of the whole arrow is fed into g, g computes some result and this result together with the input is used for evaluating f'. The ($<) is something similar to ($).
Fair enough.
... In conclusion, while I greatly appreciate you taking the time to explain your reasoning, it still looks to me like there is nothing you have gained by using arrows except adding extra unnecessary complexity in your library. So, your advice is to throw away the whole arrow stuff in hxt-10 and redefined (or rename) the combinators on the basis of monads?
Cheers,
Uwe
Yes, of course it is!!! Of course, given how much work you put into hxt, you would most likely be a fool if you actually took my advice... ;-) So, no, despite the way I am probably coming across I am not actually trying to convince you to rewrite your library from scratch to use monads. My actual goals are twofold: First (driven by genuine curiosity) to see if there is something that I missed that made arrows be the natural choice for you to use in your library. Second, to try and convince people in the future who are considering basing their libraries on arrows that they should only do this if monads do not give them enough power as library authors. Cheers, Greg

On Tuesday 12 October 2010 4:02:06 pm Gregory Crosswhite wrote:
Hughes himself said that when your arrow is an instance of ArrowApply, you are better off just sticking with monads.
Well, this is not necessarily good advice. It is true that ArrowApply will preclude some sort of static analysis. But, this does not mean that you cannot do the static analysis on the pieces of code that *can* be written using less powerful arrow combinators. The same can be said about Applicative, Monad, etc. The combinators in the former could be implemented in ways that allow some extra analysis to be done, while those in the latter are still available when absolutely necessary. I believe the Utrecht parsing library does this, and encourages parsers to be written in applicative style as much as possible for this reason. If you have nothing like that to gain, though, it may make sense to jettison arrows due merely to syntactic considerations and the like, though. -- Dan

On 10/12/10 1:22 PM, Dan Doel wrote:
On Tuesday 12 October 2010 4:02:06 pm Gregory Crosswhite wrote:
Hughes himself said that when your arrow is an instance of ArrowApply, you are better off just sticking with monads. Well, this is not necessarily good advice. It is true that ArrowApply will preclude some sort of static analysis. But, this does not mean that you cannot do the static analysis on the pieces of code that *can* be written using less powerful arrow combinators.
Okay, you make a good point here; it might be the case that it is worth implementing an Arrow interface in order to provide a set of combinators that can do static analysis and hence confer some sort of benefit such as improved performance.
The same can be said about Applicative, Monad, etc. The combinators in the former could be implemented in ways that allow some extra analysis to be done, while those in the latter are still available when absolutely necessary. I believe the Utrecht parsing library does this, and encourages parsers to be written in applicative style as much as possible for this reason.
Darnit, you are using my own arguments against me here. ;-) I say this because earlier in this forum I personally argued that it there are times when it is beneficial to have the Applicative instance not directly follow the Monad instance so that you do interesting things that you can't do with the Monad instance, such as running computations in parallel. Thus, likewise I am forced to see your point and conclude that it might be useful sometimes to define an Arrow instance in addition to a Monad instance so that the Arrow instance can take advantage of the Arrow structure to do interesting things. This has definitely given me food for thought; thank you.
If you have nothing like that to gain, though, it may make sense to jettison arrows due merely to syntactic considerations and the like, though.
Yes, I agree, and in fact this the point that I have been trying to make all along. Cheers, Greg

Hi Gregory,
As I understood, John Hughes invented the arrows as a generalisation of monads, you say it's a less powerful concept. I'm a bit puzzled with that. Could you explain these different views.
Consider the following example:
f :: Int -> m a f i = monads !! (i *5 `mod` length monads) where monads = [...] :: [m a]
In this case, we see that the action chosen by f is a non-trivial function of the input argument. In general, there is no way that we can represent this equivalently as an arrow. The reason why is because,
thanks for the explanation, I thik I got that.
So, your advice is to throw away the whole arrow stuff in hxt-10 and redefined (or rename) the combinators on the basis of monads? ... Yes, of course it is!!! Of course, given how much work you put into hxt, you would most likely be a fool if you actually took my advice... ;-)
Of course the remark about hxt-10 wasn't meant to be totally serious.
So, no, despite the way I am probably coming across I am not actually trying to convince you to rewrite your library from scratch to use monads. My actual goals are twofold: First (driven by genuine curiosity) to see if there is something that I missed that made arrows be the natural choice for you to use in your library. Second, to try and convince people in the future who are considering basing their libraries on arrows that they should only do this if monads do not give them enough power as library authors.
I'm not really convinced of your point of view. I agree much more with the point of view that Sebastiaan Visser described in his post. Let me explain this. HXT as other libraries (HXML, HaXml) defines an embedded DSL for processing XML. When starting to work with this DSL, the main task for a user is to understand the semantics of this DSL, the underlying data types, the primitive operations, the combinators, how to execute a DSL program, and how to plug in own primitive operations. 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. As a user of this DSL, I'm not really interested whether it's implemented with arrows, with monads, or something else, I just want to have the right combinators to formulate the task to be performed by the program. From the point of an implementer, we agree, that for HXT an arrow based implementation is equivalent to a monad based one. So there's no open point. 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. Cheers, Uwe

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

On 15 Oct 2010, at 10:44, Heinrich Apfelmus wrote:
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.
But then, HXT's filter combinators would return to being rather like HaXml's filter combinators, where the concept was first introduced. Personally, I'm very happy that customers avoid HXT (due to the complexity of the arrow interface), because that means more customers for HaXml... :-) Regards, Malcolm P.S. Coming soon in the next release of HaXml: full support for xmlns namespaces, and an XSDToHaskell translator.

15.10.2010 15:03, Malcolm Wallace пишет:
On 15 Oct 2010, at 10:44, Heinrich Apfelmus wrote:
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.
But then, HXT's filter combinators would return to being rather like HaXml's filter combinators, where the concept was first introduced. Personally, I'm very happy that customers avoid HXT (due to the complexity of the arrow interface), because that means more customers for HaXml... :-)
Regards, Malcolm
P.S. Coming soon in the next release of HaXml: full support for xmlns namespaces, and an XSDToHaskell translator.
Sorry, for offtopic. But how in HaXml will look equivalent this filter: data MyAttr = MyAttr String String getAttrs = deep (isElem >>> hasName "SomeTag") >>> proc x -> do aname <- getAttrValue "Name" -< x atype <- getAttrValue "Type" -< x returnA -< MyAttr aname atype I personally have swithed to HaXml because they have less memory consumption, but for extracting attributes from nodes haven't found standart method. Regards, Dmitriy

Malcolm Wallace wrote:
Heinrich Apfelmus wrote:
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.
But then, HXT's filter combinators would return to being rather like HaXml's filter combinators, where the concept was first introduced. Personally, I'm very happy that customers avoid HXT (due to the complexity of the arrow interface), because that means more customers for HaXml... :-)
Well, having seen some HXT code, the old HaXml filters appear somewhat dusty to me. ;-) For example, Nikiti Dimitriy's code
data MyAttr = MyAttr String String
getAttrs = deep (isElem >>> hasName "SomeTag") >>> proc x -> do aname <- getAttrValue "Name" -< x atype <- getAttrValue "Type" -< x returnA -< MyAttr aname atype
illustrates that there is no obvious way to extract non-XML values, like a pair of attribute values. I'm not keen on the proc syntax; this is best modeled as an applicative functor. Other useful innovations that I think are worth incorporating into HaXml in some form: * choiceA , a nifty case statement for filters, generalizing "if then else" * listA , a filter that returns the list of results as a single element. This is pretty much the only way to process XML files that use positional information as well (compared to nesting alone). For instance, the (old) Apple .plist format works like that <key>Caption</key> -- key <string>Haskell Logo</string> -- value <key>Thumbnail</key> <string>/Volumes/Macintosh HD/</string> (This is similar to the purpose of the + selector in CSS, e.g. h2 + p ) Oh, and last but not least, I think the Haddock documentation for Text.XML.HaXml.Combinators is a bit sparse. The paper should be hyperlinked from the docs, and I would very much like to see documentation for the individual filters, with laws and implementation and all. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Gregory, I use arrows (especially list arrows) in a lot of my projects and find them (after some training) easier to work with than monands. Code that I write point-free using arrows generally contains fewer bugs than code I write in monadic style. On Oct 11, 2010, at 8:48 PM, Gregory Crosswhite wrote:
Uwe,
Thank you for your reply.
On 10/11/10 6:20 AM, Uwe Schmidt wrote:
I thing, this is not a question of functionality, it's a question of style. Of course everything in hxt could have been done with monads, but does this also mean: Everything must have been done with monads?
No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover situations in which one could not use a monad. When your problem is solved by a monad there is no point in using arrows since an arrow require you to jump through extra hoops to accomplish the same goal.
I think it is unfair to say that arrows add complexity over monads. This statement can only be true to people who actually know monads and do not know arrows. This has more to do with the direction of one's knowledge than the 'complexity' (whatever this means) of a programming abstraction. Don't see arrows a less restricted monads, see them as a generalization of functions, than it will all make sense. Use them in situations that need generalization of functions, not in cases that require the power of monads.
Arrows are a generalisation of functions, so if you know all about working with functions you know (almost) all about working with arrows. When generalizing a pure algorithm, something like "f3 . f2 . f1", or in Unix pipe style "f1>>> f2>>> f3", you don't have to rewrite the code, you just generalize function composition.
Yes, but the >=> operator lets you do the same thing with monads, and in fact I use it all the time to do point-free programming with monads, so this isn't at all an advantage that arrows have over monads.
I'd rather use (.) for composition of expressions than (<=<) and I'd rather use the 'id' for identity than return. Writing my arrow computations point-free as if they were functions feels far less clumsy and a far more readable than monadic style.
When constructing code, it is of course sometimes simpler to start with a point wise version and then refactor and rewrite it into a more compact point free version. The problem with arrows seems, that the arrow style forces to start with the point free style. And that may be the main hurdle in mind.
No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. Second, they place restrictions on how you define the input arguments of the arrow because you can't feed the output of one arrow into to input of the next unless said input is captured in the arrows type.
This restriction, though not always, can be very useful. This restriction allows you to do full inspection of the arrow expression. This inspection can in some cases be used to serialize an arrow computation of statically optimize it to a more efficient form. When you don't need the power of Monads (or ArrowApply) why use a formalism that does provide this power? That will only make it harder to reason about your program, which isn't quite the Haskell way.
To be more concrete about my second point, suppose you have some monadic action
f :: a -> b -> m c
How would you structure this same action as an arrow? One thing that you could do is take one of the arguments and turn it into the input of the arrow:
f' :: a -> Arrow b c
But now you can't feed the output of an arrow into the first argument. Alternatively, you could pack both arguments into the input of the arrow:
f'' :: Arrow (a,b) c
Great, but now you have made it more awkward to use f'' because you have to always pack the arguments into a tuple, so that for example if one of the arguments is a constant then you can no longer easily use currying. The advantage of f over both alternatives is that you don't have to waste any of your time fitting multiple input arguments into the input type of an arrow.
In fact, if the first argument to f'' is usually a constant, then f'' is arguably more awkward to use in a point-free setting than f, because instead of being able to write
a >=> f 42 >=> b
You have to write something like
a >>> (const 42 &&& id) >>> f'' >>> b
Of course, if the first argument were *always* a constant then you could use f', but then you lose the ability to ever feed in the output of an arrow into the first argument. So in short, arrows force you to make choices and trade-offs that never come up when using monads.
This problem is obviously an engineering problem and not a conceptual problem. Using the tuple input gives you more power but sometimes less convenience, factoring out the argument to true function space might be more pleasant to use but is sometimes to restrictive. The choice depends on your problem domain. In most situations I've encountered this assessment does not surface a lot.
In conclusion, while I greatly appreciate you taking the time to explain your reasoning, it still looks to me like there is nothing you have gained by using arrows except adding extra unnecessary complexity in your library.
I've worked with HXT quite a lot and find XML arrows very convenient.
Cheers, Greg
Gr, Sebastiaan

Dear Sebastiaan,
I would first refer to the description of the "Change function" in a
paper by Erik Meijer (an Haskeller among the designers of F#):
http://portal.acm.org/citation.cfm?id=1297027.1297078
In short, programmers will learn something new only if the improvement
is worth the effort of the paradigm shift.
Below I add my opinions on the specific problem. A disclaimer: I am
unfamiliar with monads myself, I claim awareness of a meta-problem,
which is IMHO more important.
On Oct 12, 3:29 pm, Sebastiaan Visser
Gregory,
I use arrows (especially list arrows) in a lot of my projects and find them (after some training) easier to work with than monands. Code that I write point-free using arrows generally contains fewer bugs than code I write in monadic style.
I think it is unfair to say that arrows add complexity over monads. This statement can only be true to people who actually know monads and do not know arrows. This has more to do with the direction of one's knowledge than the 'complexity' (whatever this means) of a programming abstraction.
Were you writing a paper, your comment would be fully valid. Here we're talking about a library for people to use in practice. In the middle, somebody should make sure that people without a PhD can learn arrows, by providing documentation. The problem might be just educational, and it's not restricted to arrows, but it is still a valid problem. When you write a library for general consumption (like here), you should strive to have a simple and effective interface for people. Try to think of what's happening. Even the existence of this thread is surprising. Haskell programmers, and experienced ones, are discussing about how to express a two arguments function with arrows. Can you imagine a C programmer asking that? The answer would be "RTFM" or "STFW", or less polite than that. And that's GOOD. You can use arrows because you got an useful intuition of them. Good for you. The problem is partially the same as with monads, only to a greater extent: monads can be easy if you don't try to relate them to category theory, and they are indeed considered easy in F# (see the same paper). Again, the problem is maybe mostly educational, but it is entirely valid. Of course, the root question is: what is the purpose of Haskell? 1) Is it to produce pure research, which might then be reused in production to actually affect software engineering, and used directly by blessed PhD students? 2) Or should Haskell be used as such? Some people argue for 2), but the "research bias" of the community is still quite strong. And you can't achieve 2) well working with a research methodology. For instance, somebody needs to write _complete_ documentation (I see there is some, but it doesn't cover the basic questions you are discussing), intended for users, rather than papers. Like it happens for any other language. Of course, nobody _has to do_ anything. I'm a PhD student, I couldn't work on any of this because it wouldn't count for my career. But at least I'm aware my work won't be usable for purpose 2). (Intermediate situations, like writing a paper _and_ a dumbed-down version for general consumption, are also possible of course). Best regards

On Tue, Oct 12, 2010 at 3:00 PM, Paolo G. Giarrusso
Were you writing a paper, your comment would be fully valid. Here we're talking about a library for people to use in practice. In the middle, somebody should make sure that people without a PhD can learn arrows, by providing documentation. The problem might be just educational, and it's not restricted to arrows, but it is still a valid problem.
Oh, for crying out loud, no it isn't. I don't have a PhD. I don't have any graduate degree at all. I didn't learn anything about functional programming back when I was an undergraduate at a not-exactly-prestigious school, never mind category theory or abstract algebra or any of that stuff, and I only started even learning Haskell barely a year ago. Arrows are easy to understand. Yes, really. I'll agree that a lot of libraries on hackage could stand to have better documentation and examples of usage--and I've not actually used HXT itself so I can't speak to how well it does--but I honestly cannot begin to imagine how using a fairly straightforward type class that's part of the core libraries included with the most popular compiler is a problem.
When you write a library for general consumption (like here), you should strive to have a simple and effective interface for people.
Arrows *are* a simple and effective interface. Whether they're the best interface to choose for any specific library is a trickier question, of course, but that's because choosing how to structure a library interface is always difficult.
Try to think of what's happening. Even the existence of this thread is surprising. Haskell programmers, and experienced ones, are discussing about how to express a two arguments function with arrows. Can you imagine a C programmer asking that? The answer would be "RTFM" or "STFW", or less polite than that. And that's GOOD. You can use arrows because you got an useful intuition of them. Good for you.
There's only one way to express a general arrow with two inputs: Use a tuple, because general arrows can't be curried. The discussion is about converting a two-argument function to an arrow directly vs. using one argument as a parameter to a function that constructs a single-input arrow, and the only reason it's an issue is because the syntax for supplying a constant argument to an arrow is a bit clunkier than doing so for a function. A better analogy might be programmers using some OO language discussing whether some piece of usually-static data that an object needs should be a method parameter (likely creating a bunch of redundant code) or set just once by a constructor parameter (awkward in those cases where it does need to change). It is, as Sebastiaan Visser said, an engineering problem, not a conceptual problem. Avoiding arrows would simply produce a different set of engineering problems to consider.
Some people argue for 2), but the "research bias" of the community is still quite strong. And you can't achieve 2) well working with a research methodology. For instance, somebody needs to write _complete_ documentation (I see there is some, but it doesn't cover the basic questions you are discussing), intended for users, rather than papers. Like it happens for any other language.
I do get a little tired of finding libraries whose only documentation consists of a couple papers, found in PDF form on the author's university homepage (or worse, no documentation at all). But expecting a library like HXT to walk someone through how to use libraries that are included with GHC seems a bit unreasonable.
Of course, nobody _has to do_ anything. I'm a PhD student, I couldn't work on any of this because it wouldn't count for my career. But at least I'm aware my work won't be usable for purpose 2). (Intermediate situations, like writing a paper _and_ a dumbed-down version for general consumption, are also possible of course).
I don't like the idea that things need to be "dumbed-down" for general use. Programmers aren't stupid and they can learn new ideas. Talking about stuff like it's some crazy incomprehensible deep magic that only super-geniuses can understand is silly and not helpful. ...Well, that all probably came out sounding harsher than I intended, my apologies if so. I'm just a little weary of seeing ideas like arrows made out to be more complicated than they really are; I honestly think at least 90% of what makes them seem difficult is people telling each other how difficult they are! - C.

On 10/12/10 6:29 AM, Sebastiaan Visser wrote:
Gregory,
I use arrows (especially list arrows) in a lot of my projects and find them (after some training) easier to work with than monands. Code that I write point-free using arrows generally contains fewer bugs than code I write in monadic style.
So what it is that you like is the point-free style rather than the use of arrows. There is nothing stopping you from using point-free style with monads, and I personally prefer to do so when I can. So to repeat this again, I am not arguing against point-free style, I am arguing against basing libraries on arrows instead of monads unless one specifically needs the more general structure of the arrows because otherwise it makes life less convenient for the user as (among other reasons) it introduces extra syntax and prevents use of standard monad combinators and libraries.
I think it is unfair to say that arrows add complexity over monads. This statement can only be true to people who actually know monads and do not know arrows. This has more to do with the direction of one's knowledge than the 'complexity' (whatever this means) of a programming abstraction.
I can assure you that I have spent a lot of time looking at arrows and even once wrote and used instance of Arrow myself in a situation where a monad would not have been appropriate. To be specific: the additional complexity comes from the fact that additional notation is needed to accomplish the same goal, and from the fact that standard monad combinators and libraries cannot be used. This isn't simply a matter of being unfamiliar with arrows.
Don't see arrows a less restricted monads, see them as a generalization of functions, than it will all make sense. Use them in situations that need generalization of functions, not in cases that require the power of monads.
I am not sure what you are getting at with this, because your description contradicts my usual notion of when one uses monads and arrows --- namely, when one is working with a structure that fits one or the other of the two patterns and one wants to leverage special libraries and/or syntax.
Arrows are a generalisation of functions, so if you know all about working with functions you know (almost) all about working with arrows. When generalizing a pure algorithm, something like "f3 . f2 . f1", or in Unix pipe style "f1>>> f2>>> f3", you don't have to rewrite the code, you just generalize function composition. Yes, but the>=> operator lets you do the same thing with monads, and in fact I use it all the time to do point-free programming with monads, so this isn't at all an advantage that arrows have over monads. I'd rather use (.) for composition of expressions than (<=<) and I'd rather use the 'id' for identity than return. Writing my arrow computations point-free as if they were functions feels far less clumsy and a far more readable than monadic style.
Fair enough, but again, in exchange for these two operators you lose monadic combinators and libraries and introduce additional syntax.
When constructing code, it is of course sometimes simpler to start with a point wise version and then refactor and rewrite it into a more compact point free version. The problem with arrows seems, that the arrow style forces to start with the point free style. And that may be the main hurdle in mind.
No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. Second, they place restrictions on how you define the input arguments of the arrow because you can't feed the output of one arrow into to input of the next unless said input is captured in the arrows type. This restriction, though not always, can be very useful. This restriction allows you to do full inspection of the arrow expression. This inspection can in some cases be used to serialize an arrow computation of statically optimize it to a more efficient form.
I agree completely! This is *exactly* the kind of time when it is appropriate to use an arrow. The choice of whether to use an arrow or a monad should be based on the structure of the underlying system, with the latter to be preferred unless there is a good reason to choose the former.
When you don't need the power of Monads (or ArrowApply) why use a formalism that does provide this power? That will only make it harder to reason about your program, which isn't quite the Haskell way.
Because, again, it makes the life of the user of your library easier --- for example, when they decide to use it in a way that is perfectly legitimate but is not something you had thought of in advance. Put another way, why should one place an arbitrary restriction on the user when there is nothing gained by it?
I've worked with HXT quite a lot and find XML arrows very convenient.
Fair enough. Cheers, Greg

On Oct 11, 2010, at 11:48 AM, Gregory Crosswhite wrote:
No, but there is no point in using a formalism that adds complexity without adding functionality. Arrows are more awkward to use than monads because they were intentionally designed to be less powerful than monads in order to cover situations in which one could not use a monad. When your problem is solved by a monad there is no point in using arrows since an arrow require you to jump through extra hoops to accomplish the same goal.
But they do "add" functionality. An arrow is something like a monad/ co-monad pair. Half of the arrow is defined to parse input. The other half is defined to process the parse tree and produce output. An arrow is "just" a functor from one named type to another.
No, that is not at all the problem with arrows. The problem with arrows is that they are more restrictive than monads in two respects. First, unlike monads, in general they do not let you perform an arbitrary action in response to an input. Second, they place restrictions on how you define the input arguments of the arrow because you can't feed the output of one arrow into to input of the next unless said input is captured in the arrows type.
They aren't more restrictive. Just use an identity comonad for the input half if you want to deal with monads. You can even make monad instances for arrows of this form. The latter objection is rather the point of using an arrow. "Parser -> Process", in a single construct. There is an analogy here. A monad, in general corresponds to a catamorphism on a functor algebra. A co-monad corresponds to an anamorphism. The compositon of an anamorphism and catamorphism is a hylomorphism. A thing that unwraps and re-wraps. I do tend to use the functor type class (or category-extras, or even data.category) much more than arrows, though. It's all more-or-less the same.

On Oct 11, 3:20 pm, Uwe Schmidt
Hi Gregory,
Is there some benefit that your library gets out of using arrows that I missed which makes these costs worth it?
I thing, this is not a question of functionality, it's a question of style. Of course everything in hxt could have been done with monads, but does this also mean: Everything must have been done with monads?
I would like to answer "yes" here, following the inventor of monads, and giving some more reasons. 1) With monads, you still get a monadic interface by using Keisli, if you want. So your code would be strictly more reusable with monads. Maybe there is also an inverse of Keisli defined somewhere - it still makes more sense to use monads in your definitions. If nothing else, I don't want to start reading a 56-page tutorial [1] about an abstract concept to do XML processing (ArrowApply appears at page 20). 2) Quoting from another mail: Hughes himself said that when your arrow is an instance of ArrowApply, you are better off just sticking with monads, except for the usage of point-free notation. [See sec 2.4, page 14 of [1]] But as argued, point-free notation is possible with monads, too - at worst, nobody has put together a tutorial for doing it. Given the less widespread knowledge about arrows, their bigger complexities (twenty-seven arrow laws versus three monad laws) the reduced number of available utilities, monads are better here. My knowledge of arrows comes from an afternoon of study interleaved with other stuff (so it's less than an afternoon) - but I soon started to use "Programming with Arrows", which is _not_ linked from the reference of Control.Arrow, just from GHC's User Guide [2]. IMHO, you probably also chose to use arrows instead of monads because of bad docs by - namely, Control.Arrow docs should contain the above tip by John Hughes, together with a link to (>=>); the whole debate wouldn't need to exist. Best regards [1] "Programming with Arrows", John Hughes tutorial at "5th International Summer School on Advanced Functional Programming", 2004. [2] http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/arrow-notation.html

On Thu, 7 Oct 2010, Uwe Schmidt wrote:
HXT has grown over the years. Components for XPath, XSLT, validation with RelaxNG, picklers for conversion from/to native Haskell data, lazy parsing with tagsoup, input via curl and native Haskell HTTP and others have been added. This has led to a rather large package with a lot of dependencies.
This was also my problem. Thus I'm glad, that HXT is now split into smaller pieces! hxt-filter does not seem to be updated to hxt-9.0. How about providing hxt-filter with DEPRECATED pragmas for the functions that tell me how to rewrite functions from hxt-filter to arrows? Or is there another guide about how to move from hxt-filter to arrows?

Hello Henning,
hxt-filter does not seem to be updated to hxt-9.0. How about providing hxt-filter with DEPRECATED pragmas for the functions that tell me how to rewrite functions from hxt-filter to arrows? Or is there another guide about how to move from hxt-filter to arrows?
Sorry, but there is no complete guide for rewriting filter code into code working with arrows because of lack of time. Besides developing and documenting hxt, there are a few other things, that have to be done. It's rather easy to convert to the arrow style. All the functionality of hxt-filter is available in hxt. Most of the names and operators remain as they are. Declare type XmlFilter = LA XmlTree XmlTree That's the equivalent arrow type. When evaluating a filter expression, use runLA filter input When switching to the arrow style, some of the operators had to be renamed to the standard arrow operators, e.g. (.>) to (>>>) and (+++) ==> (<+>) For the monadic filters, mainly used for filters with IO use the Type "IOSArrow XmlTree XmlTree" and start a computation with runX, as described in the examples of the wiki page about hxt: http://www.haskell.org/haskellwiki/HXT#copyXML Just compile your sources with these changes, and use the Haskell compiler for finding ALL points, where you have to modify or rename something. If the code compiles, it will run. Please trust in strong typing, Uwe
participants (16)
-
Alexander Solla
-
C. McCann
-
Dan Doel
-
David Virebayre
-
Gene A
-
Gregory Crosswhite
-
Heinrich Apfelmus
-
Henning Thielemann
-
Henning Thielemann
-
Joachim Breitner
-
Malcolm Wallace
-
Nikitiskiy Dmitriy
-
Paolo G. Giarrusso
-
Sebastiaan Visser
-
Uwe Schmidt
-
Uwe Schmidt