minimal Prelude (was Re: Export lists in modules)

Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk
Wed Feb 22 12:12:47 EST 2006


Wolfgang Jeltsch <wolfgang at jeltsch.net> wrote:

> I would solve this problem by reducing the Prelude to just a core. 
> List  function could go, for example, (mostly) into Data.List.

There is a proposal to shrink the prelude to the minimum possible.  I
have just fleshed out some of the details, at the bottom of this page:
    http://hackage.haskell.org/trac/haskell-prime/wiki/Prelude

Here are the details, reproduced for email discussion:

Let the Prelude itself contain only entities that relate purely to
functions - no other datatypes.

module Prelude
    ( (->)
    , (.)
    , ($)
    , ($!)
    , flip
    , id
    , const
    , error
    , undefined
    , seq
    , asTypeOf
    )

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:

module Prelude.Standard
    ( module Prelude
    , module Prelude.Num
    , module Prelude.Comparison
    , module Prelude.Monad
    , module Prelude.List
    , module Prelude.Maybe
    , module Prelude.Either
    , module Prelude.Tuple
    , module Prelude.IO
    , module Prelude.Text
    )

And here are the individual fragments:

module Prelude.Num
    ( data Natural(..)
    , data Int(..)
    , data Int8(..)
    , data Int16(..)
    , data Int32(..)
    , data Int64(..)
    , data Word8(..)
    , data Word16(..)
    , data Word32(..)
    , data Word64(..)
    , data Integer(..)
    , data Float(..)
    , data Double(..)
    , type Rational
    , class Integral(..)
    , class Num(..)
    , class Fractional(..)
    , class Real(..)
    , class RealFrac(..)
    , class Floating(..)
    , class RealFloat(..)
    , gcd, lcm
    , fromIntegral, realToFrac
    , numericEnumFrom, numericEnumFromTo, numericEnumFromThen
    , numericEnumFromThenTo
    , (^), (^^), (%)
    , even, odd, subtract
    )

module Prelude.Comparison
    ( data Bool(..)
    , data Ordering(..)
    , class Eq(..)
    , class Ord(..)
    , class Enum(..)
    , class Bounded(..)
    , otherwise
    , (&&), (||), not, until
    )

module Prelude.Monad
    ( class Functor(..)
    , class Monad(..)
    , mapM, mapM_, sequence, sequence_, (=<<)
    )

module Prelude.List
    ( data [](..)
    , all, and, any, (++), break, concat, concatMap, cycle, drop, dropWhile
    , elem, filter, foldl, foldl1, foldr, foldr1, head, (!!), init, iterate
    , last, length, lines, lookup, map, maximum, minimum, notElem, null
    , or, product, repeat, replicate, reverse, scanl, scanl1, scanr, scanr1
    , span, splitAt, sum, tail, take, takeWhile, unlines, unwords, words
    )

module Prelude.Maybe
    ( data Maybe(..)
    , maybe
    )

module Prelude.Either
    ( data Either(..)
    , either
    )

module Prelude.Tuple
    ( data ()(..)
    , data (,)(..)
    , data (,,)(..)
    , data (,,,)(..)
    , data (,,,,)(..)
    , data (,,,,,)(..)
    , data (,,,,,,)(..)
    , data (,,,,,,,)(..)
    , data (,,,,,,,,)(..)
    , data (,,,,,,,,,)(..)
    , data (,,,,,,,,,,)(..)
    , data (,,,,,,,,,,,)(..)
    , data (,,,,,,,,,,,,)(..)
    , data (,,,,,,,,,,,,,)(..)
    , data (,,,,,,,,,,,,,,)(..)
    , fst, snd
    , unzip, unzip3, zip, zip3, zipWith, zipWith3
    , curry, uncurry
    )

module Prelude.IO
    ( data IO
    , data IOError(..)
    , data FilePath
    , ioError, userError, catch
    , print
    , putChar, putStr, putStrLn
    , getChar, getLine, getContents, interact
    , readFile, writeFile, appendFile, readIO, readLn
    )

module Prelude.Text
    ( data Char(..)
    , type String
    , class Read(..)
    , class Show(..)
    , type ReadS
    , type ShowS
    , read, reads, readParen, lex
    , shows, showString, showParen, showChar
    )



More information about the Haskell-prime mailing list