Repository : ssh://darcs.haskell.org//srv/darcs/packages/base On branch : master
http://hackage.haskell.org/trac/ghc/changeset/a8d4a38c51afa9adb2b982123f9575c5b6db5d6d >--------------------------------------------------------------- commit a8d4a38c51afa9adb2b982123f9575c5b6db5d6d Author: Ian Lynagh <[email protected]> Date: Sat Nov 17 21:46:03 2012 +0000 Update some H98 references to refer to H2010 >--------------------------------------------------------------- GHC/Arr.lhs | 4 ++-- GHC/IO/Exception.hs | 6 +++--- GHC/IO/FD.hs | 2 +- GHC/List.lhs | 2 +- GHC/Read.lhs | 16 ++++++++-------- Text/Printf.hs | 4 ++-- Text/Read.hs | 4 ++-- 7 files changed, 19 insertions(+), 19 deletions(-) diff --git a/GHC/Arr.lhs b/GHC/Arr.lhs index 3704eef..48bb414 100644 --- a/GHC/Arr.lhs +++ b/GHC/Arr.lhs @@ -430,7 +430,7 @@ arrEleBottom = error "(Array.!): undefined array element" -- for given indices within these bounds. -- -- The array is undefined (i.e. bottom) if any index in the list is --- out of bounds. The Haskell 98 Report further specifies that if any +-- out of bounds. The Haskell 2010 Report further specifies that if any -- two associations in the list have the same index, the value at that -- index is undefined (i.e. bottom). However in GHC's implementation, -- the value at such an index is the value part of the last association @@ -644,7 +644,7 @@ adjust f marr# (I# i#, new) next -- is the same matrix, except with the diagonal zeroed. -- -- Repeated indices in the association list are handled as for 'array': --- Haskell 98 specifies that the resulting array is undefined (i.e. bottom), +-- Haskell 2010 specifies that the resulting array is undefined (i.e. bottom), -- but GHC's implementation uses the last association for each index. {-# INLINE (//) #-} (//) :: Ix i => Array i e -> [(i, e)] -> Array i e diff --git a/GHC/IO/Exception.hs b/GHC/IO/Exception.hs index 3f386ce..ab385f4 100644 --- a/GHC/IO/Exception.hs +++ b/GHC/IO/Exception.hs @@ -194,12 +194,12 @@ ioError = ioException -- --------------------------------------------------------------------------- -- IOError type --- | The Haskell 98 type for exceptions in the 'IO' monad. +-- | The Haskell 2010 type for exceptions in the 'IO' monad. -- Any I\/O operation may raise an 'IOError' instead of returning a result. -- For a more general type of exception, including also those that arise -- in pure code, see "Control.Exception.Exception". -- --- In Haskell 98, this is an opaque type. +-- In Haskell 2010, this is an opaque type. type IOError = IOException -- |Exceptions that occur in the @IO@ monad. @@ -226,7 +226,7 @@ instance Eq IOException where -- | An abstract type that contains a value for each variant of 'IOError'. data IOErrorType - -- Haskell 98: + -- Haskell 2010: = AlreadyExists | NoSuchThing | ResourceBusy diff --git a/GHC/IO/FD.hs b/GHC/IO/FD.hs index 1b47ee9..0f37a81 100644 --- a/GHC/IO/FD.hs +++ b/GHC/IO/FD.hs @@ -217,7 +217,7 @@ nonblock_flags = o_NONBLOCK -- | Make a 'FD' from an existing file descriptor. Fails if the FD -- refers to a directory. If the FD refers to a file, `mkFD` locks --- the file according to the Haskell 98 single writer/multiple reader +-- the file according to the Haskell 2010 single writer/multiple reader -- locking semantics (this is why we need the `IOMode` argument too). mkFD :: CInt -> IOMode diff --git a/GHC/List.lhs b/GHC/List.lhs index b32cea9..02d6965 100644 --- a/GHC/List.lhs +++ b/GHC/List.lhs @@ -19,7 +19,7 @@ -- #hide module GHC.List ( - -- [] (..), -- Not Haskell 98; built in syntax + -- [] (..), -- built-in syntax; can't be used in export list map, (++), filter, concat, head, last, tail, init, null, length, (!!), diff --git a/GHC/Read.lhs b/GHC/Read.lhs index caf6a12..c5024fc 100644 --- a/GHC/Read.lhs +++ b/GHC/Read.lhs @@ -25,7 +25,7 @@ module GHC.Read -- ReadS type , ReadS - -- H98 compatibility + -- H2010 compatibility , lex , lexLitChar , readLitChar @@ -79,7 +79,7 @@ import GHC.Arr -- @'readParen' 'False' p@ parses what @p@ parses, but optionally -- surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a --- A Haskell 98 function +-- A Haskell 2010 function readParen b g = if b then mandatory else optional where optional r = g r ++ mandatory r mandatory r = do @@ -127,7 +127,7 @@ readParen b g = if b then mandatory else optional -- > infixr 5 :^: -- > data Tree a = Leaf a | Tree a :^: Tree a -- --- the derived instance of 'Read' in Haskell 98 is equivalent to +-- the derived instance of 'Read' in Haskell 2010 is equivalent to -- -- > instance (Read a) => Read (Tree a) where -- > @@ -219,7 +219,7 @@ readListPrecDefault :: Read a => ReadPrec [a] readListPrecDefault = list readPrec ------------------------------------------------------------------------ --- H98 compatibility +-- H2010 compatibility -- | The 'lex' function reads a single lexeme from the input, discarding -- initial white space, and returning the characters that constitute the @@ -236,7 +236,7 @@ readListPrecDefault = list readPrec -- * Octal and hexadecimal numerics are not recognized as a single token -- -- * Comments are not treated properly -lex :: ReadS String -- As defined by H98 +lex :: ReadS String -- As defined by H2010 lex s = readP_to_S L.hsLex s -- | Read a string representation of a character, using Haskell @@ -244,7 +244,7 @@ lex s = readP_to_S L.hsLex s -- -- > lexLitChar "\\nHello" = [("\\n", "Hello")] -- -lexLitChar :: ReadS String -- As defined by H98 +lexLitChar :: ReadS String -- As defined by H2010 lexLitChar = readP_to_S (do { (s, _) <- P.gather L.lexChar ; return s }) -- There was a skipSpaces before the P.gather L.lexChar, @@ -256,7 +256,7 @@ lexLitChar = readP_to_S (do { (s, _) <- P.gather L.lexChar ; -- -- > readLitChar "\\nHello" = [('\n', "Hello")] -- -readLitChar :: ReadS Char -- As defined by H98 +readLitChar :: ReadS Char -- As defined by H2010 readLitChar = readP_to_S L.lexChar -- | Reads a non-empty string of decimal digits. @@ -344,7 +344,7 @@ instance Read Char where return s +++ readListPrecDefault -- Looks for ['f','o','o'] - ) -- (more generous than H98 spec) + ) -- (more generous than H2010 spec) readList = readListDefault diff --git a/Text/Printf.hs b/Text/Printf.hs index 1369cfe..0546e84 100644 --- a/Text/Printf.hs +++ b/Text/Printf.hs @@ -101,7 +101,7 @@ class PrintfType t where class HPrintfType t where hspr :: Handle -> String -> [UPrintf] -> t -{- not allowed in Haskell 98 +{- not allowed in Haskell 2010 instance PrintfType String where spr fmt args = uprintf fmt (reverse args) -} @@ -130,7 +130,7 @@ class PrintfArg a where instance PrintfArg Char where toUPrintf c = UChar c -{- not allowed in Haskell 98 +{- not allowed in Haskell 2010 instance PrintfArg String where toUPrintf s = UString s -} diff --git a/Text/Read.hs b/Text/Read.hs index 0216df9..682e9b3 100644 --- a/Text/Read.hs +++ b/Text/Read.hs @@ -16,7 +16,7 @@ -- The "Text.Read" library is the canonical library to import for -- 'Read'-class facilities. For GHC only, it offers an extended and much -- improved 'Read' class, which constitutes a proposed alternative to the --- Haskell 98 'Read'. In particular, writing parsers is easier, and +-- Haskell 2010 'Read'. In particular, writing parsers is easier, and -- the parsers are much more efficient. -- ----------------------------------------------------------------------------- @@ -26,7 +26,7 @@ module Text.Read ( Read(..), ReadS, - -- * Haskell 98 functions + -- * Haskell 2010 functions reads, read, readParen, _______________________________________________ Cvs-libraries mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-libraries
