RE: Haskell 98 Revised

2001-12-05 Thread Simon Peyton-Jones

A good point.   You are right that the report is not very explicit
on this point; and right that omitting the qualifier would be in the
spirit of the story for type sigs and instance decls.  

I'd be interested to know what others think.

Simon

| -Original Message-
| From: Iavor S. Diatchki [mailto:[EMAIL PROTECTED]] 
| Sent: 04 December 2001 18:41
| To: [EMAIL PROTECTED]
| Subject: Re: Haskell 98 Revised
| 
| 
| hello,
| 
| it seems that if the qualified names in instance declarations 
| are removed, the qualified methods (data constructors) in 
| exports ought to be removed as 
| well.  example: currently in Haskell one may write
| 
| module M ( P.C(Q.f) ) where
| import qualified P
| import qualified Q
| ...
| qualifying the method (or data cosntructor) does not  give 
| any additional 
| information.  however if i read the current report correctly 
| (and i don't 
| think it is quite clear on that)  omitting the qualifier of 
| f results in an 
| invalid program as there is no method f in scope (there 
| probably are P.f 
| and Q.fhowever).   having said that, GHC accepts the 
| program without the 
| qualifier,so it seems that it essentailly ignores the qualifiers of 
| subordinate names in export lists.  so why not adjust the 
| report so that 
| such qualified names are just not allowed?
| 
| bye
| iavor
| 
| 
| 
| 
| 
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 

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



RE: Haskell 98 Revised

2001-12-05 Thread Simon Peyton-Jones

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 = ...
op2 = ...   -- 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:[EMAIL PROTECTED]] 
| Sent: 04 December 2001 12:03
| To: [EMAIL PROTECTED]
| Cc: Simon Peyton-Jones
| Subject: Haskell 98 Revised
| 
| 
| 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
| 

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



Re: Haskell 98 Revised

2001-12-05 Thread Karl-Filip Faxen

Hi!

For whatever that is worth, my semantics agrees with Simon's point here,
ie in the example code

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 = ...
op2 = ...   -- Is this ok?

the method binding for op2 is not allowed.

But then there *is* a scope issue with instance declarations. What about
the following example:

module M( C(..) ) where  -- NB: both methods exported ...
   class C a where
  op1 :: a-a
  op2 :: a-a

module N where
  import M hiding (op2)  -- ... but op2 is not imported

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

As far as I've understood, the current revision of the Report states that
a 'hiding' clause affects the qualified names as well as the unqualified
names. Then 'op2' is not visible either qualified or unqualified.

So, should it be legal to make a method declaration for it?

Cheers,

   /kff



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



Haskell 98 Revised

2001-12-04 Thread Simon Peyton-Jones

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



Re: Haskell 98 Revised

2001-12-04 Thread Iavor S. Diatchki

hello,

it seems that if the qualified names in instance declarations are removed,
the qualified methods (data constructors) in exports ought to be removed as 
well.  example: currently in Haskell one may write

module M ( P.C(Q.f) ) where
import qualified P
import qualified Q
...
qualifying the method (or data cosntructor) does not  give any additional 
information.  however if i read the current report correctly (and i don't 
think it is quite clear on that)  omitting the qualifier of f results in an 
invalid program as there is no method f in scope (there probably are P.f 
and Q.fhowever).   having said that, GHC accepts the program without the 
qualifier,so it seems that it essentailly ignores the qualifiers of 
subordinate names in export lists.  so why not adjust the report so that 
such qualified names are just not allowed?

bye
iavor






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



RE: Haskell 98 Revised

2001-11-05 Thread Simon Peyton-Jones

|
http://research.microsoft.com/~simonpj/haskell98-revised/haskell98-repor
t-html/index.html
| says Revised: October 2001 - am I seeing the latest version?

Yes you are -- my mistake.

| You still have
| lexeme - ... | qop | ...
| in the lexical syntax but have
| qop - qvarop | qconop
| in the context-free syntax - is this deliberate? It really sucks IMO.

Your message about this is still in my to deal with pile.  Last time I
looked
I didn't see an obvious solution, but now I look again, it seem simple.
(Procrastination sometimes works.)

Proposal: 

in the syntax for lexeme, replace qop by qvarsym |
qconsym.

So the syntax for lexeme becomes

lexeme - qvarid | qconid | qvarsym | qconsym | 
literal | special | reservedop | reservedid 

I think this restores the stratification between the lexical structure
(no whitespace allowed) and the syntactic structure (whitespace allowed
between lexemes).  It also makes the syntax for lexeme look more
symmetrical.

Do you agree?

Simon

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



Re: Haskell 98 Revised

2001-11-03 Thread Ian Lynagh


Hi Simon

 It's that time of the month.   I'm putting out the November release
 of the Revised Haskell 98 Report.  As ever, I earnestly seek your
 feedback.

In appendix B (syntax), B.3 (layout) says

  * A stream of tokens as specified by the lexical syntax in the Haskell
report, with the following additional tokens:
  + If the first *token after a let, where, do, or of keyword is not {, it
is preceded by {n} where n is the indentation of the *token.
  + If the first *token of a module is not { or module, then it is preceded
by {n} where n is the indentation of the *token.
  + Where the start of a *token does not follow any complete *token on the
same line, this *token is preceded by n where n is the indentation of
the *token, provided that it is not, as a consequence of the first two
rules, preceded by {n}.

I think the word token should be replaced with lexeme where I have
marked it with *.

I am also not clear what you mean by complete token?

Finally, ghci, hi and hugs seem to accept

 instance Fractional Int where

as a valid program, but the layout rule doesn't seem to specify how ot
handle this (and as the last token is a new line token some simple fixes
don't work).

If I have this module:

 module Foo where
 instance Fractional Int where
 foo = 5

then with ghci I can evaluate foo:

Compiling Foo  ( QQW.lhs, interpreted )

QQW.lhs:3:
Warning: No explicit method nor default method for `fromRational'
 In the instance declaration for `Fractional Int'
Foo foo
5
Foo

hi lets me load it but complains when I try to evaluate it:

Prelude foo
[Compiling...

Error when renaming::
Identifier foo used at 10:21 is not defined. (in overlap resolution)
...failed]
Prelude 

and hugs won't even let me load it:

Reading file QQW.lhs:
ERROR QQW.lhs:4 - No member foo in class Fractional
Prelude 

As the report stands I don't think any implementation does the right
thing, but that they should fail due to not being able to offsideify the
module as n == m on the line defining foo so the { is neither explicitly
nor implicitly provided for the idecls.


Thanks
Ian


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



Haskell 98 Revised

2001-11-02 Thread Simon Peyton-Jones

Haskellers!

It's that time of the month.   I'm putting out the November release
of the Revised Haskell 98 Report.  As ever, I earnestly seek your
feedback.  Especially I'd like to know whether I have stumbled
in rewriting the section about Enum in the light of recent email.

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

My plan is to iterate just once more (early Dec), and then freeze 
the report at Christmas.  I'm getting tired!

Simon

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



Re: Haskell 98 Revised

2001-11-02 Thread Ian Lynagh

On Fri, Nov 02, 2001 at 09:30:36AM -0800, Simon Peyton-Jones wrote:
 Haskellers!

Hi Simon  :-)

 It's that time of the month.   I'm putting out the November release
 of the Revised Haskell 98 Report.  As ever, I earnestly seek your
 feedback.  Especially I'd like to know whether I have stumbled
 in rewriting the section about Enum in the light of recent email.
 
   http://research.microsoft.com/~simonpj/haskell98-revised

http://research.microsoft.com/~simonpj/haskell98-revised/haskell98-report-html/index.html
says Revised: October 2001 - am I seeing the latest version?

Actually,
http://research.microsoft.com/~simonpj/haskell98-revised/haskell98-report-html/syntax-iso.html
has November 2001 at the bottom so I guess I am.

You still have
lexeme - ... | qop | ...
in the lexical syntax but have
qop - qvarop | qconop
in the context-free syntax - is this deliberate? It really sucks IMO.

 My plan is to iterate just once more (early Dec), and then freeze 
 the report at Christmas.  I'm getting tired!

:-)


Thanks
Ian


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