[project @ 2001-02-22 16:10:12 by rrt]
[ghc-hetmet.git] / ghc / lib / std / PrelBase.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: PrelBase.lhs,v 1.40 2001/02/18 14:45:15 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 module PrelBase
79         (
80         module PrelBase,
81         module PrelGHC,         -- Re-export PrelGHC, PrelErr & PrelNum, to avoid lots
82         module PrelErr          -- of people having to import it explicitly
83   ) 
84         where
85
86 import PrelGHC
87 import {-# SOURCE #-} PrelErr
88
89 infixr 9  .
90 infixr 5  ++, :
91 infix  4  ==, /=, <, <=, >=, >
92 infixr 3  &&
93 infixr 2  ||
94 infixl 1  >>, >>=
95 infixr 0  $
96
97 default ()              -- Double isn't available yet
98 \end{code}
99
100
101 %*********************************************************
102 %*                                                      *
103 \subsection{DEBUGGING STUFF}
104 %*  (for use when compiling PrelBase itself doesn't work)
105 %*                                                      *
106 %*********************************************************
107
108 \begin{code}
109 {-
110 data  Bool  =  False | True
111 data Ordering = LT | EQ | GT 
112 data Char = C# Char#
113 type  String = [Char]
114 data Int = I# Int#
115 data  ()  =  ()
116 data [] a = MkNil
117
118 not True = False
119 (&&) True True = True
120 otherwise = True
121
122 build = error "urk"
123 foldr = error "urk"
124
125 unpackCString# :: Addr# -> [Char]
126 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
127 unpackAppendCString# :: Addr# -> [Char] -> [Char]
128 unpackCStringUtf8# :: Addr# -> [Char]
129 unpackCString# a = error "urk"
130 unpackFoldrCString# a = error "urk"
131 unpackAppendCString# a = error "urk"
132 unpackCStringUtf8# a = error "urk"
133 -}
134 \end{code}
135
136
137 %*********************************************************
138 %*                                                      *
139 \subsection{Standard classes @Eq@, @Ord@}
140 %*                                                      *
141 %*********************************************************
142
143 \begin{code}
144 class  Eq a  where
145     (==), (/=)          :: a -> a -> Bool
146
147     (/=) x y            = not ((==) x y)
148     (==) x y            = not ((/=) x y)
149
150 class  (Eq a) => Ord a  where
151     compare             :: a -> a -> Ordering
152     (<), (<=), (>=), (>):: a -> a -> Bool
153     max, min            :: a -> a -> a
154
155 -- An instance of Ord should define either compare or <=
156 -- Using compare can be more efficient for complex types.
157     compare x y
158             | x == y    = EQ
159             | x <= y    = LT    -- NB: must be '<=' not '<' to validate the
160                                 -- above claim about the minimal things that can
161                                 -- be defined for an instance of Ord
162             | otherwise = GT
163
164     x <= y  = case compare x y of { GT -> False; _other -> True }
165     x <  y  = case compare x y of { LT -> True;  _other -> False }
166     x >= y  = case compare x y of { LT -> False; _other -> True }
167     x >  y  = case compare x y of { GT -> True;  _other -> False }
168
169         -- These two default methods use '>' rather than compare
170         -- because the latter is often more expensive
171     max x y = if x > y then x else y
172     min x y = if x > y then y else x
173 \end{code}
174
175 %*********************************************************
176 %*                                                      *
177 \subsection{Monadic classes @Functor@, @Monad@ }
178 %*                                                      *
179 %*********************************************************
180
181 \begin{code}
182 class  Functor f  where
183     fmap        :: (a -> b) -> f a -> f b
184
185 class  Monad m  where
186     (>>=)       :: m a -> (a -> m b) -> m b
187     (>>)        :: m a -> m b -> m b
188     return      :: a -> m a
189     fail        :: String -> m a
190
191     m >> k      =  m >>= \_ -> k
192     fail s      = error s
193 \end{code}
194
195
196 %*********************************************************
197 %*                                                      *
198 \subsection{The list type}
199 %*                                                      *
200 %*********************************************************
201
202 \begin{code}
203 data [] a = [] | a : [a]  -- do explicitly: deriving (Eq, Ord)
204                           -- to avoid weird names like con2tag_[]#
205
206
207 instance (Eq a) => Eq [a]  where
208 {-
209     {-# SPECIALISE instance Eq [Char] #-}
210 -}
211     []     == []     = True     
212     (x:xs) == (y:ys) = x == y && xs == ys
213     _xs    == _ys    = False                    
214
215     xs     /= ys     = if (xs == ys) then False else True
216
217 instance (Ord a) => Ord [a] where
218 {-
219     {-# SPECIALISE instance Ord [Char] #-}
220 -}
221     a <  b  = case compare a b of { LT -> True;  EQ -> False; GT -> False }
222     a <= b  = case compare a b of { LT -> True;  EQ -> True;  GT -> False }
223     a >= b  = case compare a b of { LT -> False; EQ -> True;  GT -> True  }
224     a >  b  = case compare a b of { LT -> False; EQ -> False; GT -> True  }
225
226     compare []     []     = EQ
227     compare (_:_)  []     = GT
228     compare []     (_:_)  = LT
229     compare (x:xs) (y:ys) = case compare x y of
230                                  LT -> LT       
231                                  GT -> GT               
232                                  EQ -> compare xs ys
233
234 instance Functor [] where
235     fmap = map
236
237 instance  Monad []  where
238     m >>= k             = foldr ((++) . k) [] m
239     m >> k              = foldr ((++) . (\ _ -> k)) [] m
240     return x            = [x]
241     fail _              = []
242 \end{code}
243
244 A few list functions that appear here because they are used here.
245 The rest of the prelude list functions are in PrelList.
246
247 ----------------------------------------------
248 --      foldr/build/augment
249 ----------------------------------------------
250   
251 \begin{code}
252 foldr            :: (a -> b -> b) -> b -> [a] -> b
253 -- foldr _ z []     =  z
254 -- foldr f z (x:xs) =  f x (foldr f z xs)
255 {-# INLINE foldr #-}
256 foldr k z xs = go xs
257              where
258                go []     = z
259                go (y:ys) = y `k` go ys
260
261 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
262 {-# INLINE 2 build #-}
263         -- The INLINE is important, even though build is tiny,
264         -- because it prevents [] getting inlined in the version that
265         -- appears in the interface file.  If [] *is* inlined, it
266         -- won't match with [] appearing in rules in an importing module.
267         --
268         -- The "2" says to inline in phase 2
269
270 build g = g (:) []
271
272 augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
273 {-# INLINE 2 augment #-}
274 augment g xs = g (:) xs
275
276 {-# RULES
277 "fold/build"    forall k z (g::forall b. (a->b->b) -> b -> b) . 
278                 foldr k z (build g) = g k z
279
280 "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . 
281                 foldr k z (augment g xs) = g k (foldr k z xs)
282
283 "foldr/id"      foldr (:) [] = \x->x
284 "foldr/app"     forall xs ys. foldr (:) ys xs = append xs ys
285
286 "foldr/cons"    forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
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 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 (++) = append
331
332 {-# RULES
333   "++"  forall xs ys. (++) xs ys = augment (\c n -> foldr c n xs) ys
334  #-}
335
336 append :: [a] -> [a] -> [a]
337 append []     ys = ys
338 append (x:xs) ys = x : append xs ys
339 \end{code}
340
341
342 %*********************************************************
343 %*                                                      *
344 \subsection{Type @Bool@}
345 %*                                                      *
346 %*********************************************************
347
348 \begin{code}
349 data  Bool  =  False | True  deriving (Eq, Ord)
350         -- Read in PrelRead, Show in PrelShow
351
352 -- Boolean functions
353
354 (&&), (||)              :: Bool -> Bool -> Bool
355 True  && x              =  x
356 False && _              =  False
357 True  || _              =  True
358 False || x              =  x
359
360 not                     :: Bool -> Bool
361 not True                =  False
362 not False               =  True
363
364 otherwise               :: Bool
365 otherwise               =  True
366 \end{code}
367
368
369 %*********************************************************
370 %*                                                      *
371 \subsection{The @()@ type}
372 %*                                                      *
373 %*********************************************************
374
375 The Unit type is here because virtually any program needs it (whereas
376 some programs may get away without consulting PrelTup).  Furthermore,
377 the renamer currently *always* asks for () to be in scope, so that
378 ccalls can use () as their default type; so when compiling PrelBase we
379 need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
380 it here seems more direct.)
381
382 \begin{code}
383 data  ()  =  ()
384
385 instance Eq () where
386     () == () = True
387     () /= () = False
388
389 instance Ord () where
390     () <= () = True
391     () <  () = False
392     () >= () = True
393     () >  () = False
394     max () () = ()
395     min () () = ()
396     compare () () = EQ
397 \end{code}
398
399
400 %*********************************************************
401 %*                                                      *
402 \subsection{Type @Ordering@}
403 %*                                                      *
404 %*********************************************************
405
406 \begin{code}
407 data Ordering = LT | EQ | GT deriving (Eq, Ord)
408         -- Read in PrelRead, Show in PrelShow
409 \end{code}
410
411
412 %*********************************************************
413 %*                                                      *
414 \subsection{Type @Char@ and @String@}
415 %*                                                      *
416 %*********************************************************
417
418 \begin{code}
419 type  String = [Char]
420
421 data Char = C# Char#
422
423 -- We don't use deriving for Eq and Ord, because for Ord the derived
424 -- instance defines only compare, which takes two primops.  Then
425 -- '>' uses compare, and therefore takes two primops instead of one.
426
427 instance Eq Char where
428   (C# c1) == (C# c2) = c1 `eqChar#` c2
429   (C# c1) /= (C# c2) = c1 `neChar#` c2
430
431 instance Ord Char where
432   (C# c1) >  (C# c2) = c1 `gtChar#` c2
433   (C# c1) >= (C# c2) = c1 `geChar#` c2
434   (C# c1) <= (C# c2) = c1 `leChar#` c2
435   (C# c1) <  (C# c2) = c1 `ltChar#` c2
436
437 chr :: Int -> Char
438 chr (I# i) | i >=# 0# && i <=# 0x10FFFF#
439              = C# (chr# i)
440            | otherwise = error "Prelude.chr: bad argument"
441
442 unsafeChr :: Int -> Char
443 unsafeChr (I# i) =  C# (chr# i)
444
445 ord :: Char -> Int
446 ord (C# c) =  I# (ord# c)
447 \end{code}
448
449 String equality is used when desugaring pattern-matches against strings.
450 It's worth making it fast, and providing a rule to use the fast version
451 where possible.
452
453 \begin{code}
454 eqString :: String -> String -> Bool
455 eqString []            []            = True
456 eqString (C# c1 : cs1) (C# c2 : cs2) = c1 `eqChar#` c2 && cs1 `eqString` cs2
457 eqString _             _             = False
458
459 {-# RULES
460 "eqString"  (==) = eqString
461   #-}  
462 \end{code}
463
464 %*********************************************************
465 %*                                                      *
466 \subsection{Type @Int@}
467 %*                                                      *
468 %*********************************************************
469
470 \begin{code}
471 data Int = I# Int#
472
473 zeroInt, oneInt, twoInt, maxInt, minInt :: Int
474 zeroInt = I# 0#
475 oneInt  = I# 1#
476 twoInt  = I# 2#
477 minInt  = I# (-2147483648#)     -- GHC <= 2.09 had this at -2147483647
478 maxInt  = I# 2147483647#
479
480 instance Eq Int where
481     (==) x y = x `eqInt` y
482     (/=) x y = x `neInt` y
483
484 instance Ord Int where
485     compare x y = compareInt x y 
486
487     (<)  x y = ltInt x y
488     (<=) x y = leInt x y
489     (>=) x y = geInt x y
490     (>)  x y = gtInt x y
491
492 compareInt :: Int -> Int -> Ordering
493 (I# x) `compareInt` (I# y) | x <# y    = LT
494                            | x ==# y   = EQ
495                            | otherwise = GT
496 \end{code}
497
498
499 %*********************************************************
500 %*                                                      *
501 \subsection{The function type}
502 %*                                                      *
503 %*********************************************************
504
505 \begin{code}
506 -- identity function
507 id                      :: a -> a
508 id x                    =  x
509
510 -- constant function
511 const                   :: a -> b -> a
512 const x _               =  x
513
514 -- function composition
515 {-# INLINE (.) #-}
516 (.)       :: (b -> c) -> (a -> b) -> a -> c
517 (.) f g x = f (g x)
518
519 -- flip f  takes its (first) two arguments in the reverse order of f.
520 flip                    :: (a -> b -> c) -> b -> a -> c
521 flip f x y              =  f y x
522
523 -- right-associating infix application operator (useful in continuation-
524 -- passing style)
525 ($)                     :: (a -> b) -> a -> b
526 f $ x                   =  f x
527
528 -- until p f  yields the result of applying f until p holds.
529 until                   :: (a -> Bool) -> (a -> a) -> a -> a
530 until p f x | p x       =  x
531             | otherwise =  until p f (f x)
532
533 -- asTypeOf is a type-restricted version of const.  It is usually used
534 -- as an infix operator, and its typing forces its first argument
535 -- (which is usually overloaded) to have the same type as the second.
536 asTypeOf                :: a -> a -> a
537 asTypeOf                =  const
538 \end{code}
539
540 %*********************************************************
541 %*                                                      *
542 \subsection{CCallable instances}
543 %*                                                      *
544 %*********************************************************
545
546 Defined here to avoid orphans
547
548 \begin{code}
549 instance CCallable Char
550 instance CReturnable Char
551
552 instance CCallable   Int
553 instance CReturnable Int
554
555 instance CReturnable () -- Why, exactly?
556 \end{code}
557
558
559 %*********************************************************
560 %*                                                      *
561 \subsection{Generics}
562 %*                                                      *
563 %*********************************************************
564
565 \begin{code}
566 data Unit = Unit
567 data a :+: b = Inl a | Inr b
568 data a :*: b = a :*: b
569 \end{code}
570
571
572 %*********************************************************
573 %*                                                      *
574 \subsection{Numeric primops}
575 %*                                                      *
576 %*********************************************************
577
578 Definitions of the boxed PrimOps; these will be
579 used in the case of partial applications, etc.
580
581 \begin{code}
582 {-# INLINE eqInt #-}
583 {-# INLINE neInt #-}
584 {-# INLINE gtInt #-}
585 {-# INLINE geInt #-}
586 {-# INLINE ltInt #-}
587 {-# INLINE leInt #-}
588 {-# INLINE plusInt #-}
589 {-# INLINE minusInt #-}
590 {-# INLINE timesInt #-}
591 {-# INLINE quotInt #-}
592 {-# INLINE remInt #-}
593 {-# INLINE negateInt #-}
594
595 plusInt, minusInt, timesInt, quotInt, remInt, gcdInt :: Int -> Int -> Int
596 plusInt (I# x) (I# y) = I# (x +# y)
597 minusInt(I# x) (I# y) = I# (x -# y)
598 timesInt(I# x) (I# y) = I# (x *# y)
599 quotInt (I# x) (I# y) = I# (quotInt# x y)
600 remInt  (I# x) (I# y) = I# (remInt#  x y)
601
602 gcdInt (I# a) (I# b) = g a b
603    where g 0# 0# = error "PrelBase.gcdInt: gcd 0 0 is undefined"
604          g 0# _  = I# absB
605          g _  0# = I# absA
606          g _  _  = I# (gcdInt# absA absB)
607
608          absInt x = if x <# 0# then negateInt# x else x
609
610          absA     = absInt a
611          absB     = absInt b
612
613 negateInt :: Int -> Int
614 negateInt (I# x) = I# (negateInt# x)
615
616 divInt, modInt :: Int -> Int -> Int
617 x `divInt` y 
618   | x > zeroInt && y < zeroInt = quotInt ((x `minusInt` y) `minusInt` oneInt) y
619   | x < zeroInt && y > zeroInt = quotInt ((x `minusInt` y) `plusInt`  oneInt) y
620   | otherwise      = quotInt x y
621
622 x `modInt` y 
623   | x > zeroInt && y < zeroInt || 
624     x < zeroInt && y > zeroInt  = if r/=zeroInt then r `plusInt` y else zeroInt
625   | otherwise                   = r
626   where
627     r = remInt x y
628
629 gtInt, geInt, eqInt, neInt, ltInt, leInt :: Int -> Int -> Bool
630 gtInt   (I# x) (I# y) = x ># y
631 geInt   (I# x) (I# y) = x >=# y
632 eqInt   (I# x) (I# y) = x ==# y
633 neInt   (I# x) (I# y) = x /=# y
634 ltInt   (I# x) (I# y) = x <# y
635 leInt   (I# x) (I# y) = x <=# y
636 \end{code}
637
638
639 %********************************************************
640 %*                                                      *
641 \subsection{Unpacking C strings}
642 %*                                                      *
643 %********************************************************
644
645 This code is needed for virtually all programs, since it's used for
646 unpacking the strings of error messages.
647
648 \begin{code}
649 unpackCString# :: Addr# -> [Char]
650 unpackCString# a = unpackCStringList# a
651
652 unpackCStringList# :: Addr# -> [Char]
653 unpackCStringList# addr 
654   = unpack 0#
655   where
656     unpack nh
657       | ch `eqChar#` '\0'# = []
658       | otherwise          = C# ch : unpack (nh +# 1#)
659       where
660         ch = indexCharOffAddr# addr nh
661
662 unpackAppendCString# :: Addr# -> [Char] -> [Char]
663 unpackAppendCString# addr rest
664   = unpack 0#
665   where
666     unpack nh
667       | ch `eqChar#` '\0'# = rest
668       | otherwise          = C# ch : unpack (nh +# 1#)
669       where
670         ch = indexCharOffAddr# addr nh
671
672 unpackFoldrCString# :: Addr# -> (Char  -> a -> a) -> a -> a 
673 unpackFoldrCString# addr f z 
674   = unpack 0#
675   where
676     unpack nh
677       | ch `eqChar#` '\0'# = z
678       | otherwise          = C# ch `f` unpack (nh +# 1#)
679       where
680         ch = indexCharOffAddr# addr nh
681
682 unpackCStringUtf8# :: Addr# -> [Char]
683 unpackCStringUtf8# addr 
684   = unpack 0#
685   where
686     unpack nh
687       | ch `eqChar#` '\0'#   = []
688       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
689       | ch `leChar#` '\xDF'# =
690           C# (chr# ((ord# ch                                  -# 0xC0#) `iShiftL#`  6# +#
691                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
692           unpack (nh +# 2#)
693       | ch `leChar#` '\xEF'# =
694           C# (chr# ((ord# ch                                  -# 0xE0#) `iShiftL#` 12# +#
695                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `iShiftL#`  6# +#
696                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
697           unpack (nh +# 3#)
698       | otherwise            =
699           C# (chr# ((ord# ch                                  -# 0xF0#) `iShiftL#` 18# +#
700                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `iShiftL#` 12# +#
701                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `iShiftL#`  6# +#
702                     (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
703           unpack (nh +# 4#)
704       where
705         ch = indexCharOffAddr# addr nh
706
707 unpackNBytes# :: Addr# -> Int# -> [Char]
708 unpackNBytes# _addr 0#   = []
709 unpackNBytes#  addr len# = unpack [] (len# -# 1#)
710     where
711      unpack acc i#
712       | i# <# 0#  = acc
713       | otherwise = 
714          case indexCharOffAddr# addr i# of
715             ch -> unpack (C# ch : acc) (i# -# 1#)
716
717 {-# RULES
718 "unpack"         forall a   . unpackCString# a             = build (unpackFoldrCString# a)
719 "unpack-list"    forall a   . unpackFoldrCString# a (:) [] = unpackCStringList# a
720 "unpack-append"  forall a n . unpackFoldrCString# a (:) n  = unpackAppendCString# a n
721
722 -- There's a built-in rule (in PrelRules.lhs) for
723 --      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n
724
725   #-}
726 \end{code}