89b069444830c7787610c567950a98303bbc6d69
[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@}
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    -- NB: must be '<=' not '<' to validate the
54                                 -- above claim about the minimal things that can
55                                 -- be defined for an instance of Ord
56             | otherwise = GT
57
58     x <= y  = case compare x y of { GT -> False; _other -> True }
59     x <  y  = case compare x y of { LT -> True;  _other -> False }
60     x >= y  = case compare x y of { LT -> False; _other -> True }
61     x >  y  = case compare x y of { GT -> True;  _other -> False }
62
63         -- These two default methods use '>' rather than compare
64         -- because the latter is often more expensive
65     max x y = if x > y then x else y
66     min x y = if x > y then y else x
67 \end{code}
68
69 %*********************************************************
70 %*                                                      *
71 \subsection{Monadic classes @Functor@, @Monad@ }
72 %*                                                      *
73 %*********************************************************
74
75 \begin{code}
76 class  Functor f  where
77     fmap         :: (a -> b) -> f a -> f b
78
79 class  Monad m  where
80     (>>=)       :: m a -> (a -> m b) -> m b
81     (>>)        :: m a -> m b -> m b
82     return      :: a -> m a
83     fail        :: String -> m a
84
85     m >> k      =  m >>= \_ -> k
86     fail s      = error s
87
88 \end{code}
89
90
91 %*********************************************************
92 %*                                                      *
93 \subsection{The list type}
94 %*                                                      *
95 %*********************************************************
96
97 \begin{code}
98 data [] a = [] | a : [a]  -- do explicitly: deriving (Eq, Ord)
99                           -- to avoid weird names like con2tag_[]#
100
101 instance (Eq a) => Eq [a]  where
102     {-# SPECIALISE instance Eq [Char] #-}
103     []     == []     = True     
104     (x:xs) == (y:ys) = x == y && xs == ys
105     _xs    == _ys    = False                    
106
107     xs     /= ys     = if (xs == ys) then False else True
108
109 instance (Ord a) => Ord [a] where
110     {-# SPECIALISE instance Ord [Char] #-}
111     a <  b  = case compare a b of { LT -> True;  EQ -> False; GT -> False }
112     a <= b  = case compare a b of { LT -> True;  EQ -> True;  GT -> False }
113     a >= b  = case compare a b of { LT -> False; EQ -> True;  GT -> True  }
114     a >  b  = case compare a b of { LT -> False; EQ -> False; GT -> True  }
115
116     compare []     []     = EQ
117     compare (_:_)  []     = GT
118     compare []     (_:_)  = LT
119     compare (x:xs) (y:ys) = case compare x y of
120                                  LT -> LT       
121                                  GT -> GT               
122                                  EQ -> compare xs ys
123
124 instance Functor [] where
125     fmap = map
126
127 instance  Monad []  where
128     m >>= k             = foldr ((++) . k) [] m
129     m >> k              = foldr ((++) . (\ _ -> k)) [] m
130     return x            = [x]
131     fail _              = []
132 \end{code}
133
134 A few list functions that appear here because they are used here.
135 The rest of the prelude list functions are in PrelList.
136
137 ----------------------------------------------
138 --      foldr/build/augment
139 ----------------------------------------------
140   
141 \begin{code}
142 foldr            :: (a -> b -> b) -> b -> [a] -> b
143 -- foldr _ z []     =  z
144 -- foldr f z (x:xs) =  f x (foldr f z xs)
145 {-# INLINE foldr #-}
146 foldr k z xs = go xs
147              where
148                go []     = z
149                go (x:xs) = x `k` go xs
150
151 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
152 {-# INLINE 2 build #-}
153         -- The INLINE is important, even though build is tiny,
154         -- because it prevents [] getting inlined in the version that
155         -- appears in the interface file.  If [] *is* inlined, it
156         -- won't match with [] appearing in rules in an importing module.
157         --
158         -- The "2" says to inline in phase 2
159
160 build g = g (:) []
161
162 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
163 {-# INLINE 2 augment #-}
164 augment g xs = g (:) xs
165
166 {-# RULES
167 "fold/build"    forall k z (g::forall b. (a->b->b) -> b -> b) . 
168                 foldr k z (build g) = g k z
169
170 "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . 
171                 foldr k z (augment g xs) = g k (foldr k z xs)
172
173 "foldr/id"      foldr (:) [] = \x->x
174 "foldr/app"     forall xs ys. foldr (:) ys xs = append xs ys
175
176 "foldr/cons"    forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
177 "foldr/nil"     forall k z.      foldr k z []     = z 
178  #-}
179 \end{code}
180
181
182 ----------------------------------------------
183 --              map     
184 ----------------------------------------------
185
186 \begin{code}
187 map :: (a -> b) -> [a] -> [b]
188 {-# INLINE map #-}
189 map f xs = build (\c n -> foldr (mapFB c f) n xs)
190
191 -- Note eta expanded
192 mapFB c f x ys = c (f x) ys
193
194 mapList :: (a -> b) -> [a] -> [b]
195 mapList _ []     = []
196 mapList f (x:xs) = f x : mapList f xs
197
198 {-# RULES
199 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
200 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
201  #-}
202 \end{code}
203
204
205 ----------------------------------------------
206 --              append  
207 ----------------------------------------------
208 \begin{code}
209 (++) :: [a] -> [a] -> [a]
210 {-# INLINE (++) #-}
211 xs ++ ys = augment (\c n -> foldr c n xs) ys
212
213 append :: [a] -> [a] -> [a]
214 append []     ys = ys
215 append (x:xs) ys = x : append xs ys
216 \end{code}
217
218
219 %*********************************************************
220 %*                                                      *
221 \subsection{Type @Bool@}
222 %*                                                      *
223 %*********************************************************
224
225 \begin{code}
226 data  Bool  =  False | True  deriving (Eq, Ord)
227         -- Read in PrelRead, Show in PrelShow
228
229 -- Boolean functions
230
231 (&&), (||)              :: Bool -> Bool -> Bool
232 True  && x              =  x
233 False && _              =  False
234 True  || _              =  True
235 False || x              =  x
236
237 not                     :: Bool -> Bool
238 not True                =  False
239 not False               =  True
240
241 otherwise               :: Bool
242 otherwise               =  True
243 \end{code}
244
245
246 %*********************************************************
247 %*                                                      *
248 \subsection{The @()@ type}
249 %*                                                      *
250 %*********************************************************
251
252 The Unit type is here because virtually any program needs it (whereas
253 some programs may get away without consulting PrelTup).  Furthermore,
254 the renamer currently *always* asks for () to be in scope, so that
255 ccalls can use () as their default type; so when compiling PrelBase we
256 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
257 it here seems more direct.)
258
259 \begin{code}
260 data  ()  =  ()
261
262 instance Eq () where
263     () == () = True
264     () /= () = False
265
266 instance Ord () where
267     () <= () = True
268     () <  () = False
269     () >= () = True
270     () >  () = False
271     max () () = ()
272     min () () = ()
273     compare () () = EQ
274 \end{code}
275
276
277 %*********************************************************
278 %*                                                      *
279 \subsection{Type @Ordering@}
280 %*                                                      *
281 %*********************************************************
282
283 \begin{code}
284 data Ordering = LT | EQ | GT deriving (Eq, Ord)
285         -- Read in PrelRead, Show in PrelShow
286 \end{code}
287
288
289 %*********************************************************
290 %*                                                      *
291 \subsection{Type @Char@ and @String@}
292 %*                                                      *
293 %*********************************************************
294
295 \begin{code}
296 type  String = [Char]
297
298 data Char = C# Char#
299
300 -- We don't use deriving for Eq and Ord, because for Ord the derived
301 -- instance defines only compare, which takes two primops.  Then
302 -- '>' uses compare, and therefore takes two primops instead of one.
303
304 instance Eq Char where
305   (C# c1) == (C# c2) = c1 `eqChar#` c2
306   (C# c1) /= (C# c2) = c1 `neChar#` c2
307
308 instance Ord Char where
309   (C# c1) >  (C# c2) = c1 `gtChar#` c2
310   (C# c1) >= (C# c2) = c1 `geChar#` c2
311   (C# c1) <= (C# c2) = c1 `leChar#` c2
312   (C# c1) <  (C# c2) = c1 `ltChar#` c2
313
314 chr :: Int -> Char
315 chr (I# i) | i >=# 0# && i <=# 255# = C# (chr# i)
316            | otherwise = error ("Prelude.chr: bad argument")
317
318 unsafeChr :: Int -> Char
319 unsafeChr (I# i) =  C# (chr# i)
320
321 ord :: Char -> Int
322 ord (C# c) =  I# (ord# c)
323 \end{code}
324
325
326 %*********************************************************
327 %*                                                      *
328 \subsection{Type @Int@}
329 %*                                                      *
330 %*********************************************************
331
332 \begin{code}
333 data Int = I# Int#
334
335 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
336 zeroInt = I# 0#
337 oneInt  = I# 1#
338 twoInt  = I# 2#
339 minInt  = I# (-2147483648#)     -- GHC <= 2.09 had this at -2147483647
340 maxInt  = I# 2147483647#
341
342 instance Eq Int where
343     (==) x y = x `eqInt` y
344     (/=) x y = x `neInt` y
345
346 instance Ord Int where
347     compare x y = compareInt x y 
348
349     (<)  x y = ltInt x y
350     (<=) x y = leInt x y
351     (>=) x y = geInt x y
352     (>)  x y = gtInt x y
353
354 compareInt :: Int -> Int -> Ordering
355 (I# x) `compareInt` (I# y) | x <# y    = LT
356                            | x ==# y   = EQ
357                            | otherwise = GT
358 \end{code}
359
360
361 %*********************************************************
362 %*                                                      *
363 \subsection{Type @Integer@, @Float@, @Double@}
364 %*                                                      *
365 %*********************************************************
366
367 \begin{code}
368 data Float      = F# Float#
369 data Double     = D# Double#
370
371 data Integer    
372    = S# Int#                            -- small integers
373    | J# Int# ByteArray#                 -- large integers
374
375 instance  Eq Integer  where
376     (S# i)     ==  (S# j)     = i ==# j
377     (S# i)     ==  (J# s d)   = cmpIntegerInt# s d i ==# 0#
378     (J# s d)   ==  (S# i)     = cmpIntegerInt# s d i ==# 0#
379     (J# s1 d1) ==  (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) ==# 0#
380
381     (S# i)     /=  (S# j)     = i /=# j
382     (S# i)     /=  (J# s d)   = cmpIntegerInt# s d i /=# 0#
383     (J# s d)   /=  (S# i)     = cmpIntegerInt# s d i /=# 0#
384     (J# s1 d1) /=  (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) /=# 0#
385
386 instance  Ord Integer  where
387     (S# i)     <=  (S# j)     = i <=# j
388     (J# s d)   <=  (S# i)     = cmpIntegerInt# s d i <=# 0#
389     (S# i)     <=  (J# s d)   = cmpIntegerInt# s d i >=# 0#
390     (J# s1 d1) <=  (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) <=# 0#
391
392     (S# i)     >   (S# j)     = i ># j
393     (J# s d)   >   (S# i)     = cmpIntegerInt# s d i ># 0#
394     (S# i)     >   (J# s d)   = cmpIntegerInt# s d i <# 0#
395     (J# s1 d1) >   (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) ># 0#
396
397     (S# i)     <   (S# j)     = i <# j
398     (J# s d)   <   (S# i)     = cmpIntegerInt# s d i <# 0#
399     (S# i)     <   (J# s d)   = cmpIntegerInt# s d i ># 0#
400     (J# s1 d1) <   (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) <# 0#
401
402     (S# i)     >=  (S# j)     = i >=# j
403     (J# s d)   >=  (S# i)     = cmpIntegerInt# s d i >=# 0#
404     (S# i)     >=  (J# s d)   = cmpIntegerInt# s d i <=# 0#
405     (J# s1 d1) >=  (J# s2 d2) = (cmpInteger# s1 d1 s2 d2) >=# 0#
406
407     compare (S# i)  (S# j)
408        | i ==# j = EQ
409        | i <=# j = LT
410        | otherwise = GT
411     compare (J# s d) (S# i)
412        = case cmpIntegerInt# s d i of { res# ->
413          if res# <# 0# then LT else 
414          if res# ># 0# then GT else EQ
415          }
416     compare (S# i) (J# s d)
417        = case cmpIntegerInt# s d i of { res# ->
418          if res# ># 0# then LT else 
419          if res# <# 0# then GT else EQ
420          }
421     compare (J# s1 d1) (J# s2 d2)
422        = case cmpInteger# s1 d1 s2 d2 of { res# ->
423          if res# <# 0# then LT else 
424          if res# ># 0# then GT else EQ
425          }
426 \end{code}
427
428
429 %*********************************************************
430 %*                                                      *
431 \subsection{The function type}
432 %*                                                      *
433 %*********************************************************
434
435 \begin{code}
436 -- identity function
437 id                      :: a -> a
438 id x                    =  x
439
440 -- constant function
441 const                   :: a -> b -> a
442 const x _               =  x
443
444 -- function composition
445 {-# INLINE (.) #-}
446 (.)       :: (b -> c) -> (a -> b) -> a -> c
447 (.) f g x = f (g x)
448
449 -- flip f  takes its (first) two arguments in the reverse order of f.
450 flip                    :: (a -> b -> c) -> b -> a -> c
451 flip f x y              =  f y x
452
453 -- right-associating infix application operator (useful in continuation-
454 -- passing style)
455 ($)                     :: (a -> b) -> a -> b
456 f $ x                   =  f x
457
458 -- until p f  yields the result of applying f until p holds.
459 until                   :: (a -> Bool) -> (a -> a) -> a -> a
460 until p f x | p x       =  x
461             | otherwise =  until p f (f x)
462
463 -- asTypeOf is a type-restricted version of const.  It is usually used
464 -- as an infix operator, and its typing forces its first argument
465 -- (which is usually overloaded) to have the same type as the second.
466 asTypeOf                :: a -> a -> a
467 asTypeOf                =  const
468 \end{code}
469
470 %*********************************************************
471 %*                                                      *
472 \subsection{Numeric primops}
473 %*                                                      *
474 %*********************************************************
475
476 Definitions of the boxed PrimOps; these will be
477 used in the case of partial applications, etc.
478
479 \begin{code}
480 {-# INLINE eqInt #-}
481 {-# INLINE neInt #-}
482 {-# INLINE gtInt #-}
483 {-# INLINE geInt #-}
484 {-# INLINE ltInt #-}
485 {-# INLINE leInt #-}
486 {-# INLINE plusInt #-}
487 {-# INLINE minusInt #-}
488 {-# INLINE timesInt #-}
489 {-# INLINE quotInt #-}
490 {-# INLINE remInt #-}
491 {-# INLINE negateInt #-}
492
493 plusInt, minusInt, timesInt, quotInt, remInt :: Int -> Int -> Int
494 plusInt (I# x) (I# y) = I# (x +# y)
495 minusInt(I# x) (I# y) = I# (x -# y)
496 timesInt(I# x) (I# y) = I# (x *# y)
497 quotInt (I# x) (I# y) = I# (quotInt# x y)
498 remInt  (I# x) (I# y) = I# (remInt# x y)
499
500 negateInt :: Int -> Int
501 negateInt (I# x)      = I# (negateInt# x)
502
503 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
504 gtInt   (I# x) (I# y) = x ># y
505 geInt   (I# x) (I# y) = x >=# y
506 eqInt   (I# x) (I# y) = x ==# y
507 neInt   (I# x) (I# y) = x /=# y
508 ltInt   (I# x) (I# y) = x <# y
509 leInt   (I# x) (I# y) = x <=# y
510 \end{code}
511
512 Convenient boxed Integer PrimOps.  These are 'thin-air' Ids, so
513 it's nice to have them in PrelBase.
514
515 \begin{code}
516 {-# INLINE int2Integer #-}
517 {-# INLINE addr2Integer #-}
518 int2Integer :: Int# -> Integer
519 int2Integer  i = S# i
520 addr2Integer :: Addr# -> Integer
521 addr2Integer x = case addr2Integer# x of (# s, d #) -> J# s d
522 \end{code}