Haskell 98 Revised

Simon Peyton-Jones simonpj@microsoft.com
Wed, 5 Dec 2001 03:13:54 -0800


Folks,

Concerning the recent change about instance declarations, should
this be valid?

	module M( C(op1) ) where	-- NB: op2 not exported
	   class C a where
	      op1 :: a->a
	      op2 :: a->a

	module N where
	  import M

	  instance C Int where
	    op1 =3D ...
	    op2 =3D ...		-- Is this ok?

The point here is that M does not export op2. Can
we still bind it in the instance declaration in N? The old Report
was silent on this point, and so is the new one.

I'd like to say "no, this is illegal".   Haskell uses hiding as its
main abstraction mechanism, and if op2 is hidden then an
importing module should not be able to see it in any way.

I'll clarify this; but I thought I should point out the issue.

Simon

| -----Original Message-----
| From: Simon Peyton-Jones [mailto:simonpj@microsoft.com]=20
| Sent: 04 December 2001 12:03
| To: haskell@haskell.org
| Cc: Simon Peyton-Jones
| Subject: Haskell 98 Revised
|=20
|=20
| Gentle Haskellers
|=20
| The December issue of the Haskell 98 Report is done.
|=20
| 	http://research.microsoft.com/~simonpj/haskell98-revised
|=20
| As usual, changes are highlighted in the overall bugs list=20
| thus: [Dec 2001], so you can find them easily.
|=20
| There are the usual crop of presentational improvements=20
| (thanks esp to Ian Lynagh, George Russel, Feliks Kluzniak for=20
| much careful reading). There are two non-trivial changes that=20
| I decided to adopt:
|=20
| 1.  Add showIntAtBase, showOct and showHex to the Numeric library.
|=20
| 2.  Remove the wart concerning qualified names in instance=20
| declarations.
|      This a breaking change, in the sense that exotic Haskell programs
|      may have to change, but I judge it worth it, after some=20
| consultation.
|      In particular:=20
| 	* 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)
|=20
| The other thing I'd ask you to look at particularly is the=20
| layout algorithm. George and Ian have both pointed out bugs,=20
| but it's very easy to get wrong so a few more eyeballs on it=20
| would be a Good Thing.
|=20
| The only unresolved thing I have in my pile is some stuff
| about the lexical syntax of comments, which I find it hard to=20
| get excited about.  We are definitely converging.  My earnest=20
| hope is to finally freeze the Report at Christmas.  So this=20
| is your last chance. I hope.
|=20
| Thanks
|=20
| Simon
|=20
| =
=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=
=3D
| The instance decl wart
|=20
| In Haskell 98 as she stands, when you give an instance=20
| declaration, the method name is treated as an *occurrence*=20
| and so has to be=20
| qualified if it is ambiguous:
|=20
| 	module Foo where
|=20
| 	compare =3D <something>
|=20
| 	instance Ord T where
|  	   Prelude.compare =3D ...	-- NB!
|=20
| You have to say "Prelude.compare" on the LHS, because both=20
| Prelude.compare and Foo.compare are in scope.  This is=20
| reasonable on the RHS, of course, but it is plain silly on=20
| the LHS, because it=20
| *must* refer to the compare from the Ord class!  After all,=20
| its an instance declaration for Ord. =20
|=20
| Not only is it surprising (most people think that plain=20
| "compare" should be fine) but it also adds a whole new big=20
| production to the grammar (qfunlhs).
|=20
| So, after some consulation, I have decided to remove this=20
| wierd thing. The analogy is with type signatures, where we=20
| can already write
|=20
| 	module Foo where
|=20
| 	compare :: Int -> Int
| 	compare =3D ...
|=20
| Note that we don't have to write "Foo.compare :: Int -> Int"=20
| in the type signature. =20
|=20
|=20
| The remaining question is how to explain this point in the=20
| Report. My initial conclusion is that simply deleting the=20
| offending text was enough. Explaining the problem (given that=20
| it isn't really a problem) seems to complicate matters. =20
| Nevertheless I'm entirely happy to add an explanation, if=20
| people want it and say what they'd like to see.
|=20
| The relevant section is 4.3.2. page 46 of the Report.
|=20
|=20
| _______________________________________________
| Haskell mailing list
| Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell
|=20