[project @ 2001-12-14 12:05:15 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelBase.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: PrelBase.lhs,v 1.58 2001/12/14 12:05:15 simonmar Exp $
3 %
4 % (c) The University of Glasgow, 1992-2000
5 %
6 \section[PrelBase]{Module @PrelBase@}
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 PrelGHC         Has no implementation.  It defines built-in things, and
21                 by importing it you bring them into scope.
22                 The source file is PrelGHC.hi-boot, which is just
23                 copied to make PrelGHC.hi
24
25                 Classes: CCallable, CReturnable
26
27 PrelBase        Classes: Eq, Ord, Functor, Monad
28                 Types:   list, (), Int, Bool, Ordering, Char, String
29
30 PrelTup         Types: tuples, plus instances for PrelBase classes
31
32 PrelShow        Class: Show, plus instances for PrelBase/PrelTup types
33
34 PrelEnum        Class: Enum,  plus instances for PrelBase/PrelTup types
35
36 PrelMaybe       Type: Maybe, plus instances for PrelBase classes
37
38 PrelNum         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 PrelReal        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 PrelArr         Types: Array, MutableArray, MutableVar
55
56                 Does *not* contain any ByteArray stuff (see PrelByteArr)
57                 Arrays are used by a function in PrelFloat
58
59 PrelFloat       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 PrelFloat.hi
65
66 PrelByteArr     Types: ByteArray, MutableByteArray
67                 
68                 We want this one to be after PrelFloat, 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 PrelBase
81         (
82         module PrelBase,
83         module PrelGHC,         -- Re-export PrelGHC and PrelErr, to avoid lots
84         module PrelErr          -- of people having to import it explicitly
85   ) 
86         where
87
88 import PrelGHC
89 import {-# SOURCE #-} PrelErr
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 PrelBase 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 PrelList.
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/nil"     forall k z.      foldr k z []     = z 
287
288 "augment/build" forall (g::forall b. (a->b->b) -> b -> b)
289                        (h::forall b. (a->b->b) -> b -> b) .
290                        augment g (build h) = build (\c n -> g c (h c n))
291 "augment/nil"   forall (g::forall b. (a->b->b) -> b -> b) .
292                         augment g [] = build g
293  #-}
294
295 -- This rule is true, but not (I think) useful:
296 --      augment g (augment h t) = augment (\cn -> g c (h c n)) t
297 \end{code}
298
299
300 ----------------------------------------------
301 --              map     
302 ----------------------------------------------
303
304 \begin{code}
305 map :: (a -> b) -> [a] -> [b]
306 {-# NOINLINE [1] map #-}
307 map = mapList
308
309 -- Note eta expanded
310 mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
311 mapFB c f x ys = c (f x) ys
312
313 mapList :: (a -> b) -> [a] -> [b]
314 mapList _ []     = []
315 mapList f (x:xs) = f x : mapList f xs
316
317 {-# RULES
318 "map"       forall f xs.        map f xs                = build (\c n -> foldr (mapFB c f) n xs)
319 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
320 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
321   #-}
322 \end{code}
323
324
325 ----------------------------------------------
326 --              append  
327 ----------------------------------------------
328 \begin{code}
329 (++) :: [a] -> [a] -> [a]
330 {-# NOINLINE [1] (++) #-}
331 (++) = append
332
333 {-# RULES
334 "++"    forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys
335   #-}
336
337 append :: [a] -> [a] -> [a]
338 append []     ys = ys
339 append (x:xs) ys = x : append xs ys
340 \end{code}
341
342
343 %*********************************************************
344 %*                                                      *
345 \subsection{Type @Bool@}
346 %*                                                      *
347 %*********************************************************
348
349 \begin{code}
350 data  Bool  =  False | True  deriving (Eq, Ord)
351         -- Read in PrelRead, Show in PrelShow
352
353 -- Boolean functions
354
355 (&&), (||)              :: Bool -> Bool -> Bool
356 True  && x              =  x
357 False && _              =  False
358 True  || _              =  True
359 False || x              =  x
360
361 not                     :: Bool -> Bool
362 not True                =  False
363 not False               =  True
364
365 otherwise               :: Bool
366 otherwise               =  True
367 \end{code}
368
369
370 %*********************************************************
371 %*                                                      *
372 \subsection{The @()@ type}
373 %*                                                      *
374 %*********************************************************
375
376 The Unit type is here because virtually any program needs it (whereas
377 some programs may get away without consulting PrelTup).  Furthermore,
378 the renamer currently *always* asks for () to be in scope, so that
379 ccalls can use () as their default type; so when compiling PrelBase we
380 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
381 it here seems more direct.)
382
383 \begin{code}
384 data () = ()
385
386 instance Eq () where
387     () == () = True
388     () /= () = False
389
390 instance Ord () where
391     () <= () = True
392     () <  () = False
393     () >= () = True
394     () >  () = False
395     max () () = ()
396     min () () = ()
397     compare () () = EQ
398 \end{code}
399
400
401 %*********************************************************
402 %*                                                      *
403 \subsection{Type @Ordering@}
404 %*                                                      *
405 %*********************************************************
406
407 \begin{code}
408 data Ordering = LT | EQ | GT deriving (Eq, Ord)
409         -- Read in PrelRead, Show in PrelShow
410 \end{code}
411
412
413 %*********************************************************
414 %*                                                      *
415 \subsection{Type @Char@ and @String@}
416 %*                                                      *
417 %*********************************************************
418
419 \begin{code}
420 type String = [Char]
421
422 data Char = C# Char#
423
424 -- We don't use deriving for Eq and Ord, because for Ord the derived
425 -- instance defines only compare, which takes two primops.  Then
426 -- '>' uses compare, and therefore takes two primops instead of one.
427
428 instance Eq Char where
429     (C# c1) == (C# c2) = c1 `eqChar#` c2
430     (C# c1) /= (C# c2) = c1 `neChar#` c2
431
432 instance Ord Char where
433     (C# c1) >  (C# c2) = c1 `gtChar#` c2
434     (C# c1) >= (C# c2) = c1 `geChar#` c2
435     (C# c1) <= (C# c2) = c1 `leChar#` c2
436     (C# c1) <  (C# c2) = c1 `ltChar#` c2
437
438 {-# RULES
439 "x# `eqChar#` x#" forall x#. x# `eqChar#` x# = True
440 "x# `neChar#` x#" forall x#. x# `neChar#` x# = False
441 "x# `gtChar#` x#" forall x#. x# `gtChar#` x# = False
442 "x# `geChar#` x#" forall x#. x# `geChar#` x# = True
443 "x# `leChar#` x#" forall x#. x# `leChar#` x# = True
444 "x# `ltChar#` x#" forall x#. x# `ltChar#` x# = False
445   #-}
446
447 chr :: Int -> Char
448 chr (I# i#) | int2Word# i# `leWord#` int2Word# 0x10FFFF# = C# (chr# i#)
449             | otherwise                                  = error "Prelude.chr: bad argument"
450
451 unsafeChr :: Int -> Char
452 unsafeChr (I# i#) = C# (chr# i#)
453
454 ord :: Char -> Int
455 ord (C# c#) = I# (ord# c#)
456 \end{code}
457
458 String equality is used when desugaring pattern-matches against strings.
459
460 \begin{code}
461 eqString :: String -> String -> Bool
462 eqString []       []       = True
463 eqString (c1:cs1) (c2:cs2) = c1 == c2 && cs1 `eqString` cs2
464 eqString cs1      cs2      = False
465
466 {-# RULES "eqString" (==) = eqString #-}
467 \end{code}
468
469
470 %*********************************************************
471 %*                                                      *
472 \subsection{Type @Int@}
473 %*                                                      *
474 %*********************************************************
475
476 \begin{code}
477 data Int = I# Int#
478
479 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
480 zeroInt = I# 0#
481 oneInt  = I# 1#
482 twoInt  = I# 2#
483
484 {- Seems clumsy. Should perhaps put minInt and MaxInt directly into MachDeps.h -}
485 #if WORD_SIZE_IN_BITS == 31
486 minInt  = I# (-0x40000000#)
487 maxInt  = I# 0x3FFFFFFF#
488 #elif WORD_SIZE_IN_BITS == 32
489 minInt  = I# (-0x80000000#)
490 maxInt  = I# 0x7FFFFFFF#
491 #else 
492 minInt  = I# (-0x8000000000000000#)
493 maxInt  = I# 0x7FFFFFFFFFFFFFFF#
494 #endif
495
496 instance Eq Int where
497     (==) = eqInt
498     (/=) = neInt
499
500 instance Ord Int where
501     compare = compareInt
502     (<)     = ltInt
503     (<=)    = leInt
504     (>=)    = geInt
505     (>)     = gtInt
506
507 compareInt :: Int -> Int -> Ordering
508 (I# x#) `compareInt` (I# y#) = compareInt# x# y#
509
510 compareInt# :: Int# -> Int# -> Ordering
511 compareInt# x# y#
512     | x# <#  y# = LT
513     | x# ==# y# = EQ
514     | otherwise = GT
515 \end{code}
516
517
518 %*********************************************************
519 %*                                                      *
520 \subsection{The function type}
521 %*                                                      *
522 %*********************************************************
523
524 \begin{code}
525 -- identity function
526 id                      :: a -> a
527 id x                    =  x
528
529 -- constant function
530 const                   :: a -> b -> a
531 const x _               =  x
532
533 -- function composition
534 {-# INLINE (.) #-}
535 (.)       :: (b -> c) -> (a -> b) -> a -> c
536 (.) f g x = f (g x)
537
538 -- flip f  takes its (first) two arguments in the reverse order of f.
539 flip                    :: (a -> b -> c) -> b -> a -> c
540 flip f x y              =  f y x
541
542 -- right-associating infix application operator (useful in continuation-
543 -- passing style)
544 {-# INLINE ($) #-}
545 ($)                     :: (a -> b) -> a -> b
546 f $ x                   =  f x
547
548 -- until p f  yields the result of applying f until p holds.
549 until                   :: (a -> Bool) -> (a -> a) -> a -> a
550 until p f x | p x       =  x
551             | otherwise =  until p f (f x)
552
553 -- asTypeOf is a type-restricted version of const.  It is usually used
554 -- as an infix operator, and its typing forces its first argument
555 -- (which is usually overloaded) to have the same type as the second.
556 asTypeOf                :: a -> a -> a
557 asTypeOf                =  const
558 \end{code}
559
560 %*********************************************************
561 %*                                                      *
562 \subsection{CCallable instances}
563 %*                                                      *
564 %*********************************************************
565
566 Defined here to avoid orphans
567
568 \begin{code}
569 instance CCallable Char
570 instance CReturnable Char
571
572 instance CCallable   Int
573 instance CReturnable Int
574
575 instance CReturnable () -- Why, exactly?
576 \end{code}
577
578
579 %*********************************************************
580 %*                                                      *
581 \subsection{Generics}
582 %*                                                      *
583 %*********************************************************
584
585 \begin{code}
586 data Unit = Unit
587 data a :+: b = Inl a | Inr b
588 data a :*: b = a :*: b
589 \end{code}
590
591
592 %*********************************************************
593 %*                                                      *
594 \subsection{Numeric primops}
595 %*                                                      *
596 %*********************************************************
597
598 \begin{code}
599 divInt#, modInt# :: Int# -> Int# -> Int#
600 x# `divInt#` y#
601     | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
602     | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
603     | otherwise                = x# `quotInt#` y#
604 x# `modInt#` y#
605     | (x# ># 0#) && (y# <# 0#) ||
606       (x# <# 0#) && (y# ># 0#)    = if r# /=# 0# then r# +# y# else 0#
607     | otherwise                   = r#
608     where
609     r# = x# `remInt#` y#
610 \end{code}
611
612 Definitions of the boxed PrimOps; these will be
613 used in the case of partial applications, etc.
614
615 \begin{code}
616 {-# INLINE eqInt #-}
617 {-# INLINE neInt #-}
618 {-# INLINE gtInt #-}
619 {-# INLINE geInt #-}
620 {-# INLINE ltInt #-}
621 {-# INLINE leInt #-}
622 {-# INLINE plusInt #-}
623 {-# INLINE minusInt #-}
624 {-# INLINE timesInt #-}
625 {-# INLINE quotInt #-}
626 {-# INLINE remInt #-}
627 {-# INLINE negateInt #-}
628
629 plusInt, minusInt, timesInt, quotInt, remInt, divInt, modInt, gcdInt :: Int -> Int -> Int
630 (I# x) `plusInt`  (I# y) = I# (x +# y)
631 (I# x) `minusInt` (I# y) = I# (x -# y)
632 (I# x) `timesInt` (I# y) = I# (x *# y)
633 (I# x) `quotInt`  (I# y) = I# (x `quotInt#` y)
634 (I# x) `remInt`   (I# y) = I# (x `remInt#`  y)
635 (I# x) `divInt`   (I# y) = I# (x `divInt#`  y)
636 (I# x) `modInt`   (I# y) = I# (x `modInt#`  y)
637
638 {-# RULES
639 "x# +# 0#" forall x#. x# +# 0# = x#
640 "0# +# x#" forall x#. 0# +# x# = x#
641 "x# -# 0#" forall x#. x# -# 0# = x#
642 "x# -# x#" forall x#. x# -# x# = 0#
643 "x# *# 0#" forall x#. x# *# 0# = 0#
644 "0# *# x#" forall x#. 0# *# x# = 0#
645 "x# *# 1#" forall x#. x# *# 1# = x#
646 "1# *# x#" forall x#. 1# *# x# = x#
647   #-}
648
649 gcdInt (I# a) (I# b) = g a b
650    where g 0# 0# = error "PrelBase.gcdInt: gcd 0 0 is undefined"
651          g 0# _  = I# absB
652          g _  0# = I# absA
653          g _  _  = I# (gcdInt# absA absB)
654
655          absInt x = if x <# 0# then negateInt# x else x
656
657          absA     = absInt a
658          absB     = absInt b
659
660 negateInt :: Int -> Int
661 negateInt (I# x) = I# (negateInt# x)
662
663 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
664 (I# x) `gtInt` (I# y) = x >#  y
665 (I# x) `geInt` (I# y) = x >=# y
666 (I# x) `eqInt` (I# y) = x ==# y
667 (I# x) `neInt` (I# y) = x /=# y
668 (I# x) `ltInt` (I# y) = x <#  y
669 (I# x) `leInt` (I# y) = x <=# y
670
671 {-# RULES
672 "x# ># x#"  forall x#. x# >#  x# = False
673 "x# >=# x#" forall x#. x# >=# x# = True
674 "x# ==# x#" forall x#. x# ==# x# = True
675 "x# /=# x#" forall x#. x# /=# x# = False
676 "x# <# x#"  forall x#. x# <#  x# = False
677 "x# <=# x#" forall x#. x# <=# x# = True
678   #-}
679
680 -- Wrappers for the shift operations.  The uncheckedShift# family are
681 -- undefined when the amount being shifted by is greater than the size
682 -- in bits of Int#, so these wrappers perform a check and return
683 -- either zero or -1 appropriately.
684 --
685 -- Note that these wrappers still produce undefined results when the
686 -- second argument (the shift amount) is negative.
687
688 shiftL#, shiftRL# :: Word# -> Int# -> Word#
689
690 a `shiftL#` b   | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
691                 | otherwise                = a `uncheckedShiftL#` b
692
693 a `shiftRL#` b  | b >=# WORD_SIZE_IN_BITS# = int2Word# 0#
694                 | otherwise                = a `uncheckedShiftRL#` b
695
696 iShiftL#, iShiftRA#, iShiftRL# :: Int# -> Int# -> Int#
697
698 a `iShiftL#` b  | b >=# WORD_SIZE_IN_BITS# = 0#
699                 | otherwise                = a `uncheckedIShiftL#` b
700
701 a `iShiftRA#` b | b >=# WORD_SIZE_IN_BITS# = if a <# 0# then (-1#) else 0#
702                 | otherwise                = a `uncheckedIShiftRA#` b
703
704 a `iShiftRL#` b | b >=# WORD_SIZE_IN_BITS# = 0#
705                 | otherwise                = a `uncheckedIShiftRL#` b
706
707 #if WORD_SIZE_IN_BITS == 32
708 {-# RULES
709 "narrow32Int#"  forall x#. narrow32Int#   x# = x#
710 "narrow32Word#" forall x#. narrow32Word#   x# = x#
711    #-}
712 #endif
713
714 {-# RULES
715 "int2Word2Int"  forall x#. int2Word# (word2Int# x#) = x#
716 "word2Int2Word" forall x#. word2Int# (int2Word# x#) = x#
717   #-}
718 \end{code}
719
720
721 %********************************************************
722 %*                                                      *
723 \subsection{Unpacking C strings}
724 %*                                                      *
725 %********************************************************
726
727 This code is needed for virtually all programs, since it's used for
728 unpacking the strings of error messages.
729
730 \begin{code}
731 unpackCString# :: Addr# -> [Char]
732 {-# NOINLINE [1] unpackCString# #-}
733 unpackCString# a = unpackCStringList# a
734
735 unpackCStringList# :: Addr# -> [Char]
736 unpackCStringList# addr 
737   = unpack 0#
738   where
739     unpack nh
740       | ch `eqChar#` '\0'# = []
741       | otherwise          = C# ch : unpack (nh +# 1#)
742       where
743         ch = indexCharOffAddr# addr nh
744
745 unpackAppendCString# :: Addr# -> [Char] -> [Char]
746 unpackAppendCString# addr rest
747   = unpack 0#
748   where
749     unpack nh
750       | ch `eqChar#` '\0'# = rest
751       | otherwise          = C# ch : unpack (nh +# 1#)
752       where
753         ch = indexCharOffAddr# addr nh
754
755 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
756 {-# NOINLINE [0] unpackFoldrCString# #-}
757 -- Don't inline till right at the end;
758 -- usually the unpack-list rule turns it into unpackCStringList
759 unpackFoldrCString# addr f z 
760   = unpack 0#
761   where
762     unpack nh
763       | ch `eqChar#` '\0'# = z
764       | otherwise          = C# ch `f` unpack (nh +# 1#)
765       where
766         ch = indexCharOffAddr# addr nh
767
768 unpackCStringUtf8# :: Addr# -> [Char]
769 unpackCStringUtf8# addr 
770   = unpack 0#
771   where
772     unpack nh
773       | ch `eqChar#` '\0'#   = []
774       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
775       | ch `leChar#` '\xDF'# =
776           C# (chr# ((ord# ch                                  -# 0xC0#) `uncheckedIShiftL#`  6# +#
777                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
778           unpack (nh +# 2#)
779       | ch `leChar#` '\xEF'# =
780           C# (chr# ((ord# ch                                  -# 0xE0#) `uncheckedIShiftL#` 12# +#
781                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#`  6# +#
782                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
783           unpack (nh +# 3#)
784       | otherwise            =
785           C# (chr# ((ord# ch                                  -# 0xF0#) `uncheckedIShiftL#` 18# +#
786                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12# +#
787                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#`  6# +#
788                     (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
789           unpack (nh +# 4#)
790       where
791         ch = indexCharOffAddr# addr nh
792
793 unpackNBytes# :: Addr# -> Int# -> [Char]
794 unpackNBytes# _addr 0#   = []
795 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
796     where
797      unpack acc i#
798       | i# <# 0#  = acc
799       | otherwise = 
800          case indexCharOffAddr# addr i# of
801             ch -> unpack (C# ch : acc) (i# -# 1#)
802
803 {-# RULES
804 "unpack"         forall a   . unpackCString# a             = build (unpackFoldrCString# a)
805 "unpack-list"    forall a   . unpackFoldrCString# a (:) [] = unpackCStringList# a
806 "unpack-append"  forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
807
808 -- There's a built-in rule (in PrelRules.lhs) for
809 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
810
811   #-}
812 \end{code}