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