
The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator? Thanks, Tamas

map (\x -> x - 2) [1..5] or map (flip (-) 2) [1..5] HTH Christian Tamas K Papp schrieb:
The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator?
Thanks,
Tamas

Tamas,
The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator?
What about map (flip (-) 2) [1 .. 5] or map (+ (- 2)) [1 .. 5] ? HTH, Stefan

On 17/08/06, Tamas K Papp
The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator?
There's a Prelude function for exactly this purpose, which leads your code still quite readable: Prelude> map (subtract 2) [1..5] [-1,0,1,2,3] -- -David House, dmhouse@gmail.com

Tamas K Papp wrote:
The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator?
Actually looking at the Haskell98 report, -2 seems to be treated as (negate (2)), which I find really strange because there does not appear to be any way of specifying negative literals, and the range of negative values is always 1 more than the range of positive values (when you use a fixed bit-length representation eg Int instead of Integer) I'd have thought it would have been simpler to just make the rule that -2 (no spaces between '-' and '2') would be a single lexeme, and then people could just use (negate x) or (0 - x) instead of having a special rule and a whole lot of confusion just for one arithmetic operator, which is never actually needed in the first place (just as we don't need /x because it is simple enough to write 1/x). I see with great disappointment that Haskell' Trac ticket#50 [1] looks as if it will not be accepted [2] so we're likely to be stuck with this for years to come... [1] http://hackage.haskell.org/trac/haskell-prime/ticket/50 [2] http://hackage.haskell.org/trac/haskell-prime/wiki/StrawPoll-2 So in answer to your question, you can't (except for workarounds already posted). Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Stefan Monnier
I'd have thought it would have been simpler to just make the rule that -2 (no spaces between '-' and '2') would be a single lexeme,
But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".
Well, since the normal typographical convention is that "hyphenated-words" are read as closely connected, I've always been in favour of including hyphen in variable names and using spaces to separate them from tokens, so perhaps it should just mean "the identifier 'x-2'". Though in the days of Unicode we could get round the whole thing by using code 0x002d for unary minus, 0x2010 in identifiers and 0x2212 for infix minus... and spend many a happy hour trying to tell which of the three was intended by some short horizontal line. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2006-07-14)

On Thu, Aug 17, 2006 at 11:18:59AM -0400, Stefan Monnier wrote:
I'd have thought it would have been simpler to just make the rule that -2 (no spaces between '-' and '2') would be a single lexeme,
But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".
but now at least a highlighting editor can tell the difference and highlight '-2' as a number and x as a variable. I mean, 0x22 does not mean the same thing as 0 x 32 or 0.32 or 0 . 32. we already have special lexical rules for numbers and no one has complained about any of them. but issues with the '-' handling come up quite regularly. John -- John Meacham - ⑆repetae.net⑆john⑈

I'd have thought it would have been simpler to just make the rule that -2 (no spaces between '-' and '2') would be a single lexeme
I'd have thought so too, until I implemented a parser with exponentiation. It is easy to get confused and make a parser that is too eager to include the minus sign as part of a numeric literal instead of as subtraction or unary negation (all you parser-with-exponentiation-implementers out there, pay attention!). And since many programming languages (specifically C) don't have syntax for exponentation as an infix operator (nothing authoritative to copy precedence from), I had to implement this myself, get confused and see that it was so---(I tried making the literal include the minus sign if there was no space). I never noticed this before because in a C-like language: -4*2 is the same whether parsed as (-4)*2 or -(4*2) but -4^2 is not the same whether parsed as (-4)^2 or -(4^2) (the correct version) Basically, before someone argues this with me, -4^2 should parse the same as - 4^2 which should be the same thing as 0 - 4^2 (you don't want -4^2 and 0-4^2 giving different results, no matter how much you think whitespace belongs around operators) Math follows these same rules but it's slightly harder to get confused because of the way exponentiation is written by superscripting. See http://mathforum.org/library/drmath/view/55709.html and http://mathforum.org/library/drmath/view/53240.html. I thought this was surprising, that parsing the minus sign into lexemes would cause such confusion, but it is born out in many places (Python, Frink (http://futureboy.homeip.net/frinkdocs/FrinkApplet.html), etc.) (Note: this email isn't about Haskell specifically and I'm sure issues with the minus sign in Haskell are more confusing than this; this is purely about parsing a C-like langauge extended with exponentionation and how including the minus sign in the literal is dangerous in conjuntion with exponentiation.) Jared. -- http://www.updike.org/~jared/ reverse ")-:"

Jared Updike wrote:
-4^2 is not the same whether parsed as
(-4)^2 or -(4^2) (the correct version)
Basically, before someone argues this with me,
-4^2 should parse the same as
- 4^2 which should be the same thing as
0 - 4^2
I'd argue that -4^2 should parse as (-4)^2 in the same way that: f x `op` y === (f x) `op` y I'd also argue that in maths the necessary brackets are implied by the superscripting syntax, and for programming, as long as the editor does basic highlighting of literals it would be very clear that -4 is a single lexeme. Stefan Monnier wrote:
I'd have thought it would have been simpler to just make the rule that -2 (no spaces between '-' and '2') would be a single lexeme,
But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".
Literal highlighting in the editor would make it clear that x-2 === x (-2). I think a basic issue is that at the moment it is strange that non-negative numbers can be specified as literals but negative numbers can't - they can only get in through the "back door" of evaluation - which just doesn't seem right. It's kind of like a Monty Python'esque sketch of a lecture theatre full of mathematicians where every attempt to mention a negative number is replaced by the word "apple"... ;-) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

On 17/08/06, Brian Hulley
Literal highlighting in the editor would make it clear that x-2 === x (-2). I think a basic issue is that at the moment it is strange that non-negative numbers can be specified as literals but negative numbers can't - they can only get in through the "back door" of evaluation - which just doesn't seem right.
You also can't specify string literals: they're sugar for 'a':'b':'c':[]. You seem to be arguing that syntactic sugar, and by extension, a small core language, is bad. -- -David House, dmhouse@gmail.com

On Thu, Aug 17, 2006 at 09:17:39PM +0100, David House wrote:
On 17/08/06, Brian Hulley
wrote: Literal highlighting in the editor would make it clear that x-2 === x (-2). I think a basic issue is that at the moment it is strange that non-negative numbers can be specified as literals but negative numbers can't - they can only get in through the "back door" of evaluation - which just doesn't seem right.
You also can't specify string literals: they're sugar for 'a':'b':'c':[]. You seem to be arguing that syntactic sugar, and by extension, a small core language, is bad.
No, I think he is saying this particular piece of syntactic sugar is more like syntactic castor oil. Also, the main reason it needed to be "special" was not for terms, but for n+k patterns, where you couldn't use 'negate' and have it parse properly. but n+k patterns are likely to be dropped anyway so we might as well do away with this subwart too. John -- John Meacham - ⑆repetae.net⑆john⑈

David House wrote:
On 17/08/06, Brian Hulley
wrote: Literal highlighting in the editor would make it clear that x-2 === x (-2). I think a basic issue is that at the moment it is strange that non-negative numbers can be specified as literals but negative numbers can't - they can only get in through the "back door" of evaluation - which just doesn't seem right.
You also can't specify string literals: they're sugar for 'a':'b':'c':[]. You seem to be arguing that syntactic sugar, and by extension, a small core language, is bad.
All I'm saying is that given a type, either all the inhabitants should have a literal form or none of them should, because otherwise the availability of literals skews one's relationship to the inhabitants. Ie the lack of negative literals tells me that I should think of negative integers as being "derived" from positive integers via negation, whereas the declaration data Integer = ... | -1 | 0 | 1 | ... tells me that the negative and positive integers are on an equal footing. Ie the language is sending out a "mixed message" about the integers, which is confusing. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

On Fri, Aug 18, 2006 at 12:20:54AM +0100, Brian Hulley wrote:
data Integer = ... | -1 | 0 | 1 | ...
tells me that the negative and positive integers are on an equal footing.
Ie the language is sending out a "mixed message" about the integers, which is confusing.
Not only that but there is a run-time penalty for every polymorphic negattive literal! -3 desugars to negate (fromInteger 3) rather than (fromInteger -3) so you end up having to do 2 dictionary lookups (one for fromInteger, one for negate) and indirect function calls rather than just the one. John -- John Meacham - ⑆repetae.net⑆john⑈

I'd also argue that in maths the necessary brackets are implied by the superscripting syntax
ASCII text parsing issues aside, in math, 2 -4 = ? (No you cannot ask if there is space between the 4 and the - symbol, or if I "meant" (-4)^2 or -(4^2), or if I wrote a negative sign or a subtract sign. I believe there is only one standard interpretation here.)
they can only get in through the "back door" of evaluation which just doesn't seem right.
Constant folding can eliminate any runtime cost, so effectively 0 - 2 ==> negative 2 at compile time. No problem. Jared -- http://www.updike.org/~jared/ reverse ")-:"

Jared Updike wrote:
I'd also argue that in maths the necessary brackets are implied by the superscripting syntax
ASCII text parsing issues aside, in math,
2 -4 = ?
(No you cannot ask if there is space between the 4 and the - symbol, or if I "meant" (-4)^2 or -(4^2), or if I wrote a negative sign or a subtract sign. I believe there is only one standard interpretation here.)
Yes but my point is that -4^2 is not the same as 2 -4 because the latter by convention means - (4^2). In other words, superscripts bind tighter than prefix ops but prefix ops bind tighter than infix.
they can only get in through the "back door" of evaluation which just doesn't seem right.
Constant folding can eliminate any runtime cost, so effectively 0 - 2 ==> negative 2 at compile time. No problem.
An Int8 has the range -128 to +127 inclusive, so I'd have expected a problem with the expression negate (128 :: Int8) However I see from http://en.wikipedia.org/wiki/Two's_complement#The_weird_number that this works because -128 === +128 ie negate (128::Int8) === negate (-128) -- literal to typed value === (+128) -- negation === (-128) -- overflow ignored Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Yes but my point is that -4^2 is not the same as
2 -4
because the latter by convention means - (4^2).
In other words, superscripts bind tighter than prefix ops but prefix ops bind tighter than infix.
I see. My point is that there already exists a convention[1] that the way to type in 2 -4 is -4^2 which means -(4^2) not (-4)^2 because - as a prefix op has the same precedence as binary subtraction, not super tight like normal prefix ops (i.e. normal function application) as you would like it to be (if I understand correctly). You are welcome to break an existing (unofficial) convention for the sake of lexical syntax[2]. Cheers, Jared. [1] On my TI89 calculator (where there are even two - buttons: a little "negative unary" button and a "binary subtract" button). It pretty prints 2 -4 = -16 when I punch in -4^2 (where - is the "negative unary" button). The answer is -16. Python (-4**2 = -4 ** 2 = - 4 ** 2 = -16) and Matlab and Mathematica agree (-4^2 = -4 ^ 2 = - 4 ^ 2 = -16). [2] http://wadler.blogspot.com/2006/01/bikeshed-coloring.html -- http://www.updike.org/~jared/ reverse ")-:"

Jared Updike wrote:
In other words, superscripts bind tighter than prefix ops but prefix ops bind tighter than infix.
I see. My point is that there already exists a convention[1] that the way to type in 2 -4 is -4^2 which means -(4^2) not (-4)^2 because - as a prefix op has the same precedence as binary subtraction, not super tight like normal prefix ops (i.e. normal function application) as you would like it to be (if I understand correctly). You are welcome to break an existing (unofficial) convention for the sake of lexical syntax[2]. [2] http://wadler.blogspot.com/2006/01/bikeshed-coloring.html
This choice of precedence for unary - conflicts with the normal usage in languages like C, where unary ops "obviously" bind tighter than infix. The typesetting in maths conveys a lot of info eg to distinguish f -x from f - x or f-x, and so the relationship between the visual representation and the meaning depends on a knowledge of various conventions that have evolved over time, and the knowledge of when to apply them in a given context. In contrast, a programming language should be based on general concepts uniformly applied. In Haskell we have operators, identifiers, prefix application using an identifier and infix application using a symbol, and a uniform way to convert a symbol to an identifier and vice versa, and a uniform way of forming sections. All this machinery should be enough to be satisfied with. However, someone somewhere decided that one trivial arithmetic operation, namely unary minus, should be allowed to totally ruin everything, and not only that, but that half of any number line, the positives, should (literally!) have a special advantage over the other half, the negatives. Thus while I can agree with Wadler that it's easy to have different opinions on "little" issues, I think that in this case the goal of uniformity leads to an objective answer. Of course not all languages care about being uniform or neat ;-) Best regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

On 17/08/06, Brian Hulley
Jared Updike wrote:
In other words, superscripts bind tighter than prefix ops but prefix ops bind tighter than infix.
I see. My point is that there already exists a convention[1] that the way to type in 2 -4 is -4^2 which means -(4^2) not (-4)^2 because - as a prefix op has the same precedence as binary subtraction, not super tight like normal prefix ops (i.e. normal function application) as you would like it to be (if I understand correctly). You are welcome to break an existing (unofficial) convention for the sake of lexical syntax[2]. [2] http://wadler.blogspot.com/2006/01/bikeshed-coloring.html
This choice of precedence for unary - conflicts with the normal usage in languages like C, where unary ops "obviously" bind tighter than infix.
The typesetting in maths conveys a lot of info eg to distinguish f -x from f - x or f-x, and so the relationship between the visual representation and the meaning depends on a knowledge of various conventions that have evolved over time, and the knowledge of when to apply them in a given context.
In contrast, a programming language should be based on general concepts uniformly applied. In Haskell we have operators, identifiers, prefix application using an identifier and infix application using a symbol, and a uniform way to convert a symbol to an identifier and vice versa, and a uniform way of forming sections.
All this machinery should be enough to be satisfied with. However, someone somewhere decided that one trivial arithmetic operation, namely unary minus, should be allowed to totally ruin everything, and not only that, but that half of any number line, the positives, should (literally!) have a special advantage over the other half, the negatives.
Thus while I can agree with Wadler that it's easy to have different opinions on "little" issues, I think that in this case the goal of uniformity leads to an objective answer.
Of course not all languages care about being uniform or neat ;-)
Best regards, Brian.
First, f - x, f -x, and f-x all tend to mean the same thing in mathematics, though f -x would be considered poorly typeset (and, to some degree, they're all poorly typeset, because we're using hyphens rather than the minus symbol, which really don't look the same). We tend to write f(-x) when applying a function f to the negation of x, even in circumstances when application is normally written without parentheses. Secondly, I think it's quite a reasonable thing to do to treat unary negation as a separate operation. It follows quite naturally to do so from the definition of a ring. While having separate literals for negative numbers might be okay, it seems unnecessary in light of the fact that we *do* want a nice looking unary negation symbol, which doesn't strictly apply to literals. If -x suddenly became a non-expression, and I had to write 0-x, -1*x or (negate x) instead, I'd consider that a severe enough bug that I would avoid upgrading my compiler until it was fixed. In mathematics, we don't use separate symbols for negative integers, and negated positive integers, even though in the underlying representation of the integers as equivalence classes of pairs of naturals, we can write things like -[(1,0)] = [(0,1)], which expressed in ordinary notation just says that -1 = -1. This doesn't bother us, because the two things are always equal. Another thing to note is that all the natural literals are not, as one might initially think, plain values, but actually represent the embedding of that natural number into the ring (instance of Num), by way of 0 and 1. They simply provide a convenient notation for getting particular values of many rings, but in many cases, don't get one very far at all before other functions must be introduced to construct the constant values one wants. While there always is a homomorphism from Z to a ring (represented in Haskell by fromInteger), one would get similar expressiveness by with just the nullary operators 0 and 1, and the unary negation as well as addition and multiplication (albeit with an often severe performance hit, and some annoyance, I'm not recommending we really do this, simply characterising the purpose of numeric literals). If the performance issue regarding the polymorphic literal -5 meaning negate (fromInteger 5) is a problem, it would be easy enough to agree for the compiler to find and rewrite literals like that as fromInteger (-5) instead, where -5 is the precomputed integer -5. Assuming that fromInteger is not broken, that will always mean the same thing (because fromInteger is supposed to be a homomorphism). Similarly, when the type of (fromInteger x) is known statically to be Integer, the compiler can rewrite it as x. In any event, this is a tiny constant factor performance hit. Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after performing the fromInteger transformation they may be taken as literal integers, but there is no reason that this level has to be exposed to the user. Additionally, consider things like Rational. It is possible to write some elements of Rational in terms of integer "literals", but not all of them, even if negative literals become included. Floating point literals help a bit here, but not really all that much. (Consider things like 1/3, or 1/7.) In particular, any rational number with a denominator greater than 1 is inaccessible from that interface. Based on your previously mentioned design principle that all values of a type should be expressible via literals, or none of them should be, we should in fact remove the polymorphic interface for 0,1, etc. and force the user to type 1%1 for the rational 1. But this is annoying, and destroys polymorphism! I think that design principle is broken. If it was extended to say something like "All values of a type should be possible to write solely in terms of its constructors, or none of them should be.", then potentially infinite data structures would be excluded from having exposed constructors, for no good reason other than that there are infinite values which require other operations to define. This is, in a way, rather similar to the problem with rationals. I'd also like to say that the exponentiation example is also a good one. -4^2 is *always* -16, in every sane mathematical context since unary negation is treated as an additive operation, and thus should happen after exponentiation and multiplication (though under normal circumstances, it doesn't matter whether it's done before or after multiplication). Though this is a little offtopic, another important thing to note about parsing exponentiation is that a^b^c always means a^(b^c) and not (a^b)^c, which is a fairly standard thing in mathematics, because of the tendency to automatically rewrite (a^b)^c as a^(b*c), which looks nicer (and wouldn't normally involve parentheses on the page), and that no such rule exists for the other association. While I've considered that there are reasons that requiring spaces to be included to separate operator symbols from their arguments might actually be a decent thing to have, I wouldn't recommend doing things in the way that you're suggesting. With that in place, we could have negative integer literals (provided that people really care that strongly), but that's no reason to drop unary negation altogether -- just require that a space occur between the unary minus and its parameter. However, there are certain operators, especially exponentiation, and multiplication inside an additive expression, which putting spaces around them just looks "wrong" to me, and though I might be able to get used to it, I'd probably end up recompiling things all the time over syntax errors related to it. Newcomers to the language would also probably dislike it when they typed x+y at the ghci prompt and got some error saying that x+y is not in scope. - Cale

"Cale Gibbard"
Another thing to note is that all the natural literals are not, as one might initially think, plain values, but actually represent the embedding of that natural number into the ring (instance of Num), by way of 0 and 1.
I wasn't sure where to add this, so here will have to do: I think the present design is wrong because we don't have a type for naturals. So in my view, “-1” should be “negate (fromNatural 1)” -- whatever names we use for those two functions. I can't remember right now why the early versions of Haskell didn't have a Natural type, or what makes it difficult to change to now (and I think this is something we really should do), but even given that, I think the present special casing of “-” is a reasonable compromise. Given a built in Natural type, it makes no sense to have “-” as part of the syntax for literals, since Natural literals don't have it and there's no way to add more constructors (ie negative literals) onto an existing type to get Integer, but having a symbol for negate does it in a straightforward way. * ** * For my own taste, I would have “-” as a character that can appear in identifiers and operators (but special in that if it appears at the beginning it cannot be followed by anything? Otherwise -1 would just be an identifier!) and define
- n = negate n a +- b = a + (- b)
but I think that most people would baulk at having to use “+-” for infix minus. People would similarly baulk at the opposite tack of making “-” solely infix and using something else for negate (as in ML), although finding a different token (such as “__”) for "don't care" and using “_” for unary minus doesn't seem too bad to me. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

"Cale Gibbard"
Another thing to note is that all the natural literals are not, as one might initially think, plain values, but actually represent the embedding of that natural number into the ring (instance of Num), by way of 0 and 1.
Excellent point, and good categorical thinking. The morphisms are more
important than the objects.
Jón Fairbairn
I think the present design is wrong because we don't have a type for naturals.
Meh. Naturals are reasonably useful sometimes, but not often enough, in my opinion. Any sort of numeric hierarchy designed to deal with them would be totally broken from my point of view -- if you don't at least have inverses, it's not a number, just some sort of weird algebraic structure. And if it's not in the numeric hierarchy, and so you can't do arithmetic syntactically nicely with it, what's the point? Is it better to make (^^), (^), and "take" partial functions, or to make (-) and "negate" partial functions? Hmm, here's an idea: have a Nat type, but no arithmetic defined on it besides Succ, and isZero. Of course, that makes the fastexp algorithm unfeasible, and is essentially isomorphic to [()]. Hmm. That gives
length = map (const ()) take = zipWith (flip const)
Feel free to consider this a strawman, but it *is* kind of elegant. There's no scaling loss, as these are inherently O(N). And it even means length and take can handle infinite lists. What's not to like? Of course, there's always a typeclass, where we could add all sorts of other encodings of the Peano axioms, such as binary trees,, but I don't see that that buys us much if we don't also get access to operations beyond them, such as (an _efficient_) `div` for fastexp. (Taking every n'th element (Peano encoded, of course) is _not_ good enough). -- Aaron Denney -><-

Aaron Denney
Jón Fairbairn
wrote: I think the present design is wrong because we don't have a type for naturals.
Meh. Naturals are reasonably useful sometimes, but not often enough, in my opinion. Any sort of numeric hierarchy designed to deal with them would be totally broken from my point of view -- if you don't at least have inverses, it's not a number,
Crikey. Would you really have me accept that the natural numbers aren't numbers?
just some sort of weird algebraic structure. And if it's not in the numeric hierarchy, and so you can't do arithmetic syntactically nicely with it, what's the point?
Could you elaborate? I haven't thought it through, but I can't see why splitting Num into something that puts Natural "above" Integer would be particularly problematic. Natural just has fewer operations than Integer. It doesn't have “-”, but it does have “difference:: Natural -> Natural -> Natural”, and so do the bigger types (“difference a b = abs (a - b)”)
Is it better to make (^^), (^), and "take" partial functions, or to make (-) and "negate" partial functions?
No :-). “-” and “negate” would belong to a class of which Natural had no instances. If you're the sort of person who likes having partial functions like “head” sullying the scene, you might find it convenient to have “integralToNatural” that either returns the corresponding Natural or throws an exception. Actually, if you are someone like that, you probably want to give it a shorter name...
Of course, there's always a typeclass, where we could add all sorts of other encodings of the Peano axioms, such as binary trees,, but I don't see that that buys us much if we don't also get access to operations beyond them, such as (an _efficient_) `div` for fastexp.
I don't see why Natural can't have an instance of whatever class ends up owning “div”. It's perfectly well behaved on Naturals. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2006-09-07)

On 2006-09-09, Jón Fairbairn
Aaron Denney
writes: Meh. Naturals are reasonably useful sometimes, but not often enough, in my opinion. Any sort of numeric hierarchy designed to deal with them would be totally broken from my point of view -- if you don't at least have inverses, it's not a number,
Crikey. Would you really have me accept that the natural numbers aren't numbers?
I'd like it if you would, but don't expect to convince you.
just some sort of weird algebraic structure. And if it's not in the numeric hierarchy, and so you can't do arithmetic syntactically nicely with it, what's the point?
Could you elaborate? I haven't thought it through, but I can't see why splitting Num into something that puts Natural "above" Integer would be particularly problematic.
For a Natural typeclass to be useful in keeping full-blown Integers away from functions like "take", it can't be above the ones Integer belongs to. Instead it has to "hang off the side" of the numeric hierarchy. You can split this into a "tagging" class on the side and what naturals and integer have in common. Or, of course, you could onry allow one implementation of naturals, and have the Natural typeclass not used to enforce these restriction, but just the data type itself.
Natural just has fewer operations than Integer. It doesn't have â-â, but it does have âdifference:: Natural -> Natural -> Naturalâ, and so do the bigger types (âdifference a b = abs (a - b)â)
Is difference ever a useful function? I guess I don't see it as terribly natural. Placing it in the hierarchy somewhere above the class with (-) also means we can't have a default definition in terms of (-).
Is it better to make (^^), (^), and "take" partial functions, or to make (-) and "negate" partial functions?
No :-). â-â and ânegateâ would belong to a class of which Natural had no instances.
That could work. I still don't like having a plus without a minus.
Of course, there's always a typeclass, where we could add all sorts of other encodings of the Peano axioms, such as binary trees,, but I don't see that that buys us much if we don't also get access to operations beyond them, such as (an _efficient_) `div` for fastexp.
I don't see why Natural can't have an instance of whatever class ends up owning âdivâ. It's perfectly well behaved on Naturals.
True. It seems odd to have a multiplicative (pseudo) inverse, but not an additive, though. Breaking up the numeric hierarchy too finely seems like it would be a pain -- take it to the limit of a separate class per function. What else would you drag in with "div"? "mod", (*), ...? I was thinking of useful implementations solely in terms of the Peano-axiom interface, which only really needs to be there for a default implementation. -- Aaron Denney -><-

On 10/09/06, Aaron Denney
I still don't like having a plus without a minus.
I think in practice this wouldn't really be an issue. When you're using natural numbers, you tend to be in a situation where you're either numbering things statically, and not doing any calculations with them, or you're using them as a monoid, whereby things only increase. -- -David House, dmhouse@gmail.com

Hi,
I think in practice this wouldn't really be an issue. When you're using natural numbers, you tend to be in a situation where you're either numbering things statically, and not doing any calculations with them, or you're using them as a monoid, whereby things only increase.
take? primes? fibs? ackermanns? There are lots of things things were computation is performed on natural numbers, in fact, I'd say its relatively rare to find negative integers! See "What About the Natural Numbers" - "Colin Runciman" - it's a good read :) Thanks Neil

On 2006-09-10, Neil Mitchell
Hi,
I think in practice this wouldn't really be an issue. When you're using natural numbers, you tend to be in a situation where you're either numbering things statically, and not doing any calculations with them, or you're using them as a monoid, whereby things only increase.
take? primes? fibs? ackermanns?
take is more an iteration than a numerical calculation -- it works best as pattern matching on Succ and Zero. Primes and fibs are purely generative streams that can be calculated just fine using integers. If you want to geta specific value out, then sure, index using naturals, which again is a data-structural induction. Yes, it's nice to be able to encode the invariant "x > 0". It'd also be nice to be able to encode invariants like (x > 10), or (a < x < b) for array access. But for both of these it is more natural to work with a subset of the integers, than a new type. Yes, even if this means dealing with partial functions. And, as I pointed out before, if naturals are represented asunary, then it means you can do "take infinity xs where infinity = Succ infinity"
See "What About the Natural Numbers" - "Colin Runciman" - it's a good read :)
I will when I get the chance. -- Aaron Denney -><-

On 2006-09-11, Aaron Denney
See "What About the Natural Numbers" - "Colin Runciman" - it's a good read :)
I will when I get the chance.
Finally found a copy. It is a good read. I mostly agree with him. The biggest exception is about the need for highly optimized, near the machine level, representations of the naturals. 17 years later with much better computers, I think the unary representation works just fine, and transparently conveys what it means. -- Aaron Denney -><-

On Sun, 10 Sep 2006, Aaron Denney wrote:
Of course, there's always a typeclass, where we could add all sorts of other encodings of the Peano axioms, such as binary trees,, but I don't see that that buys us much if we don't also get access to operations beyond them, such as (an _efficient_) `div` for fastexp.
I don't see why Natural can't have an instance of whatever class ends up owning âdivâ. It's perfectly well behaved on Naturals.
True. It seems odd to have a multiplicative (pseudo) inverse, but not an additive, though. Breaking up the numeric hierarchy too finely seems like it would be a pain -- take it to the limit of a separate class per function. What else would you drag in with "div"? "mod", (*), ...?
from http://darcs.haskell.org/numericprelude/src/Algebra/Core.lhs :
class (Num a) => Integral a where div, mod :: a -> a -> a divMod :: a -> a -> (a,a)
-- Minimal definition: divMod or (div and mod) div a b = fst (divMod a b) mod a b = snd (divMod a b) divMod a b = (div a b, mod a b)

On 2006-09-11, Henning Thielemann
On Sun, 10 Sep 2006, Aaron Denney wrote:
Of course, there's always a typeclass, where we could add all sorts of other encodings of the Peano axioms, such as binary trees,, but I don't see that that buys us much if we don't also get access to operations beyond them, such as (an _efficient_) `div` for fastexp.
I don't see why Natural can't have an instance of whatever class ends up owning "div". It's perfectly well behaved on Naturals.
True. It seems odd to have a multiplicative (pseudo) inverse, but not an additive, though. Breaking up the numeric hierarchy too finely seems like it would be a pain -- take it to the limit of a separate class per function. What else would you drag in with "div"? "mod", (*), ...?
from http://darcs.haskell.org/numericprelude/src/Algebra/Core.lhs :
class (Num a) => Integral a where div, mod :: a -> a -> a divMod :: a -> a -> (a,a)
-- Minimal definition: divMod or (div and mod) div a b = fst (divMod a b) mod a b = snd (divMod a b) divMod a b = (div a b, mod a b)
That particular division means that Naturals can't support div because they're not a ring, which the (Num a) in that snippet above means for this numeric hierarcy, right? So this does drag in div, mod and (*), which all seem mostly reasonable, but it also drags in (-) and "negate", which you don't want for Naturals. -- Aaron Denney -><-

Cale Gibbard wrote:
On 17/08/06, Brian Hulley
wrote: In contrast, a programming language should be based on general concepts uniformly applied. In Haskell we have operators, identifiers, prefix application using an identifier and infix application using a symbol, and a uniform way to convert a symbol to an identifier and vice versa, and a uniform way of forming sections.
Secondly, I think it's quite a reasonable thing to do to treat unary negation as a separate operation. It follows quite naturally to do so from the definition of a ring. While having separate literals for negative numbers might be okay, it seems unnecessary in light of the fact that we *do* want a nice looking unary negation symbol, which doesn't strictly apply to literals. If -x suddenly became a non-expression, and I had to write 0-x, -1*x or (negate x) instead, I'd consider that a severe enough bug that I would avoid upgrading my compiler until it was fixed.
Leaving aside the question of negative literals for the moment, what's so special about unary minus that it warrants a special syntax? For example in mathematics we have x! to represent (factorial x), which is also an important function, yet no-one is arguing that we should introduce a unary postfix operator to Haskell just to support it. In maths we also have |x| to denote another common function, (abs x), yet afaia everyone is happy to just write (abs x). Would the elimination of the special case rule for unary minus not make the language easier to understand? What's wrong with typing (negate x) in the rare cases where you can't just re-write the expression to use infix minus instead (ie x + -y ===> x - y)? Surely most programs in Haskell are not just arithmetic expressions, and while it is convenient to have infix +, -, *, `div`, `mod` for the integers, so you can do indexing over data types and other "counting" operations, I'd argue that the usual functional notation (eg (exp x) (factorial x) (negate x)) should be sufficient for the other arithmetic operations just as it's deemed sufficient for nearly everything else in Haskell! ;-)
In mathematics, we don't use separate symbols for negative integers, and negated positive integers, even though in the underlying representation of the integers as equivalence classes of pairs of naturals, we can write things like -[(1,0)] = [(0,1)], which expressed in ordinary notation just says that -1 = -1. This doesn't bother us, because the two things are always equal.
Another thing to note is that all the natural literals are not, as one might initially think, plain values, but actually represent the embedding of that natural number into the ring (instance of Num), by way of 0 and 1. They simply provide a convenient notation for getting particular values of many rings, but in many cases, don't get one very far at all before other functions must be introduced to construct the constant values one wants. While there always is a homomorphism from Z to a ring (represented in Haskell by fromInteger), one would get similar expressiveness by with just the nullary operators 0 and 1, and the unary negation as well as addition and multiplication (albeit with an often severe performance hit, and some annoyance, I'm not recommending we really do this, simply characterising the purpose of numeric literals).
If the performance issue regarding the polymorphic literal -5 meaning negate (fromInteger 5) is a problem, it would be easy enough to agree for the compiler to find and rewrite literals like that as fromInteger (-5) instead, where -5 is the precomputed integer -5. Assuming that fromInteger is not broken, that will always mean the same thing (because fromInteger is supposed to be a homomorphism). Similarly, when the type of (fromInteger x) is known statically to be Integer, the compiler can rewrite it as x. In any event, this is a tiny constant factor performance hit.
Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after performing the fromInteger transformation they may be taken as literal integers, but there is no reason that this level has to be exposed to the user.
This seems very theoretical to me. In the context of programming, I don't see the problem of just thinking of the integers as a primitive built-in data type which contains some range of positive and negative integers which I'd argue should all be treated on an equal footing when the context of discourse is the integers not the naturals. Another point is that the current treatment requires a special rule for pattern matching against a negative integer or float, which would not be needed if negative literals could be specified directly.
Additionally, consider things like Rational. It is possible to write some elements of Rational in terms of integer "literals", but not all of them, even if negative literals become included. Floating point literals help a bit here, but not really all that much. (Consider things like 1/3, or 1/7.) In particular, any rational number with a denominator greater than 1 is inaccessible from that interface. Based on your previously mentioned design principle that all values of a type should be expressible via literals, or none of them should be, we should in fact remove the polymorphic interface for 0,1, etc. and force the user to type 1%1 for the rational 1. But this is annoying, and destroys polymorphism!
I think that design principle is broken. If it was extended to say something like "All values of a type should be possible to write solely in terms of its constructors, or none of them should be.", then potentially infinite data structures would be excluded from having exposed constructors, for no good reason other than that there are infinite values which require other operations to define. This is, in a way, rather similar to the problem with rationals.
Yes I see now that that design principle appears too restrictive in general.
I'd also like to say that the exponentiation example is also a good one. -4^2 is *always* -16, in every sane mathematical context since unary negation is treated as an additive operation, and thus should happen after exponentiation and multiplication (though under normal circumstances, it doesn't matter whether it's done before or after multiplication).
In C, it wouldn't be, since there, unary ops always bind tighter than infix ops, and the precedences used in C are also used in C++, Java, C#, Javascript etc, and even ISO Prolog obeys the rule that unary minus binds tighter so making unary minus have the same precedence as infix minus just makes Haskell syntax difficult to parse for anyone coming from one of these other very popular languages. Imho, for better or worse, C has established a kind of de-facto standard that unary ops always bind tighter than infix ops in programming languages ;-) Also, it's a good example of why we should *not* have unary minus, since the above could be written with no ambiguity as: negate (4 ^ 2) or better still: negate (expNat 4 2) because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit (ie ^ or ^^ - the symbols don't give much clue what the differences between them are, only that they are both something to do with exponentiation, whereas actual words like expNat expInt would make explicit both the similarity and the difference between them).
Though this is a little offtopic, another important thing to note about parsing exponentiation is that a^b^c always means a^(b^c) and not (a^b)^c, which is a fairly standard thing in mathematics, because of the tendency to automatically rewrite (a^b)^c as a^(b*c), which looks nicer (and wouldn't normally involve parentheses on the page), and that no such rule exists for the other association.
While I've considered that there are reasons that requiring spaces to be included to separate operator symbols from their arguments might actually be a decent thing to have, I wouldn't recommend doing things in the way that you're suggesting. With that in place, we could have negative integer literals (provided that people really care that strongly), but that's no reason to drop unary negation altogether -- just require that a space occur between the unary minus and its parameter. However, there are certain operators, especially exponentiation, and multiplication inside an additive expression, which putting spaces around them just looks "wrong" to me, and though I might be able to get used to it, I'd probably end up recompiling things all the time over syntax errors related to it. Newcomers to the language would also probably dislike it when they typed x+y at the ghci prompt and got some error saying that x+y is not in scope.
I don't think there is a need to force spaces to be put around every infix application. It's only when there would be a conflict with the lexical syntax that spaces are needed, just as at the moment we have (F . G) versus (F.G), (f $ g) versus (f $g) etc. As long as one's preferred editor highlights literals differently from symbols, I think it would be difficult to not notice the distinction between "x - 2" and "x -2" if unary minus were replaced by negative literals. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hi Brian and others, I posted the original question because I didn't know how to get map (-2) working. Since the original posting, many people have presented _a priori_ arguments about the merits of different approaches, most importantly whether or not to abandon the unary - operator. As a Haskell newbie, I find the special treatment of - ugly, but as it is generally difficult to convince others about one's aesthetic judgements, I would like to suggest an approach that might add additional reasons in favor of and against the unary -. Even though I am fond of a priori arguments, I think that questions of syntax should be handled as practical ones. In most languages, choosing infix and unary operators is guided by practical considerations: for example, the infix + exists because typing plus 1 2 would take longer, make the code unreadable. In this case, the decision to make + (nothing but) an infix operator is easy, because there is no trade-off involved. But in the case of -, there is a clear tradeoff (at least in Haskell): if we allow unary -, sections like (-2) won't work. I wonder if it would be possible to take a large sample of Haskell code that people generally consider "good" (ie written by experienced programmers) and count (with a script, of course) the occurrences of (A) unary - and (B) - used as a binary operator where the programmer had to circumvent unary -, especially in sections, and including things like (flip (-) x) (+ (- x)) and other approaches people use to circumvent the problem. If A is significantly larger than B, people who wish to retain unary - would have a good case. On the other hand, if B >> A, then the removal of unary - should be at least considered. This would allow us to compare the amount of inconvenience caused by either approach in practice. Best, Tamas On Fri, Sep 08, 2006 at 03:30:33PM +0100, Brian Hulley wrote:
Leaving aside the question of negative literals for the moment, what's so special about unary minus that it warrants a special syntax? For example in mathematics we have x! to represent (factorial x), which is also an important function, yet no-one is arguing that we should introduce a unary postfix operator to Haskell just to support it.
In maths we also have |x| to denote another common function, (abs x), yet afaia everyone is happy to just write (abs x).
Would the elimination of the special case rule for unary minus not make the language easier to understand? What's wrong with typing (negate x) in the rare cases where you can't just re-write the expression to use infix minus instead (ie x + -y ===> x - y)? Surely most programs in Haskell are not just arithmetic expressions, and while it is convenient to have infix +, -, *, `div`, `mod` for the integers, so you can do indexing over data types and other "counting" operations, I'd argue that the usual functional notation (eg (exp x) (factorial x) (negate x)) should be sufficient for the other arithmetic operations just as it's deemed sufficient for nearly everything else in Haskell! ;-)
In mathematics, we don't use separate symbols for negative integers, and negated positive integers, even though in the underlying representation of the integers as equivalence classes of pairs of naturals, we can write things like -[(1,0)] = [(0,1)], which expressed in ordinary notation just says that -1 = -1. This doesn't bother us, because the two things are always equal.
Another thing to note is that all the natural literals are not, as one might initially think, plain values, but actually represent the embedding of that natural number into the ring (instance of Num), by way of 0 and 1. They simply provide a convenient notation for getting particular values of many rings, but in many cases, don't get one very far at all before other functions must be introduced to construct the constant values one wants. While there always is a homomorphism from Z to a ring (represented in Haskell by fromInteger), one would get similar expressiveness by with just the nullary operators 0 and 1, and the unary negation as well as addition and multiplication (albeit with an often severe performance hit, and some annoyance, I'm not recommending we really do this, simply characterising the purpose of numeric literals).
If the performance issue regarding the polymorphic literal -5 meaning negate (fromInteger 5) is a problem, it would be easy enough to agree for the compiler to find and rewrite literals like that as fromInteger (-5) instead, where -5 is the precomputed integer -5. Assuming that fromInteger is not broken, that will always mean the same thing (because fromInteger is supposed to be a homomorphism). Similarly, when the type of (fromInteger x) is known statically to be Integer, the compiler can rewrite it as x. In any event, this is a tiny constant factor performance hit.
Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after performing the fromInteger transformation they may be taken as literal integers, but there is no reason that this level has to be exposed to the user.
This seems very theoretical to me. In the context of programming, I don't see the problem of just thinking of the integers as a primitive built-in data type which contains some range of positive and negative integers which I'd argue should all be treated on an equal footing when the context of discourse is the integers not the naturals.
Another point is that the current treatment requires a special rule for pattern matching against a negative integer or float, which would not be needed if negative literals could be specified directly.
Additionally, consider things like Rational. It is possible to write some elements of Rational in terms of integer "literals", but not all of them, even if negative literals become included. Floating point literals help a bit here, but not really all that much. (Consider things like 1/3, or 1/7.) In particular, any rational number with a denominator greater than 1 is inaccessible from that interface. Based on your previously mentioned design principle that all values of a type should be expressible via literals, or none of them should be, we should in fact remove the polymorphic interface for 0,1, etc. and force the user to type 1%1 for the rational 1. But this is annoying, and destroys polymorphism!
I think that design principle is broken. If it was extended to say something like "All values of a type should be possible to write solely in terms of its constructors, or none of them should be.", then potentially infinite data structures would be excluded from having exposed constructors, for no good reason other than that there are infinite values which require other operations to define. This is, in a way, rather similar to the problem with rationals.
Yes I see now that that design principle appears too restrictive in general.
I'd also like to say that the exponentiation example is also a good one. -4^2 is *always* -16, in every sane mathematical context since unary negation is treated as an additive operation, and thus should happen after exponentiation and multiplication (though under normal circumstances, it doesn't matter whether it's done before or after multiplication).
In C, it wouldn't be, since there, unary ops always bind tighter than infix ops, and the precedences used in C are also used in C++, Java, C#, Javascript etc, and even ISO Prolog obeys the rule that unary minus binds tighter so making unary minus have the same precedence as infix minus just makes Haskell syntax difficult to parse for anyone coming from one of these other very popular languages. Imho, for better or worse, C has established a kind of de-facto standard that unary ops always bind tighter than infix ops in programming languages ;-)
Also, it's a good example of why we should *not* have unary minus, since the above could be written with no ambiguity as:
negate (4 ^ 2)
or better still:
negate (expNat 4 2)
because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit (ie ^ or ^^ - the symbols don't give much clue what the differences between them are, only that they are both something to do with exponentiation, whereas actual words like expNat expInt would make explicit both the similarity and the difference between them).
Though this is a little offtopic, another important thing to note about parsing exponentiation is that a^b^c always means a^(b^c) and not (a^b)^c, which is a fairly standard thing in mathematics, because of the tendency to automatically rewrite (a^b)^c as a^(b*c), which looks nicer (and wouldn't normally involve parentheses on the page), and that no such rule exists for the other association.
While I've considered that there are reasons that requiring spaces to be included to separate operator symbols from their arguments might actually be a decent thing to have, I wouldn't recommend doing things in the way that you're suggesting. With that in place, we could have negative integer literals (provided that people really care that strongly), but that's no reason to drop unary negation altogether -- just require that a space occur between the unary minus and its parameter. However, there are certain operators, especially exponentiation, and multiplication inside an additive expression, which putting spaces around them just looks "wrong" to me, and though I might be able to get used to it, I'd probably end up recompiling things all the time over syntax errors related to it. Newcomers to the language would also probably dislike it when they typed x+y at the ghci prompt and got some error saying that x+y is not in scope.
I don't think there is a need to force spaces to be put around every infix application. It's only when there would be a conflict with the lexical syntax that spaces are needed, just as at the moment we have (F . G) versus (F.G), (f $ g) versus (f $g) etc. As long as one's preferred editor highlights literals differently from symbols, I think it would be difficult to not notice the distinction between "x - 2" and "x -2" if unary minus were replaced by negative literals.
Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"Brian Hulley"
Leaving aside the question of negative literals for the moment, what's so special about unary minus that it warrants a special syntax? For example in mathematics we have x! to represent (factorial x), which is also an important function, yet no-one is arguing that we should introduce a unary postfix operator to Haskell just to support it.
In maths we also have |x| to denote another common function, (abs x), yet afaia everyone is happy to just write (abs x).
That's just a matter of how common the operator is. “-” is so common that if you asked a random passer-by they'd probably identify it correctly, whereas “!” and “|...|” would be likely to elicit a response of "no idea mate".
Would the elimination of the special case rule for unary minus not make the language easier to understand?
A bit, certainly.
What's wrong with typing (negate x) in the rare cases where you can't just re-write the expression to use infix minus instead (ie x + -y ===> x - y)?
Nothing, really. But in that case, why have a special case for negative literals? “negate 42” would be more consistent¹, and it wouldn't tax language implementors a groat if the language specified that such an application should always be folded into whatever your suggested syntax would have produced. [1] “-” is a varsym. The logical way of achieving what you suggest (ie -1 -2... as constructors for Integer) would be to make it introduce a consym the way “:” does, but then it couldn't be an infix operator anymore.
Surely most programs in Haskell are not just arithmetic expressions, and while it is convenient to have infix +, -, *, `div`, `mod` for the integers, so you can do indexing over data types and other "counting" operations, I'd argue that the usual functional notation (eg (exp x) (factorial x) (negate x)) should be sufficient for the other arithmetic operations just as it's deemed sufficient for nearly everything else in Haskell! ;-)
I can't say that I find anything disagreeable about that suggestion, though the operators aren't on Integers but belong to typeclasses.
Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after performing the fromInteger transformation they may be taken as literal integers, but there is no reason that this level has to be exposed to the user.
This seems very theoretical to me.
One of the most valuable aspects of Haskell is it's theoretical underpinning. Don't play fast and loose with that!
In the context of programming, I don't see the problem of just thinking of the integers as a primitive built-in data type which contains some range of positive and negative integers which I'd argue should all be treated on an equal footing when the context of discourse is the integers not the naturals.
I'm not sure what that means. Why should they be equal? Why shouldn't Naturals be more primitive than Integers?
Another point is that the current treatment requires a special rule for pattern matching against a negative integer
Perhaps the notional declaration
data Integer = Succ Natural | Zero | Pred Natural
(with “Succ 0” meaning 1, of course, possibly with nicer syntax and definitiely with the expectation that it'll be compiled into a decent machine representation) would address that?
or float,
Pattern matching on floats is an abomination, definitely a candidate for removal.
I'd also like to say that the exponentiation example is also a good one. -4^2 is *always* -16, in every sane mathematical context since unary negation is treated as an additive operation, and thus should happen after exponentiation and multiplication (though under normal circumstances, it doesn't matter whether it's done before or after multiplication).
In C, it wouldn't be, since there, unary ops always bind tighter than infix ops,
C is almost the last place to look for elegant language design. (Not quite the last, there's Perl and some deliberate gargoyles of languages to go after it)
or better still:
negate (expNat 4 2)
because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit
Agreed, though I'd want expt to be part of a typeclass (possibly multi-parameter to get exp:: Integral a => a -> Natural -> a as an instance?).
I don't think there is a need to force spaces to be put around every infix application. It's only when there would be a conflict with the lexical syntax that spaces are needed, just as at the moment we have (F . G) versus (F.G), (f $ g) versus (f $g) etc.
That rather goes against your simplicity of design argument, doesn't it? Why the special cases? For years I've been rather sloppy about spaces around “$”, and now when I use template haskell, this bites me. At some point in the future someone might decide that & or % is needed to introduce a new chunk of syntax, and formerly valid programmes break. So why not just say that varsym varid is in general reserved for future special syntaxes, and require varsym whitespace varid everywhere? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2006-09-07)

Jón Fairbairn wrote:
"Brian Hulley"
writes: Cale Gibbard wrote:
Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after performing the fromInteger transformation they may be taken as literal integers, but there is no reason that this level has to be exposed to the user.
This seems very theoretical to me.
One of the most valuable aspects of Haskell is it's theoretical underpinning. Don't play fast and loose with that!
You're right. I should have made a proper argument so here goes: 1) Num a implies that forall a, there is an additive inverse for a (given by (negate)) 2) I think Cale is saying that it is sufficient to have overloaded nullary operators 0 and 1 in conjunction with the (+) and (negate) methods of Num, in order to construct all elements of Num 3) I think also Cale's argument is that the other nullary operators, 2, 3, ... are just there for convenience, but that this convenience is a good thing. So my argument would be that given that we only actually need 0 and 1, but we already have 2, 3,... for convenience, there is no reason to not also have -1, -2, -3, ... as well, for even more convenience, especially as the numeric hierarchy starts with a structure where every element is required to have an additive inverse.
[1] “-” is a varsym. The logical way of achieving what you suggest (ie -1 -2... as constructors for Integer) would be to make it introduce a consym the way “:” does, but then it couldn't be an infix operator anymore.
I don't think it's necessary to use the same kind of rule for '-' as for ':'. The rule could be that a '-' immediately followed by a digit starts a negative number, otherwise the '-' is treated as it is at the moment (ie either the start of a comment or a varsym). I imagine that almost every editor at least does lexical fontification, and if so, then I don't think there could be much confusion in practice between these uses of '-'. Also, the fact that we want to allow pattern matching against negative integers suggests that positive integers and negative integers should have equal status regarding literal representation (more precisely: nullary operator overloaded for the integers), rather than having to introduce a special pattern matching rule for the negatives.
Pattern matching on floats is an abomination, definitely a candidate for removal.
Seconded.
negate (expNat 4 2)
because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit
Agreed, though I'd want expt to be part of a typeclass (possibly multi-parameter to get exp:: Integral a => a -> Natural -> a as an instance?).
Yes, a typeclass for exp would be ideal (and a newtype for Natural). Perhaps we could even use (neg) instead of (negate) in deference to the 3 letter varids used for other common arithmetic ops, to get: neg (exp 4 2) neg y * 56 ("neg" can also be read declaratively as "negative", instead of the imperative "negate".)
I don't think there is a need to force spaces to be put around every infix application. It's only when there would be a conflict with the lexical syntax that spaces are needed, just as at the moment we have (F . G) versus (F.G), (f $ g) versus (f $g) etc.
That rather goes against your simplicity of design argument, doesn't it? Why the special cases? For years I've been rather sloppy about spaces around “$”, and now when I use template haskell, this bites me. At some point in the future someone might decide that & or % is needed to introduce a new chunk of syntax, and formerly valid programmes break. So why not just say that varsym varid is in general reserved for future special syntaxes, and require varsym whitespace varid everywhere?
This would certainly be a simple rule that would also make code easier to read. Summary (imagine the different editor colours/font styles): (- 1) -- a section because of the space (-1) -- a negative number (x - 1) -- (-) x 1 (x -1) -- x applied to (-1) (x -y) -- either (x - y) or, following the above rule, a syntax error. I also agree with Tamas's suggestion that an empirical analysis of Haskell source code could be useful to determine the practical implications of unary minus, which might help to address Jared's comments about the improbability of being able to reach a consensus when everyone has such different experiences/purposes etc. Anyway no doubt I've posted enough emails about unary minus and negative literals so I'll be quiet now ;-) Best regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

On 08/09/06, Brian Hulley
Jón Fairbairn wrote:
"Brian Hulley"
writes: Cale Gibbard wrote:
Anyway, the point of all this is that 0,1,2... are not really literals at all. They're nullary operators which give particular elements of any given instance of Num. Perhaps at some level in the compiler after performing the fromInteger transformation they may be taken as literal integers, but there is no reason that this level has to be exposed to the user.
This seems very theoretical to me.
One of the most valuable aspects of Haskell is it's theoretical underpinning. Don't play fast and loose with that!
You're right. I should have made a proper argument so here goes:
1) Num a implies that forall a, there is an additive inverse for a (given by (negate)) 2) I think Cale is saying that it is sufficient to have overloaded nullary operators 0 and 1 in conjunction with the (+) and (negate) methods of Num, in order to construct all elements of Num 3) I think also Cale's argument is that the other nullary operators, 2, 3, ... are just there for convenience, but that this convenience is a good thing.
So my argument would be that given that we only actually need 0 and 1, but we already have 2, 3,... for convenience, there is no reason to not also have -1, -2, -3, ... as well, for even more convenience, especially as the numeric hierarchy starts with a structure where every element is required to have an additive inverse.
My counterargument here is that this doesn't actually increase convenience. In fact, for a lot of reasons, it decreases convenience.
[1] "-" is a varsym. The logical way of achieving what you suggest (ie -1 -2... as constructors for Integer) would be to make it introduce a consym the way ":" does, but then it couldn't be an infix operator anymore.
I don't think it's necessary to use the same kind of rule for '-' as for ':'. The rule could be that a '-' immediately followed by a digit starts a negative number, otherwise the '-' is treated as it is at the moment (ie either the start of a comment or a varsym).
I imagine that almost every editor at least does lexical fontification, and if so, then I don't think there could be much confusion in practice between these uses of '-'.
Also, the fact that we want to allow pattern matching against negative integers suggests that positive integers and negative integers should have equal status regarding literal representation (more precisely: nullary operator overloaded for the integers), rather than having to introduce a special pattern matching rule for the negatives.
Pattern matching on floats is an abomination, definitely a candidate for removal.
Seconded.
negate (expNat 4 2)
because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit
Agreed, though I'd want expt to be part of a typeclass (possibly multi-parameter to get exp:: Integral a => a -> Natural -> a as an instance?).
Yes, a typeclass for exp would be ideal (and a newtype for Natural).
Num itself needs to be split, but we can't do it sanely without something like class aliases. I actually think that the (^), (^^), (**) distinction is rather refreshing to see in a programming language. Most languages don't take the care to distinguish that there are actually different levels of definition of exponentiation. You can't just merge them -- have you looked at their types? (^^) can't be defined for Integers, but it works fine for Rational bases, (**) can't be defined for Rational bases, but works fine for floating point. Additionally, these operations have different performance and numerical properties. If we have a typeclass for this, it will be multiparameter, and there will not be a functional dependency. This could create additional annoyance in various situations. In mathematics, these operations are given the same notation, but are definitely distinguished between by the humans using them.
Perhaps we could even use (neg) instead of (negate) in deference to the 3 letter varids used for other common arithmetic ops, to get:
neg (exp 4 2) neg y * 56
("neg" can also be read declaratively as "negative", instead of the imperative "negate".)
I obviously already disagree with this whole bit anyway, but eek, don't steal exp. We already have a very important function (in fact, I'd be willing to say that it's probably the most important function in all of mathematics) called exp, and it's named after its standard name in mathematics. Also, not using infix notation for exponentiation would obfuscate many simple mathematical programs. Anything involving a polynomial will look terrible. (I don't care if you're a C programmer and you're used to polynomials looking terrible, I'm not.) I don't really care too much either way with negate <-> neg, I know some people hate abbreviations in the libraries, but that one is probably sufficiently intuitive for me.
I don't think there is a need to force spaces to be put around every infix application. It's only when there would be a conflict with the lexical syntax that spaces are needed, just as at the moment we have (F . G) versus (F.G), (f $ g) versus (f $g) etc.
That rather goes against your simplicity of design argument, doesn't it? Why the special cases? For years I've been rather sloppy about spaces around "$", and now when I use template haskell, this bites me. At some point in the future someone might decide that & or % is needed to introduce a new chunk of syntax, and formerly valid programmes break. So why not just say that varsym varid is in general reserved for future special syntaxes, and require varsym whitespace varid everywhere?
Personally, I'm not completely sure why everyone is so crazy about using (.) for module path separation and proposed record syntaxes. Sure lots of OO languages do it, so it has that going for it. Personally, I think I'd have preferred the vertical bar (pipe) symbol with no intervening spaces for both of those syntaxes. It looks decent enough, e.g. Data|Map|empty, point|x (or possibly x|point, depending on which way you'd go with record selection). It can't be an operator symbol, so it wouldn't affect things there. As for guards and data declarations, there would indeed be some issues, but everyone already conventionally adds a space before and after the bar in those cases, so that's actually far less likely to become a problem than conflicts with composition. I haven't used TH enough to really say how the quoting/splicing syntax affects me, but I have bumped into it once or twice with lambdabot.
This would certainly be a simple rule that would also make code easier to read.
Summary (imagine the different editor colours/font styles): (- 1) -- a section because of the space (-1) -- a negative number
(x - 1) -- (-) x 1 (x -1) -- x applied to (-1)
Ouch! This is likely to be a type error, but still. We seem to be introducing a lot of syntax lately that makes things different based on spaces between symbols and identifiers. Do we really want this? I have trouble reading that as x applied to -1, I'd hope that everyone would put negative values in parentheses anyway when doing things like that. The section with whitespace mattering is less-bad for some reason, but still could annoy the heck out of me when I carelessly got it wrong.
(x -y) -- either (x - y) or, following the above rule, a syntax error.
This seems like a lot of pain to me just to get section notation working for (-). When I first ran into the problem with (-) and sections, I was slightly annoyed with having to write (+ (-1)), but quickly realised that I'd be far more annoyed by not having things like (-x) work for negation. It's one of those things where if compilers were actually people, we'd probably have the meaning depend on context, but since they aren't, we really don't want to trust them with determining what we want, so it's best just to pick one. I'm going to back the traditional mathematical meaning of unary negation. It's been around hundreds of years, people know what it means from elementary school, and it's probably more common in code anyway, so let's leave it alone. As for editors, hopefully we'll eventually have a free editor which really properly parses the Haskell code for syntax highlighting. (Using some proper recovery mechanism for parse errors of course.) I think a lot of the trouble with colouring comes from the fact that people are still using regexps to define syntaxes, when if they were doing proper parses, they'd get the colours right, and the extra structural information could be used intelligently by the editor (e.g. getting indentation and alignment right automatically, allowing the user to adjust the indentation of blocks and guards all at once, sugaring and desugaring from braces-and-semicolons, etc.). There's also a lot to be said for going even farther into the compilation process to detect type errors and such, like Visual Haskell does. That said, I've never been really annoyed with the way that any program I've seen colours Haskell text. Usually it's pretty minimalist, but that's usually all right for me. It would be cool however, if programs were able to add more colour contextually to the function I was editing, for example, painting all local uses of the variable the pointer was on, which would also make it easier to see where it was bound, and when one variable has accidentally shadowed another with the same name.
I also agree with Tamas's suggestion that an empirical analysis of Haskell source code could be useful to determine the practical implications of unary minus, which might help to address Jared's comments about the improbability of being able to reach a consensus when everyone has such different experiences/purposes etc.
Even if potential sections of subtraction were more common than unary negation, I'm still not sure I'd want to change it. If one takes this approach to ridiculous extremes, one will end up Huffman encoding the entire language, which isn't necessarily such a user friendly thing to do. :) I think that the amount we'd hurt readability of the programs which did need unary negation by not making it look nice, I estimate is far more than how much we'd help the programs which could make use of sections of subtraction. - Cale

On 09/09/06, Cale Gibbard
When I first ran into the problem with (-) and sections, I was slightly annoyed with having to write (+ (-1))
Let's not forget that there is the library function 'subtract' for this purpose. What you wrote could be written as (subtract 1), which is more readable in my opinion. But hey, what do I know, I think using the underscore for unary negation (à la Emacs calculator) would be an acceptable enough compromise. -- -David House, dmhouse@gmail.com

On Sat, Sep 09, 2006 at 12:57:56AM -0400, Cale Gibbard wrote:
Num itself needs to be split, but we can't do it sanely without something like class aliases.
I think that a finer grain numeric hierarchy, while retaining Num, etc, is feasible without changing the language: unlike the case of monads, the people who will be defining instances of numeric classes are the very ones who are inconvenienced by the current hierarchy. The main impact on clients of the classes is that some functions would have more general types.

On Sat, 9 Sep 2006, Ross Paterson wrote:
On Sat, Sep 09, 2006 at 12:57:56AM -0400, Cale Gibbard wrote:
Num itself needs to be split, but we can't do it sanely without something like class aliases.
I think that a finer grain numeric hierarchy, while retaining Num, etc, is feasible without changing the language: unlike the case of monads, the people who will be defining instances of numeric classes are the very ones who are inconvenienced by the current hierarchy. The main impact on clients of the classes is that some functions would have more general types.
There are many Num instances around in libraries where people wrap to external libraries: functionalMetapost, CSound wrapper in Haskore, SuperCollider (GSL too?). What about Num (algebraically Ring) instances of polynomials, residue classes and other such advanced mathematical objects?

On Mon, Sep 11, 2006 at 04:26:30PM +0200, Henning Thielemann wrote:
On Sat, 9 Sep 2006, Ross Paterson wrote:
I think that a finer grain numeric hierarchy, while retaining Num, etc, is feasible without changing the language: unlike the case of monads, the people who will be defining instances of numeric classes are the very ones who are inconvenienced by the current hierarchy. The main impact on clients of the classes is that some functions would have more general types.
There are many Num instances around in libraries where people wrap to external libraries: functionalMetapost, CSound wrapper in Haskore, SuperCollider (GSL too?). What about Num (algebraically Ring) instances of polynomials, residue classes and other such advanced mathematical objects?
And what do abs and signum mean for Haskore's orchestra expressions, polynomials, residue classes, vectors, matrices, functions, etc? The people who define those wish they were defining Ring, but they must define Num.

On 2006-09-11, Henning Thielemann
On Sat, 9 Sep 2006, Ross Paterson wrote:
On Sat, Sep 09, 2006 at 12:57:56AM -0400, Cale Gibbard wrote:
Num itself needs to be split, but we can't do it sanely without something like class aliases.
I think that a finer grain numeric hierarchy, while retaining Num, etc, is feasible without changing the language: unlike the case of monads, the people who will be defining instances of numeric classes are the very ones who are inconvenienced by the current hierarchy. The main impact on clients of the classes is that some functions would have more general types.
There are many Num instances around in libraries where people wrap to external libraries: functionalMetapost, CSound wrapper in Haskore, SuperCollider (GSL too?). What about Num (algebraically Ring) instances of polynomials, residue classes and other such advanced mathematical objects?
Yes, they would need to move definitions around. I think it'd be worth it for Haskell'. -- Aaron Denney -><-

"Brian Hulley"
Jón Fairbairn wrote:
[1] “-” is a varsym. The logical way of achieving what you suggest (ie -1 -2... as constructors for Integer) would be to make it introduce a consym the way “:” does, but then it couldn't be an infix operator anymore.
I don't think it's necessary to use the same kind of rule for '-' as for ':'.
Not necessary, but you surely don't want yet another rule?
I imagine that almost every editor at least does lexical fontification, and if so, then I don't think there could be much confusion in practice between these uses of '-'.
I think that unnecessarily disadvantages people with poorer than average (including zero) eyesight.
Yes, a typeclass for exp would be ideal
Well, so long as you call it “exponent” or “expt”.
(and a newtype for Natural).
Here's a design principle for you: if an error can be detected at compile time, it should be. If we have literals for naturals and not negative integers, “negate 100” causes no problem, it just means “negate (fromNatural 100)”. If we have literals for integers and try to restrict them to get naturals, “-100:: Natural” becomes shorthand for “integralToNatural (-100)”, and would (in the absence of somewhat arbitrary special-casing in the compiler) give a runtime error.
I also agree with Tamas's suggestion that an empirical analysis of Haskell source code could be useful to determine the practical implications of unary minus,
It has merit and I would laud anyone who got round to doing it, but there's a danger of measuring the wrong thing. What we want to know is not what is more frequent, but what causes the greater number of misreadings and which pieces of code had the most syntax errors before they were completed, and that's harder to measure. Though if unary minus turned out to be very rare, we could just drop it. Using “(0-)” wouldn't be much of a hardship in that case.
Anyway no doubt I've posted enough emails about unary minus and negative literals so I'll be quiet now ;-)
:-) ... ? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Jón Fairbairn wrote:
"Brian Hulley"
writes: I imagine that almost every editor at least does lexical fontification, and if so, then I don't think there could be much confusion in practice between these uses of '-'.
I think that unnecessarily disadvantages people with poorer than average (including zero) eyesight.
For people lacking good eyesight the equivalent of fontification could simply be some text-to-speech system which read "-2" as "negative 2" and "x - y" as "x minus y".
Yes, a typeclass for exp would be ideal
Well, so long as you call it “exponent” or “expt”.
I'd completely forgotten about the normal (exp) function. I should have written (power) or (pow), though as Cale pointed out a typeclass may not be a suitable solution due to the lack of a functional dependency to help the compiler choose the correct overloading. - in that case I'd go back to advocating (powNat) (powInt) etc.
(and a newtype for Natural).
Here's a design principle for you: if an error can be detected at compile time, it should be. If we have literals for naturals and not negative integers, “negate 100” causes no problem, it just means “negate (fromNatural 100)”. If we have literals for integers and try to restrict them to get naturals, “-100:: Natural” becomes shorthand for “integralToNatural (-100)”, and would (in the absence of somewhat arbitrary special-casing in the compiler) give a runtime error.
Ok I'm slowly coming round to the view that having negative literals is not ideal.
I also agree with Tamas's suggestion that an empirical analysis of Haskell source code could be useful to determine the practical implications of unary minus,
It has merit and I would laud anyone who got round to doing it, but there's a danger of measuring the wrong thing. What we want to know is not what is more frequent, but what causes the greater number of misreadings and which pieces of code had the most syntax errors before they were completed, and that's harder to measure. Though if unary minus turned out to be very rare, we could just drop it. Using “(0-)” wouldn't be much of a hardship in that case.
Anyway no doubt I've posted enough emails about unary minus and negative literals so I'll be quiet now ;-)
:-) ... ?
I think the main problem with unary negation is that it's the only place in Haskell where the same symbol is being used to represent two different (ie not overloads of each other) functions. I can see why people were tempted to do this, because there is such an intimate relationship between unary minus and binary subtraction. However I feel it is a slippery slope: convenience has been put before uniformity leading to confusion. While such things might be justified in a domain specific language like mathematica or matlab, for a general purpose language like Haskell it seems less reasonable to make an exception just for one arithmetic function. Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

On Sat, 9 Sep 2006, Brian Hulley wrote:
negate (expNat 4 2)
because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit
Agreed, though I'd want expt to be part of a typeclass (possibly multi-parameter to get exp:: Integral a => a -> Natural -> a as an instance?).
Yes, a typeclass for exp would be ideal (and a newtype for Natural).
What about (expNat exponent basis) ? This argument order is more convenient for partial application. Cf. http://www.haskell.org/pipermail/haskell-cafe/2006-April/015329.html

On 2006-09-11, Henning Thielemann
On Sat, 9 Sep 2006, Brian Hulley wrote:
negate (expNat 4 2)
because this would free the ^ symbol for some more widely applicable use, and would also make the particular choice of exponentiation operator more explicit
Agreed, though I'd want expt to be part of a typeclass (possibly multi-parameter to get exp:: Integral a => a -> Natural -> a as an instance?).
Yes, a typeclass for exp would be ideal (and a newtype for Natural).
What about (expNat exponent basis) ? This argument order is more convenient for partial application.
Cf. http://www.haskell.org/pipermail/haskell-cafe/2006-April/015329.html
I don't see anything in that message supporting either argument order. Personally, I mostly use exponentials in the context of the fourier transform. Although it could be expressed by either varying the exponent or the base, I find varying the exponent to be far more natural. Consider also the specialization we have of power: exp, with a fixed base, but not square, with a fixed exponent. -- Aaron Denney -><-

On 2006-09-08, Jón Fairbairn
"Brian Hulley"
writes: In the context of programming, I don't see the problem of just thinking of the integers as a primitive built-in data type which contains some range of positive and negative integers which I'd argue should all be treated on an equal footing when the context of discourse is the integers not the naturals.
I'm not sure what that means. Why should they be equal? Why shouldn't Naturals be more primitive than Integers?
Certainly they're more primitive. Too primitive to have reasonable algebraic properties.
I don't think there is a need to force spaces to be put around every infix application. It's only when there would be a conflict with the lexical syntax that spaces are needed, just as at the moment we have (F . G) versus (F.G), (f $ g) versus (f $g) etc.
That rather goes against your simplicity of design argument, doesn't it? Why the special cases? For years I've been rather sloppy about spaces around â$â, and now when I use template haskell, this bites me. At some point in the future someone might decide that & or % is needed to introduce a new chunk of syntax, and formerly valid programmes break. So why not just say that varsym varid is in general reserved for future special syntaxes, and require varsym whitespace varid everywhere?
Hmm. Quite reasonable, actually, if we were designing the language de novo. And easily enough to write correctors for current code. -- Aaron Denney -><-

Aaron Denney
On 2006-09-08, Jón Fairbairn
wrote: Why shouldn't Naturals be more primitive than Integers?
Certainly they're more primitive. Too primitive to have reasonable algebraic properties.
Hmph. Naturals obey (a+b)+c == a+(b+c), which is a nice and reasonable algebraic property that Float and Double don't obey. In fact Float and Double have lots of /un/reasonable algebraic properties, but we still have them in the language. (I think they should be turfed out into a numerical library). -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2006-09-07)

On Sat, 9 Sep 2006, Jón Fairbairn wrote:
Aaron Denney
writes: On 2006-09-08, Jón Fairbairn
wrote: Why shouldn't Naturals be more primitive than Integers?
Certainly they're more primitive. Too primitive to have reasonable algebraic properties.
Hmph. Naturals obey (a+b)+c == a+(b+c), which is a nice and reasonable algebraic property that Float and Double don't obey. In fact Float and Double have lots of /un/reasonable algebraic properties, but we still have them in the language. (I think they should be turfed out into a numerical library).
Since floats are so different, maybe we should provide a different type hierarchy for them. Say class Additive a where (+) :: a -> a -> a ... class Additive a => Ring a where (*) :: a -> a -> a ... class ApproximateRing a where (+~) :: a -> a -> a (*~) :: a -> a -> a ... instance ApproximateRing Float instance ApproximateRing Rational instance Ring Rational Approximating numeric class instances do not satisfy the algebraically interesting laws, whereas instances of exact numeric class satisfy them. That is, floating point and fixed point numbers can only be instances of Approximate* classes and exact representations of mathematical objects like integers, rationals, complex numbers, polynomials can be instances of both exact and approximating numeric classes. However, e.g. the integers as presented in the computer still constitute no ring, because the domain is not closed. E.g. a power with sufficient high exponent lets any Haskell program run out of memory. Having different type hierarchies for approximating and exact numbers may be inconvenient at the first glance, because you have to implement say polynomial and matrix multiplication for both kinds of type classes, but they can share code and they can adapt to subtle differences. E.g. a fast determinant algorithm for a matrix over rings is totally different from a fast and numerically stable determinant computation of float matrices.

In C, it wouldn't be, since there, unary ops always bind tighter than infix ops, and the precedences used in C are also used in C++, Java, C#, Javascript etc, and even ISO Prolog obeys the rule that unary minus binds tighter so making unary minus have the same precedence as infix minus just makes Haskell syntax difficult to parse for anyone coming from one of these other very popular languages. Imho, for better or worse, C has established a kind of de-facto standard that unary ops always bind tighter than infix ops in programming languages ;-)
... in **programming languages that don't have infix exponeniation**. You missed Ruby, Python, Matlab, Mathematica (not generally a good inspiration for syntax but it has a rather large following and almost 20 years of usage), and TI calculators. These all have ^ or ** bind tighter than unary - to go along with math, not C. Since it didn't happen we will never know **if C had had infix exponentiation, what would the precedence have been relative to unary ops** or indeed if they dropped infix exponentiation, preferring pow(x,y), for exactly that reason, or what. All this talk is a design choice and folks will naturally disagree and the "right" balance for *everything*, especially since all their conflicting interactions yield so many mutually exclusive possible outcomes. I suppose I just disagree that C has said the last word about infix/unary ops because C never spoke up on the problem of unary negation and exponentiation. (And if it had, would I agree anyway? :-) I still get tripped up by unary negation in Haskell, especially with sections, parenthese, etc. But that's what hugs or ghci are for.
Also, it's a good example of why we should *not* have unary minus, since the above could be written with no ambiguity as: negate (4 ^ 2) or better still: negate (expNat 4 2) because this would free the ^ symbol for some more widely applicable use,
True. I would much rather be forced to type negate (4 ^ 2) than have -4^2 return 16 instead of -16 because the - got lexed into -4. Alternately, if you want unary ops to bind the tightest, then just eliminating ^ and replacing it with expNat, etc. would solve any precedence problems with unary minus. Jared. -- http://www.updike.org/~jared/ reverse ")-:"

On 2006-09-08, Brian Hulley
Leaving aside the question of negative literals for the moment, what's so special about unary minus that it warrants a special syntax? For example in mathematics we have x! to represent (factorial x), which is also an important function, yet no-one is arguing that we should introduce a unary postfix operator to Haskell just to support it.
Well, it seems a shame that we don't have postfix operators already. I guess that means I am arguing we should introduce a unary postfix operator, and not even have sugar for factorial, as it conflicts with array access. We *almost* do: Hugs.Base> let (!) 0 = 1; (!) x = x*((!) (x-1)) in (5 !) Sadly, Prelude> let (!) 0 = 1; (!) x = x*((!) (x-1)) in (5 !) <interactive>:1:41: No instance for (Num (t -> t1)) arising from the literal `5' at <interactive>:1:41 Probable fix: add an instance declaration for (Num (t -> t1)) In the first argument of `(!)', namely `5' In the definition of `it': it = let ! 0 = ... ! x = ... in (5 !) And hugs doesn't work with out the parentheses in the expression. We already have this great syntax, parsing semanticsi for precedence, and so forth for declaring infix operators. Couldn't we add to that slightly by declaring postfix operators as well? Actually, declaring a unary operator infix yielding a postfix operator doesn't seem like too much abuse. I could have sworn I'd seen ternary operators the same way, but
((id) `either` (id) (Left 5)) doesn't appear to work.
Then there's also the infix data constructors for postfix... Okay, that's complicated because of lack of precedence, but surely that just means extra parentheses? (I haven't thought this through to any great extent. How much would it complicate parsing? Not much, I would assume, as this fails in ghc at the type-checking stage.) (Tounge only *half* in cheek.) -- Aaron Denney -><-

Aaron Denney
We already have this great syntax, parsing semanticsi for precedence, and so forth for declaring infix operators. Couldn't we add to that slightly by declaring postfix operators as well? Actually, declaring a unary operator infix yielding a postfix operator doesn't seem like too much abuse.
Possibly not, provided they're always used as sections. (e #) already always means "supply e as the first argument to (#)").
(I haven't thought this through to any great extent. How much would it complicate parsing? Not much, I would assume, as this fails in ghc at the type-checking stage.)
I don't think it would complicate mechanical parsing unreasonably. I do think (if done without the parentheses) it might complicate /human/ parsing unreasonably. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2006-09-07)

| Well, it seems a shame that we don't have postfix operators already. | I guess that means I am arguing we should introduce a unary postfix | operator, and not even have sugar for factorial, as it conflicts with | array access. | | We *almost* do: | Hugs.Base> let (!) 0 = 1; (!) x = x*((!) (x-1)) in (5 !) | Sadly, | Prelude> let (!) 0 = 1; (!) x = x*((!) (x-1)) in (5 !) Actually, the up-coming GHC 6.6 does allow this. Some while ago I made the type checker a tiny bit more lenient about left sections, so that (x !) would typecheck iff ((!) x) typechecks. (Strictly, Haskell 98 requires that the section typechecks iff (\y. (!) x y) typechecks, and I should really have made the relaxation dependent on a flag, but I didn't.) Anyway, you get postfix operators. I'd better document this. Simon

On Thu, Aug 17, 2006 at 11:14:32AM +0100, Brian Hulley wrote:
I'd have thought it would have been simpler to just make the rule that -2 (no spaces between '-' and '2') would be a single lexeme, and then people could just use (negate x) or (0 - x) instead of having a special rule and a whole lot of confusion just for one arithmetic operator, which is never actually needed in the first place (just as we don't need /x because it is simple enough to write 1/x).
yes yes yes. the current handling of - is a huge wart that needs to be excised. I run into issues with it still and grumble to myself, and have been programming haskell for years. '-' should be part of the numerical lexical syntax and not be special in any other way. we alreday have . being treated as lexically part of a number, and 'e', and 'x' in certain cases, so why the special anoying case for '-'?
I see with great disappointment that Haskell' Trac ticket#50 [1] looks as if it will not be accepted [2] so we're likely to be stuck with this for years to come...
[1] http://hackage.haskell.org/trac/haskell-prime/ticket/50 [2] http://hackage.haskell.org/trac/haskell-prime/wiki/StrawPoll-2
I hope this changes. John -- John Meacham - ⑆repetae.net⑆john⑈
participants (16)
-
Aaron Denney
-
Brian Hulley
-
Cale Gibbard
-
Christian Maeder
-
David House
-
Henning Thielemann
-
Jared Updike
-
Jim Apple
-
John Meacham
-
Jón Fairbairn
-
Neil Mitchell
-
Ross Paterson
-
Simon Peyton-Jones
-
Stefan Holdermans
-
Stefan Monnier
-
Tamas K Papp