add Control.Monad.Instances to nhc98 build
[haskell-directory.git] / GHC / List.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.List
6 -- Copyright   :  (c) The University of Glasgow 1994-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- The List data type and its operations
14 --
15 -----------------------------------------------------------------------------
16
17 -- #hide
18 module GHC.List (
19    -- [] (..),          -- Not Haskell 98; built in syntax
20
21    map, (++), filter, concat,
22    head, last, tail, init, null, length, (!!), 
23    foldl, scanl, scanl1, foldr, foldr1, scanr, scanr1,
24    iterate, repeat, replicate, cycle,
25    take, drop, splitAt, takeWhile, dropWhile, span, break,
26    reverse, and, or,
27    any, all, elem, notElem, lookup,
28    concatMap,
29    zip, zip3, zipWith, zipWith3, unzip, unzip3,
30    errorEmptyList,
31
32 #ifndef USE_REPORT_PRELUDE
33    -- non-standard, but hidden when creating the Prelude
34    -- export list.
35    takeUInt_append
36 #endif
37
38  ) where
39
40 import {-# SOURCE #-} GHC.Err ( error )
41 import Data.Tuple()     -- Instances
42 import Data.Maybe
43 import GHC.Base
44
45 infixl 9  !!
46 infix  4 `elem`, `notElem`
47 \end{code}
48
49 %*********************************************************
50 %*                                                      *
51 \subsection{List-manipulation functions}
52 %*                                                      *
53 %*********************************************************
54
55 \begin{code}
56 -- | Extract the first element of a list, which must be non-empty.
57 head                    :: [a] -> a
58 head (x:_)              =  x
59 head []                 =  badHead
60
61 badHead = errorEmptyList "head"
62
63 -- This rule is useful in cases like 
64 --      head [y | (x,y) <- ps, x==t]
65 {-# RULES
66 "head/build"    forall (g::forall b.(a->b->b)->b->b) .
67                 head (build g) = g (\x _ -> x) badHead
68 "head/augment"  forall xs (g::forall b. (a->b->b) -> b -> b) . 
69                 head (augment g xs) = g (\x _ -> x) (head xs)
70  #-}
71
72 -- | Extract the elements after the head of a list, which must be non-empty.
73 tail                    :: [a] -> [a]
74 tail (_:xs)             =  xs
75 tail []                 =  errorEmptyList "tail"
76
77 -- | Extract the last element of a list, which must be finite and non-empty.
78 last                    :: [a] -> a
79 #ifdef USE_REPORT_PRELUDE
80 last [x]                =  x
81 last (_:xs)             =  last xs
82 last []                 =  errorEmptyList "last"
83 #else
84 -- eliminate repeated cases
85 last []                 =  errorEmptyList "last"
86 last (x:xs)             =  last' x xs
87   where last' y []     = y
88         last' _ (y:ys) = last' y ys
89 #endif
90
91 -- | Return all the elements of a list except the last one.
92 -- The list must be finite and non-empty.
93 init                    :: [a] -> [a]
94 #ifdef USE_REPORT_PRELUDE
95 init [x]                =  []
96 init (x:xs)             =  x : init xs
97 init []                 =  errorEmptyList "init"
98 #else
99 -- eliminate repeated cases
100 init []                 =  errorEmptyList "init"
101 init (x:xs)             =  init' x xs
102   where init' _ []     = []
103         init' y (z:zs) = y : init' z zs
104 #endif
105
106 -- | Test whether a list is empty.
107 null                    :: [a] -> Bool
108 null []                 =  True
109 null (_:_)              =  False
110
111 -- | 'length' returns the length of a finite list as an 'Int'.
112 -- It is an instance of the more general 'Data.List.genericLength',
113 -- the result type of which may be any kind of number.
114 length                  :: [a] -> Int
115 length l                =  len l 0#
116   where
117     len :: [a] -> Int# -> Int
118     len []     a# = I# a#
119     len (_:xs) a# = len xs (a# +# 1#)
120
121 -- | 'filter', applied to a predicate and a list, returns the list of
122 -- those elements that satisfy the predicate; i.e.,
123 --
124 -- > filter p xs = [ x | x <- xs, p x]
125
126 filter :: (a -> Bool) -> [a] -> [a]
127 filter _pred []    = []
128 filter pred (x:xs)
129   | pred x         = x : filter pred xs
130   | otherwise      = filter pred xs
131
132 {-# NOINLINE [0] filterFB #-}
133 filterFB c p x r | p x       = x `c` r
134                  | otherwise = r
135
136 {-# RULES
137 "filter"     [~1] forall p xs.  filter p xs = build (\c n -> foldr (filterFB c p) n xs)
138 "filterList" [1]  forall p.     foldr (filterFB (:) p) [] = filter p
139 "filterFB"        forall c p q. filterFB (filterFB c p) q = filterFB c (\x -> q x && p x)
140  #-}
141
142 -- Note the filterFB rule, which has p and q the "wrong way round" in the RHS.
143 --     filterFB (filterFB c p) q a b
144 --   = if q a then filterFB c p a b else b
145 --   = if q a then (if p a then c a b else b) else b
146 --   = if q a && p a then c a b else b
147 --   = filterFB c (\x -> q x && p x) a b
148 -- I originally wrote (\x -> p x && q x), which is wrong, and actually
149 -- gave rise to a live bug report.  SLPJ.
150
151
152 -- | 'foldl', applied to a binary operator, a starting value (typically
153 -- the left-identity of the operator), and a list, reduces the list
154 -- using the binary operator, from left to right:
155 --
156 -- > foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
157 --
158 -- The list must be finite.
159
160 -- We write foldl as a non-recursive thing, so that it
161 -- can be inlined, and then (often) strictness-analysed,
162 -- and hence the classic space leak on foldl (+) 0 xs
163
164 foldl        :: (a -> b -> a) -> a -> [b] -> a
165 foldl f z xs = lgo z xs
166              where
167                 lgo z []     =  z
168                 lgo z (x:xs) = lgo (f z x) xs
169
170 -- | 'scanl' is similar to 'foldl', but returns a list of successive
171 -- reduced values from the left:
172 --
173 -- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
174 --
175 -- Note that
176 --
177 -- > last (scanl f z xs) == foldl f z xs.
178
179 scanl                   :: (a -> b -> a) -> a -> [b] -> [a]
180 scanl f q ls            =  q : (case ls of
181                                 []   -> []
182                                 x:xs -> scanl f (f q x) xs)
183
184 -- | 'scanl1' is a variant of 'scanl' that has no starting value argument:
185 --
186 -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
187
188 scanl1                  :: (a -> a -> a) -> [a] -> [a]
189 scanl1 f (x:xs)         =  scanl f x xs
190 scanl1 _ []             =  []
191
192 -- foldr, foldr1, scanr, and scanr1 are the right-to-left duals of the
193 -- above functions.
194
195 -- | 'foldr1' is a variant of 'foldr' that has no starting value argument,
196 -- and thus must be applied to non-empty lists.
197
198 foldr1                  :: (a -> a -> a) -> [a] -> a
199 foldr1 _ [x]            =  x
200 foldr1 f (x:xs)         =  f x (foldr1 f xs)
201 foldr1 _ []             =  errorEmptyList "foldr1"
202
203 -- | 'scanr' is the right-to-left dual of 'scanl'.
204 -- Note that
205 --
206 -- > head (scanr f z xs) == foldr f z xs.
207
208 scanr                   :: (a -> b -> b) -> b -> [a] -> [b]
209 scanr _ q0 []           =  [q0]
210 scanr f q0 (x:xs)       =  f x q : qs
211                            where qs@(q:_) = scanr f q0 xs 
212
213 -- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
214
215 scanr1                  :: (a -> a -> a) -> [a] -> [a]
216 scanr1 f []             =  []
217 scanr1 f [x]            =  [x]
218 scanr1 f (x:xs)         =  f x q : qs
219                            where qs@(q:_) = scanr1 f xs 
220
221 -- | 'iterate' @f x@ returns an infinite list of repeated applications
222 -- of @f@ to @x@:
223 --
224 -- > iterate f x == [x, f x, f (f x), ...]
225
226 iterate :: (a -> a) -> a -> [a]
227 iterate f x =  x : iterate f (f x)
228
229 iterateFB c f x = x `c` iterateFB c f (f x)
230
231
232 {-# RULES
233 "iterate"    [~1] forall f x.   iterate f x = build (\c _n -> iterateFB c f x)
234 "iterateFB"  [1]                iterateFB (:) = iterate
235  #-}
236
237
238 -- | 'repeat' @x@ is an infinite list, with @x@ the value of every element.
239 repeat :: a -> [a]
240 {-# INLINE [0] repeat #-}
241 -- The pragma just gives the rules more chance to fire
242 repeat x = xs where xs = x : xs
243
244 {-# INLINE [0] repeatFB #-}     -- ditto
245 repeatFB c x = xs where xs = x `c` xs
246
247
248 {-# RULES
249 "repeat"    [~1] forall x. repeat x = build (\c _n -> repeatFB c x)
250 "repeatFB"  [1]  repeatFB (:)       = repeat
251  #-}
252
253 -- | 'replicate' @n x@ is a list of length @n@ with @x@ the value of
254 -- every element.
255 -- It is an instance of the more general 'Data.List.genericReplicate',
256 -- in which @n@ may be of any integral type.
257 {-# INLINE replicate #-}
258 replicate               :: Int -> a -> [a]
259 replicate n x           =  take n (repeat x)
260
261 -- | 'cycle' ties a finite list into a circular one, or equivalently,
262 -- the infinite repetition of the original list.  It is the identity
263 -- on infinite lists.
264
265 cycle                   :: [a] -> [a]
266 cycle []                = error "Prelude.cycle: empty list"
267 cycle xs                = xs' where xs' = xs ++ xs'
268
269 -- | 'takeWhile', applied to a predicate @p@ and a list @xs@, returns the
270 -- longest prefix (possibly empty) of @xs@ of elements that satisfy @p@.
271
272 takeWhile               :: (a -> Bool) -> [a] -> [a]
273 takeWhile _ []          =  []
274 takeWhile p (x:xs) 
275             | p x       =  x : takeWhile p xs
276             | otherwise =  []
277
278 -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@.
279
280 dropWhile               :: (a -> Bool) -> [a] -> [a]
281 dropWhile _ []          =  []
282 dropWhile p xs@(x:xs')
283             | p x       =  dropWhile p xs'
284             | otherwise =  xs
285
286 -- | 'take' @n@, applied to a list @xs@, returns the prefix of @xs@
287 -- of length @n@, or @xs@ itself if @n > 'length' xs@.
288 -- It is an instance of the more general 'Data.List.genericTake',
289 -- in which @n@ may be of any integral type.
290 take                   :: Int -> [a] -> [a]
291
292 -- | 'drop' @n xs@ returns the suffix of @xs@
293 -- after the first @n@ elements, or @[]@ if @n > 'length' xs@.
294 -- It is an instance of the more general 'Data.List.genericDrop',
295 -- in which @n@ may be of any integral type.
296 drop                   :: Int -> [a] -> [a]
297
298 -- | 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.
299 -- It is an instance of the more general 'Data.List.genericSplitAt',
300 -- in which @n@ may be of any integral type.
301 splitAt                :: Int -> [a] -> ([a],[a])
302
303 #ifdef USE_REPORT_PRELUDE
304 take n _      | n <= 0 =  []
305 take _ []              =  []
306 take n (x:xs)          =  x : take (n-1) xs
307
308 drop n xs     | n <= 0 =  xs
309 drop _ []              =  []
310 drop n (_:xs)          =  drop (n-1) xs
311
312 splitAt n xs           =  (take n xs, drop n xs)
313
314 #else /* hack away */
315 {-# RULES
316 "take"     [~1] forall n xs . take n xs = case n of I# n# -> build (\c nil -> foldr (takeFB c nil) (takeConst nil) xs n#)
317 "takeList"  [1] forall n xs . foldr (takeFB (:) []) (takeConst []) xs n = takeUInt n xs
318  #-}
319
320 {-# NOINLINE [0] takeConst #-}
321 -- just a version of const that doesn't get inlined too early, so we
322 -- can spot it in rules.  Also we need a type sig due to the unboxed Int#.
323 takeConst :: a -> Int# -> a
324 takeConst x _ = x
325
326 {-# NOINLINE [0] takeFB #-}
327 takeFB :: (a -> b -> c) -> c -> a -> (Int# -> b) -> Int# -> c
328 takeFB c n x xs m | m <=# 0#  = n
329                   | otherwise = x `c` xs (m -# 1#)
330
331 {-# INLINE [0] take #-}
332 take (I# n#) xs = takeUInt n# xs
333
334 -- The general code for take, below, checks n <= maxInt
335 -- No need to check for maxInt overflow when specialised
336 -- at type Int or Int# since the Int must be <= maxInt
337
338 takeUInt :: Int# -> [b] -> [b]
339 takeUInt n xs
340   | n >=# 0#  =  take_unsafe_UInt n xs
341   | otherwise =  []
342
343 take_unsafe_UInt :: Int# -> [b] -> [b]
344 take_unsafe_UInt 0#  _  = []
345 take_unsafe_UInt m   ls =
346   case ls of
347     []     -> []
348     (x:xs) -> x : take_unsafe_UInt (m -# 1#) xs
349
350 takeUInt_append :: Int# -> [b] -> [b] -> [b]
351 takeUInt_append n xs rs
352   | n >=# 0#  =  take_unsafe_UInt_append n xs rs
353   | otherwise =  []
354
355 take_unsafe_UInt_append :: Int# -> [b] -> [b] -> [b]
356 take_unsafe_UInt_append 0#  _ rs  = rs
357 take_unsafe_UInt_append m  ls rs  =
358   case ls of
359     []     -> rs
360     (x:xs) -> x : take_unsafe_UInt_append (m -# 1#) xs rs
361
362 drop (I# n#) ls
363   | n# <# 0#    = ls
364   | otherwise   = drop# n# ls
365     where
366         drop# :: Int# -> [a] -> [a]
367         drop# 0# xs      = xs
368         drop# _  xs@[]   = xs
369         drop# m# (_:xs)  = drop# (m# -# 1#) xs
370
371 splitAt (I# n#) ls
372   | n# <# 0#    = ([], ls)
373   | otherwise   = splitAt# n# ls
374     where
375         splitAt# :: Int# -> [a] -> ([a], [a])
376         splitAt# 0# xs     = ([], xs)
377         splitAt# _  xs@[]  = (xs, xs)
378         splitAt# m# (x:xs) = (x:xs', xs'')
379           where
380             (xs', xs'') = splitAt# (m# -# 1#) xs
381
382 #endif /* USE_REPORT_PRELUDE */
383
384 -- | 'span' @p xs@ is equivalent to @('takeWhile' p xs, 'dropWhile' p xs)@
385
386 span                    :: (a -> Bool) -> [a] -> ([a],[a])
387 span _ xs@[]            =  (xs, xs)
388 span p xs@(x:xs')
389          | p x          =  let (ys,zs) = span p xs' in (x:ys,zs)
390          | otherwise    =  ([],xs)
391
392 -- | 'break' @p@ is equivalent to @'span' ('not' . p)@.
393
394 break                   :: (a -> Bool) -> [a] -> ([a],[a])
395 #ifdef USE_REPORT_PRELUDE
396 break p                 =  span (not . p)
397 #else
398 -- HBC version (stolen)
399 break _ xs@[]           =  (xs, xs)
400 break p xs@(x:xs')
401            | p x        =  ([],xs)
402            | otherwise  =  let (ys,zs) = break p xs' in (x:ys,zs)
403 #endif
404
405 -- | 'reverse' @xs@ returns the elements of @xs@ in reverse order.
406 -- @xs@ must be finite.
407 reverse                 :: [a] -> [a]
408 #ifdef USE_REPORT_PRELUDE
409 reverse                 =  foldl (flip (:)) []
410 #else
411 reverse l =  rev l []
412   where
413     rev []     a = a
414     rev (x:xs) a = rev xs (x:a)
415 #endif
416
417 -- | 'and' returns the conjunction of a Boolean list.  For the result to be
418 -- 'True', the list must be finite; 'False', however, results from a 'False'
419 -- value at a finite index of a finite or infinite list.
420 and                     :: [Bool] -> Bool
421
422 -- | 'or' returns the disjunction of a Boolean list.  For the result to be
423 -- 'False', the list must be finite; 'True', however, results from a 'True'
424 -- value at a finite index of a finite or infinite list.
425 or                      :: [Bool] -> Bool
426 #ifdef USE_REPORT_PRELUDE
427 and                     =  foldr (&&) True
428 or                      =  foldr (||) False
429 #else
430 and []          =  True
431 and (x:xs)      =  x && and xs
432 or []           =  False
433 or (x:xs)       =  x || or xs
434
435 {-# RULES
436 "and/build"     forall (g::forall b.(Bool->b->b)->b->b) . 
437                 and (build g) = g (&&) True
438 "or/build"      forall (g::forall b.(Bool->b->b)->b->b) . 
439                 or (build g) = g (||) False
440  #-}
441 #endif
442
443 -- | Applied to a predicate and a list, 'any' determines if any element
444 -- of the list satisfies the predicate.
445 any                     :: (a -> Bool) -> [a] -> Bool
446
447 -- | Applied to a predicate and a list, 'all' determines if all elements
448 -- of the list satisfy the predicate.
449 all                     :: (a -> Bool) -> [a] -> Bool
450 #ifdef USE_REPORT_PRELUDE
451 any p                   =  or . map p
452 all p                   =  and . map p
453 #else
454 any _ []        = False
455 any p (x:xs)    = p x || any p xs
456
457 all _ []        =  True
458 all p (x:xs)    =  p x && all p xs
459 {-# RULES
460 "any/build"     forall p (g::forall b.(a->b->b)->b->b) . 
461                 any p (build g) = g ((||) . p) False
462 "all/build"     forall p (g::forall b.(a->b->b)->b->b) . 
463                 all p (build g) = g ((&&) . p) True
464  #-}
465 #endif
466
467 -- | 'elem' is the list membership predicate, usually written in infix form,
468 -- e.g., @x `elem` xs@.
469 elem                    :: (Eq a) => a -> [a] -> Bool
470
471 -- | 'notElem' is the negation of 'elem'.
472 notElem                 :: (Eq a) => a -> [a] -> Bool
473 #ifdef USE_REPORT_PRELUDE
474 elem x                  =  any (== x)
475 notElem x               =  all (/= x)
476 #else
477 elem _ []       = False
478 elem x (y:ys)   = x==y || elem x ys
479
480 notElem _ []    =  True
481 notElem x (y:ys)=  x /= y && notElem x ys
482 #endif
483
484 -- | 'lookup' @key assocs@ looks up a key in an association list.
485 lookup                  :: (Eq a) => a -> [(a,b)] -> Maybe b
486 lookup _key []          =  Nothing
487 lookup  key ((x,y):xys)
488     | key == x          =  Just y
489     | otherwise         =  lookup key xys
490
491 -- | Map a function over a list and concatenate the results.
492 concatMap               :: (a -> [b]) -> [a] -> [b]
493 concatMap f             =  foldr ((++) . f) []
494
495 -- | Concatenate a list of lists.
496 concat :: [[a]] -> [a]
497 concat = foldr (++) []
498
499 {-# RULES
500   "concat" forall xs. concat xs = build (\c n -> foldr (\x y -> foldr c y x) n xs)
501 -- We don't bother to turn non-fusible applications of concat back into concat
502  #-}
503
504 \end{code}
505
506
507 \begin{code}
508 -- | List index (subscript) operator, starting from 0.
509 -- It is an instance of the more general 'Data.List.genericIndex',
510 -- which takes an index of any integral type.
511 (!!)                    :: [a] -> Int -> a
512 #ifdef USE_REPORT_PRELUDE
513 xs     !! n | n < 0 =  error "Prelude.!!: negative index"
514 []     !! _         =  error "Prelude.!!: index too large"
515 (x:_)  !! 0         =  x
516 (_:xs) !! n         =  xs !! (n-1)
517 #else
518 -- HBC version (stolen), then unboxified
519 -- The semantics is not quite the same for error conditions
520 -- in the more efficient version.
521 --
522 xs !! (I# n) | n <# 0#   =  error "Prelude.(!!): negative index\n"
523              | otherwise =  sub xs n
524                          where
525                             sub :: [a] -> Int# -> a
526                             sub []     _ = error "Prelude.(!!): index too large\n"
527                             sub (y:ys) n = if n ==# 0#
528                                            then y
529                                            else sub ys (n -# 1#)
530 #endif
531 \end{code}
532
533
534 %*********************************************************
535 %*                                                      *
536 \subsection{The zip family}
537 %*                                                      *
538 %*********************************************************
539
540 \begin{code}
541 foldr2 _k z []    _ys    = z
542 foldr2 _k z _xs   []     = z
543 foldr2 k z (x:xs) (y:ys) = k x y (foldr2 k z xs ys)
544
545 foldr2_left _k  z _x _r []     = z
546 foldr2_left  k _z  x  r (y:ys) = k x y (r ys)
547
548 foldr2_right _k z  _y _r []     = z
549 foldr2_right  k _z  y  r (x:xs) = k x y (r xs)
550
551 -- foldr2 k z xs ys = foldr (foldr2_left k z)  (\_ -> z) xs ys
552 -- foldr2 k z xs ys = foldr (foldr2_right k z) (\_ -> z) ys xs
553 {-# RULES
554 "foldr2/left"   forall k z ys (g::forall b.(a->b->b)->b->b) . 
555                   foldr2 k z (build g) ys = g (foldr2_left  k z) (\_ -> z) ys
556
557 "foldr2/right"  forall k z xs (g::forall b.(a->b->b)->b->b) . 
558                   foldr2 k z xs (build g) = g (foldr2_right k z) (\_ -> z) xs
559  #-}
560 \end{code}
561
562 The foldr2/right rule isn't exactly right, because it changes
563 the strictness of foldr2 (and thereby zip)
564
565 E.g. main = print (null (zip nonobviousNil (build undefined)))
566           where   nonobviousNil = f 3
567                   f n = if n == 0 then [] else f (n-1)
568
569 I'm going to leave it though.
570
571
572 Zips for larger tuples are in the List module.
573
574 \begin{code}
575 ----------------------------------------------
576 -- | 'zip' takes two lists and returns a list of corresponding pairs.
577 -- If one input list is short, excess elements of the longer list are
578 -- discarded.
579 zip :: [a] -> [b] -> [(a,b)]
580 zip (a:as) (b:bs) = (a,b) : zip as bs
581 zip _      _      = []
582
583 {-# INLINE [0] zipFB #-}
584 zipFB c x y r = (x,y) `c` r
585
586 {-# RULES
587 "zip"      [~1] forall xs ys. zip xs ys = build (\c n -> foldr2 (zipFB c) n xs ys)
588 "zipList"  [1]  foldr2 (zipFB (:)) []   = zip
589  #-}
590 \end{code}
591
592 \begin{code}
593 ----------------------------------------------
594 -- | 'zip3' takes three lists and returns a list of triples, analogous to
595 -- 'zip'.
596 zip3 :: [a] -> [b] -> [c] -> [(a,b,c)]
597 -- Specification
598 -- zip3 =  zipWith3 (,,)
599 zip3 (a:as) (b:bs) (c:cs) = (a,b,c) : zip3 as bs cs
600 zip3 _      _      _      = []
601 \end{code}
602
603
604 -- The zipWith family generalises the zip family by zipping with the
605 -- function given as the first argument, instead of a tupling function.
606
607 \begin{code}
608 ----------------------------------------------
609 -- | 'zipWith' generalises 'zip' by zipping with the function given
610 -- as the first argument, instead of a tupling function.
611 -- For example, @'zipWith' (+)@ is applied to two lists to produce the
612 -- list of corresponding sums.
613 zipWith :: (a->b->c) -> [a]->[b]->[c]
614 zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
615 zipWith _ _      _      = []
616
617 {-# INLINE [0] zipWithFB #-}
618 zipWithFB c f x y r = (x `f` y) `c` r
619
620 {-# RULES
621 "zipWith"       [~1] forall f xs ys.    zipWith f xs ys = build (\c n -> foldr2 (zipWithFB c f) n xs ys)
622 "zipWithList"   [1]  forall f.  foldr2 (zipWithFB (:) f) [] = zipWith f
623   #-}
624 \end{code}
625
626 \begin{code}
627 -- | The 'zipWith3' function takes a function which combines three
628 -- elements, as well as three lists and returns a list of their point-wise
629 -- combination, analogous to 'zipWith'.
630 zipWith3                :: (a->b->c->d) -> [a]->[b]->[c]->[d]
631 zipWith3 z (a:as) (b:bs) (c:cs)
632                         =  z a b c : zipWith3 z as bs cs
633 zipWith3 _ _ _ _        =  []
634
635 -- | 'unzip' transforms a list of pairs into a list of first components
636 -- and a list of second components.
637 unzip    :: [(a,b)] -> ([a],[b])
638 {-# INLINE unzip #-}
639 unzip    =  foldr (\(a,b) ~(as,bs) -> (a:as,b:bs)) ([],[])
640
641 -- | The 'unzip3' function takes a list of triples and returns three
642 -- lists, analogous to 'unzip'.
643 unzip3   :: [(a,b,c)] -> ([a],[b],[c])
644 {-# INLINE unzip3 #-}
645 unzip3   =  foldr (\(a,b,c) ~(as,bs,cs) -> (a:as,b:bs,c:cs))
646                   ([],[],[])
647 \end{code}
648
649
650 %*********************************************************
651 %*                                                      *
652 \subsection{Error code}
653 %*                                                      *
654 %*********************************************************
655
656 Common up near identical calls to `error' to reduce the number
657 constant strings created when compiled:
658
659 \begin{code}
660 errorEmptyList :: String -> a
661 errorEmptyList fun =
662   error (prel_list_str ++ fun ++ ": empty list")
663
664 prel_list_str :: String
665 prel_list_str = "Prelude."
666 \end{code}