[project @ 2000-06-30 13:39:35 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
1 % ------------------------------------------------------------------------------
2 % $Id: Prelude.lhs,v 1.22 2000/06/30 13:39:36 simonmar 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         -- The fromInt method is exposed only by GlaExts
56     Real(..),
57     Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
58         -- The toInt method is exposed only by GlaExts
59     Fractional(..),
60     Floating(..),
61     RealFrac(..),
62     RealFloat(..),
63
64         -- Monad stuff, from PrelBase, and defined here
65     Monad(..),
66     Functor(..), 
67     mapM, mapM_, sequence, sequence_, (=<<),
68
69     maybe, either,
70     (&&), (||), not, otherwise,
71     subtract, even, odd, gcd, lcm, (^), (^^), 
72     fromIntegral, realToFrac,
73     --exported by PrelTup: fst, snd, curry, uncurry,
74     id, const, (.), flip, ($), until,
75     asTypeOf, error, undefined,
76     seq, ($!)
77
78   ) where
79
80 import PrelBase
81 import PrelList
82 #ifndef USE_REPORT_PRELUDE
83      hiding ( takeUInt_append )
84 #endif
85 import PrelIO
86 import PrelIOBase
87 import PrelException
88 import PrelRead
89 import PrelEnum
90 import PrelNum
91 import PrelReal
92 import PrelFloat
93 import PrelTup
94 import PrelMaybe
95 import PrelShow
96 import PrelConc
97 import PrelErr   ( error )
98
99 infixr 1 =<<
100 infixr 0 $!
101 \end{code}
102
103
104 %*********************************************************
105 %*                                                      *
106 \subsection{Miscellaneous functions}
107 %*                                                      *
108 %*********************************************************
109
110 \begin{code}
111 ($!)    :: (a -> b) -> a -> b
112 f $! x  = x `seq` f x
113
114 -- It is expected that compilers will recognize this and insert error
115 -- messages which are more appropriate to the context in which undefined 
116 -- appears. 
117
118 undefined               :: a
119 undefined               =  error "Prelude.undefined"
120 \end{code}
121
122
123 %*********************************************************
124 %*                                                      *
125 \subsection{List sum and product}
126 %*                                                      *
127 %*********************************************************
128
129 List sum and product are defined here because PrelList is too far
130 down the compilation chain to "see" the Num class.
131
132 \begin{code}
133 -- sum and product compute the sum or product of a finite list of numbers.
134 {-# SPECIALISE sum     :: [Int] -> Int #-}
135 {-# SPECIALISE sum     :: [Integer] -> Integer #-}
136 {-# SPECIALISE product :: [Int] -> Int #-}
137 {-# SPECIALISE product :: [Integer] -> Integer #-}
138 sum, product            :: (Num a) => [a] -> a
139 #ifdef USE_REPORT_PRELUDE
140 sum                     =  foldl (+) 0  
141 product                 =  foldl (*) 1
142 #else
143 sum     l       = sum' l 0
144   where
145     sum' []     a = a
146     sum' (x:xs) a = sum' xs (a+x)
147 product l       = prod l 1
148   where
149     prod []     a = a
150     prod (x:xs) a = prod xs (a*x)
151 #endif
152 \end{code}
153
154
155 %*********************************************************
156 %*                                                      *
157 \subsection{Prelude monad functions}
158 %*                                                      *
159 %*********************************************************
160
161 \begin{code}
162 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
163 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
164 f =<< x         = x >>= f
165
166 sequence       :: Monad m => [m a] -> m [a] 
167 {-# INLINE sequence #-}
168 sequence ms = foldr k (return []) ms
169             where
170               k m m' = do { x <- m; xs <- m'; return (x:xs) }
171
172 sequence_        :: Monad m => [m a] -> m () 
173 {-# INLINE sequence_ #-}
174 sequence_ ms     =  foldr (>>) (return ()) ms
175
176 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
177 {-# INLINE mapM #-}
178 mapM f as       =  sequence (map f as)
179
180 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
181 {-# INLINE mapM_ #-}
182 mapM_ f as      =  sequence_ (map f as)
183 \end{code}
184
185
186 %*********************************************************
187 %*                                                      *
188 \subsection{Coercions}
189 %*                                                      *
190 %*********************************************************
191
192 \begin{code}
193 {-# RULES
194 "fromIntegral/Int->Int"                     fromIntegral   = id :: Int     -> Int
195 "fromIntegral/Integer->Integer"             fromIntegral   = id :: Integer -> Integer
196 "fromIntegral/Int->Integer"                 fromIntegral   = int2Integer
197 "fromIntegral/Integer->Int"                 fromIntegral   = integer2Int
198 "fromIntegral/Int->Rational"     forall n . fromIntegral n = int2Integer n :% 1
199 "fromIntegral/Integer->Rational" forall n . fromIntegral n = n :% (1 :: Integer)
200 "fromIntegral/Int->Float"                   fromIntegral   = int2Float
201 "fromIntegral/Int->Double"                  fromIntegral   = int2Double
202 "fromIntegral/Integer->Float"    forall n . fromIntegral n = encodeFloat n 0 :: Float
203 "fromIntegral/Integer->Double"   forall n . fromIntegral n = encodeFloat n 0 :: Double
204  #-}
205 fromIntegral    :: (Integral a, Num b) => a -> b
206 fromIntegral    =  fromInteger . toInteger
207
208 {-# RULES
209 "realToFrac/Float->Double"      realToFrac = floatToDouble
210 "realToFrac/Double->Float"      realToFrac = doubleToFloat
211 "realToFrac/Float->Float"       realToFrac = id      :: Float    -> Float
212 "realToFrac/Double->Double"     realToFrac = id      :: Double   -> Double
213 "realToFrac/Rational->Rational" realToFrac = id      :: Rational -> Rational
214 "realToFrac/Float->Rational"    realToFrac = rf2rat  :: Float    -> Rational
215 "realToFrac/Double->Rational"   realToFrac = rf2rat  :: Double   -> Rational
216 "realToFrac/Rational->Float"    realToFrac = fromRat :: Rational -> Float
217 "realToFrac/Rational->Double"   realToFrac = fromRat :: Rational -> Double
218  #-}
219 realToFrac      :: (Real a, Fractional b) => a -> b
220 realToFrac      =  fromRational . toRational
221
222 doubleToFloat :: Double -> Float
223 doubleToFloat (D# d) = F# (double2Float# d)
224
225 floatToDouble :: Float -> Double
226 floatToDouble (F# f) = D# (float2Double# f)
227
228 {-# SPECIALIZE rf2rat ::
229     Float  -> Rational,
230     Double -> Rational
231  #-}
232 rf2rat :: RealFloat a => a -> Rational
233 rf2rat x = if n >= 0 then (m * (b ^ n)) :% 1 else m :% (b ^ (-n))
234    where (m,n) = decodeFloat x
235          b     = floatRadix  x
236 \end{code}