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

Cale Gibbard cgibbard at gmail.com
Sat Sep 9 00:57:56 EDT 2006


On 08/09/06, Brian Hulley <brianh at metamilk.com> wrote:
> Jón Fairbairn wrote:
> > "Brian Hulley" <brianh at metamilk.com> 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


More information about the Haskell-Cafe mailing list