[project @ 2001-12-21 15:07:20 by simonmar]
[ghc-base.git] / GHC / Base.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: Base.lhs,v 1.4 2001/12/21 15:07:22 simonmar Exp $
3 %
4 % (c) The University of Glasgow, 1992-2000
5 %
6 \section[GHC.Base]{Module @GHC.Base@}
7
8
9 The overall structure of the GHC Prelude is a bit tricky.
10
11   a) We want to avoid "orphan modules", i.e. ones with instance
12         decls that don't belong either to a tycon or a class
13         defined in the same module
14
15   b) We want to avoid giant modules
16
17 So the rough structure is as follows, in (linearised) dependency order
18
19
20 GHC.Prim                Has no implementation.  It defines built-in things, and
21                 by importing it you bring them into scope.
22                 The source file is GHC.Prim.hi-boot, which is just
23                 copied to make GHC.Prim.hi
24
25                 Classes: CCallable, CReturnable
26
27 GHC.Base        Classes: Eq, Ord, Functor, Monad
28                 Types:   list, (), Int, Bool, Ordering, Char, String
29
30 Data.Tup        Types: tuples, plus instances for GHC.Base classes
31
32 GHC.Show        Class: Show, plus instances for GHC.Base/GHC.Tup types
33
34 GHC.Enum        Class: Enum,  plus instances for GHC.Base/GHC.Tup types
35
36 Data.Maybe      Type: Maybe, plus instances for GHC.Base classes
37
38 GHC.Num         Class: Num, plus instances for Int
39                 Type:  Integer, plus instances for all classes so far (Eq, Ord, Num, Show)
40
41                 Integer is needed here because it is mentioned in the signature
42                 of 'fromInteger' in class Num
43
44 GHC.Real        Classes: Real, Integral, Fractional, RealFrac
45                          plus instances for Int, Integer
46                 Types:  Ratio, Rational
47                         plus intances for classes so far
48
49                 Rational is needed here because it is mentioned in the signature
50                 of 'toRational' in class Real
51
52 Ix              Classes: Ix, plus instances for Int, Bool, Char, Integer, Ordering, tuples
53
54 GHC.Arr         Types: Array, MutableArray, MutableVar
55
56                 Does *not* contain any ByteArray stuff (see GHC.ByteArr)
57                 Arrays are used by a function in GHC.Float
58
59 GHC.Float       Classes: Floating, RealFloat
60                 Types:   Float, Double, plus instances of all classes so far
61
62                 This module contains everything to do with floating point.
63                 It is a big module (900 lines)
64                 With a bit of luck, many modules can be compiled without ever reading GHC.Float.hi
65
66 GHC.ByteArr     Types: ByteArray, MutableByteArray
67                 
68                 We want this one to be after GHC.Float, because it defines arrays
69                 of unboxed floats.
70
71
72 Other Prelude modules are much easier with fewer complex dependencies.
73
74
75 \begin{code}
76 {-# OPTIONS -fno-implicit-prelude #-}
77
78 #include "MachDeps.h"
79
80 module GHC.Base
81         (
82         module GHC.Base,
83         module GHC.Prim,                -- Re-export GHC.Prim and GHC.Err, to avoid lots
84         module GHC.Err          -- of people having to import it explicitly
85   ) 
86         where
87
88 import {-# SOURCE #-} GHC.Prim
89 import {-# SOURCE #-} GHC.Err
90
91 infixr 9  .
92 infixr 5  ++, :
93 infix  4  ==, /=, <, <=, >=, >
94 infixr 3  &&
95 infixr 2  ||
96 infixl 1  >>, >>=
97 infixr 0  $
98
99 default ()              -- Double isn't available yet
100 \end{code}
101
102
103 %*********************************************************
104 %*                                                      *
105 \subsection{DEBUGGING STUFF}
106 %*  (for use when compiling GHC.Base itself doesn't work)
107 %*                                                      *
108 %*********************************************************
109
110 \begin{code}
111 {-
112 data  Bool  =  False | True
113 data Ordering = LT | EQ | GT 
114 data Char = C# Char#
115 type  String = [Char]
116 data Int = I# Int#
117 data  ()  =  ()
118 data [] a = MkNil
119
120 not True = False
121 (&&) True True = True
122 otherwise = True
123
124 build = error "urk"
125 foldr = error "urk"
126
127 unpackCString# :: Addr# -> [Char]
128 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
129 unpackAppendCString# :: Addr# -> [Char] -> [Char]
130 unpackCStringUtf8# :: Addr# -> [Char]
131 unpackCString# a = error "urk"
132 unpackFoldrCString# a = error "urk"
133 unpackAppendCString# a = error "urk"
134 unpackCStringUtf8# a = error "urk"
135 -}
136 \end{code}
137
138
139 %*********************************************************
140 %*                                                      *
141 \subsection{Standard classes @Eq@, @Ord@}
142 %*                                                      *
143 %*********************************************************
144
145 \begin{code}
146 class  Eq a  where
147     (==), (/=)           :: a -> a -> Bool
148
149     x /= y               = not (x == y)
150     x == y               = not (x /= y)
151
152 class  (Eq a) => Ord a  where
153     compare              :: a -> a -> Ordering
154     (<), (<=), (>), (>=) :: a -> a -> Bool
155     max, min             :: a -> a -> a
156
157     -- An instance of Ord should define either 'compare' or '<='.
158     -- Using 'compare' can be more efficient for complex types.
159
160     compare x y
161         | x == y    = EQ
162         | x <= y    = LT        -- NB: must be '<=' not '<' to validate the
163                                 -- above claim about the minimal things that
164                                 -- can be defined for an instance of Ord
165         | otherwise = GT
166
167     x <  y = case compare x y of { LT -> True;  _other -> False }
168     x <= y = case compare x y of { GT -> False; _other -> True }
169     x >  y = case compare x y of { GT -> True;  _other -> False }
170     x >= y = case compare x y of { LT -> False; _other -> True }
171
172         -- These two default methods use '<=' rather than 'compare'
173         -- because the latter is often more expensive
174     max x y = if x <= y then y else x
175     min x y = if x <= y then x else y
176 \end{code}
177
178 %*********************************************************
179 %*                                                      *
180 \subsection{Monadic classes @Functor@, @Monad@ }
181 %*                                                      *
182 %*********************************************************
183
184 \begin{code}
185 class  Functor f  where
186     fmap        :: (a -> b) -> f a -> f b
187
188 class  Monad m  where
189     (>>=)       :: m a -> (a -> m b) -> m b
190     (>>)        :: m a -> m b -> m b
191     return      :: a -> m a
192     fail        :: String -> m a
193
194     m >> k      = m >>= \_ -> k
195     fail s      = error s
196 \end{code}
197
198
199 %*********************************************************
200 %*                                                      *
201 \subsection{The list type}
202 %*                                                      *
203 %*********************************************************
204
205 \begin{code}
206 data [] a = [] | a : [a]  -- do explicitly: deriving (Eq, Ord)
207                           -- to avoid weird names like con2tag_[]#
208
209
210 instance (Eq a) => Eq [a] where
211     {-# SPECIALISE instance Eq [Char] #-}
212     []     == []     = True
213     (x:xs) == (y:ys) = x == y && xs == ys
214     _xs    == _ys    = False
215
216 instance (Ord a) => Ord [a] where
217     {-# SPECIALISE instance Ord [Char] #-}
218     compare []     []     = EQ
219     compare []     (_:_)  = LT
220     compare (_:_)  []     = GT
221     compare (x:xs) (y:ys) = case compare x y of
222                                 EQ    -> compare xs ys
223                                 other -> other
224
225 instance Functor [] where
226     fmap = map
227
228 instance  Monad []  where
229     m >>= k             = foldr ((++) . k) [] m
230     m >> k              = foldr ((++) . (\ _ -> k)) [] m
231     return x            = [x]
232     fail _              = []
233 \end{code}
234
235 A few list functions that appear here because they are used here.
236 The rest of the prelude list functions are in GHC.List.
237
238 ----------------------------------------------
239 --      foldr/build/augment
240 ----------------------------------------------
241   
242 \begin{code}
243 foldr            :: (a -> b -> b) -> b -> [a] -> b
244 -- foldr _ z []     =  z
245 -- foldr f z (x:xs) =  f x (foldr f z xs)
246 {-# INLINE [0] foldr #-}
247 -- Inline only in the final stage, after the foldr/cons rule has had a chance
248 foldr k z xs = go xs
249              where
250                go []     = z
251                go (y:ys) = y `k` go ys
252
253 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
254 {-# INLINE [1] build #-}
255         -- The INLINE is important, even though build is tiny,
256         -- because it prevents [] getting inlined in the version that
257         -- appears in the interface file.  If [] *is* inlined, it
258         -- won't match with [] appearing in rules in an importing module.
259         --
260         -- The "1" says to inline in phase 1
261
262 build g = g (:) []
263
264 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
265 {-# INLINE [1] augment #-}
266 augment g xs = g (:) xs
267
268 {-# RULES
269 "fold/build"    forall k z (g::forall b. (a->b->b) -> b -> b) . 
270                 foldr k z (build g) = g k z
271
272 "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . 
273                 foldr k z (augment g xs) = g k (foldr k z xs)
274
275 "foldr/id"      foldr (:) [] = \x->x
276 "foldr/app"     forall xs ys. foldr (:) ys xs = append xs ys
277
278 -- The foldr/cons rule looks nice, but it can give disastrously
279 -- bloated code when commpiling
280 --      array (a,b) [(1,2), (2,2), (3,2), ...very long list... ]
281 -- i.e. when there are very very long literal lists
282 -- So I've disabled it for now. We could have special cases
283 -- for short lists, I suppose.
284 -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
285
286 "foldr/single"  forall k z x. foldr k z [x] = k x z
287 "foldr/nil"     forall k z.   foldr k z []  = z 
288
289 "augment/build" forall (g::forall b. (a->b->b) -> b -> b)
290                        (h::forall b. (a->b->b) -> b -> b) .
291                        augment g (build h) = build (\c n -> g c (h c n))
292 "augment/nil"   forall (g::forall b. (a->b->b) -> b -> b) .
293                         augment g [] = build g
294  #-}
295
296 -- This rule is true, but not (I think) useful:
297 --      augment g (augment h t) = augment (\cn -> g c (h c n)) t
298 \end{code}
299
300
301 ----------------------------------------------
302 --              map     
303 ----------------------------------------------
304
305 \begin{code}
306 map :: (a -> b) -> [a] -> [b]
307 {-# NOINLINE [1] map #-}
308 map = mapList
309
310 -- Note eta expanded
311 mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
312 mapFB c f x ys = c (f x) ys
313
314 mapList :: (a -> b) -> [a] -> [b]
315 mapList _ []     = []
316 mapList f (x:xs) = f x : mapList f xs
317
318 {-# RULES
319 "map"       forall f xs.        map f xs                = build (\c n -> foldr (mapFB c f) n xs)
320 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
321 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
322   #-}
323 \end{code}
324
325
326 ----------------------------------------------
327 --              append  
328 ----------------------------------------------
329 \begin{code}
330 (++) :: [a] -> [a] -> [a]
331 {-# NOINLINE [1] (++) #-}
332 (++) = append
333
334 {-# RULES
335 "++"    forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys
336   #-}
337
338 append :: [a] -> [a] -> [a]
339 append []     ys = ys
340 append (x:xs) ys = x : append xs ys
341 \end{code}
342
343
344 %*********************************************************
345 %*                                                      *
346 \subsection{Type @Bool@}
347 %*                                                      *
348 %*********************************************************
349
350 \begin{code}
351 data  Bool  =  False | True  deriving (Eq, Ord)
352         -- Read in GHC.Read, Show in GHC.Show
353
354 -- Boolean functions
355
356 (&&), (||)              :: Bool -> Bool -> Bool
357 True  && x              =  x
358 False && _              =  False
359 True  || _              =  True
360 False || x              =  x
361
362 not                     :: Bool -> Bool
363 not True                =  False
364 not False               =  True
365
366 otherwise               :: Bool
367 otherwise               =  True
368 \end{code}
369
370
371 %*********************************************************
372 %*                                                      *
373 \subsection{The @()@ type}
374 %*                                                      *
375 %*********************************************************
376
377 The Unit type is here because virtually any program needs it (whereas
378 some programs may get away without consulting GHC.Tup).  Furthermore,
379 the renamer currently *always* asks for () to be in scope, so that
380 ccalls can use () as their default type; so when compiling GHC.Base we
381 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
382 it here seems more direct.)
383
384 \begin{code}
385 data () = ()
386
387 instance Eq () where
388     () == () = True
389     () /= () = False
390
391 instance Ord () where
392     () <= () = True
393     () <  () = False
394     () >= () = True
395     () >  () = False
396     max () () = ()
397     min () () = ()
398     compare () () = EQ
399 \end{code}
400
401
402 %*********************************************************
403 %*                                                      *
404 \subsection{Type @Ordering@}
405 %*                                                      *
406 %*********************************************************
407
408 \begin{code}
409 data Ordering = LT | EQ | GT deriving (Eq, Ord)
410         -- Read in GHC.Read, Show in GHC.Show
411 \end{code}
412
413
414 %*********************************************************
415 %*                                                      *
416 \subsection{Type @Char@ and @String@}
417 %*                                                      *
418 %*********************************************************
419
420 \begin{code}
421 type String = [Char]
422
423 data Char = C# Char#
424
425 -- We don't use deriving for Eq and Ord, because for Ord the derived
426 -- instance defines only compare, which takes two primops.  Then
427 -- '>' uses compare, and therefore takes two primops instead of one.
428
429 instance Eq Char where
430     (C# c1) == (C# c2) = c1 `eqChar#` c2
431     (C# c1) /= (C# c2) = c1 `neChar#` c2
432
433 instance Ord Char where
434     (C# c1) >  (C# c2) = c1 `gtChar#` c2
435     (C# c1) >= (C# c2) = c1 `geChar#` c2
436     (C# c1) <= (C# c2) = c1 `leChar#` c2
437     (C# c1) <  (C# c2) = c1 `ltChar#` c2
438
439 {-# RULES
440 "x# `eqChar#` x#" forall x#. x# `eqChar#` x# = True
441 "x# `neChar#` x#" forall x#. x# `neChar#` x# = False
442 "x# `gtChar#` x#" forall x#. x# `gtChar#` x# = False
443 "x# `geChar#` x#" forall x#. x# `geChar#` x# = True
444 "x# `leChar#` x#" forall x#. x# `leChar#` x# = True
445 "x# `ltChar#` x#" forall x#. x# `ltChar#` x# = False
446   #-}
447
448 chr :: Int -> Char
449 chr (I# i#) | int2Word# i# `leWord#` int2Word# 0x10FFFF# = C# (chr# i#)
450             | otherwise                                  = error "Prelude.chr: bad argument"
451
452 unsafeChr :: Int -> Char
453 unsafeChr (I# i#) = C# (chr# i#)
454
455 ord :: Char -> Int
456 ord (C# c#) = I# (ord# c#)
457 \end{code}
458
459 String equality is used when desugaring pattern-matches against strings.
460
461 \begin{code}
462 eqString :: String -> String -> Bool
463 eqString []       []       = True
464 eqString (c1:cs1) (c2:cs2) = c1 == c2 && cs1 `eqString` cs2
465 eqString cs1      cs2      = False
466
467 {-# RULES "eqString" (==) = eqString #-}
468 \end{code}
469
470
471 %*********************************************************
472 %*                                                      *
473 \subsection{Type @Int@}
474 %*                                                      *
475 %*********************************************************
476
477 \begin{code}
478 data Int = I# Int#
479
480 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
481 zeroInt = I# 0#
482 oneInt  = I# 1#
483 twoInt  = I# 2#
484
485 {- Seems clumsy. Should perhaps put minInt and MaxInt directly into MachDeps.h -}
486 #if WORD_SIZE_IN_BITS == 31
487 minInt  = I# (-0x40000000#)
488 maxInt  = I# 0x3FFFFFFF#
489 #elif WORD_SIZE_IN_BITS == 32
490 minInt  = I# (-0x80000000#)
491 maxInt  = I# 0x7FFFFFFF#
492 #else 
493 minInt  = I# (-0x8000000000000000#)
494 maxInt  = I# 0x7FFFFFFFFFFFFFFF#
495 #endif
496
497 instance Eq Int where
498     (==) = eqInt
499     (/=) = neInt
500
501 instance Ord Int where
502     compare = compareInt
503     (<)     = ltInt
504     (<=)    = leInt
505     (>=)    = geInt
506     (>)     = gtInt
507
508 compareInt :: Int -> Int -> Ordering
509 (I# x#) `compareInt` (I# y#) = compareInt# x# y#
510
511 compareInt# :: Int# -> Int# -> Ordering
512 compareInt# x# y#
513     | x# <#  y# = LT
514     | x# ==# y# = EQ
515     | otherwise = GT
516 \end{code}
517
518
519 %*********************************************************
520 %*                                                      *
521 \subsection{The function type}
522 %*                                                      *
523 %*********************************************************
524
525 \begin{code}
526 -- identity function
527 id                      :: a -> a
528 id x                    =  x
529
530 -- constant function
531 const                   :: a -> b -> a
532 const x _               =  x
533
534 -- function composition
535 {-# INLINE (.) #-}
536 (.)       :: (b -> c) -> (a -> b) -> a -> c
537 (.) f g x = f (g x)
538
539 -- flip f  takes its (first) two arguments in the reverse order of f.
540 flip                    :: (a -> b -> c) -> b -> a -> c
541 flip f x y              =  f y x
542
543 -- right-associating infix application operator (useful in continuation-
544 -- passing style)
545 {-# INLINE ($) #-}
546 ($)                     :: (a -> b) -> a -> b
547 f $ x                   =  f x
548
549 -- until p f  yields the result of applying f until p holds.
550 until                   :: (a -> Bool) -> (a -> a) -> a -> a
551 until p f x | p x       =  x
552             | otherwise =  until p f (f x)
553
554 -- asTypeOf is a type-restricted version of const.  It is usually used
555 -- as an infix operator, and its typing forces its first argument
556 -- (which is usually overloaded) to have the same type as the second.
557 asTypeOf                :: a -> a -> a
558 asTypeOf                =  const
559 \end{code}
560
561 %*********************************************************
562 %*                                                      *
563 \subsection{CCallable instances}
564 %*                                                      *
565 %*********************************************************
566
567 Defined here to avoid orphans
568
569 \begin{code}
570 instance CCallable Char
571 instance CReturnable Char
572
573 instance CCallable   Int
574 instance CReturnable Int
575
576 instance CReturnable () -- Why, exactly?
577 \end{code}
578
579
580 %*********************************************************
581 %*                                                      *
582 \subsection{Generics}
583 %*                                                      *
584 %*********************************************************
585
586 \begin{code}
587 data Unit = Unit
588 data a :+: b = Inl a | Inr b
589 data a :*: b = a :*: b
590 \end{code}
591
592
593 %*********************************************************
594 %*                                                      *
595 \subsection{Numeric primops}
596 %*                                                      *
597 %*********************************************************
598
599 \begin{code}
600 divInt#, modInt# :: Int# -> Int# -> Int#
601 x# `divInt#` y#
602     | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
603     | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
604     | otherwise                = x# `quotInt#` y#
605 x# `modInt#` y#
606     | (x# ># 0#) && (y# <# 0#) ||
607       (x# <# 0#) && (y# ># 0#)    = if r# /=# 0# then r# +# y# else 0#
608     | otherwise                   = r#
609     where
610     r# = x# `remInt#` y#
611 \end{code}
612
613 Definitions of the boxed PrimOps; these will be
614 used in the case of partial applications, etc.
615
616 \begin{code}
617 {-# INLINE eqInt #-}
618 {-# INLINE neInt #-}
619 {-# INLINE gtInt #-}
620 {-# INLINE geInt #-}
621 {-# INLINE ltInt #-}
622 {-# INLINE leInt #-}
623 {-# INLINE plusInt #-}
624 {-# INLINE minusInt #-}
625 {-# INLINE timesInt #-}
626 {-# INLINE quotInt #-}
627 {-# INLINE remInt #-}
628 {-# INLINE negateInt #-}
629
630 plusInt, minusInt, timesInt, quotInt, remInt, divInt, modInt, gcdInt :: Int -> Int -> Int
631 (I# x) `plusInt`  (I# y) = I# (x +# y)
632 (I# x) `minusInt` (I# y) = I# (x -# y)
633 (I# x) `timesInt` (I# y) = I# (x *# y)
634 (I# x) `quotInt`  (I# y) = I# (x `quotInt#` y)
635 (I# x) `remInt`   (I# y) = I# (x `remInt#`  y)
636 (I# x) `divInt`   (I# y) = I# (x `divInt#`  y)
637 (I# x) `modInt`   (I# y) = I# (x `modInt#`  y)
638
639 {-# RULES
640 "x# +# 0#" forall x#. x# +# 0# = x#
641 "0# +# x#" forall x#. 0# +# x# = x#
642 "x# -# 0#" forall x#. x# -# 0# = x#
643 "x# -# x#" forall x#. x# -# x# = 0#
644 "x# *# 0#" forall x#. x# *# 0# = 0#
645 "0# *# x#" forall x#. 0# *# x# = 0#
646 "x# *# 1#" forall x#. x# *# 1# = x#
647 "1# *# x#" forall x#. 1# *# x# = x#
648   #-}
649
650 gcdInt (I# a) (I# b) = g a b
651    where g 0# 0# = error "GHC.Base.gcdInt: gcd 0 0 is undefined"
652          g 0# _  = I# absB
653          g _  0# = I# absA
654          g _  _  = I# (gcdInt# absA absB)
655
656          absInt x = if x <# 0# then negateInt# x else x
657
658          absA     = absInt a
659          absB     = absInt b
660
661 negateInt :: Int -> Int
662 negateInt (I# x) = I# (negateInt# x)
663
664 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
665 (I# x) `gtInt` (I# y) = x >#  y
666 (I# x) `geInt` (I# y) = x >=# y
667 (I# x) `eqInt` (I# y) = x ==# y
668 (I# x) `neInt` (I# y) = x /=# y
669 (I# x) `ltInt` (I# y) = x <#  y
670 (I# x) `leInt` (I# y) = x <=# y
671
672 {-# RULES
673 "x# ># x#"  forall x#. x# >#  x# = False
674 "x# >=# x#" forall x#. x# >=# x# = True
675 "x# ==# x#" forall x#. x# ==# x# = True
676 "x# /=# x#" forall x#. x# /=# x# = False
677 "x# <# x#"  forall x#. x# <#  x# = False
678 "x# <=# x#" forall x#. x# <=# x# = True
679   #-}
680
681 -- Wrappers for the shift operations.  The uncheckedShift# family are
682 -- undefined when the amount being shifted by is greater than the size
683 -- in bits of Int#, so these wrappers perform a check and return
684 -- either zero or -1 appropriately.
685 --
686 -- Note that these wrappers still produce undefined results when the
687 -- second argument (the shift amount) is negative.
688
689 shiftL#, shiftRL# :: Word# -> Int# -> Word#
690
691 a `shiftL#` b   | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
692                 | otherwise                = a `uncheckedShiftL#` b
693
694 a `shiftRL#` b  | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
695                 | otherwise                = a `uncheckedShiftRL#` b
696
697 iShiftL#, iShiftRA#, iShiftRL# :: Int# -> Int# -> Int#
698
699 a `iShiftL#` b  | b >=# WORD_SIZE_IN_BITS# = 0#
700                 | otherwise                = a `uncheckedIShiftL#` b
701
702 a `iShiftRA#` b | b >=# WORD_SIZE_IN_BITS# = if a <# 0# then (-1#) else 0#
703                 | otherwise                = a `uncheckedIShiftRA#` b
704
705 a `iShiftRL#` b | b >=# WORD_SIZE_IN_BITS# = 0#
706                 | otherwise                = a `uncheckedIShiftRL#` b
707
708 #if WORD_SIZE_IN_BITS == 32
709 {-# RULES
710 "narrow32Int#"  forall x#. narrow32Int#   x# = x#
711 "narrow32Word#" forall x#. narrow32Word#   x# = x#
712    #-}
713 #endif
714
715 {-# RULES
716 "int2Word2Int"  forall x#. int2Word# (word2Int# x#) = x#
717 "word2Int2Word" forall x#. word2Int# (int2Word# x#) = x#
718   #-}
719 \end{code}
720
721
722 %********************************************************
723 %*                                                      *
724 \subsection{Unpacking C strings}
725 %*                                                      *
726 %********************************************************
727
728 This code is needed for virtually all programs, since it's used for
729 unpacking the strings of error messages.
730
731 \begin{code}
732 unpackCString# :: Addr# -> [Char]
733 {-# NOINLINE [1] unpackCString# #-}
734 unpackCString# a = unpackCStringList# a
735
736 unpackCStringList# :: Addr# -> [Char]
737 unpackCStringList# addr 
738   = unpack 0#
739   where
740     unpack nh
741       | ch `eqChar#` '\0'# = []
742       | otherwise          = C# ch : unpack (nh +# 1#)
743       where
744         ch = indexCharOffAddr# addr nh
745
746 unpackAppendCString# :: Addr# -> [Char] -> [Char]
747 unpackAppendCString# addr rest
748   = unpack 0#
749   where
750     unpack nh
751       | ch `eqChar#` '\0'# = rest
752       | otherwise          = C# ch : unpack (nh +# 1#)
753       where
754         ch = indexCharOffAddr# addr nh
755
756 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
757 {-# NOINLINE [0] unpackFoldrCString# #-}
758 -- Don't inline till right at the end;
759 -- usually the unpack-list rule turns it into unpackCStringList
760 unpackFoldrCString# addr f z 
761   = unpack 0#
762   where
763     unpack nh
764       | ch `eqChar#` '\0'# = z
765       | otherwise          = C# ch `f` unpack (nh +# 1#)
766       where
767         ch = indexCharOffAddr# addr nh
768
769 unpackCStringUtf8# :: Addr# -> [Char]
770 unpackCStringUtf8# addr 
771   = unpack 0#
772   where
773     unpack nh
774       | ch `eqChar#` '\0'#   = []
775       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
776       | ch `leChar#` '\xDF'# =
777           C# (chr# ((ord# ch                                  -# 0xC0#) `uncheckedIShiftL#`  6# +#
778                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
779           unpack (nh +# 2#)
780       | ch `leChar#` '\xEF'# =
781           C# (chr# ((ord# ch                                  -# 0xE0#) `uncheckedIShiftL#` 12# +#
782                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#`  6# +#
783                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
784           unpack (nh +# 3#)
785       | otherwise            =
786           C# (chr# ((ord# ch                                  -# 0xF0#) `uncheckedIShiftL#` 18# +#
787                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12# +#
788                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#`  6# +#
789                     (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
790           unpack (nh +# 4#)
791       where
792         ch = indexCharOffAddr# addr nh
793
794 unpackNBytes# :: Addr# -> Int# -> [Char]
795 unpackNBytes# _addr 0#   = []
796 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
797     where
798      unpack acc i#
799       | i# <# 0#  = acc
800       | otherwise = 
801          case indexCharOffAddr# addr i# of
802             ch -> unpack (C# ch : acc) (i# -# 1#)
803
804 {-# RULES
805 "unpack"         forall a   . unpackCString# a             = build (unpackFoldrCString# a)
806 "unpack-list"    forall a   . unpackFoldrCString# a (:) [] = unpackCStringList# a
807 "unpack-append"  forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
808
809 -- There's a built-in rule (in GHC.Rules.lhs) for
810 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
811
812   #-}
813 \end{code}