[project @ 2000-03-22 12:01:57 by rrt]
[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 "augment/build" forall (g::forall b. (a->b->b) -> b -> b)
248                        (h::forall b. (a->b->b) -> b -> b) .
249                        augment g (build h) = build (\c n -> g c (h c n))
250 "augment/nil"   forall (g::forall b. (a->b->b) -> b -> b) .
251                         augment g [] = build g
252  #-}
253
254 -- This rule is true, but not (I think) useful:
255 --      augment g (augment h t) = augment (\cn -> g c (h c n)) t
256 \end{code}
257
258
259 ----------------------------------------------
260 --              map     
261 ----------------------------------------------
262
263 \begin{code}
264 map :: (a -> b) -> [a] -> [b]
265 {-# INLINE map #-}
266 map f xs = build (\c n -> foldr (mapFB c f) n xs)
267
268 -- Note eta expanded
269 mapFB c f x ys = c (f x) ys
270
271 mapList :: (a -> b) -> [a] -> [b]
272 mapList _ []     = []
273 mapList f (x:xs) = f x : mapList f xs
274
275 {-# RULES
276 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
277 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
278  #-}
279 \end{code}
280
281
282 ----------------------------------------------
283 --              append  
284 ----------------------------------------------
285 \begin{code}
286 (++) :: [a] -> [a] -> [a]
287 {-# INLINE (++) #-}
288 xs ++ ys = augment (\c n -> foldr c n xs) ys
289
290 append :: [a] -> [a] -> [a]
291 append []     ys = ys
292 append (x:xs) ys = x : append xs ys
293 \end{code}
294
295
296 %*********************************************************
297 %*                                                      *
298 \subsection{Type @Bool@}
299 %*                                                      *
300 %*********************************************************
301
302 \begin{code}
303 data  Bool  =  False | True  deriving (Eq, Ord)
304         -- Read in PrelRead, Show in PrelShow
305
306 -- Boolean functions
307
308 (&&), (||)              :: Bool -> Bool -> Bool
309 True  && x              =  x
310 False && _              =  False
311 True  || _              =  True
312 False || x              =  x
313
314 not                     :: Bool -> Bool
315 not True                =  False
316 not False               =  True
317
318 otherwise               :: Bool
319 otherwise               =  True
320 \end{code}
321
322
323 %*********************************************************
324 %*                                                      *
325 \subsection{The @()@ type}
326 %*                                                      *
327 %*********************************************************
328
329 The Unit type is here because virtually any program needs it (whereas
330 some programs may get away without consulting PrelTup).  Furthermore,
331 the renamer currently *always* asks for () to be in scope, so that
332 ccalls can use () as their default type; so when compiling PrelBase we
333 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
334 it here seems more direct.)
335
336 \begin{code}
337 data  ()  =  ()
338
339 instance Eq () where
340     () == () = True
341     () /= () = False
342
343 instance Ord () where
344     () <= () = True
345     () <  () = False
346     () >= () = True
347     () >  () = False
348     max () () = ()
349     min () () = ()
350     compare () () = EQ
351 \end{code}
352
353
354 %*********************************************************
355 %*                                                      *
356 \subsection{Type @Ordering@}
357 %*                                                      *
358 %*********************************************************
359
360 \begin{code}
361 data Ordering = LT | EQ | GT deriving (Eq, Ord)
362         -- Read in PrelRead, Show in PrelShow
363 \end{code}
364
365
366 %*********************************************************
367 %*                                                      *
368 \subsection{Type @Char@ and @String@}
369 %*                                                      *
370 %*********************************************************
371
372 \begin{code}
373 type  String = [Char]
374
375 data Char = C# Char#
376
377 -- We don't use deriving for Eq and Ord, because for Ord the derived
378 -- instance defines only compare, which takes two primops.  Then
379 -- '>' uses compare, and therefore takes two primops instead of one.
380
381 instance Eq Char where
382   (C# c1) == (C# c2) = c1 `eqChar#` c2
383   (C# c1) /= (C# c2) = c1 `neChar#` c2
384
385 instance Ord Char where
386   (C# c1) >  (C# c2) = c1 `gtChar#` c2
387   (C# c1) >= (C# c2) = c1 `geChar#` c2
388   (C# c1) <= (C# c2) = c1 `leChar#` c2
389   (C# c1) <  (C# c2) = c1 `ltChar#` c2
390
391 chr :: Int -> Char
392 chr (I# i) | i >=# 0# && i <=# 255# = C# (chr# i)
393            | otherwise = error ("Prelude.chr: bad argument")
394
395 unsafeChr :: Int -> Char
396 unsafeChr (I# i) =  C# (chr# i)
397
398 ord :: Char -> Int
399 ord (C# c) =  I# (ord# c)
400 \end{code}
401
402
403 %*********************************************************
404 %*                                                      *
405 \subsection{Type @Int@}
406 %*                                                      *
407 %*********************************************************
408
409 \begin{code}
410 data Int = I# Int#
411
412 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
413 zeroInt = I# 0#
414 oneInt  = I# 1#
415 twoInt  = I# 2#
416 minInt  = I# (-2147483648#)     -- GHC <= 2.09 had this at -2147483647
417 maxInt  = I# 2147483647#
418
419 instance Eq Int where
420     (==) x y = x `eqInt` y
421     (/=) x y = x `neInt` y
422
423 instance Ord Int where
424     compare x y = compareInt x y 
425
426     (<)  x y = ltInt x y
427     (<=) x y = leInt x y
428     (>=) x y = geInt x y
429     (>)  x y = gtInt x y
430
431 compareInt :: Int -> Int -> Ordering
432 (I# x) `compareInt` (I# y) | x <# y    = LT
433                            | x ==# y   = EQ
434                            | otherwise = GT
435 \end{code}
436
437
438 %*********************************************************
439 %*                                                      *
440 \subsection{The function type}
441 %*                                                      *
442 %*********************************************************
443
444 \begin{code}
445 -- identity function
446 id                      :: a -> a
447 id x                    =  x
448
449 -- constant function
450 const                   :: a -> b -> a
451 const x _               =  x
452
453 -- function composition
454 {-# INLINE (.) #-}
455 (.)       :: (b -> c) -> (a -> b) -> a -> c
456 (.) f g x = f (g x)
457
458 -- flip f  takes its (first) two arguments in the reverse order of f.
459 flip                    :: (a -> b -> c) -> b -> a -> c
460 flip f x y              =  f y x
461
462 -- right-associating infix application operator (useful in continuation-
463 -- passing style)
464 ($)                     :: (a -> b) -> a -> b
465 f $ x                   =  f x
466
467 -- until p f  yields the result of applying f until p holds.
468 until                   :: (a -> Bool) -> (a -> a) -> a -> a
469 until p f x | p x       =  x
470             | otherwise =  until p f (f x)
471
472 -- asTypeOf is a type-restricted version of const.  It is usually used
473 -- as an infix operator, and its typing forces its first argument
474 -- (which is usually overloaded) to have the same type as the second.
475 asTypeOf                :: a -> a -> a
476 asTypeOf                =  const
477 \end{code}
478
479 %*********************************************************
480 %*                                                      *
481 \subsection{CCallable instances}
482 %*                                                      *
483 %*********************************************************
484
485 Defined here to avoid orphans
486
487 \begin{code}
488 instance CCallable Char
489 instance CReturnable Char
490
491 instance CCallable   Int
492 instance CReturnable Int
493
494 -- DsCCall knows how to pass strings...
495 instance CCallable   [Char]
496
497 instance CReturnable () -- Why, exactly?
498 \end{code}
499
500
501 %*********************************************************
502 %*                                                      *
503 \subsection{Numeric primops}
504 %*                                                      *
505 %*********************************************************
506
507 Definitions of the boxed PrimOps; these will be
508 used in the case of partial applications, etc.
509
510 \begin{code}
511 {-# INLINE eqInt #-}
512 {-# INLINE neInt #-}
513 {-# INLINE gtInt #-}
514 {-# INLINE geInt #-}
515 {-# INLINE ltInt #-}
516 {-# INLINE leInt #-}
517 {-# INLINE plusInt #-}
518 {-# INLINE minusInt #-}
519 {-# INLINE timesInt #-}
520 {-# INLINE quotInt #-}
521 {-# INLINE remInt #-}
522 {-# INLINE negateInt #-}
523
524 plusInt, minusInt, timesInt, quotInt, remInt, gcdInt :: Int -> Int -> Int
525 plusInt (I# x) (I# y) = I# (x +# y)
526 minusInt(I# x) (I# y) = I# (x -# y)
527 timesInt(I# x) (I# y) = I# (x *# y)
528 quotInt (I# x) (I# y) = I# (quotInt# x y)
529 remInt  (I# x) (I# y) = I# (remInt# x y)
530 gcdInt (I# a)  (I# b) = I# (gcdInt# a b)
531
532 negateInt :: Int -> Int
533 negateInt (I# x)      = I# (negateInt# x)
534
535 divInt, modInt :: Int -> Int -> Int
536 x `divInt` y 
537   | x > zeroInt && y < zeroInt = quotInt ((x `minusInt` y) `minusInt` oneInt) y
538   | x < zeroInt && y > zeroInt = quotInt ((x `minusInt` y) `plusInt`  oneInt) y
539   | otherwise      = quotInt x y
540
541 x `modInt` y 
542   | x > zeroInt && y < zeroInt || 
543     x < zeroInt && y > zeroInt  = if r/=zeroInt then r `plusInt` y else zeroInt
544   | otherwise                   = r
545   where
546     r = remInt x y
547
548 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
549 gtInt   (I# x) (I# y) = x ># y
550 geInt   (I# x) (I# y) = x >=# y
551 eqInt   (I# x) (I# y) = x ==# y
552 neInt   (I# x) (I# y) = x /=# y
553 ltInt   (I# x) (I# y) = x <# y
554 leInt   (I# x) (I# y) = x <=# y
555 \end{code}
556
557
558 %********************************************************
559 %*                                                      *
560 \subsection{Unpacking C strings}
561 %*                                                      *
562 %********************************************************
563
564 This code is needed for virtually all programs, since it's used for
565 unpacking the strings of error messages.
566
567 \begin{code}
568 unpackCString#  :: Addr# -> [Char]
569 {-# INLINE unpackCString# #-}
570 unpackCString# a = build (unpackFoldrCString# a)
571
572 unpackCStringList#  :: Addr# -> [Char]
573 unpackCStringList# addr 
574   = unpack 0#
575   where
576     unpack nh
577       | ch `eqChar#` '\0'# = []
578       | otherwise          = C# ch : unpack (nh +# 1#)
579       where
580         ch = indexCharOffAddr# addr nh
581
582 unpackAppendCString# :: Addr# -> [Char] -> [Char]
583 unpackAppendCString# addr rest
584   = unpack 0#
585   where
586     unpack nh
587       | ch `eqChar#` '\0'# = rest
588       | otherwise          = C# ch : unpack (nh +# 1#)
589       where
590         ch = indexCharOffAddr# addr nh
591
592 unpackFoldrCString#  :: Addr# -> (Char  -> a -> a) -> a -> a 
593 unpackFoldrCString# addr f z 
594   = unpack 0#
595   where
596     unpack nh
597       | ch `eqChar#` '\0'# = z
598       | otherwise          = C# ch `f` unpack (nh +# 1#)
599       where
600         ch = indexCharOffAddr# addr nh
601
602 unpackNBytes#      :: Addr# -> Int#   -> [Char]
603   -- This one is called by the compiler to unpack literal 
604   -- strings with NULs in them; rare. It's strict!
605   -- We don't try to do list deforestation for this one
606
607 unpackNBytes# _addr 0#   = []
608 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
609     where
610      unpack acc i#
611       | i# <# 0#  = acc
612       | otherwise = 
613          case indexCharOffAddr# addr i# of
614             ch -> unpack (C# ch : acc) (i# -# 1#)
615
616 {-# RULES
617 "unpack-list"    forall a   . unpackFoldrCString# a (:) [] = unpackCStringList# a
618 "unpack-append"  forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
619
620 -- There's a built-in rule (in PrelRules.lhs) for
621 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
622
623   #-}
624 \end{code}