c35d3c0fabb0e454637701059849d3ba749284af
[ghc-hetmet.git] / ghc / lib / std / PrelBase.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: PrelBase.lhs,v 1.46 2001/04/27 20:30:55 qrczak 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
219     compare []     []     = EQ
220     compare []     (_:_)  = LT
221     compare (_:_)  []     = GT
222     compare (x:xs) (y:ys) = case compare x y of
223                                 EQ    -> compare xs ys
224                                 other -> other
225
226 instance Functor [] where
227     fmap = map
228
229 instance  Monad []  where
230     m >>= k             = foldr ((++) . k) [] m
231     m >> k              = foldr ((++) . (\ _ -> k)) [] m
232     return x            = [x]
233     fail _              = []
234 \end{code}
235
236 A few list functions that appear here because they are used here.
237 The rest of the prelude list functions are in PrelList.
238
239 ----------------------------------------------
240 --      foldr/build/augment
241 ----------------------------------------------
242   
243 \begin{code}
244 foldr            :: (a -> b -> b) -> b -> [a] -> b
245 -- foldr _ z []     =  z
246 -- foldr f z (x:xs) =  f x (foldr f z xs)
247 {-# INLINE foldr #-}
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 2 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 "2" says to inline in phase 2
261
262 build g = g (:) []
263
264 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
265 {-# INLINE 2 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 "foldr/cons"    forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
279 "foldr/nil"     forall k z.      foldr k z []     = z 
280
281 "augment/build" forall (g::forall b. (a->b->b) -> b -> b)
282                        (h::forall b. (a->b->b) -> b -> b) .
283                        augment g (build h) = build (\c n -> g c (h c n))
284 "augment/nil"   forall (g::forall b. (a->b->b) -> b -> b) .
285                         augment g [] = build g
286  #-}
287
288 -- This rule is true, but not (I think) useful:
289 --      augment g (augment h t) = augment (\cn -> g c (h c n)) t
290 \end{code}
291
292
293 ----------------------------------------------
294 --              map     
295 ----------------------------------------------
296
297 \begin{code}
298 map :: (a -> b) -> [a] -> [b]
299 map = mapList
300
301 -- Note eta expanded
302 mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
303 mapFB c f x ys = c (f x) ys
304
305 mapList :: (a -> b) -> [a] -> [b]
306 mapList _ []     = []
307 mapList f (x:xs) = f x : mapList f xs
308
309 {-# RULES
310 "map"       forall f xs.        map f xs                = build (\c n -> foldr (mapFB c f) n xs)
311 "mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g) 
312 "mapList"   forall f.           foldr (mapFB (:) f) []  = mapList f
313  #-}
314 \end{code}
315
316
317 ----------------------------------------------
318 --              append  
319 ----------------------------------------------
320 \begin{code}
321 (++) :: [a] -> [a] -> [a]
322 (++) = append
323
324 {-# RULES
325   "++"  forall xs ys. (++) xs ys = augment (\c n -> foldr c n xs) ys
326  #-}
327
328 append :: [a] -> [a] -> [a]
329 append []     ys = ys
330 append (x:xs) ys = x : append xs ys
331 \end{code}
332
333
334 %*********************************************************
335 %*                                                      *
336 \subsection{Type @Bool@}
337 %*                                                      *
338 %*********************************************************
339
340 \begin{code}
341 data  Bool  =  False | True  deriving (Eq, Ord)
342         -- Read in PrelRead, Show in PrelShow
343
344 -- Boolean functions
345
346 (&&), (||)              :: Bool -> Bool -> Bool
347 True  && x              =  x
348 False && _              =  False
349 True  || _              =  True
350 False || x              =  x
351
352 not                     :: Bool -> Bool
353 not True                =  False
354 not False               =  True
355
356 otherwise               :: Bool
357 otherwise               =  True
358 \end{code}
359
360
361 %*********************************************************
362 %*                                                      *
363 \subsection{The @()@ type}
364 %*                                                      *
365 %*********************************************************
366
367 The Unit type is here because virtually any program needs it (whereas
368 some programs may get away without consulting PrelTup).  Furthermore,
369 the renamer currently *always* asks for () to be in scope, so that
370 ccalls can use () as their default type; so when compiling PrelBase we
371 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
372 it here seems more direct.)
373
374 \begin{code}
375 data  ()  =  ()
376
377 instance Eq () where
378     () == () = True
379     () /= () = False
380
381 instance Ord () where
382     () <= () = True
383     () <  () = False
384     () >= () = True
385     () >  () = False
386     max () () = ()
387     min () () = ()
388     compare () () = EQ
389 \end{code}
390
391
392 %*********************************************************
393 %*                                                      *
394 \subsection{Type @Ordering@}
395 %*                                                      *
396 %*********************************************************
397
398 \begin{code}
399 data Ordering = LT | EQ | GT deriving (Eq, Ord)
400         -- Read in PrelRead, Show in PrelShow
401 \end{code}
402
403
404 %*********************************************************
405 %*                                                      *
406 \subsection{Type @Char@ and @String@}
407 %*                                                      *
408 %*********************************************************
409
410 \begin{code}
411 type String = [Char]
412
413 data Char = C# Char#
414
415 -- We don't use deriving for Eq and Ord, because for Ord the derived
416 -- instance defines only compare, which takes two primops.  Then
417 -- '>' uses compare, and therefore takes two primops instead of one.
418
419 instance Eq Char where
420   (C# c1) == (C# c2) = c1 `eqChar#` c2
421   (C# c1) /= (C# c2) = c1 `neChar#` c2
422
423 instance Ord Char where
424   (C# c1) >  (C# c2) = c1 `gtChar#` c2
425   (C# c1) >= (C# c2) = c1 `geChar#` c2
426   (C# c1) <= (C# c2) = c1 `leChar#` c2
427   (C# c1) <  (C# c2) = c1 `ltChar#` c2
428
429 {- XXX
430 {-# RULES
431 "x# `eqChar#` x#" forall x#. eqChar# x# x# = True
432 "x# `neChar#` x#" forall x#. neChar# x# x# = False
433 "x# `gtChar#` x#" forall x#. gtChar# x# x# = False
434 "x# `geChar#` x#" forall x#. geChar# x# x# = True
435 "x# `leChar#` x#" forall x#. leChar# x# x# = True
436 "x# `ltChar#` x#" forall x#. ltChar# x# x# = False
437     #-}
438 -}
439
440 chr :: Int -> Char
441 chr (I# i) | i >=# 0# && i <=# 0x10FFFF# = C# (chr# i)
442            | otherwise                   = error "Prelude.chr: bad argument"
443
444 unsafeChr :: Int -> Char
445 unsafeChr (I# i) =  C# (chr# i)
446
447 ord :: Char -> Int
448 ord (C# c) =  I# (ord# c)
449 \end{code}
450
451 String equality is used when desugaring pattern-matches against strings.
452
453 \begin{code}
454 eqString :: String -> String -> Bool
455 eqString = (==)
456 \end{code}
457
458 %*********************************************************
459 %*                                                      *
460 \subsection{Type @Int@}
461 %*                                                      *
462 %*********************************************************
463
464 \begin{code}
465 data Int = I# Int#
466
467 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
468 zeroInt = I# 0#
469 oneInt  = I# 1#
470 twoInt  = I# 2#
471 #if WORD_SIZE_IN_BYTES == 4
472 minInt  = I# (-0x80000000#)
473 maxInt  = I# 0x7FFFFFFF#
474 #else
475 minInt  = I# (-0x8000000000000000#)
476 maxInt  = I# 0x7FFFFFFFFFFFFFFF#
477 #endif
478
479 instance Eq Int where
480     (==) = eqInt
481     (/=) = neInt
482
483 instance Ord Int where
484     compare = compareInt
485
486     (<)  = ltInt
487     (<=) = leInt
488     (>=) = geInt
489     (>)  = gtInt
490
491 compareInt :: Int -> Int -> Ordering
492 (I# x) `compareInt` (I# y) = compareInt# x y
493
494 compareInt# :: Int# -> Int# -> Ordering
495 compareInt# x# y#
496  | x# <#  y# = LT
497  | x# ==# y# = EQ
498  | otherwise = GT
499 \end{code}
500
501
502 %*********************************************************
503 %*                                                      *
504 \subsection{The function type}
505 %*                                                      *
506 %*********************************************************
507
508 \begin{code}
509 -- identity function
510 id                      :: a -> a
511 id x                    =  x
512
513 -- constant function
514 const                   :: a -> b -> a
515 const x _               =  x
516
517 -- function composition
518 {-# INLINE (.) #-}
519 (.)       :: (b -> c) -> (a -> b) -> a -> c
520 (.) f g x = f (g x)
521
522 -- flip f  takes its (first) two arguments in the reverse order of f.
523 flip                    :: (a -> b -> c) -> b -> a -> c
524 flip f x y              =  f y x
525
526 -- right-associating infix application operator (useful in continuation-
527 -- passing style)
528 {-# INLINE ($) #-}
529 ($)                     :: (a -> b) -> a -> b
530 f $ x                   =  f x
531
532 -- until p f  yields the result of applying f until p holds.
533 until                   :: (a -> Bool) -> (a -> a) -> a -> a
534 until p f x | p x       =  x
535             | otherwise =  until p f (f x)
536
537 -- asTypeOf is a type-restricted version of const.  It is usually used
538 -- as an infix operator, and its typing forces its first argument
539 -- (which is usually overloaded) to have the same type as the second.
540 asTypeOf                :: a -> a -> a
541 asTypeOf                =  const
542 \end{code}
543
544 %*********************************************************
545 %*                                                      *
546 \subsection{CCallable instances}
547 %*                                                      *
548 %*********************************************************
549
550 Defined here to avoid orphans
551
552 \begin{code}
553 instance CCallable Char
554 instance CReturnable Char
555
556 instance CCallable   Int
557 instance CReturnable Int
558
559 instance CReturnable () -- Why, exactly?
560 \end{code}
561
562
563 %*********************************************************
564 %*                                                      *
565 \subsection{Generics}
566 %*                                                      *
567 %*********************************************************
568
569 \begin{code}
570 data Unit = Unit
571 data a :+: b = Inl a | Inr b
572 data a :*: b = a :*: b
573 \end{code}
574
575
576 %*********************************************************
577 %*                                                      *
578 \subsection{Numeric primops}
579 %*                                                      *
580 %*********************************************************
581
582 \begin{code}
583 divInt#, modInt# :: Int# -> Int# -> Int#
584 x# `divInt#` y#
585     | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
586     | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
587     | otherwise                = x# `quotInt#` y#
588 x# `modInt#` y#
589     | (x# ># 0#) && (y# <# 0#) ||
590       (x# <# 0#) && (y# ># 0#)    = if r# /=# 0# then r# +# y# else 0#
591     | otherwise                   = r#
592     where
593     r# = x# `remInt#` y#
594 \end{code}
595
596 Definitions of the boxed PrimOps; these will be
597 used in the case of partial applications, etc.
598
599 \begin{code}
600 {-# INLINE eqInt #-}
601 {-# INLINE neInt #-}
602 {-# INLINE gtInt #-}
603 {-# INLINE geInt #-}
604 {-# INLINE ltInt #-}
605 {-# INLINE leInt #-}
606 {-# INLINE plusInt #-}
607 {-# INLINE minusInt #-}
608 {-# INLINE timesInt #-}
609 {-# INLINE quotInt #-}
610 {-# INLINE remInt #-}
611 {-# INLINE negateInt #-}
612
613 plusInt, minusInt, timesInt, quotInt, remInt, divInt, modInt, gcdInt :: Int -> Int -> Int
614 (I# x) `plusInt`  (I# y) = I# (x +# y)
615 (I# x) `minusInt` (I# y) = I# (x -# y)
616 (I# x) `timesInt` (I# y) = I# (x *# y)
617 (I# x) `quotInt`  (I# y) = I# (x `quotInt#` y)
618 (I# x) `remInt`   (I# y) = I# (x `remInt#`  y)
619 (I# x) `divInt`   (I# y) = I# (x `divInt#`  y)
620 (I# x) `modInt`   (I# y) = I# (x `modInt#`  y)
621
622 {- XXX
623 {-# RULES
624 "x# +# 0#" forall x#. x# +# 0# = x#
625 "0# +# x#" forall x#. 0# +# x# = x#
626 "x# -# 0#" forall x#. x# -# 0# = x#
627 "x# -# x#" forall x#. x# -# x# = 0#
628 "x# *# 0#" forall x#. x# *# 0# = 0#
629 "0# *# x#" forall x#. 0# *# x# = 0#
630 "x# *# 1#" forall x#. x# *# 1# = x#
631 "1# *# x#" forall x#. 1# *# x# = x#
632     #-}
633 -}
634
635 gcdInt (I# a) (I# b) = g a b
636    where g 0# 0# = error "PrelBase.gcdInt: gcd 0 0 is undefined"
637          g 0# _  = I# absB
638          g _  0# = I# absA
639          g _  _  = I# (gcdInt# absA absB)
640
641          absInt x = if x <# 0# then negateInt# x else x
642
643          absA     = absInt a
644          absB     = absInt b
645
646 negateInt :: Int -> Int
647 negateInt (I# x) = I# (negateInt# x)
648
649 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
650 (I# x) `gtInt` (I# y) = x >#  y
651 (I# x) `geInt` (I# y) = x >=# y
652 (I# x) `eqInt` (I# y) = x ==# y
653 (I# x) `neInt` (I# y) = x /=# y
654 (I# x) `ltInt` (I# y) = x <#  y
655 (I# x) `leInt` (I# y) = x <=# y
656
657 {- XXX
658 {-# RULES
659 "x# >#  x#" forall x#. x# >#  x# = False
660 "x# >=# x#" forall x#. x# >=# x# = True
661 "x# ==# x#" forall x#. x# ==# x# = True
662 "x# /=# x#" forall x#. x# /=# x# = False
663 "x# <#  x#" forall x#. x# <#  x# = False
664 "x# <=# x#" forall x#. x# <=# x# = True
665     #-}
666
667 #if WORD_SIZE_IN_BYTES == 4
668 {-# RULES
669 "intToInt32#"   forall x#. intToInt32#   x# = x#
670 "wordToWord32#" forall x#. wordToWord32# x# = x#
671      #-}
672 #endif
673
674 {-# RULES
675 "int2Word2Int"  forall x#. int2Word# (word2Int# x#) = x#
676 "word2Int2Word" forall x#. word2Int# (int2Word# x#) = x#
677     #-}
678 -}
679 \end{code}
680
681
682 %********************************************************
683 %*                                                      *
684 \subsection{Unpacking C strings}
685 %*                                                      *
686 %********************************************************
687
688 This code is needed for virtually all programs, since it's used for
689 unpacking the strings of error messages.
690
691 \begin{code}
692 unpackCString# :: Addr# -> [Char]
693 unpackCString# a = unpackCStringList# a
694
695 unpackCStringList# :: Addr# -> [Char]
696 unpackCStringList# addr 
697   = unpack 0#
698   where
699     unpack nh
700       | ch `eqChar#` '\0'# = []
701       | otherwise          = C# ch : unpack (nh +# 1#)
702       where
703         ch = indexCharOffAddr# addr nh
704
705 unpackAppendCString# :: Addr# -> [Char] -> [Char]
706 unpackAppendCString# addr rest
707   = unpack 0#
708   where
709     unpack nh
710       | ch `eqChar#` '\0'# = rest
711       | otherwise          = C# ch : unpack (nh +# 1#)
712       where
713         ch = indexCharOffAddr# addr nh
714
715 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
716 unpackFoldrCString# addr f z 
717   = unpack 0#
718   where
719     unpack nh
720       | ch `eqChar#` '\0'# = z
721       | otherwise          = C# ch `f` unpack (nh +# 1#)
722       where
723         ch = indexCharOffAddr# addr nh
724
725 unpackCStringUtf8# :: Addr# -> [Char]
726 unpackCStringUtf8# addr 
727   = unpack 0#
728   where
729     unpack nh
730       | ch `eqChar#` '\0'#   = []
731       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
732       | ch `leChar#` '\xDF'# =
733           C# (chr# ((ord# ch                                  -# 0xC0#) `iShiftL#`  6# +#
734                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
735           unpack (nh +# 2#)
736       | ch `leChar#` '\xEF'# =
737           C# (chr# ((ord# ch                                  -# 0xE0#) `iShiftL#` 12# +#
738                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `iShiftL#`  6# +#
739                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
740           unpack (nh +# 3#)
741       | otherwise            =
742           C# (chr# ((ord# ch                                  -# 0xF0#) `iShiftL#` 18# +#
743                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `iShiftL#` 12# +#
744                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `iShiftL#`  6# +#
745                     (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
746           unpack (nh +# 4#)
747       where
748         ch = indexCharOffAddr# addr nh
749
750 unpackNBytes# :: Addr# -> Int# -> [Char]
751 unpackNBytes# _addr 0#   = []
752 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
753     where
754      unpack acc i#
755       | i# <# 0#  = acc
756       | otherwise = 
757          case indexCharOffAddr# addr i# of
758             ch -> unpack (C# ch : acc) (i# -# 1#)
759
760 {-# RULES
761 "unpack"         forall a   . unpackCString# a             = build (unpackFoldrCString# a)
762 "unpack-list"    forall a   . unpackFoldrCString# a (:) [] = unpackCStringList# a
763 "unpack-append"  forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
764
765 -- There's a built-in rule (in PrelRules.lhs) for
766 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
767
768   #-}
769 \end{code}