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