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