add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Prelude.hs
index 8ee9330..4c183ae 100644 (file)
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns #-}
+
 -----------------------------------------------------------------------------
--- 
+-- |
 -- Module      :  Prelude
 -- Copyright   :  (c) The University of Glasgow 2001
--- License     :  BSD-style (see the file libraries/core/LICENSE)
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
 -- 
 -- Maintainer  :  libraries@haskell.org
--- Stability   :  provisional
+-- Stability   :  stable
 -- Portability :  portable
 --
--- $Id: Prelude.hs,v 1.1 2001/06/28 14:15:01 simonmar Exp $
---
--- Standard module imported by default into Haskell modules.
+-- The Prelude: a standard module imported by default into all Haskell
+-- modules.  For more documentation, see the Haskell 98 Report
+-- <http://www.haskell.org/onlinereport/>.
 --
 -----------------------------------------------------------------------------
 
 module Prelude (
 
-       -- List things
-    [] (..),
+    -- * Standard types, classes and related functions
+
+    -- ** Basic data types
+    Bool(False, True),
+    (&&), (||), not, otherwise,
+
+    Maybe(Nothing, Just),
+    maybe,
+
+    Either(Left, Right),
+    either,
+
+    Ordering(LT, EQ, GT),
+    Char, String,
+
+    -- *** Tuples
+    fst, snd, curry, uncurry,
+
+#if defined(__NHC__)
+    []((:), []),        -- Not legal Haskell 98;
+                        -- ... available through built-in syntax
+    module Data.Tuple,  -- Includes tuple types
+    ()(..),             -- Not legal Haskell 98
+    (->),               -- ... available through built-in syntax
+#endif
+#ifdef __HUGS__
+    (:),                -- Not legal Haskell 98
+#endif
 
-    map, (++), filter, concat,
-    head, last, tail, init, null, length, (!!), 
-    foldl, foldl1, scanl, scanl1, foldr, foldr1, scanr, scanr1,
+    -- ** Basic type classes
+    Eq((==), (/=)),
+    Ord(compare, (<), (<=), (>=), (>), max, min),
+    Enum(succ, pred, toEnum, fromEnum, enumFrom, enumFromThen,
+         enumFromTo, enumFromThenTo),
+    Bounded(minBound, maxBound),
+
+    -- ** Numbers
+
+    -- *** Numeric types
+    Int, Integer, Float, Double,
+    Rational,
+
+    -- *** Numeric type classes
+    Num((+), (-), (*), negate, abs, signum, fromInteger),
+    Real(toRational),
+    Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
+    Fractional((/), recip, fromRational),
+    Floating(pi, exp, log, sqrt, (**), logBase, sin, cos, tan,
+             asin, acos, atan, sinh, cosh, tanh, asinh, acosh, atanh),
+    RealFrac(properFraction, truncate, round, ceiling, floor),
+    RealFloat(floatRadix, floatDigits, floatRange, decodeFloat,
+              encodeFloat, exponent, significand, scaleFloat, isNaN,
+              isInfinite, isDenormalized, isIEEE, isNegativeZero, atan2),
+
+    -- *** Numeric functions
+    subtract, even, odd, gcd, lcm, (^), (^^),
+    fromIntegral, realToFrac,
+
+    -- ** Monads and functors
+    Monad((>>=), (>>), return, fail),
+    Functor(fmap),
+    mapM, mapM_, sequence, sequence_, (=<<),
+
+    -- ** Miscellaneous functions
+    id, const, (.), flip, ($), until,
+    asTypeOf, error, undefined,
+    seq, ($!),
+
+    -- * List operations
+    map, (++), filter,
+    head, last, tail, init, null, length, (!!),
+    reverse,
+    -- ** Reducing lists (folds)
+    foldl, foldl1, foldr, foldr1,
+    -- *** Special folds
+    and, or, any, all,
+    sum, product,
+    concat, concatMap,
+    maximum, minimum,
+    -- ** Building lists
+    -- *** Scans
+    scanl, scanl1, scanr, scanr1,
+    -- *** Infinite lists
     iterate, repeat, replicate, cycle,
+    -- ** Sublists
     take, drop, splitAt, takeWhile, dropWhile, span, break,
-    reverse, and, or,
-    any, all, elem, notElem, lookup,
-    maximum, minimum, concatMap,
+    -- ** Searching lists
+    elem, notElem, lookup,
+    -- ** Zipping and unzipping lists
     zip, zip3, zipWith, zipWith3, unzip, unzip3,
-
+    -- ** Functions on strings
     lines, words, unlines, unwords,
-    sum, product,
 
-        -- Everything from Text.Read and Text.Show
-    ReadS, ShowS,
-    Read(readsPrec, readList),
+    -- * Converting to and from @String@
+    -- ** Converting to @String@
+    ShowS,
     Show(showsPrec, showList, show),
-    reads, shows, read, lex, 
-    showChar, showString, readParen, showParen,
-    
-        -- Everything corresponding to the Report's PreludeIO
-    ioError, userError, catch,
-    FilePath, IOError,
+    shows,
+    showChar, showString, showParen,
+    -- ** Converting from @String@
+    ReadS,
+    Read(readsPrec, readList),
+    reads, readParen, read, lex,
+
+    -- * Basic Input and output
+    IO,
+    -- ** Simple I\/O operations
+    -- All I/O functions defined here are character oriented.  The
+    -- treatment of the newline character will vary on different systems.
+    -- For example, two characters of input, return and linefeed, may
+    -- read as a single newline character.  These functions cannot be
+    -- used portably for binary I/O.
+    -- *** Output functions
     putChar,
     putStr, putStrLn, print,
+    -- *** Input functions
     getChar,
     getLine, getContents, interact,
+    -- *** Files
+    FilePath,
     readFile, writeFile, appendFile, readIO, readLn,
-
-    Bool(..),
-    Maybe(..),
-    Either(..),
-    Ordering(..), 
-    Char, String, Int, Integer, Float, Double, IO,
-    Rational,
-    []((:), []),
-    
-    module GHC.Tup,
-        -- Includes tuple types + fst, snd, curry, uncurry
-    ()(..),            -- The unit type
-    (->),              -- functions
-    
-    Eq(..),
-    Ord(..), 
-    Enum(..),
-    Bounded(..), 
-    Num(..),
-    Real(..),
-    Integral(..),
-    Fractional(..),
-    Floating(..),
-    RealFrac(..),
-    RealFloat(..),
-
-       -- Monad stuff, from GHC.Base, and defined here
-    Monad(..),
-    Functor(..), 
-    mapM, mapM_, sequence, sequence_, (=<<),
-
-    maybe, either,
-    (&&), (||), not, otherwise,
-    subtract, even, odd, gcd, lcm, (^), (^^), 
-    fromIntegral, realToFrac,
-    --exported by GHC.Tup: fst, snd, curry, uncurry,
-    id, const, (.), flip, ($), until,
-    asTypeOf, error, undefined,
-    seq, ($!)
+    -- ** Exception handling in the I\/O monad
+    IOError, ioError, userError, catch
 
   ) where
 
+#ifndef __HUGS__
 import Control.Monad
 import System.IO
-import Text.Read
-import Text.Show
+import System.IO.Error
 import Data.List
 import Data.Either
 import Data.Maybe
-import Data.Bool
+import Data.Tuple
+#endif
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
-import GHC.IOBase
-import GHC.Exception
-import GHC.Read
+-- import GHC.IO
+-- import GHC.IO.Exception
+import Text.Read
 import GHC.Enum
 import GHC.Num
 import GHC.Real
 import GHC.Float
-import GHC.Tup
 import GHC.Show
-import GHC.Conc
-import GHC.Err   ( error, undefined )
+import GHC.Err   ( undefined )
 #endif
 
-infixr 0 $!
+#ifdef __HUGS__
+import Hugs.Prelude
+#endif
 
+#ifndef __HUGS__
+infixr 0 $!
+#endif
 
 -- -----------------------------------------------------------------------------
 -- Miscellaneous functions
 
+-- | Strict (call-by-value) application, defined in terms of 'seq'.
 ($!)    :: (a -> b) -> a -> b
+#ifdef __GLASGOW_HASKELL__
+f $! x  = let !vx = x in f vx  -- see #2273
+#elif !defined(__HUGS__)
 f $! x  = x `seq` f x
+#endif
 
-
+#ifdef __HADDOCK__
+-- | The value of @'seq' a b@ is bottom if @a@ is bottom, and otherwise
+-- equal to @b@.  'seq' is usually introduced to improve performance by
+-- avoiding unneeded laziness.
+seq :: a -> b -> b
+seq _ y = y
+#endif