1e860720453b3761c93d55d509f97fb75d0fb854
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
1 % ------------------------------------------------------------------------------
2 % $Id: Prelude.lhs,v 1.23 2001/02/22 13:17:59 simonpj Exp $
3 %
4 % (c) The University of Glasgow, 1992-2000
5 %
6
7 \section[Prelude]{Module @Prelude@}
8
9 We add the option -fno-implicit-prelude here to tell the reader that
10 special names such as () and -> shouldn't be resolved to Prelude.()
11 and Prelude.-> (as they are normally). -- SDM 8/10/97
12
13 \begin{code}
14 {-# OPTIONS -fno-implicit-prelude #-}
15
16 module Prelude (
17
18         -- Everything corresponding to the Report's PreludeList
19     module PrelList, 
20     lines, words, unlines, unwords,
21     sum, product,
22
23         -- Everything corresponding to the Report's PreludeText
24     ReadS, ShowS,
25     Read(readsPrec, readList),
26     Show(showsPrec, showList, show),
27     reads, shows, read, lex, 
28     showChar, showString, readParen, showParen,
29     
30         -- Everything corresponding to the Report's PreludeIO
31     FilePath, IOError,
32     ioError, userError, catch,
33     putChar, putStr, putStrLn, print,
34     getChar, getLine, getContents, interact,
35     readFile, writeFile, appendFile, readIO, readLn,
36
37     Bool(..),
38     Maybe(..),
39     Either(..),
40     Ordering(..), 
41     Char, String, Int, Integer, Float, Double, IO,
42     Rational,
43     []((:), []),
44     
45     module PrelTup,
46         -- Includes tuple types + fst, snd, curry, uncurry
47     ()(..),             -- The unit type
48     (->),               -- functions
49     
50     Eq(..),
51     Ord(..), 
52     Enum(..),
53     Bounded(..), 
54     Num((+), (-), (*), negate, abs, signum, fromInteger),
55     Real(..),
56     Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
57         -- The toInt method is exposed only by GlaExts
58     Fractional(..),
59     Floating(..),
60     RealFrac(..),
61     RealFloat(..),
62
63         -- Monad stuff, from PrelBase, and defined here
64     Monad(..),
65     Functor(..), 
66     mapM, mapM_, sequence, sequence_, (=<<),
67
68     maybe, either,
69     (&&), (||), not, otherwise,
70     subtract, even, odd, gcd, lcm, (^), (^^), 
71     fromIntegral, realToFrac,
72     --exported by PrelTup: fst, snd, curry, uncurry,
73     id, const, (.), flip, ($), until,
74     asTypeOf, error, undefined,
75     seq, ($!)
76
77   ) where
78
79 import PrelBase
80 import PrelList
81 #ifndef USE_REPORT_PRELUDE
82      hiding ( takeUInt_append )
83 #endif
84 import PrelIO
85 import PrelIOBase
86 import PrelException
87 import PrelRead
88 import PrelEnum
89 import PrelNum
90 import PrelReal
91 import PrelFloat
92 import PrelTup
93 import PrelMaybe
94 import PrelShow
95 import PrelConc
96 import PrelErr   ( error )
97
98 infixr 1 =<<
99 infixr 0 $!
100 \end{code}
101
102
103 %*********************************************************
104 %*                                                      *
105 \subsection{Miscellaneous functions}
106 %*                                                      *
107 %*********************************************************
108
109 \begin{code}
110 ($!)    :: (a -> b) -> a -> b
111 f $! x  = x `seq` f x
112
113 -- It is expected that compilers will recognize this and insert error
114 -- messages which are more appropriate to the context in which undefined 
115 -- appears. 
116
117 undefined               :: a
118 undefined               =  error "Prelude.undefined"
119 \end{code}
120
121
122 %*********************************************************
123 %*                                                      *
124 \subsection{List sum and product}
125 %*                                                      *
126 %*********************************************************
127
128 List sum and product are defined here because PrelList is too far
129 down the compilation chain to "see" the Num class.
130
131 \begin{code}
132 -- sum and product compute the sum or product of a finite list of numbers.
133 {-# SPECIALISE sum     :: [Int] -> Int #-}
134 {-# SPECIALISE sum     :: [Integer] -> Integer #-}
135 {-# SPECIALISE product :: [Int] -> Int #-}
136 {-# SPECIALISE product :: [Integer] -> Integer #-}
137 sum, product            :: (Num a) => [a] -> a
138 #ifdef USE_REPORT_PRELUDE
139 sum                     =  foldl (+) 0  
140 product                 =  foldl (*) 1
141 #else
142 sum     l       = sum' l 0
143   where
144     sum' []     a = a
145     sum' (x:xs) a = sum' xs (a+x)
146 product l       = prod l 1
147   where
148     prod []     a = a
149     prod (x:xs) a = prod xs (a*x)
150 #endif
151 \end{code}
152
153
154 %*********************************************************
155 %*                                                      *
156 \subsection{Prelude monad functions}
157 %*                                                      *
158 %*********************************************************
159
160 \begin{code}
161 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
162 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
163 f =<< x         = x >>= f
164
165 sequence       :: Monad m => [m a] -> m [a] 
166 {-# INLINE sequence #-}
167 sequence ms = foldr k (return []) ms
168             where
169               k m m' = do { x <- m; xs <- m'; return (x:xs) }
170
171 sequence_        :: Monad m => [m a] -> m () 
172 {-# INLINE sequence_ #-}
173 sequence_ ms     =  foldr (>>) (return ()) ms
174
175 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
176 {-# INLINE mapM #-}
177 mapM f as       =  sequence (map f as)
178
179 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
180 {-# INLINE mapM_ #-}
181 mapM_ f as      =  sequence_ (map f as)
182 \end{code}
183
184
185 %*********************************************************
186 %*                                                      *
187 \subsection{Coercions}
188 %*                                                      *
189 %*********************************************************
190
191 \begin{code}
192 {-# RULES
193 "fromIntegral/Int->Int"                     fromIntegral   = id :: Int     -> Int
194 "fromIntegral/Integer->Integer"             fromIntegral   = id :: Integer -> Integer
195 "fromIntegral/Int->Integer"                 fromIntegral   = int2Integer
196 "fromIntegral/Integer->Int"                 fromIntegral   = integer2Int
197 "fromIntegral/Int->Rational"     forall n . fromIntegral n = int2Integer n :% 1
198 "fromIntegral/Integer->Rational" forall n . fromIntegral n = n :% (1 :: Integer)
199 "fromIntegral/Int->Float"                   fromIntegral   = int2Float
200 "fromIntegral/Int->Double"                  fromIntegral   = int2Double
201 "fromIntegral/Integer->Float"    forall n . fromIntegral n = encodeFloat n 0 :: Float
202 "fromIntegral/Integer->Double"   forall n . fromIntegral n = encodeFloat n 0 :: Double
203  #-}
204 fromIntegral    :: (Integral a, Num b) => a -> b
205 fromIntegral    =  fromInteger . toInteger
206
207 {-# RULES
208 "realToFrac/Float->Double"      realToFrac = floatToDouble
209 "realToFrac/Double->Float"      realToFrac = doubleToFloat
210 "realToFrac/Float->Float"       realToFrac = id      :: Float    -> Float
211 "realToFrac/Double->Double"     realToFrac = id      :: Double   -> Double
212 "realToFrac/Rational->Rational" realToFrac = id      :: Rational -> Rational
213 "realToFrac/Float->Rational"    realToFrac = rf2rat  :: Float    -> Rational
214 "realToFrac/Double->Rational"   realToFrac = rf2rat  :: Double   -> Rational
215 "realToFrac/Rational->Float"    realToFrac = fromRat :: Rational -> Float
216 "realToFrac/Rational->Double"   realToFrac = fromRat :: Rational -> Double
217  #-}
218 realToFrac      :: (Real a, Fractional b) => a -> b
219 realToFrac      =  fromRational . toRational
220
221 doubleToFloat :: Double -> Float
222 doubleToFloat (D# d) = F# (double2Float# d)
223
224 floatToDouble :: Float -> Double
225 floatToDouble (F# f) = D# (float2Double# f)
226
227 {-# SPECIALIZE rf2rat ::
228     Float  -> Rational,
229     Double -> Rational
230  #-}
231 rf2rat :: RealFloat a => a -> Rational
232 rf2rat x = if n >= 0 then (m * (b ^ n)) :% 1 else m :% (b ^ (-n))
233    where (m,n) = decodeFloat x
234          b     = floatRadix  x
235 \end{code}