Second draft of the Haskell 2010 report available

Ian Lynagh igloo at earth.li
Wed Jun 30 19:36:01 EDT 2010


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



More information about the Haskell-prime mailing list