Second draft of the Haskell 2010 report available

The second draft of the Haskell 2010 report is now available in PDF and HTML formats (the PDF looks a lot nicer): http://www.haskell.org/~simonmar/haskell-2010-draft-report-2.pdf http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskell.html relative to the first draft, which was only publicised on the haskell-prime mailing list, I have now updated the libraries too. Rather than update all the library documentation manually, I (perhaps rashly) decided to make a LaTeX backend for Haddock instead, and generate the report automatically from the library source code. Getting this to work turned out to be a lot more effort than I anticipated, but I think the results are quite attractive. Once the new Haddock backend is incorporated upstream, we'll finally have the ability to generate decent typeset API documentation. Furthermore, this should make it much easier to incorporate more libraries in future versions of the Haskell standard, should we decide to do so. Right now, the HTML version of the report is generated from the LaTeX sources, including the libraries. We could use the Haddock HTML output instead, but that would entail some difficulties with cross-references from the language part of the report to the libraries, which is why I've left it this way for now. This is why the libraries part of the report is bereft of hyperlinks in HTML; but at least it is well indexed in the PDF version. Summary of the library changes in Haskell 2010 relative to Haskell 98 and the FFI specification: * All libraries have been updated to their hierarchical names * The following library modules were dropped from the standard, due to being obsolete or superseded. Replacements are not part of the standard yet, but it is expected that they will be replaced in the future: Directory, System, Time, Locale, CPUTime, Random In the case of System, some functions have moved to the new modules System.Environment and System.Exit. * Foreign.Marshal.Error: functions on IOError moved to System.Error (this is where they've been in base for ever). * Data.List: added intercalate, subsequences, permutations, foldl', foldl1', stripPrefix (H2010 Data.List matches the current base version). * Data.Char: various additions of Unicode predicates (e.g. isLetter, isMark, isNumber), the GeneralCategory type and generalCategory. (matches the base version) * Control.Monad: added forM, forM_, (>=>), (<=<), forever, foldM_, replicateM, replicateM_ (matches the base version). * System.IO: added fixIO, hSetFileSize, hTell, hIsTerminalDevice, hSetEcho, hGetEcho, hShow. The base version has various additions: hGetBuf/hPutBuf, binary Handles, encodings, and newline support, but I erred on the side of being conservative here: these APIs need discussion, and in some cases are probably not suitable for the standard in their current state at all. * System.IO.Error: new module, providing functionality that was in Foreign.Marshal.Error in the FFI spec. * System.IO.Exit: new module, functionality moved from H98 System * System.Environment: new module, functionality moved from H98 System We expect to provide exactly these libraries in GHC 6.14, although the exact mechanism has yet to be decided; for discussion see http://www.haskell.org/pipermail/haskell-prime/2010-April/003158.html Comments on the draft report are welcome, before I finalise this and sign off on Haskell 2010. Cheers, Simon

In Foreign.C.Error, the table of values of errno causes an unfortunate page break, and it overflows the fresh page as well. (As in, some values are invisible beyond the bottom of the page, rather than flowing onto the next.) Regards, Malcolm
Comments on the draft report are welcome, before I finalise this and sign off on Haskell 2010.

On 29/06/2010 16:38, malcolm.wallace wrote:
In Foreign.C.Error, the table of values of errno causes an unfortunate page break, and it overflows the fresh page as well. (As in, some values are invisible beyond the bottom of the page, rather than flowing onto the next.)
Well spotted, thanks. Now fixed. Cheers, Simon

I have now updated the libraries too. Rather than update all the library documentation manually, I (perhaps rashly) decided to make a LaTeX backend for Haddock instead, and generate the report automatically from the library source code.
Perhaps I should have mentioned (before sending a formatting error report): thanks, this looks great! Auto-generation is definitely the way to go, and well worth the effort. I did notice one other small item, which is perhaps an infelicity rather than an error. The documentation for Data.List (20.10.1), the "By" operations, mentions "It is often convenient to use these functions together with Data.Function.on". But sadly, Data.Function is not one of the libraries in the H'2010 set. I would personally be happy to add it, but perhaps it is too late, and we will need to wait for H'2011. Regards, Malcolm

On Tue, Jun 29, 2010 at 04:01:54PM +0100, Simon Marlow wrote:
The second draft of the Haskell 2010 report is now available in PDF and HTML formats (the PDF looks a lot nicer):
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2.pdf http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskell.html
Great work! I noticed a few things as I skimmed through it: p12(x) "It too is intended to be a" -> "It too was intended to be a" p40(24) In "local bindings are of the form let decls." there is a lot more white space between "let" and "decls" than there is in the BNF on the previous page p60(44) There are some odd-looking spaces before closing parentheses in the first paragraph. p62(46) "Ix" -> "Data.Ix" (3 times) p79(63) "Maybe" -> "Data.Maybe" p82(66) "List" -> "Data.List" p121(105) "Char, Monad, IO, and Numeric" -> "Data.Char, Control.Monad, System.IO and Numeric" p121(105) "List" -> "Data.List" p122(106) "Ratio" -> "Data.Ratio" p133(117) "Char" -> "Data.Char" p139(123) "Char" -> "Data.Char" p171(155) "module provide the" -> "module provides the" p171(155) This is a bit klunky, talking about Control.Monad providing things that are actually defined in the Prelude. The "The instances of Functor [...] defined in the Prelude" is odd if you don't realise that. p172(156) Do you mean to have these instances?: instance Functor ReadP instance Monad P instance Monad ReadP p173(157) I don't think the report should refer to the mtl package. p173(157) Do you mean to have these instances?: instance MonadPlus P instance MonadPlus ReadP p175(159) Odd space after "xm" in "[x1, x2, ..., xm ]" p177(161) The "module Data.Ix" looks confusing; I assume it's being listed as an export? The paragraph above it doesn't look associated with it. p178(162) Talks about the difference between H98 and GHC p178(162) "nonstrict" -> "non-strict" p179(163) Is strictness of the accumulating function actually relevant? p179(163) Talks about the difference between H98 and GHC p180(164) "module Array" -> "module Data.Array" "module Ix" -> "module Data.Ix" "import Ix" -> "import Data.Ix" "import List" -> "import Data.List" Something has gone wrong with 2 of the error calls. p186(170) Do you mean to have these instances?: instance Bits WordPtr instance Bits IntPtr p193(177) Do you mean to have these instances?: instance Typeable1 Complex instance (Data a, RealFloat a) => Data (Complex a) p194(178) "module Complex" -> "module Data.Complex" p195(179) Bad indentation in the Fractional instance p197(181) "see the section of the Haskell report dealing with arithmetic sequences)" should be a link p201(185) three bullet points are indented more than the other one C20: There are a number of references to "Data.List.foo" rather than just "foo", presumably from when the docs were in the Prelude rather than Data.List C20: In example, sometimes "==" is used but in other cases "->" is used p222(206) "module Maybe" -> "module Data.Maybe" p226(210) "module Ratio" -> "module Data.Ratio" p227(211) Bad indentation in Show instance p229(213) I don't understand "One non-obvious consequence of this is that negate should not raise an error on negative arguments." p229(213) "see the section of the Haskell report dealing with arithmetic sequences" should be a link p235(219) Do you mean to have these instances?: instance Typeable ExitCode instance Exception ExitCode p236(220) "sucessfully" -> "successfully" p244(228) "Construct a Haskell 98 I/O error" p245(229) "additionlly" -> "additionally" p252(236) onwards: Lots of Typeable instances, and Typeable is also given in the list of classes in the 30.1.1, 30.1.2 and 30.1.3 opening paragraphs. p258(242) Talks about Data.Time p262(246) "A Finalizer" -> "A finalizer" p262(246) "like addForeignPtrFinalizerEnv" -> "Like addForeignPtrFinalizerEnv" p263(247) Mentions MVars p263(247) I don't think there should be GHC notes in the report p270(254) Delete "This version traverses the array backwards using an accumulating parameter, which uses constant stack space. The previous version using mapM needed linear stack space." p276(260) "marshall" -> "marshal" p278(262) Why is e.g. "Char" unqualified but "Prelude.Double" qualified? p285(269) Do you mean to have these instances?: instance Storable WordPtr instance Storable IntPtr p289(273) "System.IO.openFile" -> "openFile" p291(275) "System.IO.hFlush" -> "hFlush" (twice) p291(275) "System.IO.hlookAhead" -> "hlookAhead" Thanks Ian

http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch3.html infixexp → lexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp This grammar rule describes a right associative nesting of (any) infix operators "qop" and prefix negation as binding weaker than any infix. Thus a parser would create from "- 1 /= 1 && a" the tree "- (1 /= (1 && a))". Would it not be better to give an ambiguous grammar and leave it to the infix resolution algorithm to allow only the intended trees, rather than letting the infix resolution algorithm correct a wrong tree? My suggestion would be to change the rule to: infixexp → infixexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp thus only replacing the first lexp by infixexp. Cheers Christian

On 06/07/2010 13:17, Christian Maeder wrote:
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch3.html
infixexp → lexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp
This grammar rule describes a right associative nesting of (any) infix operators "qop" and prefix negation as binding weaker than any infix.
Thus a parser would create from "- 1 /= 1&& a" the tree "- (1 /= (1&& a))".
The grammar is non-ambiguous and all you have to do is flatten the result to apply fixity resolution. I don't really see how generalising the grammar would help - the tree still has to be flattened to apply fixity resolution, and the parser would have to make an arbitrary choice from one of the possible parses. Or perhaps I'm missing something here? Cheers, Simon
Would it not be better to give an ambiguous grammar and leave it to the infix resolution algorithm to allow only the intended trees, rather than letting the infix resolution algorithm correct a wrong tree?
My suggestion would be to change the rule to:
infixexp → infixexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp
thus only replacing the first lexp by infixexp.
Cheers Christian
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Simon Marlow schrieb:
On 06/07/2010 13:17, Christian Maeder wrote:
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch3.html
infixexp → lexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp
This grammar rule describes a right associative nesting of (any) infix operators "qop" and prefix negation as binding weaker than any infix.
Thus a parser would create from "- 1 /= 1&& a" the tree "- (1 /= (1&& a))".
The grammar is non-ambiguous and all you have to do is flatten the result to apply fixity resolution. I don't really see how generalising the grammar would help - the tree still has to be flattened to apply fixity resolution, and the parser would have to make an arbitrary choice from one of the possible parses. Or perhaps I'm missing something here?
An ambiguous grammar (as abstract syntax for expressions) would cover the tree after fixity resolution, too. The non-ambiguous grammar only describes a temporarily wrong tree for fixity resolution. Christian

On 07/07/2010 15:47, Christian Maeder wrote:
Simon Marlow schrieb:
On 06/07/2010 13:17, Christian Maeder wrote:
http://www.haskell.org/~simonmar/haskell-2010-draft-report-2/haskellch3.html
infixexp → lexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp
This grammar rule describes a right associative nesting of (any) infix operators "qop" and prefix negation as binding weaker than any infix.
Thus a parser would create from "- 1 /= 1&& a" the tree "- (1 /= (1&& a))".
The grammar is non-ambiguous and all you have to do is flatten the result to apply fixity resolution. I don't really see how generalising the grammar would help - the tree still has to be flattened to apply fixity resolution, and the parser would have to make an arbitrary choice from one of the possible parses. Or perhaps I'm missing something here?
An ambiguous grammar (as abstract syntax for expressions) would cover the tree after fixity resolution, too.
The non-ambiguous grammar only describes a temporarily wrong tree for fixity resolution.
Yes it does, intentionally. But I see your point, and arguably the current grammar is inconsistent; prefix negation should move to lexp to be consistent with lpat (and to avoid the strange parse you point out above). I suppose my concern is that if we generalised the grammar, then we would have to also explain why the grammar was ambiguous and that a parser should pick a suitable parse before applying fixity resolution. As you say, it's a presentational point, I'm not against changing it. Cheers, Simon

Simon Marlow schrieb:
prefix negation should move to lexp to be consistent with lpat
prefix negation should not move to lexp, because this would rule out "- 1 ^ 2" as negated infix expression "- (1 ^ 2)", whereas a negated infix pattern is impossible. Unary minus is no constructor and cannot be defined. The latter should be (or is already?) mentioned somewhere. You could move prefix negation to lexp, if you allow the fixity resolution to construct negated infix expression that are not covered by the grammar (as currently happens anyway). Moving prefix negation from lpat to pat to be consistent with infixexp would be overkill, though. Christian

On 07/07/10 16:56, Christian Maeder wrote:
Simon Marlow schrieb:
prefix negation should move to lexp to be consistent with lpat
prefix negation should not move to lexp, because this would rule out "- 1 ^ 2" as negated infix expression "- (1 ^ 2)",
It wouldn't - remember the grammar just parses infix expressions as a list, they get rearranged by fixity resolution. I'm arguing that the current grammar is halfway between two consistent positions: one in which prefix negation is lexp, the other is your proposal to make the grammar ambiguous. So we should do one or the other.
whereas a negated infix pattern is impossible. Unary minus is no constructor and cannot be defined. The latter should be (or is already?) mentioned somewhere.
You could move prefix negation to lexp, if you allow the fixity resolution to construct negated infix expression that are not covered by the grammar (as currently happens anyway).
Right, that's what I'm saying. No change needed to fixity resolution, just move prefix negation into lexp.
Moving prefix negation from lpat to pat to be consistent with infixexp would be overkill, though.
Yes. Cheers, Simon

Simon Marlow schrieb:
On 07/07/10 16:56, Christian Maeder wrote:
Simon Marlow schrieb:
prefix negation should move to lexp to be consistent with lpat
prefix negation should not move to lexp, because this would rule out "- 1 ^ 2" as negated infix expression "- (1 ^ 2)",
It wouldn't - remember the grammar just parses infix expressions as a list, they get rearranged by fixity resolution.
I'm arguing that the current grammar is halfway between two consistent positions: one in which prefix negation is lexp, the other is your proposal to make the grammar ambiguous. So we should do one or the other.
How about a rule like: infixexp -> [-] lexp { qop [-] lexp } to stress the sequence of tokens for fixity resolution and to avoid the impressions of wrong trees (as moving "-" into lexp would).
whereas a negated infix pattern is impossible. Unary minus is no constructor and cannot be defined. The latter should be (or is already?) mentioned somewhere.
It should be mentioned in the report that the strongly binding prefix minus in patterns can be rejected by fixity resolution! Otherwise it is not clear if accepting "-1 * -2" (as pattern) is a (ghc) bug or an accidental (language) feature. Cheers Christian
You could move prefix negation to lexp, if you allow the fixity resolution to construct negated infix expression that are not covered by the grammar (as currently happens anyway).
Right, that's what I'm saying. No change needed to fixity resolution, just move prefix negation into lexp.
Moving prefix negation from lpat to pat to be consistent with infixexp would be overkill, though.
Yes.
Cheers, Simon

On 08/07/2010 10:02, Christian Maeder wrote:
Simon Marlow schrieb:
On 07/07/10 16:56, Christian Maeder wrote:
Simon Marlow schrieb:
prefix negation should move to lexp to be consistent with lpat
prefix negation should not move to lexp, because this would rule out "- 1 ^ 2" as negated infix expression "- (1 ^ 2)",
It wouldn't - remember the grammar just parses infix expressions as a list, they get rearranged by fixity resolution.
I'm arguing that the current grammar is halfway between two consistent positions: one in which prefix negation is lexp, the other is your proposal to make the grammar ambiguous. So we should do one or the other.
How about a rule like:
infixexp -> [-] lexp { qop [-] lexp }
to stress the sequence of tokens for fixity resolution and to avoid the impressions of wrong trees (as moving "-" into lexp would).
Yes, that's better.
whereas a negated infix pattern is impossible. Unary minus is no constructor and cannot be defined. The latter should be (or is already?) mentioned somewhere.
It should be mentioned in the report that the strongly binding prefix minus in patterns can be rejected by fixity resolution! Otherwise it is not clear if accepting "-1 * -2" (as pattern) is a (ghc) bug or an accidental (language) feature.
If we changed patterns in the same way as you suggest for expressions above, then this would become clearer, right? Cheers, Simon
Cheers Christian
You could move prefix negation to lexp, if you allow the fixity resolution to construct negated infix expression that are not covered by the grammar (as currently happens anyway).
Right, that's what I'm saying. No change needed to fixity resolution, just move prefix negation into lexp.
Moving prefix negation from lpat to pat to be consistent with infixexp would be overkill, though.
Yes.
Cheers, Simon

Simon Marlow schrieb:
If we changed patterns in the same way as you suggest for expressions above, then this would become clearer, right?
By this change you would loose the important restriction that "-" is only legal to denote negated (integer or float) constants, which would then move from the grammar to the informal description. Any choice is fine. Christian

1.2: "it is essentially a slightly sugared variant of the lambda calculus" Should it be the simply-typed lambda calculus? Also, there should be a reference; a significant percentage of those reading this report will have never heard of the lambda calculus. "with a straightforward denotational semantics" Seems that it should be so. Has anyone actually ever done that? If so, reference. If not, qualify. 1.3: "Errors in Haskell are semantically equivalent to _|_. Technically, they are not distinguishable from nontermination, so the language includes no mechanism for detecting or acting upon errors. However, implementations will probably try to provide useful information about errors. See Section 3.1 [where error and undefined are described]." This paragraph has always been very unsatisfying, especially since the Report itself does in fact provide a way of catching some errors at least since Haskell 98. 41.1: "The fail method of the IO instance of the Monad class raises a userError" Should be the default fail method. Regards, Yitz

On 16:01 Tue 29 Jun , Simon Marlow wrote:
Comments on the draft report are welcome, before I finalise this and sign off on Haskell 2010.
Part II, "The Haskell 2010 Libraries", appears to be completely missing the Numeric module. -- Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)

On 06/07/2010 15:50, Nick Bowler wrote:
On 16:01 Tue 29 Jun , Simon Marlow wrote:
Comments on the draft report are welcome, before I finalise this and sign off on Haskell 2010.
Part II, "The Haskell 2010 Libraries", appears to be completely missing the Numeric module.
Numeric was added in the final verison. Cheers, Simon
participants (7)
-
Christian Maeder
-
Ian Lynagh
-
Malcolm Wallace
-
malcolm.wallace
-
Nick Bowler
-
Simon Marlow
-
Yitzchak Gale