Arc Forumnew | comments | leaders | submitlogin
Infix support in wart
4 points by akkartik 4216 days ago | 33 comments
Wart now supports a quick-n-dirty implementation of an infix scheme. Here's an excerpt from http://github.com/akkartik/wart#readme[1] with the details:

  wart> (3 + 1)
  4
You don't need spaces around infix ops.

  wart> 3+1
  4
Infix ops don't compromise homoiconicity; wart parses them into lisp forms so your macros don't have to worry about them:

  a+b
  => (+ a b)
Infix ops are always left-associative.

  a+b+c
  => (+ (+ a b) c)
Range comparisons are convenient as long as they return the last arg on success (because of left-associativity) and pass nils through:

  (a > b > c)
  => (> (> a b) c)   ; watch out if b is nil!

  (> nil x)          ; should always return nil!
You can mix infix ops with regular prefix lisp:

  (a + (f b))
  => (+ a (f b))

  (a + f.b)
  => (+ a (f b))

  (fib n-1)
  => (fib (- n 1))

  (f a + b c*d)
  => (f (+ a b) (* c d))
Operator precedence is not hardcoded. Instead, there is just one rule: operators surrounded by whitespace have lower precedence than operators that are not.

  (n * n-1)
  => (* n (- n 1))
You can create your own infix ops:

  def (<>) (a b)     ; def <> (a b) would become <> def (a b)
    (~iso a b)

  wart> (1 <> 2)
  1
To permit arbitrary infix ops, wart makes them distinct from regular symbols. Regular symbols can only contain letters, digits, and the characters ':', '?', '!' and '_'. Infix ops can only contain other characters. Thus, the sets of 'infix chars' and 'symbol chars' are disjoint. This implies that wart won't let you define some traditional lisp names that you might be used to:

  *global*                      ; I would just say Global
  => error

  uppercase-char-p
  => (- uppercase (- char p))   ; probably not what you want

  (char> a "p")
  => ((> char a) p)             ; probably not what you want
To create multi-word symbols, use underscores or camelCase. I'm trying out capitalizing globals.

While regular symbols can't be used in infix mode, infix ops can be used like regular symbols.

  (+ a b)
  => (+ a b)
To use an infix op in a higher-level function, wrap it in parens:

  (map ++ '(1 2 3))
  => Error: map is not a number

  (map (++) '(1 2 3))             ; hello haskell!
  => (2 3 4)
Infix operators can coexist with paren-insertion:

  a +
    b+c * d

  => (+ a (* (+ b c) d))
However, if your infix expressions need multiple lines, ask if they're worth doing in infix. The following is actually harder to read in infix:

  (* some_function.some_argument
     (+ some_other_function.some_other_argument
        some_random_constant))
I prefer to use infix only for simple expressions with short variable names. And I never use infix in macro expansions. After all, macros are the whole reason we have s-expressions.

---

Comments, questions, criticisms? I'm wary that the interpreter is getting more complex, so this might be temporary. One open question: Can we represent some ssyntax in infix? ':' and '&' in particular seem like they should become infix operators, but there might be weird interactions with precedence. A more immediate issue is that I would lose keyword symbols like :a.

I'm unsure whether it's a good idea to use infix for assignment; prefix seems to make mutations more salient. I'm also keeping equality checking in prefix because I love the name iso so much :)

[1] http://github.com/akkartik/wart/tree/79476f0d230d1c5eb6b20ebc116507e0a12785de#readme to be precise.



2 points by fallintothis 4215 days ago | link

Some thoughts as they come to me (so forgive me if they're poorly formulated; I should be going to bed anyway):

1) I was appalled up until the "disjoint characters" part. Maybe open with that next time, so I know there's a disciplined way of telling what might be an infix operator. Don't scare me like that! :)

2) The global earmuffs are easy to dismiss. Angle brackets, I can live without (just change a->b names to use the word to). But

  uppercase-char-p
  => (- uppercase (- char p))   ; probably not what you want
Ouch. Hyphens are by far my favorite separator in identifiers. Alas, infix will pretty much always ruin them.

3) operators surrounded by whitespace have lower precedence than operators that are not

So is this two levels of precedence, or as many levels as there are spaces? If I read right, it's the former: operators surrounded by any space versus those surrounded by no space. I like this idea, because it's a disciplined way of doing the http://arclanguage.org/item?id=16726 stuff. If you need more than two levels, cut your tomfoolery out and put in some parentheses!

4) The whole thing smacks a lot of Haskell's infix operators: special characters only, can still use them in prefix & define your own (as long as you wrap the name in parentheses!), etc. The key difference is the precedence & associativity thing (where wart is more like Smalltalk). Is this for simplicity/generality, or are there any technical reasons to avoid precedence rules? Because Haskell's way still seems fairly disciplined, by letting users assign numbers to the level of precedence & specify associativity. And those at least gives a certain level of control to today's Exacting Programmer On The Go (TM).

5) Haskell has a syntax for turning prefix operators into infix ones.

  foo a b = a + b

  1 `foo` 2 == foo 1 2
Thoughts?

6) Your point about range comparisons is an interesting one, because a long time ago I was mulling over anaphora's usefulness but lack of prevalence. Namely, it's undermined by t. If there's only one canonical false value, I was thinking it would pay to prefer returning a datum to indicate boolean truth, because then at least you can use your function in anaphoric contexts. But then, I was wondering how confusing it would make debugging code or pretty-printing results. Imagine plugging in a predicate and getting a non-boolean out of it, so it looks like the result of a computation more than an answer to a question.

7) I'm wary that the interpreter is getting more complex, so this might be temporary.

That's what worries me the most. Minimalism and special syntax don't often go well together (usually just to the extent that the syntax is itself minimal). At the same time, your efforts do seem a more measured (and user-definable) approach than the Readable guy's, so I've definitely got to hand it to you there.

8) I'd look forward to rocketnia's feedback. He has a knack for turning up odd edge cases. :P

9) Can we represent some ssyntax in infix?

Don't see why not, for the two-argument ones (&, :, ., and !, get notwithstanding). and and compose are fully-associative, so no problem. As long as the user expects precedence to follow the regular infix rules, nothing should be a surprise, even if it doesn't work like Arc's ssyntax does. E.g., using Arc's precedence, a:b.c and a.b:c will give compose top priority regardless:

  arc> (ssexpand 'a:b.c)
  (compose a b.c)
  arc> (ssexpand 'a.b:c)
  (compose a.b c)
The expectation in wart would (necessarily) be whitespace-then-left-associativity, so to match Arc's semantics, you'd have to use

  a : b.c           ; or just a:b.c, with left-associativity
  =>
  (compose a (b c))
and

  a.b : c
  =>
  (compose (a b) c)
respectively. But this is more flexible, too, because you have the option to do

  a . b:c           ; hope you don't have dotted lists?  Or just use a.b:c
  =>
  (a (compose b c))
10) I think it might even be a lot to ask for ssyntax and infix stuff to coexist. Ssyntax is already a finicky little sub-language of its own (in Arc); if it can be replaced with a more general mechanism, so much the better.

11) [1] http://github.com/akkartik/wart/tree/79476f0d23#readme to be precise.

Link's dead?

-----

1 point by fallintothis 4215 days ago | link

Another question that occurred to me:

Could you explain, specifically, how infix operators react to the presence/absence of parentheses? Ignoring the treatment of tokenization (what with whitespace vs nonwhitespace operators), is the context-sensitive grammar roughly like so?

  ( infix a b ... )   -->   ( infix a b ... )
  ( a infix b ... )   -->   ( infix a b ... )
  a infix b ...       -->   ( infix a b ) ...
where the last rule would create the behavior

  ( ... a b infix c ... ) --> ( ... a ( infix b c ) ... )
That's as much as I can gather from the examples, but I'd like having a clear mental model.

-----

2 points by akkartik 4215 days ago | link

There isn't a unified grammar for the language, I'm afraid. I've built wart in layers:

a) parse lisp as usual. This layer doesn't know about the regular vs infix distinction, so a, a-1 and ++a and ++ are all just tokens.

b) expand infix ops inside symbols, e.g. a+1 => (a + 1)

c) scan for operators inside lists and pinch them with the adjacent elements.

  (.. a ++ b ..) => (.. (++ a b) ..)
Edit: Notice that this is different from your example:

  (a infix b ..) => ((infix a b) ..)

-----

2 points by Pauan 4215 days ago | link

"Ouch. Hyphens are by far my favorite separator in identifiers. Alas, infix will pretty much always ruin them."

I have to agree. That's one of the things I really like about Lisps, as compared to languages like JS where you have to use camelCase or _

-----

1 point by akkartik 4215 days ago | link

"The key difference [to Haskell] is the precedence & associativity thing (where wart is more like Smalltalk). Is this for simplicity/generality, or are there any technical reasons to avoid precedence rules?"

Hmm, I started out from the perspective in http://sourceforge.net/p/readable/wiki/Rationale that precedence violates homoiconicity. But if it happens in the reader and macros always see real s-expressions I suppose there isn't a technical issue.

My only other response: 9 levels of precedence?! Cut your tomfoolery! :)

---

I momentarily considered haskell's backticks, but there's a problem finding a reasonable character. And I wanted to not make the language more complex.

-----

1 point by fallintothis 4215 days ago | link

My only other response: 9 levels of precedence?! Cut your tomfoolery! :)

Ha! So, "for simplicity's sake" it is. :P

(Also, you can thank my sleepy attempts at self-censoring "cut that shit out" for my sounding like https://www.youtube.com/watch?v=nltVuSH-lQM)

-----

1 point by akkartik 4215 days ago | link

"If you need more than two levels, cut your tomfoolery out and put in some parentheses!"

Exactly! The discussion at http://arclanguage.org/item?id=16749 yesterday was invaluable in bringing me back (relatively) to the fold. And it was also easier to implement :o)

-----

1 point by akkartik 4215 days ago | link

Thanks for all those comments! After mulling them I think I'll feel better if I can eliminate ssyntax in favor of infix operators. But there's two challenges to that:

  a.b vs dotted lists
  f:g vs :syms
I'm gonna take the rest out next.

-----

1 point by fallintothis 4215 days ago | link

  a.b vs dotted lists
I was trying to think of alternatives, thought "maybe a more complex symbol for one of the uses, like ..?", then wondered about a potential edge case. Really, I'm just thinking of the parsing algorithm---or, rather, lexing. If . was defined as the ssyntax is, would a..b expand into ((a) b)? Without spaces, it's fairly clear that certain arguments are "empty", since it could conceivably be tokenized as two .s. But a++b probably wouldn't tokenize to two +s. Suppose both . and .. were defined; how would a..b be resolved? Longest-operator-first?

  f:g vs :syms
Could always go with another symbol for function composition. | comes to mind, but it's more like "reverse compose" at a Unix shell. On the other hand, as far as the function composition operator is concerned, I've seen mathematicians define it both ways---$(f \circ g)(x) = f(g(x))$ and $(f \circ g)(x) = g(f(x))$. No technical reason you couldn't use a pipe, just conventional.

-----

2 points by akkartik 4215 days ago | link

Yeah, currently:

  a..b
  => ((a) b)
My reflex: I'm ok with breaking this corner case and just treating it as a single op like infix a++b. Juxtaposing infix ops isn't really on my radar.

Update: Hmm, a more valuable use case that I might have to give up:

  f:~g
Update 4 hours later: Ah, perhaps I don't have to give it up! We could just define new operators:

  mac (:~) (f g)
    `(: ,f (~ ,g))

  mac (.-) (f n)
    `(,f (- ,n))
Yeah, this could work. a..b is still challenging to define, though..

-----

1 point by fallintothis 4215 days ago | link

Really, I'm just thinking of the parsing algorithm---or, rather, lexing.

Oh yeah, and how does it work for negative number literals? I assume

  (f n-1)   --> (f (- n 1))
  (f n - 1) --> (f (- n 1))
because the minus either does or does not have spaces around it, but

  (f n -1) --> (f n -1)
because the minus sign only has spaces on one side?

-----

1 point by akkartik 4215 days ago | link

Yeah. I never treat an op as infix if it has whitespace on just one side.

There is one ugly special-case here:

  f.-1   ; => (f -1)
http://github.com/akkartik/wart/blob/8211614d63/014infix.cc#...

-----

1 point by akkartik 4214 days ago | link

Ok, erstwhile ssyntax is now all infix: [1] http://github.com/akkartik/wart/commit/365a2ce3ac

Check out the details below, and give me your reactions. Is this too ugly to be worthwhile?

Excluding tests, this change reclaimed ~50 LoC. In all, this whole experiment has costed 225 LoC. I'm going to play with it for a bit before I decide to back it out.

---

Compromises:

1. In wart, unlike arc, you could mix unquote with ssyntax: car.,x, etc. This had to go.

2. You can no longer use ssyntax with operators: ++. used to expand to (++); now it's just a three-character op. Haskell's prefix syntax is now required to escape infix.

3. list.-1 is now a call to the .- op. As planned (http://arclanguage.org/item?id=16801) I just defined it to do what I mean, but it's a kinda ugly user-space coupling. And it requires handling assignment separately. (http://github.com/akkartik/wart/blob/365a2ce3ac/040.wart#L27; http://github.com/akkartik/wart/blob/365a2ce3ac/047assign.wa...)

As a happy bonus, ++.n is now ++n.

---

Some special-cases are hardcoded into the reader:

1. Periods can be part of operators, but dotted list syntax now uses ..., which is never an operator.

2. Period at end of symbol calls it. prn. is (prn), not (prn .)

3. Colon at start of symbol is part of the symbol. This was always true, for keyword args. It means I can't define :~ to support f:~g; it just didn't seem worth another special-case.

4. Bang at the end of a symbol is part of the symbol, for mac!, reverse!, etc.

5. Bang has another special-case. In keeping with left-associativity, prefix ops are always highest-precedence:

  ~odd?.n  ; => (. (~ odd?) n)
However, ! at the start of a symbol is _lowest_ precedence:

  !cdr.x  ; => (not (. cdr x))
Perhaps I'll get rid of this feature. We'll see.

-----

2 points by fallintothis 4213 days ago | link

1. Periods can be part of operators, but dotted list syntax now uses ..., which is never an operator.

Seems a worthwhile trade-off. Dotted lists are used infrequently enough, and an ellipsis does just as well as a single dot.

2. Period at end of symbol calls it. prn. is (prn), not (prn .)

Hm. So this is like a vestigial instance of ssyntax?

3. Colon at start of symbol is part of the symbol. This was always true, for keyword args. It means I can't define :~ to support f:~g; it just didn't seem worth another special-case.

Yeah, wouldn't want a special case on top of a special case! :)

4. Bang at the end of a symbol is part of the symbol, for mac!, reverse!, etc.

Have you considered a non-operator character for this use, to ditch the special case? I'm partial to mac=, reverse=, etc. I mean, since = isn't used for comparison anyway. And assuming that = is actually not an operator character. Did you ever decide if you wanted = to be an infix operator (and thus character)?

5. Bang has another special-case.

Whoa. Did I miss where this infix notation extended to prefix operators? Or does this work the same way ssyntax did? And if so, in what sense has ssyntax been removed? :)

Is this too ugly to be worthwhile?

Hm...parsing is getting too complicated for my tastes. But then, my taste is for parentheses. :P

Still, carving out special cases so ssyntax still "mostly works" isn't quite what I envision as a way to unify away ssyntax. Basically, is "traditional" (inasmuch as Arc establishes tradition) ssyntax prohibitively useful? Or can we do without some of its uses in the name of a more general infix notation without the complications of special symbol parsing?

-----

2 points by akkartik 4213 days ago | link

Ok, I've tried to be ruthless and take the ssyntax stuff out. '!' is now always part of regular symbols, just like '?'. There's no prefix version like !a. And there's also no infix version, like f!sym.

It turns out this doesn't actually bring back any parens. !x becomes no.x or not.x. And in some situations I can replace a!b with a'b. (Maybe that's too clever.)

I've also dropped support for turning x. into (x). Not even traditional arc has that. Now x. turns into (x .).

Only remaining special-cases: '...', and ':' at start of sym is part of the sym.

Whoa. Did I miss where this infix notation extended to prefix operators?

Good point. This happened as part of the elimination of ssyntax, but I figured it was intuitive to extend left-associativity to prefix ops. However, now I see that:

  (f a + b) => (f (+ a b))
but:

  (- a + b) => (+ (- a) b)
Is that weird?

Thanks for the comments! This really seems like an improvement over my original idea.

-----

2 points by fallintothis 4212 days ago | link

Thanks for the comments! This really seems like an improvement over my original idea.

I'm glad you think so. I try to make my suggestions as nonprescriptive as possible, though (in full disclosure) I'm liable to lead you in circles back to prefix notation if you follow them too far. :P

It was that or lose <=, etc.

Oh, duh. Move along, nothing to see here!

Only remaining special-cases: '...', and ':' at start of sym is part of the sym.

I'm really okay with ..., because it doesn't feel like a "special case" as much as it does a built-in keyword; I wouldn't expect to be able to redefine fn or if, either. I don't really have an opinion on the :keyword symbols.

  (f a + b) => (f (+ a b))
but:

  (- a + b) => (+ (- a) b)
Is that weird?

Maybe, maybe not. It's not like every other language doesn't do mixfix with their "infix" notation. I just wasn't sure how it worked. Do you declare that certain operators are prefix? Or are they all potentially prefix, like

  ( mixfix a b ... )   -->   ( ( mixfix a ) b ... )
where mixfix is any operator, a and b are any normal token, and ... is 0 or more tokens? Or something like that?

  x-1.0
What's the intuitive way to parse this?

I'd say as subtraction of a float: (- x 1.0). If nothing else, I can't imagine a reason to do ((- x 1) 0).

Is it worth getting right, or should we just say, "don't use floats with infix"?

My gut reaction is that it's worth getting right, because programming languages shouldn't be ambiguous.

I notice that a lot of these problems seem to come from using the dot. Thinking back about ssyntax now, it occurs to me that the dot is probably the least-used among them, in Arc. If I were to guess from my own code, I'd rank their usage descending as ~, :, !, ., &. But hey, we can put numbers to that:

  (= arcfiles* '("strings.arc" "pprint.arc" "code.arc" "html.arc" "srv.arc" "app.arc" "prompt.arc")
     allfiles* (rem empty (lines:tostring:system "find ~/arc -name \\*.arc")))

  (def ssyntax-popularity (files)
    (let tallies (table)
      (each symbol (keep ssyntax (flat (map errsafe:readall:infile files)))
        (each char (string symbol)
          (when (find char ":~&.!")
            (++ (tallies char 0)))))
      (sortable tallies)))

  arc> (ssyntax-popularity arcfiles*)
  ((#\~ 13) (#\! 9) (#\: 3) (#\& 1) (#\. 1))

  arc> (ssyntax-popularity allfiles*)
  ((#\! 532) (#\: 144) (#\~ 122) (#\. 58) (#\& 27))
Mind you, it's been awhile, so I have no clue what all is in my personal ~/arc directory. Probably various experiments and output from things like sscontract (http://arclanguage.org/item?id=11179) and so on. All the same, the dot is low on the totem pole. I personally wouldn't be heartbroken to have to write (f x) instead of f.x, and you could reclaim the regular dotted list syntax. Would it be worthwhile to backtrack at this point and get !, :, and ~ functionality without worrying about .? There were some existing issues with ! and : (name collisions). ~ is prefix, but if you have a way of extending the infix notation for subtraction, surely it would apply to ~? Related thought: f ~ g could replace the f:~g you were worried about before.

Anyway, just some random thoughts off the top of my head. Do what you will with them.

-----

1 point by akkartik 4211 days ago | link

Yeah you're right that using period as both an infix op and inside floats is kinda messy. I use it a lot more than you, so I'm still going through the five stages of grief in giving it up. In the meantime I've hacked together support for floats. Basically, the reader tries to greedily scan in a float everytime it encounters a sym-op boundary. Some increasingly weird examples:

  wart> e=5
  wart> e-2.0
  3
  wart> e-3e-3
  4.997
  wart> 3e-3-e
  -4.997
Perhaps this is reasonable. We have a rule that's simple to explain, whose implications can be subtle to work out, but which programmers are expected to exercise taste in using. That could describe all of lisp.

-----

2 points by rocketnia 4211 days ago | link

"We have a rule that's simple to explain, whose implications can be subtle to work out, but which programmers are expected to exercise taste in using. That could describe all of lisp."

I don't think the syntax for numbers is very easy to explain. That's the weak link, IMO.

If it were me, I'd have no number literals, just a tool for translating number-like symbols into numbers. Of course, that approach would make arithmetic even less readable. :)

I think the next simplest option is to treat digits as a separate partition of characters like the partitions for infix and non-infix. Digits are sufficient to represent unsigned bigints with a simple syntax. Then most of the additional features of C's float syntax could be addressed by other operators:

  -20.002e23
  ==>
  (neg (20.@1002 * 10^23))
This hackish .@ operator, which simulates a decimal point, could be defined in Arc as follows:

  (def dot-at (a b)
    (while (<= 2 b)
      (zap [/ _ 10] b))
    (+ a (- b 1)))
You could avoid the need for this hack by treating . as a number character, but then you lose it as an operator.

-----

1 point by akkartik 4211 days ago | link

"Do you declare that certain operators are prefix? Or are they all potentially prefix?"

Yeah any op can be used in prefix.

-----

2 points by Pauan 4213 days ago | link

"Basically, is "traditional" (inasmuch as Arc establishes tradition) ssyntax prohibitively useful?"

I don't think so. Nulan completely ditched Arc's ssyntax and only uses significant whitespace, ":" and ";". Yet, despite that, it's capable of getting rid of almost all parentheses.

Oh, by the way, ":" in Nulan has a completely different meaning from ":" in Arc. I just chose it because I thought it looked nice.

-----

1 point by akkartik 4213 days ago | link

Actually, there's one major remaining question. This no longer works:

  x-1.0
What's the intuitive way to parse this? Is it worth getting right, or should we just say, "don't use floats with infix"? Especially since wart recognizes whatever formats the underlying C recognizes:

  -2.14e-3
It'll get complex fast to mix that with infix operators..

-----

1 point by akkartik 4213 days ago | link

Did you ever decide if you wanted = to be an infix operator (and thus character)?

Yes, it's always been infix, so wart lost def= and function= when it gained infix ops. It was that or lose <=, etc. The question in my mind was more of style: even if assignment can be in infix, should I always use prefix?

-----

1 point by akkartik 4215 days ago | link

  > a . b:c     ; hope you don't have dotted lists?  Or just use a.b:c
Boy do I have dotted lists. You'll take them from my cold dead hands :)

-----

1 point by fallintothis 4215 days ago | link

:) I merely meant that it would break if you had dotted lists---syntax collision.

-----

1 point by akkartik 4215 days ago | link

Link's dead?

Huh, turns out github won't let me shorten tree urls like commit urls. For a second I thought I'd found my first hash prefix collision :) Fixed.

-----

1 point by akkartik 4216 days ago | link

Here's the fast fibonacci from SICP 1.19 in wart[1]:

  def fib(n)
    (fib_iter 1 0 0 1 n)

  def fib_iter(a b p q n)
    (if
      (iso n 0)
        b
      even?.n
        (fib_iter a
                  b
                  p*p + q*q
                  q*q + 2*p*q
                  n/2)
      :else
        (fib_iter (b*q + a*q + a*p)
                  (b*p + a*q)
                  p
                  q
                  n-1))
[1] http://arclanguage.org/item?id=16699

-----

1 point by akkartik 4215 days ago | link

Rather to my amazement, these test cases work as expected:

  a-1.0

  a.0-1.0
Any other stress test ideas?

-----

4 points by fallintothis 4215 days ago | link

Any other stress test ideas?

Depending on how you parse number literals, there are the examples at the end of http://arclanguage.org/item?id=10149 which I used for stress-testing ssyntax/number highlighting.

-----

3 points by fallintothis 4214 days ago | link

Just in case there are any that are useful, I also used http://pastebin.com/YqxZydyw to test syntax highlighting. A lot of the tests have to do with recognizing Scheme numeric literals, though.

-----

1 point by dehrenberg 4216 days ago | link

I really like this syntax. Getting rid of precedence is definitely good. (You can also go right-associative like K, which has its small advantages.) To me, the most interesting part is the way you make whitespace significant. It's a great idea that I haven't heard before. It could be tempting to make that more intricate, but that's probably more trouble than it's worth in practice.

-----

1 point by akkartik 4216 days ago | link

Hi Dan! Thanks! Yeah I tried counting spaces like we do for python indent, but that's probably not worth the trouble.

I can't take credit for the whitespace idea. rocketnia pointed out that a project called merd first came up with it (http://arclanguage.org/item?id=16724).

And yes I considered going right-associative. In fact, I originally meant to make it right-associative, but ended up showing my C roots :) I might still revisit this decision. Can you point me at right-associativity's advantages?

-----

1 point by dehrenberg 4215 days ago | link

APL and K are right-associative.

-----

2 points by rocketnia 4211 days ago | link

A good reason to make something right-associative is if it takes a Foo and a Bar and gives you a Bar in return. In this case, left-associative grouping would only lead to type errors.

Taking a look at Haskell's right-associative operators, the cons operator (:) seems to follow that rule, and others seem to take into account other idiosyncrasies. Here are my guesses for each operator:

Exponentiation to the power of a natural number (a ^ b ^ c), an integer (a ^^ b ^^ c), or a float (a b c) is right-associative, probably to match the parentheses-less math notation: (a (b c)).

The function type constructor (a -> b -> result) is right-associative (a -> (b -> result)) so that it's easy to use multi-parameter curried functions. For the same reason, function currying/application (func a b) is left-associative ((func a) b).

Low-precedence function application (a $ b $ c) is right-associative. This might be because (a b c) tends to be sufficient for passing the usual curried parameters, so (a $ b $ c) is reserved for cases where the output of each ($) isn't another function to apply. If this is true, ($) usually takes a function and a non-function and returns a non-function, so it's naturally right-associative.

Haskell has a few other right-associative operators out of the box, but I'm not sure why. In some cases, maybe it helps with perfomance.

http://www.haskell.org/onlinereport/decls.html

-----