[project @ 2002-02-12 11:44:54 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / List.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: List.lhs,v 1.13 2001/08/29 10:12:34 simonmar Exp $
3 %
4 % (c) The University of Glasgow, 1994-2000
5 %
6
7 \section[List]{Module @List@}
8
9 \begin{code}
10 module List 
11    ( 
12 #ifndef __HUGS__
13      []((:), [])
14    , 
15 #endif
16
17       elemIndex        -- :: (Eq a) => a -> [a] -> Maybe Int
18    , elemIndices       -- :: (Eq a) => a -> [a] -> [Int]
19
20    , find              -- :: (a -> Bool) -> [a] -> Maybe a
21    , findIndex         -- :: (a -> Bool) -> [a] -> Maybe Int
22    , findIndices       -- :: (a -> Bool) -> [a] -> [Int]
23    
24    , nub               -- :: (Eq a) => [a] -> [a]
25    , nubBy             -- :: (a -> a -> Bool) -> [a] -> [a]
26
27    , delete            -- :: (Eq a) => a -> [a] -> [a]
28    , deleteBy          -- :: (a -> a -> Bool) -> a -> [a] -> [a]
29    , (\\)              -- :: (Eq a) => [a] -> [a] -> [a]
30    , deleteFirstsBy    -- :: (a -> a -> Bool) -> [a] -> [a] -> [a]
31    
32    , union             -- :: (Eq a) => [a] -> [a] -> [a]
33    , unionBy           -- :: (a -> a -> Bool) -> [a] -> [a] -> [a]
34
35    , intersect         -- :: (Eq a) => [a] -> [a] -> [a]
36    , intersectBy       -- :: (a -> a -> Bool) -> [a] -> [a] -> [a]
37
38    , intersperse       -- :: a -> [a] -> [a]
39    , transpose         -- :: [[a]] -> [[a]]
40    , partition         -- :: (a -> Bool) -> [a] -> ([a], [a])
41
42    , group             -- :: Eq a => [a] -> [[a]]
43    , groupBy           -- :: (a -> a -> Bool) -> [a] -> [[a]]
44
45    , inits             -- :: [a] -> [[a]]
46    , tails             -- :: [a] -> [[a]]
47
48    , isPrefixOf        -- :: (Eq a) => [a] -> [a] -> Bool
49    , isSuffixOf        -- :: (Eq a) => [a] -> [a] -> Bool
50    
51    , mapAccumL         -- :: (a -> b -> (a,c)) -> a -> [b] -> (a,[c])
52    , mapAccumR         -- :: (a -> b -> (a,c)) -> a -> [b] -> (a,[c])
53    
54    , sort              -- :: (Ord a) => [a] -> [a]
55    , sortBy            -- :: (a -> a -> Ordering) -> [a] -> [a]
56    
57    , insert            -- :: (Ord a) => a -> [a] -> [a]
58    , insertBy          -- :: (a -> a -> Ordering) -> a -> [a] -> [a]
59    
60    , maximumBy         -- :: (a -> a -> Ordering) -> [a] -> a
61    , minimumBy         -- :: (a -> a -> Ordering) -> [a] -> a
62    
63    , genericLength     -- :: (Integral a) => [b] -> a
64    , genericTake       -- :: (Integral a) => a -> [b] -> [b]
65    , genericDrop       -- :: (Integral a) => a -> [b] -> [b]
66    , genericSplitAt    -- :: (Integral a) => a -> [b] -> ([b], [b])
67    , genericIndex      -- :: (Integral a) => [b] -> a -> b
68    , genericReplicate  -- :: (Integral a) => a -> b -> [b]
69    
70    , unfoldr            -- :: (b -> Maybe (a, b)) -> b -> [a]
71
72    , zip4, zip5, zip6, zip7
73    , zipWith4, zipWith5, zipWith6, zipWith7
74    , unzip4, unzip5, unzip6, unzip7
75
76    , map               -- :: ( a -> b ) -> [a] -> [b]
77    , (++)              -- :: [a] -> [a] -> [a]
78    , concat            -- :: [[a]] -> [a]
79    , filter            -- :: (a -> Bool) -> [a] -> [a]
80    , head              -- :: [a] -> a
81    , last              -- :: [a] -> a
82    , tail              -- :: [a] -> [a]
83    , init              -- :: [a] -> [a]
84    , null              -- :: [a] -> Bool
85    , length            -- :: [a] -> Int
86    , (!!)              -- :: [a] -> Int -> a
87    , foldl             -- :: (a -> b -> a) -> a -> [b] -> a
88    , foldl1            -- :: (a -> a -> a) -> [a] -> a
89    , scanl             -- :: (a -> b -> a) -> a -> [b] -> [a]
90    , scanl1            -- :: (a -> a -> a) -> [a] -> [a]
91    , foldr             -- :: (a -> b -> b) -> b -> [a] -> b
92    , foldr1            -- :: (a -> a -> a) -> [a] -> a
93    , scanr             -- :: (a -> b -> b) -> b -> [a] -> [b]
94    , scanr1            -- :: (a -> a -> a) -> [a] -> [a]
95    , iterate           -- :: (a -> a) -> a -> [a]
96    , repeat            -- :: a -> [a]
97    , replicate         -- :: Int -> a -> [a]
98    , cycle             -- :: [a] -> [a]
99    , take              -- :: Int -> [a] -> [a]
100    , drop              -- :: Int -> [a] -> [a]
101    , splitAt           -- :: Int -> [a] -> ([a], [a])
102    , takeWhile         -- :: (a -> Bool) -> [a] -> [a]
103    , dropWhile         -- :: (a -> Bool) -> [a] -> [a]
104    , span              -- :: (a -> Bool) -> [a] -> ([a], [a])
105    , break             -- :: (a -> Bool) -> [a] -> ([a], [a])
106
107    , lines             -- :: String   -> [String]
108    , words             -- :: String   -> [String]
109    , unlines           -- :: [String] -> String
110    , unwords           -- :: [String] -> String
111    , reverse           -- :: [a] -> [a]
112    , and               -- :: [Bool] -> Bool
113    , or                -- :: [Bool] -> Bool
114    , any               -- :: (a -> Bool) -> [a] -> Bool
115    , all               -- :: (a -> Bool) -> [a] -> Bool
116    , elem              -- :: a -> [a] -> Bool
117    , notElem           -- :: a -> [a] -> Bool
118    , lookup            -- :: (Eq a) => a -> [(a,b)] -> Maybe b
119    , sum               -- :: (Num a) => [a] -> a
120    , product           -- :: (Num a) => [a] -> a
121    , maximum           -- :: (Ord a) => [a] -> a
122    , minimum           -- :: (Ord a) => [a] -> a
123    , concatMap         -- :: (a -> [b]) -> [a] -> [b]
124    , zip               -- :: [a] -> [b] -> [(a,b)]
125    , zip3  
126    , zipWith           -- :: (a -> b -> c) -> [a] -> [b] -> [c]
127    , zipWith3
128    , unzip             -- :: [(a,b)] -> ([a],[b])
129    , unzip3
130
131      -- Implementation checked wrt. Haskell 98 lib report, 1/99.
132    ) where
133
134 import Prelude
135 import Maybe    ( listToMaybe )
136
137 #ifndef __HUGS__
138 import PrelShow ( lines, words, unlines, unwords )
139 import PrelBase ( Int(..), map, (++) )
140 import PrelGHC  ( (+#) )
141 #endif
142
143 infix 5 \\ 
144 \end{code}
145
146 %*********************************************************
147 %*                                                      *
148 \subsection{List functions}
149 %*                                                      *
150 %*********************************************************
151
152 \begin{code}
153 elemIndex       :: Eq a => a -> [a] -> Maybe Int
154 elemIndex x     = findIndex (x==)
155
156 elemIndices     :: Eq a => a -> [a] -> [Int]
157 elemIndices x   = findIndices (x==)
158
159 find            :: (a -> Bool) -> [a] -> Maybe a
160 find p          = listToMaybe . filter p
161
162 findIndex       :: (a -> Bool) -> [a] -> Maybe Int
163 findIndex p     = listToMaybe . findIndices p
164
165 findIndices      :: (a -> Bool) -> [a] -> [Int]
166
167 #ifdef USE_REPORT_PRELUDE
168 findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
169 #else
170 #ifdef __HUGS__
171 findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
172 #else 
173 -- Efficient definition
174 findIndices p ls = loop 0# ls
175                  where
176                    loop _ [] = []
177                    loop n (x:xs) | p x       = I# n : loop (n +# 1#) xs
178                                  | otherwise = loop (n +# 1#) xs
179 #endif  /* __HUGS__ */
180 #endif  /* USE_REPORT_PRELUDE */
181
182 isPrefixOf              :: (Eq a) => [a] -> [a] -> Bool
183 isPrefixOf [] _         =  True
184 isPrefixOf _  []        =  False
185 isPrefixOf (x:xs) (y:ys)=  x == y && isPrefixOf xs ys
186
187 isSuffixOf              :: (Eq a) => [a] -> [a] -> Bool
188 isSuffixOf x y          =  reverse x `isPrefixOf` reverse y
189
190 -- nub (meaning "essence") remove duplicate elements from its list argument.
191 nub                     :: (Eq a) => [a] -> [a]
192 #ifdef USE_REPORT_PRELUDE
193 nub                     =  nubBy (==)
194 #else
195 -- stolen from HBC
196 nub l                   = nub' l []             -- '
197   where
198     nub' [] _           = []                    -- '
199     nub' (x:xs) ls                              -- '
200         | x `elem` ls   = nub' xs ls            -- '
201         | otherwise     = x : nub' xs (x:ls)    -- '
202 #endif
203
204 nubBy                   :: (a -> a -> Bool) -> [a] -> [a]
205 #ifdef USE_REPORT_PRELUDE
206 nubBy eq []             =  []
207 nubBy eq (x:xs)         =  x : nubBy eq (filter (\ y -> not (eq x y)) xs)
208 #else
209 nubBy eq l              = nubBy' l []
210   where
211     nubBy' [] _         = []
212     nubBy' (y:ys) xs
213        | elem_by eq y xs = nubBy' ys xs 
214        | otherwise       = y : nubBy' ys (y:xs)
215
216 -- Not exported:
217 -- Note that we keep the call to `eq` with arguments in the
218 -- same order as in the reference implementation
219 -- 'xs' is the list of things we've seen so far, 
220 -- 'y' is the potential new element
221 elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
222 elem_by _  _ []         =  False
223 elem_by eq y (x:xs)     =  x `eq` y || elem_by eq y xs
224 #endif
225
226
227 -- delete x removes the first occurrence of x from its list argument.
228 delete                  :: (Eq a) => a -> [a] -> [a]
229 delete                  =  deleteBy (==)
230
231 deleteBy                :: (a -> a -> Bool) -> a -> [a] -> [a]
232 deleteBy _  _ []        = []
233 deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
234
235 -- list difference (non-associative).  In the result of xs \\ ys,
236 -- the first occurrence of each element of ys in turn (if any)
237 -- has been removed from xs.  Thus, (xs ++ ys) \\ xs == ys.
238 (\\)                    :: (Eq a) => [a] -> [a] -> [a]
239 (\\)                    =  foldl (flip delete)
240
241 -- List union, remove the elements of first list from second.
242 union                   :: (Eq a) => [a] -> [a] -> [a]
243 union                   = unionBy (==)
244
245 unionBy                 :: (a -> a -> Bool) -> [a] -> [a] -> [a]
246 unionBy eq xs ys        =  xs ++ foldl (flip (deleteBy eq)) (nubBy eq ys) xs
247
248 intersect               :: (Eq a) => [a] -> [a] -> [a]
249 intersect               =  intersectBy (==)
250
251 intersectBy             :: (a -> a -> Bool) -> [a] -> [a] -> [a]
252 intersectBy eq xs ys    =  [x | x <- xs, any (eq x) ys]
253
254 -- intersperse sep inserts sep between the elements of its list argument.
255 -- e.g. intersperse ',' "abcde" == "a,b,c,d,e"
256 intersperse             :: a -> [a] -> [a]
257 intersperse _   []      = []
258 intersperse _   [x]     = [x]
259 intersperse sep (x:xs)  = x : sep : intersperse sep xs
260
261 transpose               :: [[a]] -> [[a]]
262 transpose []             = []
263 transpose ([]   : xss)   = transpose xss
264 transpose ((x:xs) : xss) = (x : [h | (h:t) <- xss]) : transpose (xs : [ t | (h:t) <- xss])
265
266
267 -- partition takes a predicate and a list and returns a pair of lists:
268 -- those elements of the argument list that do and do not satisfy the
269 -- predicate, respectively; i,e,,
270 -- partition p xs == (filter p xs, filter (not . p) xs).
271 partition               :: (a -> Bool) -> [a] -> ([a],[a])
272 {-# INLINE partition #-}
273 partition p xs = foldr (select p) ([],[]) xs
274
275 select p x (ts,fs) | p x       = (x:ts,fs)
276                    | otherwise = (ts, x:fs)
277 \end{code}
278
279 @mapAccumL@ behaves like a combination
280 of  @map@ and @foldl@;
281 it applies a function to each element of a list, passing an accumulating
282 parameter from left to right, and returning a final value of this
283 accumulator together with the new list.
284
285 \begin{code}
286
287 mapAccumL :: (acc -> x -> (acc, y)) -- Function of elt of input list
288                                     -- and accumulator, returning new
289                                     -- accumulator and elt of result list
290           -> acc            -- Initial accumulator 
291           -> [x]            -- Input list
292           -> (acc, [y])     -- Final accumulator and result list
293 mapAccumL _ s []        =  (s, [])
294 mapAccumL f s (x:xs)    =  (s'',y:ys)
295                            where (s', y ) = f s x
296                                  (s'',ys) = mapAccumL f s' xs
297 \end{code}
298
299 @mapAccumR@ does the same, but working from right to left instead.  Its type is
300 the same as @mapAccumL@, though.
301
302 \begin{code}
303 mapAccumR :: (acc -> x -> (acc, y))     -- Function of elt of input list
304                                         -- and accumulator, returning new
305                                         -- accumulator and elt of result list
306             -> acc              -- Initial accumulator
307             -> [x]              -- Input list
308             -> (acc, [y])               -- Final accumulator and result list
309 mapAccumR _ s []        =  (s, [])
310 mapAccumR f s (x:xs)    =  (s'', y:ys)
311                            where (s'',y ) = f s' x
312                                  (s', ys) = mapAccumR f s xs
313 \end{code}
314
315 \begin{code}
316 insert :: Ord a => a -> [a] -> [a]
317 insert e ls = insertBy (compare) e ls
318
319 insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
320 insertBy _   x [] = [x]
321 insertBy cmp x ys@(y:ys')
322  = case cmp x y of
323      GT -> y : insertBy cmp x ys'
324      _  -> x : ys
325
326 maximumBy               :: (a -> a -> Ordering) -> [a] -> a
327 maximumBy _ []          =  error "List.maximumBy: empty list"
328 maximumBy cmp xs        =  foldl1 max xs
329                         where
330                            max x y = case cmp x y of
331                                         GT -> x
332                                         _  -> y
333
334 minimumBy               :: (a -> a -> Ordering) -> [a] -> a
335 minimumBy _ []          =  error "List.minimumBy: empty list"
336 minimumBy cmp xs        =  foldl1 min xs
337                         where
338                            min x y = case cmp x y of
339                                         GT -> y
340                                         _  -> x
341
342 genericLength           :: (Num i) => [b] -> i
343 genericLength []        =  0
344 genericLength (_:l)     =  1 + genericLength l
345
346 genericTake             :: (Integral i) => i -> [a] -> [a]
347 genericTake 0 _         =  []
348 genericTake _ []        =  []
349 genericTake n (x:xs) | n > 0  =  x : genericTake (n-1) xs
350 genericTake _  _        =  error "List.genericTake: negative argument"
351
352 genericDrop             :: (Integral i) => i -> [a] -> [a]
353 genericDrop 0 xs        =  xs
354 genericDrop _ []        =  []
355 genericDrop n (_:xs) | n > 0  =  genericDrop (n-1) xs
356 genericDrop _ _         =  error "List.genericDrop: negative argument"
357
358 genericSplitAt          :: (Integral i) => i -> [b] -> ([b],[b])
359 genericSplitAt 0 xs     =  ([],xs)
360 genericSplitAt _ []     =  ([],[])
361 genericSplitAt n (x:xs) | n > 0  =  (x:xs',xs'') where
362                                (xs',xs'') = genericSplitAt (n-1) xs
363 genericSplitAt _ _      =  error "List.genericSplitAt: negative argument"
364
365
366 genericIndex :: (Integral a) => [b] -> a -> b
367 genericIndex (x:_)  0 = x
368 genericIndex (_:xs) n 
369  | n > 0     = genericIndex xs (n-1)
370  | otherwise = error "List.genericIndex: negative argument."
371 genericIndex _ _      = error "List.genericIndex: index too large."
372
373 genericReplicate        :: (Integral i) => i -> a -> [a]
374 genericReplicate n x    =  genericTake n (repeat x)
375
376
377 zip4                    :: [a] -> [b] -> [c] -> [d] -> [(a,b,c,d)]
378 zip4                    =  zipWith4 (,,,)
379
380 zip5                    :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a,b,c,d,e)]
381 zip5                    =  zipWith5 (,,,,)
382
383 zip6                    :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> 
384                               [(a,b,c,d,e,f)]
385 zip6                    =  zipWith6 (,,,,,)
386
387 zip7                    :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] ->
388                               [g] -> [(a,b,c,d,e,f,g)]
389 zip7                    =  zipWith7 (,,,,,,)
390
391 zipWith4                :: (a->b->c->d->e) -> [a]->[b]->[c]->[d]->[e]
392 zipWith4 z (a:as) (b:bs) (c:cs) (d:ds)
393                         =  z a b c d : zipWith4 z as bs cs ds
394 zipWith4 _ _ _ _ _      =  []
395
396 zipWith5                :: (a->b->c->d->e->f) -> 
397                            [a]->[b]->[c]->[d]->[e]->[f]
398 zipWith5 z (a:as) (b:bs) (c:cs) (d:ds) (e:es)
399                         =  z a b c d e : zipWith5 z as bs cs ds es
400 zipWith5 _ _ _ _ _ _    = []
401
402 zipWith6                :: (a->b->c->d->e->f->g) ->
403                            [a]->[b]->[c]->[d]->[e]->[f]->[g]
404 zipWith6 z (a:as) (b:bs) (c:cs) (d:ds) (e:es) (f:fs)
405                         =  z a b c d e f : zipWith6 z as bs cs ds es fs
406 zipWith6 _ _ _ _ _ _ _  = []
407
408 zipWith7                :: (a->b->c->d->e->f->g->h) ->
409                            [a]->[b]->[c]->[d]->[e]->[f]->[g]->[h]
410 zipWith7 z (a:as) (b:bs) (c:cs) (d:ds) (e:es) (f:fs) (g:gs)
411                    =  z a b c d e f g : zipWith7 z as bs cs ds es fs gs
412 zipWith7 _ _ _ _ _ _ _ _ = []
413
414 unzip4                  :: [(a,b,c,d)] -> ([a],[b],[c],[d])
415 unzip4                  =  foldr (\(a,b,c,d) ~(as,bs,cs,ds) ->
416                                         (a:as,b:bs,c:cs,d:ds))
417                                  ([],[],[],[])
418
419 unzip5                  :: [(a,b,c,d,e)] -> ([a],[b],[c],[d],[e])
420 unzip5                  =  foldr (\(a,b,c,d,e) ~(as,bs,cs,ds,es) ->
421                                         (a:as,b:bs,c:cs,d:ds,e:es))
422                                  ([],[],[],[],[])
423
424 unzip6                  :: [(a,b,c,d,e,f)] -> ([a],[b],[c],[d],[e],[f])
425 unzip6                  =  foldr (\(a,b,c,d,e,f) ~(as,bs,cs,ds,es,fs) ->
426                                         (a:as,b:bs,c:cs,d:ds,e:es,f:fs))
427                                  ([],[],[],[],[],[])
428
429 unzip7          :: [(a,b,c,d,e,f,g)] -> ([a],[b],[c],[d],[e],[f],[g])
430 unzip7          =  foldr (\(a,b,c,d,e,f,g) ~(as,bs,cs,ds,es,fs,gs) ->
431                                 (a:as,b:bs,c:cs,d:ds,e:es,f:fs,g:gs))
432                          ([],[],[],[],[],[],[])
433
434
435
436 deleteFirstsBy          :: (a -> a -> Bool) -> [a] -> [a] -> [a]
437 deleteFirstsBy eq       =  foldl (flip (deleteBy eq))
438
439
440 -- group splits its list argument into a list of lists of equal, adjacent
441 -- elements.  e.g.,
442 -- group "Mississippi" == ["M","i","ss","i","ss","i","pp","i"]
443 group                   :: (Eq a) => [a] -> [[a]]
444 group                   =  groupBy (==)
445
446 groupBy                 :: (a -> a -> Bool) -> [a] -> [[a]]
447 groupBy _  []           =  []
448 groupBy eq (x:xs)       =  (x:ys) : groupBy eq zs
449                            where (ys,zs) = span (eq x) xs
450
451 -- inits xs returns the list of initial segments of xs, shortest first.
452 -- e.g., inits "abc" == ["","a","ab","abc"]
453 inits                   :: [a] -> [[a]]
454 inits []                =  [[]]
455 inits (x:xs)            =  [[]] ++ map (x:) (inits xs)
456
457 -- tails xs returns the list of all final segments of xs, longest first.
458 -- e.g., tails "abc" == ["abc", "bc", "c",""]
459 tails                   :: [a] -> [[a]]
460 tails []                =  [[]]
461 tails xxs@(_:xs)        =  xxs : tails xs
462
463 \end{code}
464
465 %-----------------------------------------------------------------------------
466 Quick Sort algorithm taken from HBC's QSort library.
467
468 \begin{code}
469 sort :: (Ord a) => [a] -> [a]
470 sortBy :: (a -> a -> Ordering) -> [a] -> [a]
471
472 #ifdef USE_REPORT_PRELUDE
473 sort = sortBy compare
474 sortBy cmp = foldr (insertBy cmp) []
475 #else
476
477 sortBy cmp l = qsort cmp l []
478 sort l = qsort compare l []
479
480 -- rest is not exported:
481
482 -- qsort is stable and does not concatenate.
483 qsort :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
484 qsort _   []     r = r
485 qsort _   [x]    r = x:r
486 qsort cmp (x:xs) r = qpart cmp x xs [] [] r
487
488 -- qpart partitions and sorts the sublists
489 qpart :: (a -> a -> Ordering) -> a -> [a] -> [a] -> [a] -> [a] -> [a]
490 qpart cmp x [] rlt rge r =
491     -- rlt and rge are in reverse order and must be sorted with an
492     -- anti-stable sorting
493     rqsort cmp rlt (x:rqsort cmp rge r)
494 qpart cmp x (y:ys) rlt rge r =
495     case cmp x y of
496         GT -> qpart cmp x ys (y:rlt) rge r
497         _  -> qpart cmp x ys rlt (y:rge) r
498
499 -- rqsort is as qsort but anti-stable, i.e. reverses equal elements
500 rqsort :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
501 rqsort _   []     r = r
502 rqsort _   [x]    r = x:r
503 rqsort cmp (x:xs) r = rqpart cmp x xs [] [] r
504
505 rqpart :: (a -> a -> Ordering) -> a -> [a] -> [a] -> [a] -> [a] -> [a]
506 rqpart cmp x [] rle rgt r =
507     qsort cmp rle (x:qsort cmp rgt r)
508 rqpart cmp x (y:ys) rle rgt r =
509     case cmp y x of
510         GT -> rqpart cmp x ys rle (y:rgt) r
511         _  -> rqpart cmp x ys (y:rle) rgt r
512
513 #endif /* USE_REPORT_PRELUDE */
514 \end{code}
515
516 \begin{verbatim}
517   unfoldr f' (foldr f z xs) == (z,xs)
518
519  if the following holds:
520
521    f' (f x y) = Just (x,y)
522    f' z       = Nothing
523 \end{verbatim}
524
525 \begin{code}
526 unfoldr      :: (b -> Maybe (a, b)) -> b -> [a]
527 unfoldr f b  =
528   case f b of
529    Just (a,new_b) -> a : unfoldr f new_b
530    Nothing        -> []
531 \end{code}