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