[Haskell-cafe] Re: map (-2) [1..5]

Jón Fairbairn jon.fairbairn at cl.cam.ac.uk
Fri Sep 8 12:46:39 EDT 2006


"Brian Hulley" <brianh at metamilk.com> writes:


> 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 at cl.cam.ac.uk
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-09-07)



More information about the Haskell-Cafe mailing list