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