Adjust behaviour of gcd
[ghc-base.git] / Prelude.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Prelude
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  stable
11 -- Portability :  portable
12 --
13 -- The Prelude: a standard module imported by default into all Haskell
14 -- modules.  For more documentation, see the Haskell 98 Report
15 -- <http://www.haskell.org/onlinereport/>.
16 --
17 -----------------------------------------------------------------------------
18
19 module Prelude (
20
21     -- * Standard types, classes and related functions
22
23     -- ** Basic data types
24     Bool(False, True),
25     (&&), (||), not, otherwise,
26
27     Maybe(Nothing, Just),
28     maybe,
29
30     Either(Left, Right),
31     either,
32
33     Ordering(LT, EQ, GT),
34     Char, String,
35
36     -- *** Tuples
37     fst, snd, curry, uncurry,
38
39 #if defined(__NHC__)
40     []((:), []),        -- Not legal Haskell 98;
41                         -- ... available through built-in syntax
42     module Data.Tuple,  -- Includes tuple types
43     ()(..),             -- Not legal Haskell 98
44     (->),               -- ... available through built-in syntax
45 #endif
46 #ifdef __HUGS__
47     (:),                -- Not legal Haskell 98
48 #endif
49
50     -- ** Basic type classes
51     Eq((==), (/=)),
52     Ord(compare, (<), (<=), (>=), (>), max, min),
53     Enum(succ, pred, toEnum, fromEnum, enumFrom, enumFromThen,
54          enumFromTo, enumFromThenTo),
55     Bounded(minBound, maxBound),
56
57     -- ** Numbers
58
59     -- *** Numeric types
60     Int, Integer, Float, Double,
61     Rational,
62
63     -- *** Numeric type classes
64     Num((+), (-), (*), negate, abs, signum, fromInteger),
65     Real(toRational),
66     Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
67     Fractional((/), recip, fromRational),
68     Floating(pi, exp, log, sqrt, (**), logBase, sin, cos, tan,
69              asin, acos, atan, sinh, cosh, tanh, asinh, acosh, atanh),
70     RealFrac(properFraction, truncate, round, ceiling, floor),
71     RealFloat(floatRadix, floatDigits, floatRange, decodeFloat,
72               encodeFloat, exponent, significand, scaleFloat, isNaN,
73               isInfinite, isDenormalized, isIEEE, isNegativeZero, atan2),
74
75     -- *** Numeric functions
76     subtract, even, odd, gcd, lcm, (^), (^^),
77     fromIntegral, realToFrac,
78
79     -- ** Monads and functors
80     Monad((>>=), (>>), return, fail),
81     Functor(fmap),
82     mapM, mapM_, sequence, sequence_, (=<<),
83
84     -- ** Miscellaneous functions
85     id, const, (.), flip, ($), until,
86     asTypeOf, error, undefined,
87     seq, ($!),
88
89     -- * List operations
90     map, (++), filter,
91     head, last, tail, init, null, length, (!!),
92     reverse,
93     -- ** Reducing lists (folds)
94     foldl, foldl1, foldr, foldr1,
95     -- *** Special folds
96     and, or, any, all,
97     sum, product,
98     concat, concatMap,
99     maximum, minimum,
100     -- ** Building lists
101     -- *** Scans
102     scanl, scanl1, scanr, scanr1,
103     -- *** Infinite lists
104     iterate, repeat, replicate, cycle,
105     -- ** Sublists
106     take, drop, splitAt, takeWhile, dropWhile, span, break,
107     -- ** Searching lists
108     elem, notElem, lookup,
109     -- ** Zipping and unzipping lists
110     zip, zip3, zipWith, zipWith3, unzip, unzip3,
111     -- ** Functions on strings
112     lines, words, unlines, unwords,
113
114     -- * Converting to and from @String@
115     -- ** Converting to @String@
116     ShowS,
117     Show(showsPrec, showList, show),
118     shows,
119     showChar, showString, showParen,
120     -- ** Converting from @String@
121     ReadS,
122     Read(readsPrec, readList),
123     reads, readParen, read, lex,
124
125     -- * Basic Input and output
126     IO,
127     -- ** Simple I\/O operations
128     -- All I/O functions defined here are character oriented.  The
129     -- treatment of the newline character will vary on different systems.
130     -- For example, two characters of input, return and linefeed, may
131     -- read as a single newline character.  These functions cannot be
132     -- used portably for binary I/O.
133     -- *** Output functions
134     putChar,
135     putStr, putStrLn, print,
136     -- *** Input functions
137     getChar,
138     getLine, getContents, interact,
139     -- *** Files
140     FilePath,
141     readFile, writeFile, appendFile, readIO, readLn,
142     -- ** Exception handling in the I\/O monad
143     IOError, ioError, userError, catch
144
145   ) where
146
147 #ifndef __HUGS__
148 import Control.Monad
149 import System.IO
150 import System.IO.Error
151 import Data.List
152 import Data.Either
153 import Data.Maybe
154 import Data.Tuple
155 #endif
156
157 #ifdef __GLASGOW_HASKELL__
158 import GHC.Base
159 -- import GHC.IO
160 -- import GHC.IO.Exception
161 import Text.Read
162 import GHC.Enum
163 import GHC.Num
164 import GHC.Real
165 import GHC.Float
166 import GHC.Show
167 import GHC.Err   ( undefined )
168 #endif
169
170 #ifdef __HUGS__
171 import Hugs.Prelude
172 #endif
173
174 #ifndef __HUGS__
175 infixr 0 $!
176 #endif
177
178 -- -----------------------------------------------------------------------------
179 -- Miscellaneous functions
180
181 -- | Strict (call-by-value) application, defined in terms of 'seq'.
182 ($!)    :: (a -> b) -> a -> b
183 #ifdef __GLASGOW_HASKELL__
184 f $! x  = let !vx = x in f vx  -- see #2273
185 #elif !defined(__HUGS__)
186 f $! x  = x `seq` f x
187 #endif
188
189 #ifdef __HADDOCK__
190 -- | The value of @'seq' a b@ is bottom if @a@ is bottom, and otherwise
191 -- equal to @b@.  'seq' is usually introduced to improve performance by
192 -- avoiding unneeded laziness.
193 seq :: a -> b -> b
194 seq _ y = y
195 #endif