[project @ 2005-02-05 00:41:35 by ross]
[ghc-base.git] / GHC / Base.lhs
1 \section[GHC.Base]{Module @GHC.Base@}
2
3 The overall structure of the GHC Prelude is a bit tricky.
4
5   a) We want to avoid "orphan modules", i.e. ones with instance
6         decls that don't belong either to a tycon or a class
7         defined in the same module
8
9   b) We want to avoid giant modules
10
11 So the rough structure is as follows, in (linearised) dependency order
12
13
14 GHC.Prim                Has no implementation.  It defines built-in things, and
15                 by importing it you bring them into scope.
16                 The source file is GHC.Prim.hi-boot, which is just
17                 copied to make GHC.Prim.hi
18
19 GHC.Base        Classes: Eq, Ord, Functor, Monad
20                 Types:   list, (), Int, Bool, Ordering, Char, String
21
22 Data.Tup        Types: tuples, plus instances for GHC.Base classes
23
24 GHC.Show        Class: Show, plus instances for GHC.Base/GHC.Tup types
25
26 GHC.Enum        Class: Enum,  plus instances for GHC.Base/GHC.Tup types
27
28 Data.Maybe      Type: Maybe, plus instances for GHC.Base classes
29
30 GHC.Num         Class: Num, plus instances for Int
31                 Type:  Integer, plus instances for all classes so far (Eq, Ord, Num, Show)
32
33                 Integer is needed here because it is mentioned in the signature
34                 of 'fromInteger' in class Num
35
36 GHC.Real        Classes: Real, Integral, Fractional, RealFrac
37                          plus instances for Int, Integer
38                 Types:  Ratio, Rational
39                         plus intances for classes so far
40
41                 Rational is needed here because it is mentioned in the signature
42                 of 'toRational' in class Real
43
44 Ix              Classes: Ix, plus instances for Int, Bool, Char, Integer, Ordering, tuples
45
46 GHC.Arr         Types: Array, MutableArray, MutableVar
47
48                 Does *not* contain any ByteArray stuff (see GHC.ByteArr)
49                 Arrays are used by a function in GHC.Float
50
51 GHC.Float       Classes: Floating, RealFloat
52                 Types:   Float, Double, plus instances of all classes so far
53
54                 This module contains everything to do with floating point.
55                 It is a big module (900 lines)
56                 With a bit of luck, many modules can be compiled without ever reading GHC.Float.hi
57
58 GHC.ByteArr     Types: ByteArray, MutableByteArray
59                 
60                 We want this one to be after GHC.Float, because it defines arrays
61                 of unboxed floats.
62
63
64 Other Prelude modules are much easier with fewer complex dependencies.
65
66 \begin{code}
67 {-# OPTIONS_GHC -fno-implicit-prelude #-}
68 -----------------------------------------------------------------------------
69 -- |
70 -- Module      :  GHC.Base
71 -- Copyright   :  (c) The University of Glasgow, 1992-2002
72 -- License     :  see libraries/base/LICENSE
73 -- 
74 -- Maintainer  :  cvs-ghc@haskell.org
75 -- Stability   :  internal
76 -- Portability :  non-portable (GHC extensions)
77 --
78 -- Basic data types and classes.
79 -- 
80 -----------------------------------------------------------------------------
81
82 #include "MachDeps.h"
83
84 -- #hide
85 module GHC.Base
86         (
87         module GHC.Base,
88         module GHC.Prim,        -- Re-export GHC.Prim and GHC.Err, to avoid lots
89         module GHC.Err          -- of people having to import it explicitly
90   ) 
91         where
92
93 import GHC.Prim
94 import {-# SOURCE #-} GHC.Err
95
96 infixr 9  .
97 infixr 5  ++, :
98 infix  4  ==, /=, <, <=, >=, >
99 infixr 3  &&
100 infixr 2  ||
101 infixl 1  >>, >>=
102 infixr 0  $
103
104 default ()              -- Double isn't available yet
105 \end{code}
106
107
108 %*********************************************************
109 %*                                                      *
110 \subsection{DEBUGGING STUFF}
111 %*  (for use when compiling GHC.Base itself doesn't work)
112 %*                                                      *
113 %*********************************************************
114
115 \begin{code}
116 {-
117 data  Bool  =  False | True
118 data Ordering = LT | EQ | GT 
119 data Char = C# Char#
120 type  String = [Char]
121 data Int = I# Int#
122 data  ()  =  ()
123 data [] a = MkNil
124
125 not True = False
126 (&&) True True = True
127 otherwise = True
128
129 build = error "urk"
130 foldr = error "urk"
131
132 unpackCString# :: Addr# -> [Char]
133 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
134 unpackAppendCString# :: Addr# -> [Char] -> [Char]
135 unpackCStringUtf8# :: Addr# -> [Char]
136 unpackCString# a = error "urk"
137 unpackFoldrCString# a = error "urk"
138 unpackAppendCString# a = error "urk"
139 unpackCStringUtf8# a = error "urk"
140 -}
141 \end{code}
142
143
144 %*********************************************************
145 %*                                                      *
146 \subsection{Standard classes @Eq@, @Ord@}
147 %*                                                      *
148 %*********************************************************
149
150 \begin{code}
151
152 -- | The 'Eq' class defines equality ('==') and inequality ('/=').
153 -- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
154 -- and 'Eq' may be derived for any datatype whose constituents are also
155 -- instances of 'Eq'.
156 --
157 -- Minimal complete definition: either '==' or '/='.
158 --
159 class  Eq a  where
160     (==), (/=)           :: a -> a -> Bool
161
162     x /= y               = not (x == y)
163     x == y               = not (x /= y)
164
165 -- | The 'Ord' class is used for totally ordered datatypes.
166 --
167 -- Instances of 'Ord' can be derived for any user-defined
168 -- datatype whose constituent types are in 'Ord'.  The declared order
169 -- of the constructors in the data declaration determines the ordering
170 -- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
171 -- comparison to determine the precise ordering of two objects.
172 --
173 -- Minimal complete definition: either 'compare' or '<='.
174 -- Using 'compare' can be more efficient for complex types.
175 --
176 class  (Eq a) => Ord a  where
177     compare              :: a -> a -> Ordering
178     (<), (<=), (>), (>=) :: a -> a -> Bool
179     max, min             :: a -> a -> a
180
181     compare x y
182         | x == y    = EQ
183         | x <= y    = LT        -- NB: must be '<=' not '<' to validate the
184                                 -- above claim about the minimal things that
185                                 -- can be defined for an instance of Ord
186         | otherwise = GT
187
188     x <  y = case compare x y of { LT -> True;  _other -> False }
189     x <= y = case compare x y of { GT -> False; _other -> True }
190     x >  y = case compare x y of { GT -> True;  _other -> False }
191     x >= y = case compare x y of { LT -> False; _other -> True }
192
193         -- These two default methods use '<=' rather than 'compare'
194         -- because the latter is often more expensive
195     max x y = if x <= y then y else x
196     min x y = if x <= y then x else y
197 \end{code}
198
199 %*********************************************************
200 %*                                                      *
201 \subsection{Monadic classes @Functor@, @Monad@ }
202 %*                                                      *
203 %*********************************************************
204
205 \begin{code}
206 {- | The 'Functor' class is used for types that can be mapped over.
207 Instances of 'Functor' should satisfy the following laws:
208
209 > fmap id  ==  id
210 > fmap (f . g)  ==  fmap f . fmap g
211
212 The instances of 'Functor' for lists, 'Maybe' and 'IO' defined in the "Prelude"
213 satisfy these laws.
214 -}
215
216 class  Functor f  where
217     fmap        :: (a -> b) -> f a -> f b
218
219 {- | The 'Monad' class defines the basic operations over a /monad/.
220 Instances of 'Monad' should satisfy the following laws:
221
222 > return a >>= k  ==  k a
223 > m >>= return  ==  m
224 > m >>= (\x -> k x >>= h)  ==  (m >>= k) >>= h
225
226 Instances of both 'Monad' and 'Functor' should additionally satisfy the law:
227
228 > fmap f xs  ==  xs >>= return . f
229
230 The instances of 'Monad' for lists, 'Maybe' and 'IO' defined in the "Prelude"
231 satisfy these laws.
232 -}
233
234 class  Monad m  where
235     (>>=)       :: forall a b. m a -> (a -> m b) -> m b
236     (>>)        :: forall a b. m a -> m b -> m b
237         -- Explicit for-alls so that we know what order to
238         -- give type arguments when desugaring
239     return      :: a -> m a
240     fail        :: String -> m a
241
242     m >> k      = m >>= \_ -> k
243     fail s      = error s
244 \end{code}
245
246
247 %*********************************************************
248 %*                                                      *
249 \subsection{The list type}
250 %*                                                      *
251 %*********************************************************
252
253 \begin{code}
254 data [] a = [] | a : [a]  -- do explicitly: deriving (Eq, Ord)
255                           -- to avoid weird names like con2tag_[]#
256
257
258 instance (Eq a) => Eq [a] where
259     {-# SPECIALISE instance Eq [Char] #-}
260     []     == []     = True
261     (x:xs) == (y:ys) = x == y && xs == ys
262     _xs    == _ys    = False
263
264 instance (Ord a) => Ord [a] where
265     {-# SPECIALISE instance Ord [Char] #-}
266     compare []     []     = EQ
267     compare []     (_:_)  = LT
268     compare (_:_)  []     = GT
269     compare (x:xs) (y:ys) = case compare x y of
270                                 EQ    -> compare xs ys
271                                 other -> other
272
273 instance Functor [] where
274     fmap = map
275
276 instance  Monad []  where
277     m >>= k             = foldr ((++) . k) [] m
278     m >> k              = foldr ((++) . (\ _ -> k)) [] m
279     return x            = [x]
280     fail _              = []
281 \end{code}
282
283 A few list functions that appear here because they are used here.
284 The rest of the prelude list functions are in GHC.List.
285
286 ----------------------------------------------
287 --      foldr/build/augment
288 ----------------------------------------------
289   
290 \begin{code}
291 -- | 'foldr', applied to a binary operator, a starting value (typically
292 -- the right-identity of the operator), and a list, reduces the list
293 -- using the binary operator, from right to left:
294 --
295 -- > foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
296
297 foldr            :: (a -> b -> b) -> b -> [a] -> b
298 -- foldr _ z []     =  z
299 -- foldr f z (x:xs) =  f x (foldr f z xs)
300 {-# INLINE [0] foldr #-}
301 -- Inline only in the final stage, after the foldr/cons rule has had a chance
302 foldr k z xs = go xs
303              where
304                go []     = z
305                go (y:ys) = y `k` go ys
306
307 -- | A list producer that can be fused with 'foldr'.
308 -- This function is merely
309 --
310 -- >    build g = g (:) []
311 --
312 -- but GHC's simplifier will transform an expression of the form
313 -- @'foldr' k z ('build' g)@, which may arise after inlining, to @g k z@,
314 -- which avoids producing an intermediate list.
315
316 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
317 {-# INLINE [1] build #-}
318         -- The INLINE is important, even though build is tiny,
319         -- because it prevents [] getting inlined in the version that
320         -- appears in the interface file.  If [] *is* inlined, it
321         -- won't match with [] appearing in rules in an importing module.
322         --
323         -- The "1" says to inline in phase 1
324
325 build g = g (:) []
326
327 -- | A list producer that can be fused with 'foldr'.
328 -- This function is merely
329 --
330 -- >    augment g xs = g (:) xs
331 --
332 -- but GHC's simplifier will transform an expression of the form
333 -- @'foldr' k z ('augment' g xs)@, which may arise after inlining, to
334 -- @g k ('foldr' k z xs)@, which avoids producing an intermediate list.
335
336 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
337 {-# INLINE [1] augment #-}
338 augment g xs = g (:) xs
339
340 {-# RULES
341 "fold/build"    forall k z (g::forall b. (a->b->b) -> b -> b) . 
342                 foldr k z (build g) = g k z
343
344 "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . 
345                 foldr k z (augment g xs) = g k (foldr k z xs)
346
347 "foldr/id"                        foldr (:) [] = \x->x
348 "foldr/app"     [1] forall xs ys. foldr (:) ys xs = xs ++ ys
349         -- Only activate this from phase 1, because that's
350         -- when we disable the rule that expands (++) into foldr
351
352 -- The foldr/cons rule looks nice, but it can give disastrously
353 -- bloated code when commpiling
354 --      array (a,b) [(1,2), (2,2), (3,2), ...very long list... ]
355 -- i.e. when there are very very long literal lists
356 -- So I've disabled it for now. We could have special cases
357 -- for short lists, I suppose.
358 -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
359
360 "foldr/single"  forall k z x. foldr k z [x] = k x z
361 "foldr/nil"     forall k z.   foldr k z []  = z 
362
363 "augment/build" forall (g::forall b. (a->b->b) -> b -> b)
364                        (h::forall b. (a->b->b) -> b -> b) .
365                        augment g (build h) = build (\c n -> g c (h c n))
366 "augment/nil"   forall (g::forall b. (a->b->b) -> b -> b) .
367                         augment g [] = build g
368  #-}
369
370 -- This rule is true, but not (I think) useful:
371 --      augment g (augment h t) = augment (\cn -> g c (h c n)) t
372 \end{code}
373
374
375 ----------------------------------------------
376 --              map     
377 ----------------------------------------------
378
379 \begin{code}
380 -- | 'map' @f xs@ is the list obtained by applying @f@ to each element
381 -- of @xs@, i.e.,
382 --
383 -- > map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
384 -- > map f [x1, x2, ...] == [f x1, f x2, ...]
385
386 map :: (a -> b) -> [a] -> [b]
387 map _ []     = []
388 map f (x:xs) = f x : map f xs
389
390 -- Note eta expanded
391 mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
392 {-# INLINE [0] mapFB #-}
393 mapFB c f x ys = c (f x) ys
394
395 -- The rules for map work like this.
396 -- 
397 -- Up to (but not including) phase 1, we use the "map" rule to
398 -- rewrite all saturated applications of map with its build/fold 
399 -- form, hoping for fusion to happen.
400 -- In phase 1 and 0, we switch off that rule, inline build, and
401 -- switch on the "mapList" rule, which rewrites the foldr/mapFB
402 -- thing back into plain map.  
403 --
404 -- It's important that these two rules aren't both active at once 
405 -- (along with build's unfolding) else we'd get an infinite loop 
406 -- in the rules.  Hence the activation control below.
407 --
408 -- The "mapFB" rule optimises compositions of map.
409 --
410 -- This same pattern is followed by many other functions: 
411 -- e.g. append, filter, iterate, repeat, etc.
412
413 {-# RULES
414 "map"       [~1] forall f xs.   map f xs                = build (\c n -> foldr (mapFB c f) n xs)
415 "mapList"   [1]  forall f.      foldr (mapFB (:) f) []  = map f
416 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
417   #-}
418 \end{code}
419
420
421 ----------------------------------------------
422 --              append  
423 ----------------------------------------------
424 \begin{code}
425 -- | Append two lists, i.e.,
426 --
427 -- > [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn]
428 -- > [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
429 --
430 -- If the first list is not finite, the result is the first list.
431
432 (++) :: [a] -> [a] -> [a]
433 (++) []     ys = ys
434 (++) (x:xs) ys = x : xs ++ ys
435
436 {-# RULES
437 "++"    [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys
438   #-}
439
440 \end{code}
441
442
443 %*********************************************************
444 %*                                                      *
445 \subsection{Type @Bool@}
446 %*                                                      *
447 %*********************************************************
448
449 \begin{code}
450 -- |The 'Bool' type is an enumeration.  It is defined with 'False'
451 -- first so that the corresponding 'Prelude.Enum' instance will give
452 -- 'Prelude.fromEnum' 'False' the value zero, and
453 -- 'Prelude.fromEnum' 'True' the value 1.
454 data  Bool  =  False | True  deriving (Eq, Ord)
455         -- Read in GHC.Read, Show in GHC.Show
456
457 -- Boolean functions
458
459 -- | Boolean \"and\"
460 (&&)                    :: Bool -> Bool -> Bool
461 True  && x              =  x
462 False && _              =  False
463
464 -- | Boolean \"or\"
465 (||)                    :: Bool -> Bool -> Bool
466 True  || _              =  True
467 False || x              =  x
468
469 -- | Boolean \"not\"
470 not                     :: Bool -> Bool
471 not True                =  False
472 not False               =  True
473
474 -- |'otherwise' is defined as the value 'True'.  It helps to make
475 -- guards more readable.  eg.
476 --
477 -- >  f x | x < 0     = ...
478 -- >      | otherwise = ...
479 otherwise               :: Bool
480 otherwise               =  True
481 \end{code}
482
483
484 %*********************************************************
485 %*                                                      *
486 \subsection{The @()@ type}
487 %*                                                      *
488 %*********************************************************
489
490 The Unit type is here because virtually any program needs it (whereas
491 some programs may get away without consulting GHC.Tup).  Furthermore,
492 the renamer currently *always* asks for () to be in scope, so that
493 ccalls can use () as their default type; so when compiling GHC.Base we
494 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
495 it here seems more direct.)
496
497 \begin{code}
498 -- | The unit datatype @()@ has one non-undefined member, the nullary
499 -- constructor @()@.
500 data () = ()
501
502 instance Eq () where
503     () == () = True
504     () /= () = False
505
506 instance Ord () where
507     () <= () = True
508     () <  () = False
509     () >= () = True
510     () >  () = False
511     max () () = ()
512     min () () = ()
513     compare () () = EQ
514 \end{code}
515
516
517 %*********************************************************
518 %*                                                      *
519 \subsection{Type @Ordering@}
520 %*                                                      *
521 %*********************************************************
522
523 \begin{code}
524 -- | Represents an ordering relationship between two values: less
525 -- than, equal to, or greater than.  An 'Ordering' is returned by
526 -- 'compare'.
527 data Ordering = LT | EQ | GT deriving (Eq, Ord)
528         -- Read in GHC.Read, Show in GHC.Show
529 \end{code}
530
531
532 %*********************************************************
533 %*                                                      *
534 \subsection{Type @Char@ and @String@}
535 %*                                                      *
536 %*********************************************************
537
538 \begin{code}
539 -- | A 'String' is a list of characters.  String constants in Haskell are values
540 -- of type 'String'.
541 --
542 type String = [Char]
543
544 {-| The character type 'Char' is an enumeration whose values represent
545 Unicode (or equivalently ISO 10646) characters.
546 This set extends the ISO 8859-1 (Latin-1) character set
547 (the first 256 charachers), which is itself an extension of the ASCII
548 character set (the first 128 characters).
549 A character literal in Haskell has type 'Char'.
550
551 To convert a 'Char' to or from the corresponding 'Int' value defined
552 by Unicode, use 'Prelude.toEnum' and 'Prelude.fromEnum' from the
553 'Prelude.Enum' class respectively (or equivalently 'ord' and 'chr').
554 -}
555 data Char = C# Char#
556
557 -- We don't use deriving for Eq and Ord, because for Ord the derived
558 -- instance defines only compare, which takes two primops.  Then
559 -- '>' uses compare, and therefore takes two primops instead of one.
560
561 instance Eq Char where
562     (C# c1) == (C# c2) = c1 `eqChar#` c2
563     (C# c1) /= (C# c2) = c1 `neChar#` c2
564
565 instance Ord Char where
566     (C# c1) >  (C# c2) = c1 `gtChar#` c2
567     (C# c1) >= (C# c2) = c1 `geChar#` c2
568     (C# c1) <= (C# c2) = c1 `leChar#` c2
569     (C# c1) <  (C# c2) = c1 `ltChar#` c2
570
571 {-# RULES
572 "x# `eqChar#` x#" forall x#. x# `eqChar#` x# = True
573 "x# `neChar#` x#" forall x#. x# `neChar#` x# = False
574 "x# `gtChar#` x#" forall x#. x# `gtChar#` x# = False
575 "x# `geChar#` x#" forall x#. x# `geChar#` x# = True
576 "x# `leChar#` x#" forall x#. x# `leChar#` x# = True
577 "x# `ltChar#` x#" forall x#. x# `ltChar#` x# = False
578   #-}
579
580 -- | The 'Prelude.toEnum' method restricted to the type 'Data.Char.Char'.
581 chr :: Int -> Char
582 chr (I# i#) | int2Word# i# `leWord#` int2Word# 0x10FFFF# = C# (chr# i#)
583             | otherwise                                  = error "Prelude.chr: bad argument"
584
585 unsafeChr :: Int -> Char
586 unsafeChr (I# i#) = C# (chr# i#)
587
588 -- | The 'Prelude.fromEnum' method restricted to the type 'Data.Char.Char'.
589 ord :: Char -> Int
590 ord (C# c#) = I# (ord# c#)
591 \end{code}
592
593 String equality is used when desugaring pattern-matches against strings.
594
595 \begin{code}
596 eqString :: String -> String -> Bool
597 eqString []       []       = True
598 eqString (c1:cs1) (c2:cs2) = c1 == c2 && cs1 `eqString` cs2
599 eqString cs1      cs2      = False
600
601 {-# RULES "eqString" (==) = eqString #-}
602 \end{code}
603
604
605 %*********************************************************
606 %*                                                      *
607 \subsection{Type @Int@}
608 %*                                                      *
609 %*********************************************************
610
611 \begin{code}
612 data Int = I# Int#
613 -- ^A fixed-precision integer type with at least the range @[-2^29 .. 2^29-1]@.
614 -- The exact range for a given implementation can be determined by using
615 -- 'Prelude.minBound' and 'Prelude.maxBound' from the 'Prelude.Bounded' class.
616
617 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
618 zeroInt = I# 0#
619 oneInt  = I# 1#
620 twoInt  = I# 2#
621
622 {- Seems clumsy. Should perhaps put minInt and MaxInt directly into MachDeps.h -}
623 #if WORD_SIZE_IN_BITS == 31
624 minInt  = I# (-0x40000000#)
625 maxInt  = I# 0x3FFFFFFF#
626 #elif WORD_SIZE_IN_BITS == 32
627 minInt  = I# (-0x80000000#)
628 maxInt  = I# 0x7FFFFFFF#
629 #else 
630 minInt  = I# (-0x8000000000000000#)
631 maxInt  = I# 0x7FFFFFFFFFFFFFFF#
632 #endif
633
634 instance Eq Int where
635     (==) = eqInt
636     (/=) = neInt
637
638 instance Ord Int where
639     compare = compareInt
640     (<)     = ltInt
641     (<=)    = leInt
642     (>=)    = geInt
643     (>)     = gtInt
644
645 compareInt :: Int -> Int -> Ordering
646 (I# x#) `compareInt` (I# y#) = compareInt# x# y#
647
648 compareInt# :: Int# -> Int# -> Ordering
649 compareInt# x# y#
650     | x# <#  y# = LT
651     | x# ==# y# = EQ
652     | otherwise = GT
653 \end{code}
654
655
656 %*********************************************************
657 %*                                                      *
658 \subsection{The function type}
659 %*                                                      *
660 %*********************************************************
661
662 \begin{code}
663 -- | Identity function.
664 id                      :: a -> a
665 id x                    =  x
666
667 -- lazy function; this is just the same as id, but its unfolding
668 -- and strictness are over-ridden by the definition in MkId.lhs
669 -- That way, it does not get inlined, and the strictness analyser
670 -- sees it as lazy.  Then the worker/wrapper phase inlines it.
671 -- Result: happiness
672 lazy :: a -> a
673 lazy x = x
674
675 -- Assertion function.  This simply ignores its boolean argument.
676 -- The compiler may rewrite it to @('assertError' line)@.
677
678 -- | If the first argument evaluates to 'True', then the result is the
679 -- second argument.  Otherwise an 'AssertionFailed' exception is raised,
680 -- containing a 'String' with the source file and line number of the
681 -- call to 'assert'.
682 --
683 -- Assertions can normally be turned on or off with a compiler flag
684 -- (for GHC, assertions are normally on unless the @-fignore-asserts@
685 -- option is given).  When assertions are turned off, the first
686 -- argument to 'assert' is ignored, and the second argument is
687 -- returned as the result.
688
689 --      SLPJ: in 5.04 etc 'assert' is in GHC.Prim,
690 --      but from Template Haskell onwards it's simply
691 --      defined here in Base.lhs
692 assert :: Bool -> a -> a
693 assert pred r = r
694  
695 -- | Constant function.
696 const                   :: a -> b -> a
697 const x _               =  x
698
699 -- | Function composition.
700 {-# INLINE (.) #-}
701 (.)       :: (b -> c) -> (a -> b) -> a -> c
702 (.) f g x = f (g x)
703
704 -- | @'flip' f@ takes its (first) two arguments in the reverse order of @f@.
705 flip                    :: (a -> b -> c) -> b -> a -> c
706 flip f x y              =  f y x
707
708 -- | Application operator.  This operator is redundant, since ordinary
709 -- application @(f x)@ means the same as @(f '$' x)@. However, '$' has
710 -- low, right-associative binding precedence, so it sometimes allows
711 -- parentheses to be omitted; for example:
712 --
713 -- >     f $ g $ h x  =  f (g (h x))
714 --
715 -- It is also useful in higher-order situations, such as @'map' ('$' 0) xs@,
716 -- or @'Data.List.zipWith' ('$') fs xs@.
717 {-# INLINE ($) #-}
718 ($)                     :: (a -> b) -> a -> b
719 f $ x                   =  f x
720
721 -- | @'until' p f@ yields the result of applying @f@ until @p@ holds.
722 until                   :: (a -> Bool) -> (a -> a) -> a -> a
723 until p f x | p x       =  x
724             | otherwise =  until p f (f x)
725
726 -- | 'asTypeOf' is a type-restricted version of 'const'.  It is usually
727 -- used as an infix operator, and its typing forces its first argument
728 -- (which is usually overloaded) to have the same type as the second.
729 asTypeOf                :: a -> a -> a
730 asTypeOf                =  const
731 \end{code}
732
733 %*********************************************************
734 %*                                                      *
735 \subsection{Generics}
736 %*                                                      *
737 %*********************************************************
738
739 \begin{code}
740 data Unit = Unit
741 #ifndef __HADDOCK__
742 data (:+:) a b = Inl a | Inr b
743 data (:*:) a b = a :*: b
744 #endif
745 \end{code}
746
747 %*********************************************************
748 %*                                                      *
749 \subsection{@getTag@}
750 %*                                                      *
751 %*********************************************************
752
753 Returns the 'tag' of a constructor application; this function is used
754 by the deriving code for Eq, Ord and Enum.
755
756 The primitive dataToTag# requires an evaluated constructor application
757 as its argument, so we provide getTag as a wrapper that performs the
758 evaluation before calling dataToTag#.  We could have dataToTag#
759 evaluate its argument, but we prefer to do it this way because (a)
760 dataToTag# can be an inline primop if it doesn't need to do any
761 evaluation, and (b) we want to expose the evaluation to the
762 simplifier, because it might be possible to eliminate the evaluation
763 in the case when the argument is already known to be evaluated.
764
765 \begin{code}
766 {-# INLINE getTag #-}
767 getTag :: a -> Int#
768 getTag x = x `seq` dataToTag# x
769 \end{code}
770
771 %*********************************************************
772 %*                                                      *
773 \subsection{Numeric primops}
774 %*                                                      *
775 %*********************************************************
776
777 \begin{code}
778 divInt# :: Int# -> Int# -> Int#
779 x# `divInt#` y#
780         -- Be careful NOT to overflow if we do any additional arithmetic
781         -- on the arguments...  the following  previous version of this
782         -- code has problems with overflow:
783 --    | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
784 --    | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
785     | (x# ># 0#) && (y# <# 0#) = ((x# -# 1#) `quotInt#` y#) -# 1#
786     | (x# <# 0#) && (y# ># 0#) = ((x# +# 1#) `quotInt#` y#) -# 1#
787     | otherwise                = x# `quotInt#` y#
788
789 modInt# :: Int# -> Int# -> Int#
790 x# `modInt#` y#
791     | (x# ># 0#) && (y# <# 0#) ||
792       (x# <# 0#) && (y# ># 0#)    = if r# /=# 0# then r# +# y# else 0#
793     | otherwise                   = r#
794     where
795     r# = x# `remInt#` y#
796 \end{code}
797
798 Definitions of the boxed PrimOps; these will be
799 used in the case of partial applications, etc.
800
801 \begin{code}
802 {-# INLINE eqInt #-}
803 {-# INLINE neInt #-}
804 {-# INLINE gtInt #-}
805 {-# INLINE geInt #-}
806 {-# INLINE ltInt #-}
807 {-# INLINE leInt #-}
808 {-# INLINE plusInt #-}
809 {-# INLINE minusInt #-}
810 {-# INLINE timesInt #-}
811 {-# INLINE quotInt #-}
812 {-# INLINE remInt #-}
813 {-# INLINE negateInt #-}
814
815 plusInt, minusInt, timesInt, quotInt, remInt, divInt, modInt, gcdInt :: Int -> Int -> Int
816 (I# x) `plusInt`  (I# y) = I# (x +# y)
817 (I# x) `minusInt` (I# y) = I# (x -# y)
818 (I# x) `timesInt` (I# y) = I# (x *# y)
819 (I# x) `quotInt`  (I# y) = I# (x `quotInt#` y)
820 (I# x) `remInt`   (I# y) = I# (x `remInt#`  y)
821 (I# x) `divInt`   (I# y) = I# (x `divInt#`  y)
822 (I# x) `modInt`   (I# y) = I# (x `modInt#`  y)
823
824 {-# RULES
825 "x# +# 0#" forall x#. x# +# 0# = x#
826 "0# +# x#" forall x#. 0# +# x# = x#
827 "x# -# 0#" forall x#. x# -# 0# = x#
828 "x# -# x#" forall x#. x# -# x# = 0#
829 "x# *# 0#" forall x#. x# *# 0# = 0#
830 "0# *# x#" forall x#. 0# *# x# = 0#
831 "x# *# 1#" forall x#. x# *# 1# = x#
832 "1# *# x#" forall x#. 1# *# x# = x#
833   #-}
834
835 gcdInt (I# a) (I# b) = g a b
836    where g 0# 0# = error "GHC.Base.gcdInt: gcd 0 0 is undefined"
837          g 0# _  = I# absB
838          g _  0# = I# absA
839          g _  _  = I# (gcdInt# absA absB)
840
841          absInt x = if x <# 0# then negateInt# x else x
842
843          absA     = absInt a
844          absB     = absInt b
845
846 negateInt :: Int -> Int
847 negateInt (I# x) = I# (negateInt# x)
848
849 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
850 (I# x) `gtInt` (I# y) = x >#  y
851 (I# x) `geInt` (I# y) = x >=# y
852 (I# x) `eqInt` (I# y) = x ==# y
853 (I# x) `neInt` (I# y) = x /=# y
854 (I# x) `ltInt` (I# y) = x <#  y
855 (I# x) `leInt` (I# y) = x <=# y
856
857 {-# RULES
858 "x# ># x#"  forall x#. x# >#  x# = False
859 "x# >=# x#" forall x#. x# >=# x# = True
860 "x# ==# x#" forall x#. x# ==# x# = True
861 "x# /=# x#" forall x#. x# /=# x# = False
862 "x# <# x#"  forall x#. x# <#  x# = False
863 "x# <=# x#" forall x#. x# <=# x# = True
864   #-}
865
866 {-# RULES
867 "plusFloat x 0.0"   forall x#. plusFloat#  x#   0.0# = x#
868 "plusFloat 0.0 x"   forall x#. plusFloat#  0.0# x#   = x#
869 "minusFloat x 0.0"  forall x#. minusFloat# x#   0.0# = x#
870 "minusFloat x x"    forall x#. minusFloat# x#   x#   = 0.0#
871 "timesFloat x 0.0"  forall x#. timesFloat# x#   0.0# = 0.0#
872 "timesFloat0.0 x"   forall x#. timesFloat# 0.0# x#   = 0.0#
873 "timesFloat x 1.0"  forall x#. timesFloat# x#   1.0# = x#
874 "timesFloat 1.0 x"  forall x#. timesFloat# 1.0# x#   = x#
875 "divideFloat x 1.0" forall x#. divideFloat# x#  1.0# = x#
876   #-}
877
878 {-# RULES
879 "plusDouble x 0.0"   forall x#. (+##) x#    0.0## = x#
880 "plusDouble 0.0 x"   forall x#. (+##) 0.0## x#    = x#
881 "minusDouble x 0.0"  forall x#. (-##) x#    0.0## = x#
882 "minusDouble x x"    forall x#. (-##) x#    x#    = 0.0##
883 "timesDouble x 0.0"  forall x#. (*##) x#    0.0## = 0.0##
884 "timesDouble 0.0 x"  forall x#. (*##) 0.0## x#    = 0.0##
885 "timesDouble x 1.0"  forall x#. (*##) x#    1.0## = x#
886 "timesDouble 1.0 x"  forall x#. (*##) 1.0## x#    = x#
887 "divideDouble x 1.0" forall x#. (/##) x#    1.0## = x#
888   #-}
889
890 -- Wrappers for the shift operations.  The uncheckedShift# family are
891 -- undefined when the amount being shifted by is greater than the size
892 -- in bits of Int#, so these wrappers perform a check and return
893 -- either zero or -1 appropriately.
894 --
895 -- Note that these wrappers still produce undefined results when the
896 -- second argument (the shift amount) is negative.
897
898 -- | Shift the argument left by the specified number of bits
899 -- (which must be non-negative).
900 shiftL# :: Word# -> Int# -> Word#
901 a `shiftL#` b   | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
902                 | otherwise                = a `uncheckedShiftL#` b
903
904 -- | Shift the argument right by the specified number of bits
905 -- (which must be non-negative).
906 shiftRL# :: Word# -> Int# -> Word#
907 a `shiftRL#` b  | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
908                 | otherwise                = a `uncheckedShiftRL#` b
909
910 -- | Shift the argument left by the specified number of bits
911 -- (which must be non-negative).
912 iShiftL# :: Int# -> Int# -> Int#
913 a `iShiftL#` b  | b >=# WORD_SIZE_IN_BITS# = 0#
914                 | otherwise                = a `uncheckedIShiftL#` b
915
916 -- | Shift the argument right (signed) by the specified number of bits
917 -- (which must be non-negative).
918 iShiftRA# :: Int# -> Int# -> Int#
919 a `iShiftRA#` b | b >=# WORD_SIZE_IN_BITS# = if a <# 0# then (-1#) else 0#
920                 | otherwise                = a `uncheckedIShiftRA#` b
921
922 -- | Shift the argument right (unsigned) by the specified number of bits
923 -- (which must be non-negative).
924 iShiftRL# :: Int# -> Int# -> Int#
925 a `iShiftRL#` b | b >=# WORD_SIZE_IN_BITS# = 0#
926                 | otherwise                = a `uncheckedIShiftRL#` b
927
928 #if WORD_SIZE_IN_BITS == 32
929 {-# RULES
930 "narrow32Int#"  forall x#. narrow32Int#   x# = x#
931 "narrow32Word#" forall x#. narrow32Word#   x# = x#
932    #-}
933 #endif
934
935 {-# RULES
936 "int2Word2Int"  forall x#. int2Word# (word2Int# x#) = x#
937 "word2Int2Word" forall x#. word2Int# (int2Word# x#) = x#
938   #-}
939 \end{code}
940
941
942 %********************************************************
943 %*                                                      *
944 \subsection{Unpacking C strings}
945 %*                                                      *
946 %********************************************************
947
948 This code is needed for virtually all programs, since it's used for
949 unpacking the strings of error messages.
950
951 \begin{code}
952 unpackCString# :: Addr# -> [Char]
953 {-# NOINLINE [1] unpackCString# #-}
954 unpackCString# addr 
955   = unpack 0#
956   where
957     unpack nh
958       | ch `eqChar#` '\0'# = []
959       | otherwise          = C# ch : unpack (nh +# 1#)
960       where
961         ch = indexCharOffAddr# addr nh
962
963 unpackAppendCString# :: Addr# -> [Char] -> [Char]
964 unpackAppendCString# addr rest
965   = unpack 0#
966   where
967     unpack nh
968       | ch `eqChar#` '\0'# = rest
969       | otherwise          = C# ch : unpack (nh +# 1#)
970       where
971         ch = indexCharOffAddr# addr nh
972
973 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
974 {-# NOINLINE [0] unpackFoldrCString# #-}
975 -- Don't inline till right at the end;
976 -- usually the unpack-list rule turns it into unpackCStringList
977 unpackFoldrCString# addr f z 
978   = unpack 0#
979   where
980     unpack nh
981       | ch `eqChar#` '\0'# = z
982       | otherwise          = C# ch `f` unpack (nh +# 1#)
983       where
984         ch = indexCharOffAddr# addr nh
985
986 unpackCStringUtf8# :: Addr# -> [Char]
987 unpackCStringUtf8# addr 
988   = unpack 0#
989   where
990     unpack nh
991       | ch `eqChar#` '\0'#   = []
992       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
993       | ch `leChar#` '\xDF'# =
994           C# (chr# (((ord# ch                                  -# 0xC0#) `uncheckedIShiftL#`  6#) +#
995                      (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
996           unpack (nh +# 2#)
997       | ch `leChar#` '\xEF'# =
998           C# (chr# (((ord# ch                                  -# 0xE0#) `uncheckedIShiftL#` 12#) +#
999                     ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#`  6#) +#
1000                      (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
1001           unpack (nh +# 3#)
1002       | otherwise            =
1003           C# (chr# (((ord# ch                                  -# 0xF0#) `uncheckedIShiftL#` 18#) +#
1004                     ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +#
1005                     ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#`  6#) +#
1006                      (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
1007           unpack (nh +# 4#)
1008       where
1009         ch = indexCharOffAddr# addr nh
1010
1011 unpackNBytes# :: Addr# -> Int# -> [Char]
1012 unpackNBytes# _addr 0#   = []
1013 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
1014     where
1015      unpack acc i#
1016       | i# <# 0#  = acc
1017       | otherwise = 
1018          case indexCharOffAddr# addr i# of
1019             ch -> unpack (C# ch : acc) (i# -# 1#)
1020
1021 {-# RULES
1022 "unpack"       [~1] forall a   . unpackCString# a                  = build (unpackFoldrCString# a)
1023 "unpack-list"  [1]  forall a   . unpackFoldrCString# a (:) [] = unpackCString# a
1024 "unpack-append"     forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
1025
1026 -- There's a built-in rule (in PrelRules.lhs) for
1027 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
1028
1029   #-}
1030 \end{code}
1031
1032 #ifdef __HADDOCK__
1033 \begin{code}
1034 -- | A special argument for the 'Control.Monad.ST.ST' type constructor,
1035 -- indexing a state embedded in the 'Prelude.IO' monad by
1036 -- 'Control.Monad.ST.stToIO'.
1037 data RealWorld
1038 \end{code}
1039 #endif