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