[project @ 2005-01-11 16:04:08 by simonmar]
[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 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
307 {-# INLINE [1] build #-}
308         -- The INLINE is important, even though build is tiny,
309         -- because it prevents [] getting inlined in the version that
310         -- appears in the interface file.  If [] *is* inlined, it
311         -- won't match with [] appearing in rules in an importing module.
312         --
313         -- The "1" says to inline in phase 1
314
315 build g = g (:) []
316
317 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
318 {-# INLINE [1] augment #-}
319 augment g xs = g (:) xs
320
321 {-# RULES
322 "fold/build"    forall k z (g::forall b. (a->b->b) -> b -> b) . 
323                 foldr k z (build g) = g k z
324
325 "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . 
326                 foldr k z (augment g xs) = g k (foldr k z xs)
327
328 "foldr/id"                        foldr (:) [] = \x->x
329 "foldr/app"     [1] forall xs ys. foldr (:) ys xs = xs ++ ys
330         -- Only activate this from phase 1, because that's
331         -- when we disable the rule that expands (++) into foldr
332
333 -- The foldr/cons rule looks nice, but it can give disastrously
334 -- bloated code when commpiling
335 --      array (a,b) [(1,2), (2,2), (3,2), ...very long list... ]
336 -- i.e. when there are very very long literal lists
337 -- So I've disabled it for now. We could have special cases
338 -- for short lists, I suppose.
339 -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
340
341 "foldr/single"  forall k z x. foldr k z [x] = k x z
342 "foldr/nil"     forall k z.   foldr k z []  = z 
343
344 "augment/build" forall (g::forall b. (a->b->b) -> b -> b)
345                        (h::forall b. (a->b->b) -> b -> b) .
346                        augment g (build h) = build (\c n -> g c (h c n))
347 "augment/nil"   forall (g::forall b. (a->b->b) -> b -> b) .
348                         augment g [] = build g
349  #-}
350
351 -- This rule is true, but not (I think) useful:
352 --      augment g (augment h t) = augment (\cn -> g c (h c n)) t
353 \end{code}
354
355
356 ----------------------------------------------
357 --              map     
358 ----------------------------------------------
359
360 \begin{code}
361 -- | 'map' @f xs@ is the list obtained by applying @f@ to each element
362 -- of @xs@, i.e.,
363 --
364 -- > map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
365 -- > map f [x1, x2, ...] == [f x1, f x2, ...]
366
367 map :: (a -> b) -> [a] -> [b]
368 map _ []     = []
369 map f (x:xs) = f x : map f xs
370
371 -- Note eta expanded
372 mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
373 {-# INLINE [0] mapFB #-}
374 mapFB c f x ys = c (f x) ys
375
376 -- The rules for map work like this.
377 -- 
378 -- Up to (but not including) phase 1, we use the "map" rule to
379 -- rewrite all saturated applications of map with its build/fold 
380 -- form, hoping for fusion to happen.
381 -- In phase 1 and 0, we switch off that rule, inline build, and
382 -- switch on the "mapList" rule, which rewrites the foldr/mapFB
383 -- thing back into plain map.  
384 --
385 -- It's important that these two rules aren't both active at once 
386 -- (along with build's unfolding) else we'd get an infinite loop 
387 -- in the rules.  Hence the activation control below.
388 --
389 -- The "mapFB" rule optimises compositions of map.
390 --
391 -- This same pattern is followed by many other functions: 
392 -- e.g. append, filter, iterate, repeat, etc.
393
394 {-# RULES
395 "map"       [~1] forall f xs.   map f xs                = build (\c n -> foldr (mapFB c f) n xs)
396 "mapList"   [1]  forall f.      foldr (mapFB (:) f) []  = map f
397 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
398   #-}
399 \end{code}
400
401
402 ----------------------------------------------
403 --              append  
404 ----------------------------------------------
405 \begin{code}
406 -- | Append two lists, i.e.,
407 --
408 -- > [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn]
409 -- > [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
410 --
411 -- If the first list is not finite, the result is the first list.
412
413 (++) :: [a] -> [a] -> [a]
414 (++) []     ys = ys
415 (++) (x:xs) ys = x : xs ++ ys
416
417 {-# RULES
418 "++"    [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys
419   #-}
420
421 \end{code}
422
423
424 %*********************************************************
425 %*                                                      *
426 \subsection{Type @Bool@}
427 %*                                                      *
428 %*********************************************************
429
430 \begin{code}
431 -- |The 'Bool' type is an enumeration.  It is defined with 'False'
432 -- first so that the corresponding 'Prelude.Enum' instance will give
433 -- 'Prelude.fromEnum' 'False' the value zero, and
434 -- 'Prelude.fromEnum' 'True' the value 1.
435 data  Bool  =  False | True  deriving (Eq, Ord)
436         -- Read in GHC.Read, Show in GHC.Show
437
438 -- Boolean functions
439
440 -- | Boolean \"and\"
441 (&&)                    :: Bool -> Bool -> Bool
442 True  && x              =  x
443 False && _              =  False
444
445 -- | Boolean \"or\"
446 (||)                    :: Bool -> Bool -> Bool
447 True  || _              =  True
448 False || x              =  x
449
450 -- | Boolean \"not\"
451 not                     :: Bool -> Bool
452 not True                =  False
453 not False               =  True
454
455 -- |'otherwise' is defined as the value 'True'.  It helps to make
456 -- guards more readable.  eg.
457 --
458 -- >  f x | x < 0     = ...
459 -- >      | otherwise = ...
460 otherwise               :: Bool
461 otherwise               =  True
462 \end{code}
463
464
465 %*********************************************************
466 %*                                                      *
467 \subsection{The @()@ type}
468 %*                                                      *
469 %*********************************************************
470
471 The Unit type is here because virtually any program needs it (whereas
472 some programs may get away without consulting GHC.Tup).  Furthermore,
473 the renamer currently *always* asks for () to be in scope, so that
474 ccalls can use () as their default type; so when compiling GHC.Base we
475 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
476 it here seems more direct.)
477
478 \begin{code}
479 -- | The unit datatype @()@ has one non-undefined member, the nullary
480 -- constructor @()@.
481 data () = ()
482
483 instance Eq () where
484     () == () = True
485     () /= () = False
486
487 instance Ord () where
488     () <= () = True
489     () <  () = False
490     () >= () = True
491     () >  () = False
492     max () () = ()
493     min () () = ()
494     compare () () = EQ
495 \end{code}
496
497
498 %*********************************************************
499 %*                                                      *
500 \subsection{Type @Ordering@}
501 %*                                                      *
502 %*********************************************************
503
504 \begin{code}
505 -- | Represents an ordering relationship between two values: less
506 -- than, equal to, or greater than.  An 'Ordering' is returned by
507 -- 'compare'.
508 data Ordering = LT | EQ | GT deriving (Eq, Ord)
509         -- Read in GHC.Read, Show in GHC.Show
510 \end{code}
511
512
513 %*********************************************************
514 %*                                                      *
515 \subsection{Type @Char@ and @String@}
516 %*                                                      *
517 %*********************************************************
518
519 \begin{code}
520 -- | A 'String' is a list of characters.  String constants in Haskell are values
521 -- of type 'String'.
522 --
523 type String = [Char]
524
525 {-| The character type 'Char' is an enumeration whose values represent
526 Unicode (or equivalently ISO 10646) characters.
527 This set extends the ISO 8859-1 (Latin-1) character set
528 (the first 256 charachers), which is itself an extension of the ASCII
529 character set (the first 128 characters).
530 A character literal in Haskell has type 'Char'.
531
532 To convert a 'Char' to or from the corresponding 'Int' value defined
533 by Unicode, use 'Prelude.toEnum' and 'Prelude.fromEnum' from the
534 'Prelude.Enum' class respectively (or equivalently 'ord' and 'chr').
535 -}
536 data Char = C# Char#
537
538 -- We don't use deriving for Eq and Ord, because for Ord the derived
539 -- instance defines only compare, which takes two primops.  Then
540 -- '>' uses compare, and therefore takes two primops instead of one.
541
542 instance Eq Char where
543     (C# c1) == (C# c2) = c1 `eqChar#` c2
544     (C# c1) /= (C# c2) = c1 `neChar#` c2
545
546 instance Ord Char where
547     (C# c1) >  (C# c2) = c1 `gtChar#` c2
548     (C# c1) >= (C# c2) = c1 `geChar#` c2
549     (C# c1) <= (C# c2) = c1 `leChar#` c2
550     (C# c1) <  (C# c2) = c1 `ltChar#` c2
551
552 {-# RULES
553 "x# `eqChar#` x#" forall x#. x# `eqChar#` x# = True
554 "x# `neChar#` x#" forall x#. x# `neChar#` x# = False
555 "x# `gtChar#` x#" forall x#. x# `gtChar#` x# = False
556 "x# `geChar#` x#" forall x#. x# `geChar#` x# = True
557 "x# `leChar#` x#" forall x#. x# `leChar#` x# = True
558 "x# `ltChar#` x#" forall x#. x# `ltChar#` x# = False
559   #-}
560
561 -- | The 'Prelude.toEnum' method restricted to the type 'Data.Char.Char'.
562 chr :: Int -> Char
563 chr (I# i#) | int2Word# i# `leWord#` int2Word# 0x10FFFF# = C# (chr# i#)
564             | otherwise                                  = error "Prelude.chr: bad argument"
565
566 unsafeChr :: Int -> Char
567 unsafeChr (I# i#) = C# (chr# i#)
568
569 -- | The 'Prelude.fromEnum' method restricted to the type 'Data.Char.Char'.
570 ord :: Char -> Int
571 ord (C# c#) = I# (ord# c#)
572 \end{code}
573
574 String equality is used when desugaring pattern-matches against strings.
575
576 \begin{code}
577 eqString :: String -> String -> Bool
578 eqString []       []       = True
579 eqString (c1:cs1) (c2:cs2) = c1 == c2 && cs1 `eqString` cs2
580 eqString cs1      cs2      = False
581
582 {-# RULES "eqString" (==) = eqString #-}
583 \end{code}
584
585
586 %*********************************************************
587 %*                                                      *
588 \subsection{Type @Int@}
589 %*                                                      *
590 %*********************************************************
591
592 \begin{code}
593 data Int = I# Int#
594 -- ^A fixed-precision integer type with at least the range @[-2^29 .. 2^29-1]@.
595 -- The exact range for a given implementation can be determined by using
596 -- 'Prelude.minBound' and 'Prelude.maxBound' from the 'Prelude.Bounded' class.
597
598 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
599 zeroInt = I# 0#
600 oneInt  = I# 1#
601 twoInt  = I# 2#
602
603 {- Seems clumsy. Should perhaps put minInt and MaxInt directly into MachDeps.h -}
604 #if WORD_SIZE_IN_BITS == 31
605 minInt  = I# (-0x40000000#)
606 maxInt  = I# 0x3FFFFFFF#
607 #elif WORD_SIZE_IN_BITS == 32
608 minInt  = I# (-0x80000000#)
609 maxInt  = I# 0x7FFFFFFF#
610 #else 
611 minInt  = I# (-0x8000000000000000#)
612 maxInt  = I# 0x7FFFFFFFFFFFFFFF#
613 #endif
614
615 instance Eq Int where
616     (==) = eqInt
617     (/=) = neInt
618
619 instance Ord Int where
620     compare = compareInt
621     (<)     = ltInt
622     (<=)    = leInt
623     (>=)    = geInt
624     (>)     = gtInt
625
626 compareInt :: Int -> Int -> Ordering
627 (I# x#) `compareInt` (I# y#) = compareInt# x# y#
628
629 compareInt# :: Int# -> Int# -> Ordering
630 compareInt# x# y#
631     | x# <#  y# = LT
632     | x# ==# y# = EQ
633     | otherwise = GT
634 \end{code}
635
636
637 %*********************************************************
638 %*                                                      *
639 \subsection{The function type}
640 %*                                                      *
641 %*********************************************************
642
643 \begin{code}
644 -- | Identity function.
645 id                      :: a -> a
646 id x                    =  x
647
648 -- lazy function; this is just the same as id, but its unfolding
649 -- and strictness are over-ridden by the definition in MkId.lhs
650 -- That way, it does not get inlined, and the strictness analyser
651 -- sees it as lazy.  Then the worker/wrapper phase inlines it.
652 -- Result: happiness
653 lazy :: a -> a
654 lazy x = x
655
656 -- | Assertion function.  This simply ignores its boolean argument.
657 -- The compiler may rewrite it to @('assertError' line)@.
658
659 --      SLPJ: in 5.04 etc 'assert' is in GHC.Prim,
660 --      but from Template Haskell onwards it's simply
661 --      defined here in Base.lhs
662 assert :: Bool -> a -> a
663 assert pred r = r
664  
665 -- | Constant function.
666 const                   :: a -> b -> a
667 const x _               =  x
668
669 -- | Function composition.
670 {-# INLINE (.) #-}
671 (.)       :: (b -> c) -> (a -> b) -> a -> c
672 (.) f g x = f (g x)
673
674 -- | @'flip' f@ takes its (first) two arguments in the reverse order of @f@.
675 flip                    :: (a -> b -> c) -> b -> a -> c
676 flip f x y              =  f y x
677
678 -- | Application operator.  This operator is redundant, since ordinary
679 -- application @(f x)@ means the same as @(f '$' x)@. However, '$' has
680 -- low, right-associative binding precedence, so it sometimes allows
681 -- parentheses to be omitted; for example:
682 --
683 -- >     f $ g $ h x  =  f (g (h x))
684 --
685 -- It is also useful in higher-order situations, such as @'map' ('$' 0) xs@,
686 -- or @'Data.List.zipWith' ('$') fs xs@.
687 {-# INLINE ($) #-}
688 ($)                     :: (a -> b) -> a -> b
689 f $ x                   =  f x
690
691 -- | @'until' p f@ yields the result of applying @f@ until @p@ holds.
692 until                   :: (a -> Bool) -> (a -> a) -> a -> a
693 until p f x | p x       =  x
694             | otherwise =  until p f (f x)
695
696 -- | 'asTypeOf' is a type-restricted version of 'const'.  It is usually
697 -- used as an infix operator, and its typing forces its first argument
698 -- (which is usually overloaded) to have the same type as the second.
699 asTypeOf                :: a -> a -> a
700 asTypeOf                =  const
701 \end{code}
702
703 %*********************************************************
704 %*                                                      *
705 \subsection{Generics}
706 %*                                                      *
707 %*********************************************************
708
709 \begin{code}
710 data Unit = Unit
711 #ifndef __HADDOCK__
712 data (:+:) a b = Inl a | Inr b
713 data (:*:) a b = a :*: b
714 #endif
715 \end{code}
716
717 %*********************************************************
718 %*                                                      *
719 \subsection{@getTag@}
720 %*                                                      *
721 %*********************************************************
722
723 Returns the 'tag' of a constructor application; this function is used
724 by the deriving code for Eq, Ord and Enum.
725
726 The primitive dataToTag# requires an evaluated constructor application
727 as its argument, so we provide getTag as a wrapper that performs the
728 evaluation before calling dataToTag#.  We could have dataToTag#
729 evaluate its argument, but we prefer to do it this way because (a)
730 dataToTag# can be an inline primop if it doesn't need to do any
731 evaluation, and (b) we want to expose the evaluation to the
732 simplifier, because it might be possible to eliminate the evaluation
733 in the case when the argument is already known to be evaluated.
734
735 \begin{code}
736 {-# INLINE getTag #-}
737 getTag :: a -> Int#
738 getTag x = x `seq` dataToTag# x
739 \end{code}
740
741 %*********************************************************
742 %*                                                      *
743 \subsection{Numeric primops}
744 %*                                                      *
745 %*********************************************************
746
747 \begin{code}
748 divInt# :: Int# -> Int# -> Int#
749 x# `divInt#` y#
750         -- Be careful NOT to overflow if we do any additional arithmetic
751         -- on the arguments...  the following  previous version of this
752         -- code has problems with overflow:
753 --    | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
754 --    | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
755     | (x# ># 0#) && (y# <# 0#) = ((x# -# 1#) `quotInt#` y#) -# 1#
756     | (x# <# 0#) && (y# ># 0#) = ((x# +# 1#) `quotInt#` y#) -# 1#
757     | otherwise                = x# `quotInt#` y#
758
759 modInt# :: Int# -> Int# -> Int#
760 x# `modInt#` y#
761     | (x# ># 0#) && (y# <# 0#) ||
762       (x# <# 0#) && (y# ># 0#)    = if r# /=# 0# then r# +# y# else 0#
763     | otherwise                   = r#
764     where
765     r# = x# `remInt#` y#
766 \end{code}
767
768 Definitions of the boxed PrimOps; these will be
769 used in the case of partial applications, etc.
770
771 \begin{code}
772 {-# INLINE eqInt #-}
773 {-# INLINE neInt #-}
774 {-# INLINE gtInt #-}
775 {-# INLINE geInt #-}
776 {-# INLINE ltInt #-}
777 {-# INLINE leInt #-}
778 {-# INLINE plusInt #-}
779 {-# INLINE minusInt #-}
780 {-# INLINE timesInt #-}
781 {-# INLINE quotInt #-}
782 {-# INLINE remInt #-}
783 {-# INLINE negateInt #-}
784
785 plusInt, minusInt, timesInt, quotInt, remInt, divInt, modInt, gcdInt :: Int -> Int -> Int
786 (I# x) `plusInt`  (I# y) = I# (x +# y)
787 (I# x) `minusInt` (I# y) = I# (x -# y)
788 (I# x) `timesInt` (I# y) = I# (x *# y)
789 (I# x) `quotInt`  (I# y) = I# (x `quotInt#` y)
790 (I# x) `remInt`   (I# y) = I# (x `remInt#`  y)
791 (I# x) `divInt`   (I# y) = I# (x `divInt#`  y)
792 (I# x) `modInt`   (I# y) = I# (x `modInt#`  y)
793
794 {-# RULES
795 "x# +# 0#" forall x#. x# +# 0# = x#
796 "0# +# x#" forall x#. 0# +# x# = x#
797 "x# -# 0#" forall x#. x# -# 0# = x#
798 "x# -# x#" forall x#. x# -# x# = 0#
799 "x# *# 0#" forall x#. x# *# 0# = 0#
800 "0# *# x#" forall x#. 0# *# x# = 0#
801 "x# *# 1#" forall x#. x# *# 1# = x#
802 "1# *# x#" forall x#. 1# *# x# = x#
803   #-}
804
805 gcdInt (I# a) (I# b) = g a b
806    where g 0# 0# = error "GHC.Base.gcdInt: gcd 0 0 is undefined"
807          g 0# _  = I# absB
808          g _  0# = I# absA
809          g _  _  = I# (gcdInt# absA absB)
810
811          absInt x = if x <# 0# then negateInt# x else x
812
813          absA     = absInt a
814          absB     = absInt b
815
816 negateInt :: Int -> Int
817 negateInt (I# x) = I# (negateInt# x)
818
819 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
820 (I# x) `gtInt` (I# y) = x >#  y
821 (I# x) `geInt` (I# y) = x >=# y
822 (I# x) `eqInt` (I# y) = x ==# y
823 (I# x) `neInt` (I# y) = x /=# y
824 (I# x) `ltInt` (I# y) = x <#  y
825 (I# x) `leInt` (I# y) = x <=# y
826
827 {-# RULES
828 "x# ># x#"  forall x#. x# >#  x# = False
829 "x# >=# x#" forall x#. x# >=# x# = True
830 "x# ==# x#" forall x#. x# ==# x# = True
831 "x# /=# x#" forall x#. x# /=# x# = False
832 "x# <# x#"  forall x#. x# <#  x# = False
833 "x# <=# x#" forall x#. x# <=# x# = True
834   #-}
835
836 {-# RULES
837 "plusFloat x 0.0"   forall x#. plusFloat#  x#   0.0# = x#
838 "plusFloat 0.0 x"   forall x#. plusFloat#  0.0# x#   = x#
839 "minusFloat x 0.0"  forall x#. minusFloat# x#   0.0# = x#
840 "minusFloat x x"    forall x#. minusFloat# x#   x#   = 0.0#
841 "timesFloat x 0.0"  forall x#. timesFloat# x#   0.0# = 0.0#
842 "timesFloat0.0 x"   forall x#. timesFloat# 0.0# x#   = 0.0#
843 "timesFloat x 1.0"  forall x#. timesFloat# x#   1.0# = x#
844 "timesFloat 1.0 x"  forall x#. timesFloat# 1.0# x#   = x#
845 "divideFloat x 1.0" forall x#. divideFloat# x#  1.0# = x#
846   #-}
847
848 {-# RULES
849 "plusDouble x 0.0"   forall x#. (+##) x#    0.0## = x#
850 "plusDouble 0.0 x"   forall x#. (+##) 0.0## x#    = x#
851 "minusDouble x 0.0"  forall x#. (-##) x#    0.0## = x#
852 "minusDouble x x"    forall x#. (-##) x#    x#    = 0.0##
853 "timesDouble x 0.0"  forall x#. (*##) x#    0.0## = 0.0##
854 "timesDouble 0.0 x"  forall x#. (*##) 0.0## x#    = 0.0##
855 "timesDouble x 1.0"  forall x#. (*##) x#    1.0## = x#
856 "timesDouble 1.0 x"  forall x#. (*##) 1.0## x#    = x#
857 "divideDouble x 1.0" forall x#. (/##) x#    1.0## = x#
858   #-}
859
860 -- Wrappers for the shift operations.  The uncheckedShift# family are
861 -- undefined when the amount being shifted by is greater than the size
862 -- in bits of Int#, so these wrappers perform a check and return
863 -- either zero or -1 appropriately.
864 --
865 -- Note that these wrappers still produce undefined results when the
866 -- second argument (the shift amount) is negative.
867
868 shiftL#, shiftRL# :: Word# -> Int# -> Word#
869
870 a `shiftL#` b   | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
871                 | otherwise                = a `uncheckedShiftL#` b
872
873 a `shiftRL#` b  | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
874                 | otherwise                = a `uncheckedShiftRL#` b
875
876 iShiftL#, iShiftRA#, iShiftRL# :: Int# -> Int# -> Int#
877
878 a `iShiftL#` b  | b >=# WORD_SIZE_IN_BITS# = 0#
879                 | otherwise                = a `uncheckedIShiftL#` b
880
881 a `iShiftRA#` b | b >=# WORD_SIZE_IN_BITS# = if a <# 0# then (-1#) else 0#
882                 | otherwise                = a `uncheckedIShiftRA#` b
883
884 a `iShiftRL#` b | b >=# WORD_SIZE_IN_BITS# = 0#
885                 | otherwise                = a `uncheckedIShiftRL#` b
886
887 #if WORD_SIZE_IN_BITS == 32
888 {-# RULES
889 "narrow32Int#"  forall x#. narrow32Int#   x# = x#
890 "narrow32Word#" forall x#. narrow32Word#   x# = x#
891    #-}
892 #endif
893
894 {-# RULES
895 "int2Word2Int"  forall x#. int2Word# (word2Int# x#) = x#
896 "word2Int2Word" forall x#. word2Int# (int2Word# x#) = x#
897   #-}
898 \end{code}
899
900
901 %********************************************************
902 %*                                                      *
903 \subsection{Unpacking C strings}
904 %*                                                      *
905 %********************************************************
906
907 This code is needed for virtually all programs, since it's used for
908 unpacking the strings of error messages.
909
910 \begin{code}
911 unpackCString# :: Addr# -> [Char]
912 {-# NOINLINE [1] unpackCString# #-}
913 unpackCString# addr 
914   = unpack 0#
915   where
916     unpack nh
917       | ch `eqChar#` '\0'# = []
918       | otherwise          = C# ch : unpack (nh +# 1#)
919       where
920         ch = indexCharOffAddr# addr nh
921
922 unpackAppendCString# :: Addr# -> [Char] -> [Char]
923 unpackAppendCString# addr rest
924   = unpack 0#
925   where
926     unpack nh
927       | ch `eqChar#` '\0'# = rest
928       | otherwise          = C# ch : unpack (nh +# 1#)
929       where
930         ch = indexCharOffAddr# addr nh
931
932 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
933 {-# NOINLINE [0] unpackFoldrCString# #-}
934 -- Don't inline till right at the end;
935 -- usually the unpack-list rule turns it into unpackCStringList
936 unpackFoldrCString# addr f z 
937   = unpack 0#
938   where
939     unpack nh
940       | ch `eqChar#` '\0'# = z
941       | otherwise          = C# ch `f` unpack (nh +# 1#)
942       where
943         ch = indexCharOffAddr# addr nh
944
945 unpackCStringUtf8# :: Addr# -> [Char]
946 unpackCStringUtf8# addr 
947   = unpack 0#
948   where
949     unpack nh
950       | ch `eqChar#` '\0'#   = []
951       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
952       | ch `leChar#` '\xDF'# =
953           C# (chr# (((ord# ch                                  -# 0xC0#) `uncheckedIShiftL#`  6#) +#
954                      (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
955           unpack (nh +# 2#)
956       | ch `leChar#` '\xEF'# =
957           C# (chr# (((ord# ch                                  -# 0xE0#) `uncheckedIShiftL#` 12#) +#
958                     ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#`  6#) +#
959                      (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
960           unpack (nh +# 3#)
961       | otherwise            =
962           C# (chr# (((ord# ch                                  -# 0xF0#) `uncheckedIShiftL#` 18#) +#
963                     ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +#
964                     ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#`  6#) +#
965                      (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
966           unpack (nh +# 4#)
967       where
968         ch = indexCharOffAddr# addr nh
969
970 unpackNBytes# :: Addr# -> Int# -> [Char]
971 unpackNBytes# _addr 0#   = []
972 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
973     where
974      unpack acc i#
975       | i# <# 0#  = acc
976       | otherwise = 
977          case indexCharOffAddr# addr i# of
978             ch -> unpack (C# ch : acc) (i# -# 1#)
979
980 {-# RULES
981 "unpack"       [~1] forall a   . unpackCString# a                  = build (unpackFoldrCString# a)
982 "unpack-list"  [1]  forall a   . unpackFoldrCString# a (:) [] = unpackCString# a
983 "unpack-append"     forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
984
985 -- There's a built-in rule (in PrelRules.lhs) for
986 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
987
988   #-}
989 \end{code}
990
991 #ifdef __HADDOCK__
992 \begin{code}
993 -- | A special argument for the 'Control.Monad.ST.ST' type constructor,
994 -- indexing a state embedded in the 'Prelude.IO' monad by
995 -- 'Control.Monad.ST.stToIO'.
996 data RealWorld
997 \end{code}
998 #endif