[project @ 1999-12-20 10:34:27 by simonpj]
[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 The overall structure of the GHC Prelude is a bit tricky.
8
9   a) We want to avoid "orphan modules", i.e. ones with instance
10         decls that don't belong either to a tycon or a class
11         defined in the same module
12
13   b) We want to avoid giant modules
14
15 So the rough structure is as follows, in (linearised) dependency order
16
17
18 PrelGHC         Has no implementation.  It defines built-in things, and
19                 by importing it you bring them into scope.
20                 The source file is PrelGHC.hi-boot, which is just
21                 copied to make PrelGHC.hi
22
23                 Classes: CCallable, CReturnable
24
25 PrelBase        Classes: Eq, Ord, Functor, Monad
26                 Types:   list, (), Int, Bool, Ordering, Char, String
27
28 PrelTup         Types: tuples, plus instances for PrelBase classes
29
30 PrelShow        Class: Show, plus instances for PrelBase/PrelTup types
31
32 PrelEnum        Class: Enum,  plus instances for PrelBase/PrelTup types
33
34 PrelMaybe       Type: Maybe, plus instances for PrelBase classes
35
36 PrelNum         Class: Num, plus instances for Int
37                 Type:  Integer, plus instances for all classes so far (Eq, Ord, Num, Show)
38
39                 Integer is needed here because it is mentioned in the signature
40                 of 'fromInteger' in class Num
41
42 PrelReal        Classes: Real, Integral, Fractional, RealFrac
43                          plus instances for Int, Integer
44                 Types:  Ratio, Rational
45                         plus intances for classes so far
46
47                 Rational is needed here because it is mentioned in the signature
48                 of 'toRational' in class Real
49
50 Ix              Classes: Ix, plus instances for Int, Bool, Char, Integer, Ordering, tuples
51
52 PrelArr         Types: Array, MutableArray, MutableVar
53
54                 Does *not* contain any ByteArray stuff (see PrelByteArr)
55                 Arrays are used by a function in PrelFloat
56
57 PrelFloat       Classes: Floating, RealFloat
58                 Types:   Float, Double, plus instances of all classes so far
59
60                 This module contains everything to do with floating point.
61                 It is a big module (900 lines)
62                 With a bit of luck, many modules can be compiled without ever reading PrelFloat.hi
63
64 PrelByteArr     Types: ByteArray, MutableByteArray
65                 
66                 We want this one to be after PrelFloat, because it defines arrays
67                 of unboxed floats.
68
69
70 Other Prelude modules are much easier with fewer complex dependencies.
71
72
73 \begin{code}
74 {-# OPTIONS -fno-implicit-prelude #-}
75
76 module PrelBase
77         (
78         module PrelBase,
79         module PrelGHC          -- Re-export PrelGHC, to avoid lots of people 
80                                 -- having to import it explicitly
81   ) 
82         where
83
84 import {-# SOURCE #-} PrelErr ( error )
85 import PrelGHC
86
87 infixr 9  .
88 infixr 5  ++, :
89 infix  4  ==, /=, <, <=, >=, >
90 infixr 3  &&
91 infixr 2  ||
92 infixl 1  >>, >>=
93 infixr 0  $
94
95 default ()              -- Double isn't available yet
96 \end{code}
97
98
99 %*********************************************************
100 %*                                                      *
101 \subsection{Standard classes @Eq@, @Ord@}
102 %*                                                      *
103 %*********************************************************
104
105 \begin{code}
106 class  Eq a  where
107     (==), (/=)          :: a -> a -> Bool
108
109     x /= y              =  not (x == y)
110     x == y              = not  (x /= y)
111
112 class  (Eq a) => Ord a  where
113     compare             :: a -> a -> Ordering
114     (<), (<=), (>=), (>):: a -> a -> Bool
115     max, min            :: a -> a -> a
116
117 -- An instance of Ord should define either compare or <=
118 -- Using compare can be more efficient for complex types.
119     compare x y
120             | x == y    = EQ
121             | x <= y    = LT    -- NB: must be '<=' not '<' to validate the
122                                 -- above claim about the minimal things that can
123                                 -- be defined for an instance of Ord
124             | otherwise = GT
125
126     x <= y  = case compare x y of { GT -> False; _other -> True }
127     x <  y  = case compare x y of { LT -> True;  _other -> False }
128     x >= y  = case compare x y of { LT -> False; _other -> True }
129     x >  y  = case compare x y of { GT -> True;  _other -> False }
130
131         -- These two default methods use '>' rather than compare
132         -- because the latter is often more expensive
133     max x y = if x > y then x else y
134     min x y = if x > y then y else x
135 \end{code}
136
137 %*********************************************************
138 %*                                                      *
139 \subsection{Monadic classes @Functor@, @Monad@ }
140 %*                                                      *
141 %*********************************************************
142
143 \begin{code}
144 class  Functor f  where
145     fmap         :: (a -> b) -> f a -> f b
146
147 class  Monad m  where
148     (>>=)       :: m a -> (a -> m b) -> m b
149     (>>)        :: m a -> m b -> m b
150     return      :: a -> m a
151     fail        :: String -> m a
152
153     m >> k      =  m >>= \_ -> k
154     fail s      = error s
155
156 \end{code}
157
158
159 %*********************************************************
160 %*                                                      *
161 \subsection{The list type}
162 %*                                                      *
163 %*********************************************************
164
165 \begin{code}
166 data [] a = [] | a : [a]  -- do explicitly: deriving (Eq, Ord)
167                           -- to avoid weird names like con2tag_[]#
168
169 instance (Eq a) => Eq [a]  where
170     {-# SPECIALISE instance Eq [Char] #-}
171     []     == []     = True     
172     (x:xs) == (y:ys) = x == y && xs == ys
173     _xs    == _ys    = False                    
174
175     xs     /= ys     = if (xs == ys) then False else True
176
177 instance (Ord a) => Ord [a] where
178     {-# SPECIALISE instance Ord [Char] #-}
179     a <  b  = case compare a b of { LT -> True;  EQ -> False; GT -> False }
180     a <= b  = case compare a b of { LT -> True;  EQ -> True;  GT -> False }
181     a >= b  = case compare a b of { LT -> False; EQ -> True;  GT -> True  }
182     a >  b  = case compare a b of { LT -> False; EQ -> False; GT -> True  }
183
184     compare []     []     = EQ
185     compare (_:_)  []     = GT
186     compare []     (_:_)  = LT
187     compare (x:xs) (y:ys) = case compare x y of
188                                  LT -> LT       
189                                  GT -> GT               
190                                  EQ -> compare xs ys
191
192 instance Functor [] where
193     fmap = map
194
195 instance  Monad []  where
196     m >>= k             = foldr ((++) . k) [] m
197     m >> k              = foldr ((++) . (\ _ -> k)) [] m
198     return x            = [x]
199     fail _              = []
200 \end{code}
201
202 A few list functions that appear here because they are used here.
203 The rest of the prelude list functions are in PrelList.
204
205 ----------------------------------------------
206 --      foldr/build/augment
207 ----------------------------------------------
208   
209 \begin{code}
210 foldr            :: (a -> b -> b) -> b -> [a] -> b
211 -- foldr _ z []     =  z
212 -- foldr f z (x:xs) =  f x (foldr f z xs)
213 {-# INLINE foldr #-}
214 foldr k z xs = go xs
215              where
216                go []     = z
217                go (x:xs) = x `k` go xs
218
219 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
220 {-# INLINE 2 build #-}
221         -- The INLINE is important, even though build is tiny,
222         -- because it prevents [] getting inlined in the version that
223         -- appears in the interface file.  If [] *is* inlined, it
224         -- won't match with [] appearing in rules in an importing module.
225         --
226         -- The "2" says to inline in phase 2
227
228 build g = g (:) []
229
230 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
231 {-# INLINE 2 augment #-}
232 augment g xs = g (:) xs
233
234 {-# RULES
235 "fold/build"    forall k z (g::forall b. (a->b->b) -> b -> b) . 
236                 foldr k z (build g) = g k z
237
238 "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . 
239                 foldr k z (augment g xs) = g k (foldr k z xs)
240
241 "foldr/id"      foldr (:) [] = \x->x
242 "foldr/app"     forall xs ys. foldr (:) ys xs = append xs ys
243
244 "foldr/cons"    forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
245 "foldr/nil"     forall k z.      foldr k z []     = z 
246  #-}
247 \end{code}
248
249
250 ----------------------------------------------
251 --              map     
252 ----------------------------------------------
253
254 \begin{code}
255 map :: (a -> b) -> [a] -> [b]
256 {-# INLINE map #-}
257 map f xs = build (\c n -> foldr (mapFB c f) n xs)
258
259 -- Note eta expanded
260 mapFB c f x ys = c (f x) ys
261
262 mapList :: (a -> b) -> [a] -> [b]
263 mapList _ []     = []
264 mapList f (x:xs) = f x : mapList f xs
265
266 {-# RULES
267 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
268 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
269  #-}
270 \end{code}
271
272
273 ----------------------------------------------
274 --              append  
275 ----------------------------------------------
276 \begin{code}
277 (++) :: [a] -> [a] -> [a]
278 {-# INLINE (++) #-}
279 xs ++ ys = augment (\c n -> foldr c n xs) ys
280
281 append :: [a] -> [a] -> [a]
282 append []     ys = ys
283 append (x:xs) ys = x : append xs ys
284 \end{code}
285
286
287 %*********************************************************
288 %*                                                      *
289 \subsection{Type @Bool@}
290 %*                                                      *
291 %*********************************************************
292
293 \begin{code}
294 data  Bool  =  False | True  deriving (Eq, Ord)
295         -- Read in PrelRead, Show in PrelShow
296
297 -- Boolean functions
298
299 (&&), (||)              :: Bool -> Bool -> Bool
300 True  && x              =  x
301 False && _              =  False
302 True  || _              =  True
303 False || x              =  x
304
305 not                     :: Bool -> Bool
306 not True                =  False
307 not False               =  True
308
309 otherwise               :: Bool
310 otherwise               =  True
311 \end{code}
312
313
314 %*********************************************************
315 %*                                                      *
316 \subsection{The @()@ type}
317 %*                                                      *
318 %*********************************************************
319
320 The Unit type is here because virtually any program needs it (whereas
321 some programs may get away without consulting PrelTup).  Furthermore,
322 the renamer currently *always* asks for () to be in scope, so that
323 ccalls can use () as their default type; so when compiling PrelBase we
324 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
325 it here seems more direct.)
326
327 \begin{code}
328 data  ()  =  ()
329
330 instance Eq () where
331     () == () = True
332     () /= () = False
333
334 instance Ord () where
335     () <= () = True
336     () <  () = False
337     () >= () = True
338     () >  () = False
339     max () () = ()
340     min () () = ()
341     compare () () = EQ
342 \end{code}
343
344
345 %*********************************************************
346 %*                                                      *
347 \subsection{Type @Ordering@}
348 %*                                                      *
349 %*********************************************************
350
351 \begin{code}
352 data Ordering = LT | EQ | GT deriving (Eq, Ord)
353         -- Read in PrelRead, Show in PrelShow
354 \end{code}
355
356
357 %*********************************************************
358 %*                                                      *
359 \subsection{Type @Char@ and @String@}
360 %*                                                      *
361 %*********************************************************
362
363 \begin{code}
364 type  String = [Char]
365
366 data Char = C# Char#
367
368 -- We don't use deriving for Eq and Ord, because for Ord the derived
369 -- instance defines only compare, which takes two primops.  Then
370 -- '>' uses compare, and therefore takes two primops instead of one.
371
372 instance Eq Char where
373   (C# c1) == (C# c2) = c1 `eqChar#` c2
374   (C# c1) /= (C# c2) = c1 `neChar#` c2
375
376 instance Ord Char where
377   (C# c1) >  (C# c2) = c1 `gtChar#` c2
378   (C# c1) >= (C# c2) = c1 `geChar#` c2
379   (C# c1) <= (C# c2) = c1 `leChar#` c2
380   (C# c1) <  (C# c2) = c1 `ltChar#` c2
381
382 chr :: Int -> Char
383 chr (I# i) | i >=# 0# && i <=# 255# = C# (chr# i)
384            | otherwise = error ("Prelude.chr: bad argument")
385
386 unsafeChr :: Int -> Char
387 unsafeChr (I# i) =  C# (chr# i)
388
389 ord :: Char -> Int
390 ord (C# c) =  I# (ord# c)
391 \end{code}
392
393
394 %*********************************************************
395 %*                                                      *
396 \subsection{Type @Int@}
397 %*                                                      *
398 %*********************************************************
399
400 \begin{code}
401 data Int = I# Int#
402
403 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
404 zeroInt = I# 0#
405 oneInt  = I# 1#
406 twoInt  = I# 2#
407 minInt  = I# (-2147483648#)     -- GHC <= 2.09 had this at -2147483647
408 maxInt  = I# 2147483647#
409
410 instance Eq Int where
411     (==) x y = x `eqInt` y
412     (/=) x y = x `neInt` y
413
414 instance Ord Int where
415     compare x y = compareInt x y 
416
417     (<)  x y = ltInt x y
418     (<=) x y = leInt x y
419     (>=) x y = geInt x y
420     (>)  x y = gtInt x y
421
422 compareInt :: Int -> Int -> Ordering
423 (I# x) `compareInt` (I# y) | x <# y    = LT
424                            | x ==# y   = EQ
425                            | otherwise = GT
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{CCallable instances}
473 %*                                                      *
474 %*********************************************************
475
476 Defined here to avoid orphans
477
478 \begin{code}
479 instance CCallable Char
480 instance CReturnable Char
481
482 instance CCallable   Int
483 instance CReturnable Int
484
485 -- DsCCall knows how to pass strings...
486 instance CCallable   [Char]
487
488 instance CReturnable () -- Why, exactly?
489 \end{code}
490
491
492 %*********************************************************
493 %*                                                      *
494 \subsection{Numeric primops}
495 %*                                                      *
496 %*********************************************************
497
498 Definitions of the boxed PrimOps; these will be
499 used in the case of partial applications, etc.
500
501 \begin{code}
502 {-# INLINE eqInt #-}
503 {-# INLINE neInt #-}
504 {-# INLINE gtInt #-}
505 {-# INLINE geInt #-}
506 {-# INLINE ltInt #-}
507 {-# INLINE leInt #-}
508 {-# INLINE plusInt #-}
509 {-# INLINE minusInt #-}
510 {-# INLINE timesInt #-}
511 {-# INLINE quotInt #-}
512 {-# INLINE remInt #-}
513 {-# INLINE negateInt #-}
514
515 plusInt, minusInt, timesInt, quotInt, remInt, gcdInt :: Int -> Int -> Int
516 plusInt (I# x) (I# y) = I# (x +# y)
517 minusInt(I# x) (I# y) = I# (x -# y)
518 timesInt(I# x) (I# y) = I# (x *# y)
519 quotInt (I# x) (I# y) = I# (quotInt# x y)
520 remInt  (I# x) (I# y) = I# (remInt# x y)
521 gcdInt (I# a)  (I# b) = I# (gcdInt# a b)
522
523 negateInt :: Int -> Int
524 negateInt (I# x)      = I# (negateInt# x)
525
526 divInt, modInt :: Int -> Int -> Int
527 x `divInt` y 
528   | x > zeroInt && y < zeroInt = quotInt ((x `minusInt` y) `minusInt` oneInt) y
529   | x < zeroInt && y > zeroInt = quotInt ((x `minusInt` y) `plusInt`  oneInt) y
530   | otherwise      = quotInt x y
531
532 x `modInt` y 
533   | x > zeroInt && y < zeroInt || 
534     x < zeroInt && y > zeroInt  = if r/=zeroInt then r `plusInt` y else zeroInt
535   | otherwise                   = r
536   where
537     r = remInt x y
538
539 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
540 gtInt   (I# x) (I# y) = x ># y
541 geInt   (I# x) (I# y) = x >=# y
542 eqInt   (I# x) (I# y) = x ==# y
543 neInt   (I# x) (I# y) = x /=# y
544 ltInt   (I# x) (I# y) = x <# y
545 leInt   (I# x) (I# y) = x <=# y
546 \end{code}
547