Wanted: warning option for usages of unary minus

Isaac Dupree isaacdupree at charter.net
Thu May 17 06:37:04 EDT 2007


-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

Iavor Diatchki wrote:
> Hello,
> 
> I agree with Simon on this one: "x-1" should parse as expected (i.e.,
> the infix operator "-" applied to two arguments "x" and "1"). Having
> this result in a type error would be confusing to both beginners and
> working Haskell programmers.
> 
> I think that if we want to change anything at all, we should simply
> eliminate the unary negation operator without changing the lexer
> (i.e., we would have only positive literals).  Then we would have to
> be explicit about what is currently happening implicitly in
> Haskell98---we would write "negate 1" instead of "-1".
> 
> However, I don't thinks that this change is justified---as far as I
> can see, the only benefit is that it simplifies the parser.  However,
> the change is not backward compatible and may break some programs.

Simplifies the _mental_ parser, much more important than the compilers'
parsers which are already implemented.

Here is what I am thinking to do:

In my own code, since there seems to be so much difficulty with the
matter, don't use (-X) to mean negative for any kind of X whatsoever.
For this I want a warning for ALL usages of the unary minus operator.
I'll define a function for my negative literals that calls fromInteger
and negate in the order I would prefer to my sensibilities, which is
actually different from the order that the Report specifies for (-x) :

> {-# INLINE negative #-}
> negative :: Num a => Integer -> a
> negative a = fromInteger (negate a)

I might feel like having a parallel

> {-# INLINE positive #-}
> positive :: Num a => Integer -> a
> positive a = fromInteger a

(e.g. C has a unary + operator... and "positive" even has the same
number-of-characters length as "negative"!).


For GHC's unboxed negative literals I think I will still change the
lexer/parser since the current way it's done is rather confusing anyway
(as previously described)


I don't know what else is worth implementing... NOT an option to turn
off parsing of unary minus, since warnings are good and it would just
create more incompatibility.  John Meacham, since you seem to be
interested, what are your thoughts now?  Advice on flag names - or any
other discussion! is anyone interested in having something, say so? -
would be appreciated.


Isaac
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGTDBQHgcxvIWYTTURAt14AJ9+Avd3FJ54+f0eNzUBFM7tOPy5TgCfRys8
usEFDx9uNH2UjUHBbG9kyGs=
=M3CU
-----END PGP SIGNATURE-----


More information about the Haskell-prime mailing list