[project @ 1997-08-25 22:37:25 by sof]
[ghc-hetmet.git] / ghc / lib / required / List.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1996
3 %
4
5 \section[List]{Module @Lhar@}
6
7 \begin{code}
8 module List ( 
9     {- 
10       This list follows the type signatures for the
11       standard List interface.
12     -}
13     elemIndex, elemIndices,
14     find, findIndex, findIndices,
15     nub, nubBy, 
16     delete, deleteBy, (\\), deleteFirstsBy,
17     union, unionBy, 
18     intersect, intersectBy,
19     group, groupBy,
20     inits, tails,
21     isPrefixOf, isSuffixOf,
22     intersperse, transpose, partition, 
23     mapAccumL, mapAccumR,
24     sort, sortBy, 
25     insertBy, 
26     maximumBy, minimumBy,
27     genericTake,  genericDrop, genericSplitAt, 
28     genericIndex, genericReplicate, genericLength, 
29     
30     zip4, zip5, zip6, zip7,
31     zipWith4, zipWith5, zipWith6, zipWith7,
32     unzip4, unzip5, unzip6, unzip7
33
34   ) where
35
36 import Prelude
37 import Maybe (listToMaybe)
38
39 infix 5 \\
40 \end{code}
41
42 %*********************************************************
43 %*                                                      *
44 \subsection{List functions}
45 %*                                                      *
46 %*********************************************************
47
48 \begin{code}
49 elemIndex       :: Eq a => a -> [a] -> Maybe Int
50 elemIndex x     = findIndex (x==)
51
52 elemIndices     :: Eq a => a -> [a] -> [Int]
53 elemIndices x   = findIndices (x==)
54
55 find            :: (a -> Bool) -> [a] -> Maybe a
56 find p          = listToMaybe . filter p
57
58 findIndex       :: (a -> Bool) -> [a] -> Maybe Int
59 findIndex p     = listToMaybe . findIndices p
60
61 findIndices      :: (a -> Bool) -> [a] -> [Int]
62 findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
63
64 isPrefixOf              :: (Eq a) => [a] -> [a] -> Bool
65 isPrefixOf [] _         =  True
66 isPrefixOf _  []        =  False
67 isPrefixOf (x:xs) (y:ys)=  x == y && isPrefixOf xs ys
68
69 isSuffixOf              :: (Eq a) => [a] -> [a] -> Bool
70 isSuffixOf x y          =  reverse x `isPrefixOf` reverse y
71
72 -- nub (meaning "essence") remove duplicate elements from its list argument.
73 nub                     :: (Eq a) => [a] -> [a]
74 #ifdef USE_REPORT_PRELUDE
75 nub                     =  nubBy (==)
76 #else
77 -- stolen from HBC
78 nub l                   = nub' l []
79   where
80     nub' [] _           = []
81     nub' (x:xs) l       = if x `elem` l then nub' xs l else x : nub' xs (x:l)
82 #endif
83
84 nubBy                   :: (a -> a -> Bool) -> [a] -> [a]
85 #ifdef USE_REPORT_PRELUDE
86 nubBy eq []             =  []
87 nubBy eq (x:xs)         =  x : nubBy eq (filter (\ y -> not (eq x y)) xs)
88 #else
89 nubBy eq l              = nubBy' l []
90   where
91     nubBy' [] _         = []
92     nubBy' (x:xs) l     = if elemBy eq x l then nubBy' xs l else x : nubBy' xs (x:l)
93
94 --not exported:
95 elemBy :: (a -> a -> Bool) -> a -> [a] -> Bool
96 elemBy eq _ []          =  False
97 elemBy eq x (y:ys)      =  x `eq` y || elemBy eq x ys
98 #endif
99
100
101 -- delete x removes the first occurrence of x from its list argument.
102 delete                  :: (Eq a) => a -> [a] -> [a]
103 delete                  =  deleteBy (==)
104
105 deleteBy                :: (a -> a -> Bool) -> a -> [a] -> [a]
106 deleteBy eq x []        = []
107 deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
108
109 -- list difference (non-associative).  In the result of xs \\ ys,
110 -- the first occurrence of each element of ys in turn (if any)
111 -- has been removed from xs.  Thus, (xs ++ ys) \\ xs == ys.
112 (\\)                    :: (Eq a) => [a] -> [a] -> [a]
113 (\\)                    =  foldl (flip delete)
114
115 -- List union, remove the elements of first list from second.
116 union                   :: (Eq a) => [a] -> [a] -> [a]
117 union                   = unionBy (==)
118
119 unionBy                 :: (a -> a -> Bool) -> [a] -> [a] -> [a]
120 unionBy eq xs ys        =  xs ++ foldl (flip (deleteBy eq)) ys xs
121
122 intersect               :: (Eq a) => [a] -> [a] -> [a]
123 intersect               =  intersectBy (==)
124
125 intersectBy             :: (a -> a -> Bool) -> [a] -> [a] -> [a]
126 intersectBy eq xs ys    =  [x | x <- xs, any (eq x) ys]
127
128 -- intersperse sep inserts sep between the elements of its list argument.
129 -- e.g. intersperse ',' "abcde" == "a,b,c,d,e"
130 intersperse             :: a -> [a] -> [a]
131 intersperse sep []      = []
132 intersperse sep [x]     = [x]
133 intersperse sep (x:xs)  = x : sep : intersperse sep xs
134
135 transpose               :: [[a]] -> [[a]]
136 transpose               =  foldr
137                              (\xs xss -> zipWith (:) xs (xss ++ repeat []))
138                              []
139
140
141 -- partition takes a predicate and a list and returns a pair of lists:
142 -- those elements of the argument list that do and do not satisfy the
143 -- predicate, respectively; i,e,,
144 -- partition p xs == (filter p xs, filter (not . p) xs).
145 partition               :: (a -> Bool) -> [a] -> ([a],[a])
146 partition p xs          =  foldr select ([],[]) xs
147                            where select x (ts,fs) | p x       = (x:ts,fs)
148                                                   | otherwise = (ts, x:fs)
149 \end{code}
150
151 @mapAccumL@ behaves like a combination
152 of  @map@ and @foldl@;
153 it applies a function to each element of a list, passing an accumulating
154 parameter from left to right, and returning a final value of this
155 accumulator together with the new list.
156
157 \begin{code}
158
159 mapAccumL :: (acc -> x -> (acc, y)) -- Function of elt of input list
160                                     -- and accumulator, returning new
161                                     -- accumulator and elt of result list
162           -> acc            -- Initial accumulator 
163           -> [x]            -- Input list
164           -> (acc, [y])     -- Final accumulator and result list
165 mapAccumL f s []        =  (s, [])
166 mapAccumL f s (x:xs)    =  (s'',y:ys)
167                            where (s', y ) = f s x
168                                  (s'',ys) = mapAccumL f s' xs
169 \end{code}
170
171 @mapAccumR@ does the same, but working from right to left instead.  Its type is
172 the same as @mapAccumL@, though.
173
174 \begin{code}
175 mapAccumR :: (acc -> x -> (acc, y))     -- Function of elt of input list
176                                         -- and accumulator, returning new
177                                         -- accumulator and elt of result list
178             -> acc              -- Initial accumulator
179             -> [x]              -- Input list
180             -> (acc, [y])               -- Final accumulator and result list
181 mapAccumR f s []        =  (s, [])
182 mapAccumR f s (x:xs)    =  (s'', y:ys)
183                            where (s'',y ) = f s' x
184                                  (s', ys) = mapAccumR f s xs
185 \end{code}
186
187 \begin{code}
188 sort :: (Ord a) => [a] -> [a]
189 sort = sortBy compare
190
191 sortBy :: (a -> a -> Ordering) -> [a] -> [a]
192 sortBy cmp = foldr (insertBy cmp) []
193
194 insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
195 insertBy cmp x [] = [x]
196 insertBy cmp x ys@(y:ys')
197  = case cmp x y of
198      GT -> y : insertBy cmp x ys'
199      _  -> x : ys
200
201 maximumBy               :: (a -> a -> a) -> [a] -> a
202 maximumBy max []        =  error "List.maximumBy: empty list"
203 maximumBy max xs        =  foldl1 max xs
204
205 minimumBy               :: (a -> a -> a) -> [a] -> a
206 minimumBy min []        =  error "List.minimumBy: empty list"
207 minimumBy min xs        =  foldl1 min xs
208
209 genericLength           :: (Num i) => [b] -> i
210 genericLength []        =  0
211 genericLength (_:l)     =  1 + genericLength l
212
213 genericTake             :: (Integral i) => i -> [a] -> [a]
214 genericTake 0 _         =  []
215 genericTake _ []        =  []
216 genericTake n (x:xs) | n > 0  =  x : genericTake (n-1) xs
217 genericTake _  _        =  error "List.genericTake: negative argument"
218
219 genericDrop             :: (Integral i) => i -> [a] -> [a]
220 genericDrop 0 xs        =  xs
221 genericDrop _ []        =  []
222 genericDrop n (_:xs) | n > 0  =  genericDrop (n-1) xs
223 genericDrop _ _         =  error "List.genericDrop: negative argument"
224
225 genericSplitAt          :: (Integral i) => i -> [b] -> ([b],[b])
226 genericSplitAt 0 xs     =  ([],xs)
227 genericSplitAt _ []     =  ([],[])
228 genericSplitAt n (x:xs) | n > 0  =  (x:xs',xs'') where
229                                (xs',xs'') = genericSplitAt (n-1) xs
230 genericSplitAt _ _      =  error "List.genericSplitAt: negative argument"
231
232
233 genericIndex :: (Integral a) => [b] -> a -> b
234 genericIndex (x:_)  0 = x
235 genericIndex (_:xs) n 
236  | n > 0     = genericIndex xs (n-1)
237  | otherwise = error "List.genericIndex: negative argument."
238 genericIndex _ _      = error "List.genericIndex: index too large."
239
240 genericReplicate        :: (Integral i) => i -> a -> [a]
241 genericReplicate n x    =  genericTake n (repeat x)
242
243
244 zip4                    :: [a] -> [b] -> [c] -> [d] -> [(a,b,c,d)]
245 zip4                    =  zipWith4 (,,,)
246
247 zip5                    :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a,b,c,d,e)]
248 zip5                    =  zipWith5 (,,,,)
249
250 zip6                    :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> 
251                               [(a,b,c,d,e,f)]
252 zip6                    =  zipWith6 (,,,,,)
253
254 zip7                    :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] ->
255                               [g] -> [(a,b,c,d,e,f,g)]
256 zip7                    =  zipWith7 (,,,,,,)
257
258 zipWith4                :: (a->b->c->d->e) -> [a]->[b]->[c]->[d]->[e]
259 zipWith4 z (a:as) (b:bs) (c:cs) (d:ds)
260                         =  z a b c d : zipWith4 z as bs cs ds
261 zipWith4 _ _ _ _ _      =  []
262
263 zipWith5                :: (a->b->c->d->e->f) -> 
264                            [a]->[b]->[c]->[d]->[e]->[f]
265 zipWith5 z (a:as) (b:bs) (c:cs) (d:ds) (e:es)
266                         =  z a b c d e : zipWith5 z as bs cs ds es
267 zipWith5 _ _ _ _ _ _    = []
268
269 zipWith6                :: (a->b->c->d->e->f->g) ->
270                            [a]->[b]->[c]->[d]->[e]->[f]->[g]
271 zipWith6 z (a:as) (b:bs) (c:cs) (d:ds) (e:es) (f:fs)
272                         =  z a b c d e f : zipWith6 z as bs cs ds es fs
273 zipWith6 _ _ _ _ _ _ _  = []
274
275 zipWith7                :: (a->b->c->d->e->f->g->h) ->
276                            [a]->[b]->[c]->[d]->[e]->[f]->[g]->[h]
277 zipWith7 z (a:as) (b:bs) (c:cs) (d:ds) (e:es) (f:fs) (g:gs)
278                    =  z a b c d e f g : zipWith7 z as bs cs ds es fs gs
279 zipWith7 _ _ _ _ _ _ _ _ = []
280
281 unzip4                  :: [(a,b,c,d)] -> ([a],[b],[c],[d])
282 unzip4                  =  foldr (\(a,b,c,d) ~(as,bs,cs,ds) ->
283                                         (a:as,b:bs,c:cs,d:ds))
284                                  ([],[],[],[])
285
286 unzip5                  :: [(a,b,c,d,e)] -> ([a],[b],[c],[d],[e])
287 unzip5                  =  foldr (\(a,b,c,d,e) ~(as,bs,cs,ds,es) ->
288                                         (a:as,b:bs,c:cs,d:ds,e:es))
289                                  ([],[],[],[],[])
290
291 unzip6                  :: [(a,b,c,d,e,f)] -> ([a],[b],[c],[d],[e],[f])
292 unzip6                  =  foldr (\(a,b,c,d,e,f) ~(as,bs,cs,ds,es,fs) ->
293                                         (a:as,b:bs,c:cs,d:ds,e:es,f:fs))
294                                  ([],[],[],[],[],[])
295
296 unzip7          :: [(a,b,c,d,e,f,g)] -> ([a],[b],[c],[d],[e],[f],[g])
297 unzip7          =  foldr (\(a,b,c,d,e,f,g) ~(as,bs,cs,ds,es,fs,gs) ->
298                                 (a:as,b:bs,c:cs,d:ds,e:es,f:fs,g:gs))
299                          ([],[],[],[],[],[],[])
300
301
302
303 deleteFirstsBy          :: (a -> a -> Bool) -> [a] -> [a] -> [a]
304 deleteFirstsBy eq       =  foldl (flip (deleteBy eq))
305
306
307 -- group splits its list argument into a list of lists of equal, adjacent
308 -- elements.  e.g.,
309 -- group "Mississippi" == ["M","i","ss","i","ss","i","pp","i"]
310 group                   :: (Eq a) => [a] -> [[a]]
311 group                   =  groupBy (==)
312
313 groupBy                 :: (a -> a -> Bool) -> [a] -> [[a]]
314 groupBy eq []           =  []
315 groupBy eq (x:xs)       =  (x:ys) : groupBy eq zs
316                            where (ys,zs) = span (eq x) xs
317
318 -- inits xs returns the list of initial segments of xs, shortest first.
319 -- e.g., inits "abc" == ["","a","ab","abc"]
320 inits                   :: [a] -> [[a]]
321 inits []                =  [[]]
322 inits (x:xs)            =  [[]] ++ map (x:) (inits xs)
323
324 -- tails xs returns the list of all final segments of xs, longest first.
325 -- e.g., tails "abc" == ["abc", "bc", "c",""]
326 tails                   :: [a] -> [[a]]
327 tails []                =  [[]]
328 tails xxs@(_:xs)        =  xxs : tails xs
329
330 \end{code}