[project @ 1999-05-21 13:37:07 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelBase.lhs
1 %
2 % (c) The GRAP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[PrelBase]{Module @PrelBase@}
5
6
7 \begin{code}
8 {-# OPTIONS -fno-implicit-prelude #-}
9
10 module PrelBase
11         (
12         module PrelBase,
13         module PrelGHC          -- Re-export PrelGHC, to avoid lots of people 
14                                 -- having to import it explicitly
15   ) 
16         where
17
18 import {-# SOURCE #-} PrelErr ( error )
19 import PrelGHC
20
21 infixr 9  .
22 infixr 5  ++, :
23 infix  4  ==, /=, <, <=, >=, >
24 infixr 3  &&
25 infixr 2  ||
26 infixl 1  >>, >>=
27 infixr 0  $
28 \end{code}
29
30
31 %*********************************************************
32 %*                                                      *
33 \subsection{Standard classes @Eq@, @Ord@, @Bounded@
34 %*                                                      *
35 %*********************************************************
36
37 \begin{code}
38 class  Eq a  where
39     (==), (/=)          :: a -> a -> Bool
40
41     x /= y              =  not (x == y)
42     x == y              = not  (x /= y)
43
44 class  (Eq a) => Ord a  where
45     compare             :: a -> a -> Ordering
46     (<), (<=), (>=), (>):: a -> a -> Bool
47     max, min            :: a -> a -> a
48
49 -- An instance of Ord should define either compare or <=
50 -- Using compare can be more efficient for complex types.
51     compare x y
52             | x == y    = EQ
53             | x <  y    = LT
54             | otherwise = GT
55
56     x <= y  = case compare x y of { GT -> False; other -> True }
57     x <  y  = case compare x y of { LT -> True;  other -> False }
58     x >= y  = case compare x y of { LT -> False; other -> True }
59     x >  y  = case compare x y of { GT -> True;  other -> False }
60
61         -- These two default methods use '>' rather than compare
62         -- because the latter is often more expensive
63     max x y = if x > y then x else y
64     min x y = if x > y then y else x
65 \end{code}
66
67 %*********************************************************
68 %*                                                      *
69 \subsection{Monadic classes @Functor@, @Monad@ }
70 %*                                                      *
71 %*********************************************************
72
73 \begin{code}
74 class  Functor f  where
75     fmap         :: (a -> b) -> f a -> f b
76
77 class  Monad m  where
78     (>>=)       :: m a -> (a -> m b) -> m b
79     (>>)        :: m a -> m b -> m b
80     return      :: a -> m a
81     fail        :: String -> m a
82
83     m >> k      =  m >>= \_ -> k
84     fail s      = error s
85
86 \end{code}
87
88
89 %*********************************************************
90 %*                                                      *
91 \subsection{The list type}
92 %*                                                      *
93 %*********************************************************
94
95 \begin{code}
96 data [] a = [] | a : [a]  -- do explicitly: deriving (Eq, Ord)
97                           -- to avoid weird names like con2tag_[]#
98
99 instance (Eq a) => Eq [a]  where
100     []     == []     = True     
101     (x:xs) == (y:ys) = x == y && xs == ys
102     _xs    == _ys    = False                    
103
104     xs     /= ys     = if (xs == ys) then False else True
105
106 instance (Ord a) => Ord [a] where
107     a <  b  = case compare a b of { LT -> True;  EQ -> False; GT -> False }
108     a <= b  = case compare a b of { LT -> True;  EQ -> True;  GT -> False }
109     a >= b  = case compare a b of { LT -> False; EQ -> True;  GT -> True  }
110     a >  b  = case compare a b of { LT -> False; EQ -> False; GT -> True  }
111
112     compare []     []     = EQ
113     compare (_:_)  []     = GT
114     compare []     (_:_)  = LT
115     compare (x:xs) (y:ys) = case compare x y of
116                                  LT -> LT       
117                                  GT -> GT               
118                                  EQ -> compare xs ys
119
120 instance Functor [] where
121     fmap = map
122
123 instance  Monad []  where
124     m >>= k             = foldr ((++) . k) [] m
125     m >> k              = foldr ((++) . (\ _ -> k)) [] m
126     return x            = [x]
127     fail _              = []
128 \end{code}
129
130 A few list functions that appear here because they are used here.
131 The rest of the prelude list functions are in PrelList.
132
133 ----------------------------------------------
134 --      foldr/build/augment
135 ----------------------------------------------
136   
137 \begin{code}
138 foldr            :: (a -> b -> b) -> b -> [a] -> b
139 foldr _ z []     =  z
140 foldr f z (x:xs) =  f x (foldr f z xs)
141
142 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
143 {-# INLINE build #-}
144         -- The INLINE is important, even though build is tiny,
145         -- because it prevents [] getting inlined in the version that
146         -- appears in the interface file.  If [] *is* inlined, it
147         -- won't match with [] appearing in rules in an importing module.
148 build g = g (:) []
149
150 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
151 {-# INLINE augment #-}
152 augment g xs = g (:) xs
153
154 {-# RULES
155 "fold/build"    forall k,z,g::forall b. (a->b->b) -> b -> b . 
156                 foldr k z (build g) = g k z
157
158 "foldr/augment" forall k,z,xs,g::forall b. (a->b->b) -> b -> b . 
159                 foldr k z (augment g xs) = g k (foldr k z xs)
160
161 "foldr/id"      foldr (:) [] = \x->x
162 "foldr/app"     forall xs, ys. foldr (:) ys xs = append xs ys
163
164 "foldr/cons"    forall k,z,x,xs. foldr k z (x:xs) = k x (foldr k z xs)
165 "foldr/nil"     forall k,z.      foldr k z []     = z 
166  #-}
167 \end{code}
168
169
170 ----------------------------------------------
171 --              map     
172 ----------------------------------------------
173
174 \begin{code}
175 map :: (a -> b) -> [a] -> [b]
176 {-# INLINE map #-}
177 map f xs = build (\c n -> foldr (mapFB c f) n xs)
178
179 mapFB c f xs = c (f xs)
180
181 mapList :: (a -> b) -> [a] -> [b]
182 mapList _ []     = []
183 mapList f (x:xs) = f x : mapList f xs
184
185 {-# RULES
186 "mapFB"     forall c,f,g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
187 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
188  #-}
189 \end{code}
190
191
192 ----------------------------------------------
193 --              append  
194 ----------------------------------------------
195 \begin{code}
196 (++) :: [a] -> [a] -> [a]
197 {-# INLINE (++) #-}
198 xs ++ ys = augment (\c n -> foldr c n xs) ys
199
200 append :: [a] -> [a] -> [a]
201 append []     ys = ys
202 append (x:xs) ys = x : append xs ys
203 \end{code}
204
205
206 %*********************************************************
207 %*                                                      *
208 \subsection{Type @Bool@}
209 %*                                                      *
210 %*********************************************************
211
212 \begin{code}
213 data  Bool  =  False | True  deriving (Eq, Ord)
214         -- Read in PrelRead, Show in PrelShow
215
216 -- Boolean functions
217
218 (&&), (||)              :: Bool -> Bool -> Bool
219 True  && x              =  x
220 False && _              =  False
221 True  || _              =  True
222 False || x              =  x
223
224 not                     :: Bool -> Bool
225 not True                =  False
226 not False               =  True
227
228 otherwise               :: Bool
229 otherwise               =  True
230 \end{code}
231
232
233 %*********************************************************
234 %*                                                      *
235 \subsection{The @()@ type}
236 %*                                                      *
237 %*********************************************************
238
239 The Unit type is here because virtually any program needs it (whereas
240 some programs may get away without consulting PrelTup).  Furthermore,
241 the renamer currently *always* asks for () to be in scope, so that
242 ccalls can use () as their default type; so when compiling PrelBase we
243 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
244 it here seems more direct.
245
246 \begin{code}
247 data  ()  =  ()
248
249 instance Eq () where
250     () == () = True
251     () /= () = False
252
253 instance Ord () where
254     () <= () = True
255     () <  () = False
256     () >= () = True
257     () >  () = False
258     max () () = ()
259     min () () = ()
260     compare () () = EQ
261 \end{code}
262
263
264 %*********************************************************
265 %*                                                      *
266 \subsection{Type @Ordering@}
267 %*                                                      *
268 %*********************************************************
269
270 \begin{code}
271 data Ordering = LT | EQ | GT deriving (Eq, Ord)
272         -- Read in PrelRead, Show in PrelShow
273 \end{code}
274
275
276 %*********************************************************
277 %*                                                      *
278 \subsection{Type @Char@ and @String@}
279 %*                                                      *
280 %*********************************************************
281
282 \begin{code}
283 type  String = [Char]
284
285 data Char = C# Char#    deriving (Eq, Ord)
286
287 chr :: Int -> Char
288 chr (I# i) | i >=# 0# && i <=# 255# = C# (chr# i)
289            | otherwise = error ("Prelude.chr: bad argument")
290
291 unsafeChr :: Int -> Char
292 unsafeChr (I# i) =  C# (chr# i)
293
294 ord :: Char -> Int
295 ord (C# c) =  I# (ord# c)
296 \end{code}
297
298
299 %*********************************************************
300 %*                                                      *
301 \subsection{Type @Int@}
302 %*                                                      *
303 %*********************************************************
304
305 \begin{code}
306 data Int = I# Int#
307
308 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
309 zeroInt = I# 0#
310 oneInt  = I# 1#
311 twoInt  = I# 2#
312 minInt  = I# (-2147483648#)     -- GHC <= 2.09 had this at -2147483647
313 maxInt  = I# 2147483647#
314
315 instance Eq Int where
316     (==) x y = x `eqInt` y
317     (/=) x y = x `neInt` y
318
319 instance Ord Int where
320     compare x y = compareInt x y 
321
322     (<)  x y = ltInt x y
323     (<=) x y = leInt x y
324     (>=) x y = geInt x y
325     (>)  x y = gtInt x y
326
327 compareInt :: Int -> Int -> Ordering
328 (I# x) `compareInt` (I# y) | x <# y    = LT
329                            | x ==# y   = EQ
330                            | otherwise = GT
331 \end{code}
332
333
334 %*********************************************************
335 %*                                                      *
336 \subsection{Type @Integer@, @Float@, @Double@}
337 %*                                                      *
338 %*********************************************************
339
340 \begin{code}
341 data Float      = F# Float#
342 data Double     = D# Double#
343
344 data Integer    
345    = S# Int#                            -- small integers
346    | J# Int# ByteArray#                 -- large integers
347
348 instance  Eq Integer  where
349     (S# i)     ==  (S# j)     = i ==# j
350     (S# i)     ==  (J# s d)   = cmpIntegerInt# s d i ==# 0#
351     (J# s d)   ==  (S# i)     = cmpIntegerInt# s d i ==# 0#
352     (J# s1 d1) ==  (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) ==# 0#
353
354     (S# i)     /=  (S# j)     = i /=# j
355     (S# i)     /=  (J# s d)   = cmpIntegerInt# s d i /=# 0#
356     (J# s d)   /=  (S# i)     = cmpIntegerInt# s d i /=# 0#
357     (J# s1 d1) /=  (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) /=# 0#
358 \end{code}
359
360
361 %*********************************************************
362 %*                                                      *
363 \subsection{The function type}
364 %*                                                      *
365 %*********************************************************
366
367 \begin{code}
368 -- identity function
369 id                      :: a -> a
370 id x                    =  x
371
372 -- constant function
373 const                   :: a -> b -> a
374 const x _               =  x
375
376 -- function composition
377 {-# INLINE (.) #-}
378 (.)       :: (b -> c) -> (a -> b) -> a -> c
379 (.) f g x = f (g x)
380
381 -- flip f  takes its (first) two arguments in the reverse order of f.
382 flip                    :: (a -> b -> c) -> b -> a -> c
383 flip f x y              =  f y x
384
385 -- right-associating infix application operator (useful in continuation-
386 -- passing style)
387 ($)                     :: (a -> b) -> a -> b
388 f $ x                   =  f x
389
390 -- until p f  yields the result of applying f until p holds.
391 until                   :: (a -> Bool) -> (a -> a) -> a -> a
392 until p f x | p x       =  x
393             | otherwise =  until p f (f x)
394
395 -- asTypeOf is a type-restricted version of const.  It is usually used
396 -- as an infix operator, and its typing forces its first argument
397 -- (which is usually overloaded) to have the same type as the second.
398 asTypeOf                :: a -> a -> a
399 asTypeOf                =  const
400 \end{code}
401
402 %*********************************************************
403 %*                                                      *
404 \subsection{Numeric primops}
405 %*                                                      *
406 %*********************************************************
407
408 Definitions of the boxed PrimOps; these will be
409 used in the case of partial applications, etc.
410
411 \begin{code}
412 {-# INLINE eqInt #-}
413 {-# INLINE neInt #-}
414 {-# INLINE gtInt #-}
415 {-# INLINE geInt #-}
416 {-# INLINE ltInt #-}
417 {-# INLINE leInt #-}
418 {-# INLINE plusInt #-}
419 {-# INLINE minusInt #-}
420 {-# INLINE timesInt #-}
421 {-# INLINE quotInt #-}
422 {-# INLINE remInt #-}
423 {-# INLINE negateInt #-}
424
425 plusInt, minusInt, timesInt, quotInt, remInt :: Int -> Int -> Int
426 plusInt (I# x) (I# y) = I# (x +# y)
427 minusInt(I# x) (I# y) = I# (x -# y)
428 timesInt(I# x) (I# y) = I# (x *# y)
429 quotInt (I# x) (I# y) = I# (quotInt# x y)
430 remInt  (I# x) (I# y) = I# (remInt# x y)
431
432 negateInt :: Int -> Int
433 negateInt (I# x)      = I# (negateInt# x)
434
435 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
436 gtInt   (I# x) (I# y) = x ># y
437 geInt   (I# x) (I# y) = x >=# y
438 eqInt   (I# x) (I# y) = x ==# y
439 neInt   (I# x) (I# y) = x /=# y
440 ltInt   (I# x) (I# y) = x <# y
441 leInt   (I# x) (I# y) = x <=# y
442 \end{code}
443
444 Convenient boxed Integer PrimOps.  These are 'thin-air' Ids, so
445 it's nice to have them in PrelBase.
446
447 \begin{code}
448 {-# INLINE int2Integer #-}
449 {-# INLINE addr2Integer #-}
450 int2Integer :: Int# -> Integer
451 int2Integer  i = S# i
452 addr2Integer :: Addr# -> Integer
453 addr2Integer x = case addr2Integer# x of (# s, d #) -> J# s d
454 \end{code}