| ... | @@ -141,11 +141,11 @@ module Prelude |
... | @@ -141,11 +141,11 @@ module Prelude |
|
|
```
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
|
Everything else that is currently in the Haskell'98 Prelude is re-distributed across a variety of small modules. Where a syntactic desugaring rule currently uses an entity from the Prelude, the new interpretation is that it uses whatever binding of that entity is in scope - if there is no such entity in scope, it is an error. For compatibility, we define a wrapper module called Prelude.Standard which re-exports the original Haskell'98 Prelude:
|
|
Everything else that is currently in the Haskell'98 Prelude is re-distributed across a variety of small modules. Where a syntactic desugaring rule currently uses an entity from the Prelude, the new interpretation is that it uses whatever binding of that entity is in scope - if there is no such entity in scope, it is an error. For compatibility, we define a wrapper module called Prelude.Haskell98 which re-exports the original Haskell'98 Prelude:
|
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
module Prelude.Standard
|
|
module Prelude.Haskell98
|
|
|
( module Prelude
|
|
( module Prelude
|
|
|
, module Prelude.Num
|
|
, module Prelude.Num
|
|
|
, module Prelude.Comparison
|
|
, module Prelude.Comparison
|
| ... | @@ -160,25 +160,29 @@ module Prelude.Standard |
... | @@ -160,25 +160,29 @@ module Prelude.Standard |
|
|
```
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
|
And here are the individual fragments:
|
|
The rules for implicit import of the Prelude are now as follows. The new minimal Prelude is imported implicitly unless there is an explicit mention of it in an import decl. The larger Prelude.Haskell98 is implicitly imported *only* when the `module Main where` header is omitted from a main program module. This ensures that extremely simple programs continue to work without needing to add a new import, but in all other cases, one must explicitly choose whether to use the Prelude.Haskell98, or something else. We expect implementations might want to provide a flag like *-fimplicit-prelude* to automatically add an import of Prelude.Haskell98 to legacy modules.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Here are the individual fragments of the re-organised Prelude:
|
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
module Prelude.Num
|
|
module Prelude.Num
|
|
|
( data Natural(..)
|
|
( Natural(..) -- new in h-prime?
|
|
|
, data Int(..)
|
|
, Int(..)
|
|
|
, data Int8(..)
|
|
, Int8(..) -- previously in Data.Int
|
|
|
, data Int16(..)
|
|
, Int16(..)
|
|
|
, data Int32(..)
|
|
, Int32(..)
|
|
|
, data Int64(..)
|
|
, Int64(..)
|
|
|
, data Word8(..)
|
|
, Word8(..) -- previously in Data.Word
|
|
|
, data Word16(..)
|
|
, Word16(..)
|
|
|
, data Word32(..)
|
|
, Word32(..)
|
|
|
, data Word64(..)
|
|
, Word64(..)
|
|
|
, data Integer(..)
|
|
, Integer(..)
|
|
|
, data Float(..)
|
|
, Float(..)
|
|
|
, data Double(..)
|
|
, Double(..)
|
|
|
, type Rational
|
|
, Rational
|
|
|
, class Integral(..)
|
|
, class Integral(..)
|
|
|
, class Num(..)
|
|
, class Num(..)
|
|
|
, class Fractional(..)
|
|
, class Fractional(..)
|
| ... | @@ -195,8 +199,8 @@ module Prelude.Num |
... | @@ -195,8 +199,8 @@ module Prelude.Num |
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.Comparison
|
|
module Prelude.Comparison
|
|
|
( data Bool(..)
|
|
( Bool(..)
|
|
|
, data Ordering(..)
|
|
, Ordering(..)
|
|
|
, class Eq(..)
|
|
, class Eq(..)
|
|
|
, class Ord(..)
|
|
, class Ord(..)
|
|
|
, class Enum(..)
|
|
, class Enum(..)
|
| ... | @@ -212,7 +216,7 @@ module Prelude.Monad |
... | @@ -212,7 +216,7 @@ module Prelude.Monad |
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.List
|
|
module Prelude.List
|
|
|
( data [](..)
|
|
( [](..)
|
|
|
, all, and, any, (++), break, concat, concatMap, cycle, drop, dropWhile
|
|
, all, and, any, (++), break, concat, concatMap, cycle, drop, dropWhile
|
|
|
, elem, filter, foldl, foldl1, foldr, foldr1, head, (!!), init, iterate
|
|
, elem, filter, foldl, foldl1, foldr, foldr1, head, (!!), init, iterate
|
|
|
, last, length, lines, lookup, map, maximum, minimum, notElem, null
|
|
, last, length, lines, lookup, map, maximum, minimum, notElem, null
|
| ... | @@ -221,40 +225,40 @@ module Prelude.List |
... | @@ -221,40 +225,40 @@ module Prelude.List |
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.Maybe
|
|
module Prelude.Maybe
|
|
|
( data Maybe(..)
|
|
( Maybe(..)
|
|
|
, maybe
|
|
, maybe
|
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.Either
|
|
module Prelude.Either
|
|
|
( data Either(..)
|
|
( Either(..)
|
|
|
, either
|
|
, either
|
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.Tuple
|
|
module Prelude.Tuple
|
|
|
( data ()(..)
|
|
( ()(..)
|
|
|
, data (,)(..)
|
|
, (,)(..)
|
|
|
, data (,,)(..)
|
|
, (,,)(..)
|
|
|
, data (,,,)(..)
|
|
, (,,,)(..)
|
|
|
, data (,,,,)(..)
|
|
, (,,,,)(..)
|
|
|
, data (,,,,,)(..)
|
|
, (,,,,,)(..)
|
|
|
, data (,,,,,,)(..)
|
|
, (,,,,,,)(..)
|
|
|
, data (,,,,,,,)(..)
|
|
, (,,,,,,,)(..)
|
|
|
, data (,,,,,,,,)(..)
|
|
, (,,,,,,,,)(..)
|
|
|
, data (,,,,,,,,,)(..)
|
|
, (,,,,,,,,,)(..)
|
|
|
, data (,,,,,,,,,,)(..)
|
|
, (,,,,,,,,,,)(..)
|
|
|
, data (,,,,,,,,,,,)(..)
|
|
, (,,,,,,,,,,,)(..)
|
|
|
, data (,,,,,,,,,,,,)(..)
|
|
, (,,,,,,,,,,,,)(..)
|
|
|
, data (,,,,,,,,,,,,,)(..)
|
|
, (,,,,,,,,,,,,,)(..)
|
|
|
, data (,,,,,,,,,,,,,,)(..)
|
|
, (,,,,,,,,,,,,,,)(..)
|
|
|
, fst, snd
|
|
, fst, snd
|
|
|
, unzip, unzip3, zip, zip3, zipWith, zipWith3
|
|
, unzip, unzip3, zip, zip3, zipWith, zipWith3
|
|
|
, curry, uncurry
|
|
, curry, uncurry
|
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.IO
|
|
module Prelude.IO
|
|
|
( data IO
|
|
( IO
|
|
|
, data IOError(..)
|
|
, IOError(..)
|
|
|
, data FilePath
|
|
, FilePath
|
|
|
, ioError, userError, catch
|
|
, ioError, userError, catch
|
|
|
, print
|
|
, print
|
|
|
, putChar, putStr, putStrLn
|
|
, putChar, putStr, putStrLn
|
| ... | @@ -263,12 +267,12 @@ module Prelude.IO |
... | @@ -263,12 +267,12 @@ module Prelude.IO |
|
|
)
|
|
)
|
|
|
|
|
|
|
|
module Prelude.Text
|
|
module Prelude.Text
|
|
|
( data Char(..)
|
|
( Char(..)
|
|
|
, type String
|
|
, String
|
|
|
, class Read(..)
|
|
, class Read(..)
|
|
|
, class Show(..)
|
|
, class Show(..)
|
|
|
, type ReadS
|
|
, ReadS
|
|
|
, type ShowS
|
|
, ShowS
|
|
|
, read, reads, readParen, lex
|
|
, read, reads, readParen, lex
|
|
|
, shows, showString, showParen, showChar
|
|
, shows, showString, showParen, showChar
|
|
|
)
|
|
)
|
| ... | | ... | |