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