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

Brian Hulley brianh at metamilk.com
Fri Sep 8 23:23:15 EDT 2006


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.

> [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 



More information about the Haskell-Cafe mailing list