Gentle Haskellers

The December issue of the Haskell 98 Report is done.

        http://research.microsoft.com/~simonpj/haskell98-revised

As usual, changes are highlighted in the overall bugs list thus: [Dec
2001],
so you can find them easily.

There are the usual crop of presentational improvements (thanks
esp to Ian Lynagh, George Russel, Feliks Kluzniak for much careful
reading).
There are two non-trivial changes that I decided to adopt:

1.  Add showIntAtBase, showOct and showHex to the Numeric library.

2.  Remove the wart concerning qualified names in instance declarations.
     This a breaking change, in the sense that exotic Haskell programs
     may have to change, but I judge it worth it, after some
consultation.
     In particular: 
        * if you use H/Direct, you'll have to re-generate your
                Haskell files with a different flag
        * if you use the Edison library, you'll need a new copy of
                the library (this isn't a problem in practice because it
                comes bundled with your compiler)

The other thing I'd ask you to look at particularly is the layout
algorithm.
George and Ian have both pointed out bugs, but it's very easy to get
wrong
so a few more eyeballs on it would be a Good Thing.

The only unresolved thing I have in my pile is some stuff
about the lexical syntax of comments, which I find it hard to get
excited about.  We are definitely converging.  My earnest hope is to
finally freeze the Report at Christmas.  So this is your last chance.
I hope.

Thanks

Simon

==========================
The instance decl wart

In Haskell 98 as she stands, when you give an instance declaration,
the method name is treated as an *occurrence* and so has to be 
qualified if it is ambiguous:

        module Foo where

        compare = <something>

        instance Ord T where
           Prelude.compare = ...        -- NB!

You have to say "Prelude.compare" on the LHS, because both
Prelude.compare and Foo.compare are in scope.  This is reasonable
on the RHS, of course, but it is plain silly on the LHS, because it 
*must* refer to the compare from the Ord class!  After all, its an
instance
declaration for Ord.  

Not only is it surprising (most people think that plain "compare" should
be fine) but it also adds a whole new big production to the grammar
(qfunlhs).

So, after some consulation, I have decided to remove this wierd thing.
The analogy is with type signatures, where we can already write

        module Foo where

        compare :: Int -> Int
        compare = ...

Note that we don't have to write "Foo.compare :: Int -> Int" in the
type signature.  


The remaining question is how to explain this point in the Report.
My initial conclusion is that simply deleting the offending text was
enough.
Explaining the problem (given that it isn't really a problem) seems to
complicate matters.  Nevertheless I'm entirely happy to add an
explanation, if people want it and say what they'd like to see.

The relevant section is 4.3.2. page 46 of the Report.


_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to