| Portability | portable | 
|---|---|
| Stability | stable | 
| Maintainer | libraries@haskell.org | 
Data.List
Contents
Description
Operations on lists.
- (++) :: [a] -> [a] -> [a]
- head :: [a] -> a
- last :: [a] -> a
- tail :: [a] -> [a]
- init :: [a] -> [a]
- null :: [a] -> Bool
- length :: [a] -> Int
- map :: (a -> b) -> [a] -> [b]
- reverse :: [a] -> [a]
- intersperse :: a -> [a] -> [a]
- intercalate :: [a] -> [[a]] -> [a]
- transpose :: [[a]] -> [[a]]
- subsequences :: [a] -> [[a]]
- permutations :: [a] -> [[a]]
- foldl :: (a -> b -> a) -> a -> [b] -> a
- foldl' :: (a -> b -> a) -> a -> [b] -> a
- foldl1 :: (a -> a -> a) -> [a] -> a
- foldl1' :: (a -> a -> a) -> [a] -> a
- foldr :: (a -> b -> b) -> b -> [a] -> b
- foldr1 :: (a -> a -> a) -> [a] -> a
- concat :: [[a]] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
- and :: [Bool] -> Bool
- or :: [Bool] -> Bool
- any :: (a -> Bool) -> [a] -> Bool
- all :: (a -> Bool) -> [a] -> Bool
- sum :: Num a => [a] -> a
- product :: Num a => [a] -> a
- maximum :: Ord a => [a] -> a
- minimum :: Ord a => [a] -> a
- scanl :: (a -> b -> a) -> a -> [b] -> [a]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
- iterate :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- cycle :: [a] -> [a]
- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
- group :: Eq a => [a] -> [[a]]
- inits :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- isSuffixOf :: Eq a => [a] -> [a] -> Bool
- isInfixOf :: Eq a => [a] -> [a] -> Bool
- elem :: Eq a => a -> [a] -> Bool
- notElem :: Eq a => a -> [a] -> Bool
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- find :: (a -> Bool) -> [a] -> Maybe a
- filter :: (a -> Bool) -> [a] -> [a]
- partition :: (a -> Bool) -> [a] -> ([a], [a])
- (!!) :: [a] -> Int -> a
- elemIndex :: Eq a => a -> [a] -> Maybe Int
- elemIndices :: Eq a => a -> [a] -> [Int]
- findIndex :: (a -> Bool) -> [a] -> Maybe Int
- findIndices :: (a -> Bool) -> [a] -> [Int]
- zip :: [a] -> [b] -> [(a, b)]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
- zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
- zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
- zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
- unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
- unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
- unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
- lines :: String -> [String]
- words :: String -> [String]
- unlines :: [String] -> String
- unwords :: [String] -> String
- nub :: Eq a => [a] -> [a]
- delete :: Eq a => a -> [a] -> [a]
- (\\) :: Eq a => [a] -> [a] -> [a]
- union :: Eq a => [a] -> [a] -> [a]
- intersect :: Eq a => [a] -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- insert :: Ord a => a -> [a] -> [a]
- nubBy :: (a -> a -> Bool) -> [a] -> [a]
- deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]
- deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- maximumBy :: (a -> a -> Ordering) -> [a] -> a
- minimumBy :: (a -> a -> Ordering) -> [a] -> a
- genericLength :: Num i => [b] -> i
- genericTake :: Integral i => i -> [a] -> [a]
- genericDrop :: Integral i => i -> [a] -> [a]
- genericSplitAt :: Integral i => i -> [b] -> ([b], [b])
- genericIndex :: Integral a => [b] -> a -> b
- genericReplicate :: Integral i => i -> a -> [a]
Basic functions
(++) :: [a] -> [a] -> [a]Source
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
Return all the elements of a list except the last one. The list must be non-empty.
List transformations
map :: (a -> b) -> [a] -> [b]Source
map f xs is the list obtained by applying f to each element
 of xs, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
reverse xs returns the elements of xs in reverse order.
 xs must be finite.
intersperse :: a -> [a] -> [a]Source
The intersperse function takes an element and a list and
 `intersperses' that element between the elements of the list.
 For example,
intersperse ',' "abcde" == "a,b,c,d,e"
intercalate :: [a] -> [[a]] -> [a]Source
intercalate xs xss is equivalent to (.
 It inserts the list concat (intersperse xs xss))xs in between the lists in xss and concatenates the
 result.
transpose :: [[a]] -> [[a]]Source
The transpose function transposes the rows and columns of its argument.
 For example,
transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]]
subsequences :: [a] -> [[a]]Source
The subsequences function returns the list of all subsequences of the argument.
subsequences "abc" == ["","a","b","ab","c","ac","bc","abc"]
permutations :: [a] -> [[a]]Source
The permutations function returns the list of all permutations of the argument.
permutations "abc" == ["abc","bac","cba","bca","cab","acb"]
Reducing lists (folds)
foldl :: (a -> b -> a) -> a -> [b] -> aSource
foldl, applied to a binary operator, a starting value (typically
 the left-identity of the operator), and a list, reduces the list
 using the binary operator, from left to right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
The list must be finite.
foldr :: (a -> b -> b) -> b -> [a] -> bSource
foldr, applied to a binary operator, a starting value (typically
 the right-identity of the operator), and a list, reduces the list
 using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Special folds
product :: Num a => [a] -> aSource
The product function computes the product of a finite list of numbers.
Building lists
Scans
Accumulating maps
Infinite lists
iterate :: (a -> a) -> a -> [a]Source
iterate f x returns an infinite list of repeated applications
 of f to x:
iterate f x == [x, f x, f (f x), ...]
replicate :: Int -> a -> [a]Source
replicate n x is a list of length n with x the value of
 every element.
 It is an instance of the more general Data.List.genericReplicate,
 in which n may be of any integral type.
cycle ties a finite list into a circular one, or equivalently,
 the infinite repetition of the original list.  It is the identity
 on infinite lists.
Unfolding
unfoldr :: (b -> Maybe (a, b)) -> b -> [a]Source
The unfoldr function is a `dual' to foldr: while foldr
 reduces a list to a summary value, unfoldr builds a list from
 a seed value.  The function takes the element and returns Nothing
 if it is done producing the list or returns Just (a,b), in which
 case, a is a prepended to the list and b is used as the next
 element in a recursive call.  For example,
iterate f == unfoldr (\x -> Just (x, f x))
In some cases, unfoldr can undo a foldr operation:
unfoldr f' (foldr f z xs) == xs
if the following holds:
f' (f x y) = Just (x,y) f' z = Nothing
A simple use of unfoldr:
unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10 [10,9,8,7,6,5,4,3,2,1]
Sublists
Extracting sublists
take :: Int -> [a] -> [a]Source
take n, applied to a list xs, returns the prefix of xs
 of length n, or xs itself if n > :
length xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general Data.List.genericTake,
 in which n may be of any integral type.
drop :: Int -> [a] -> [a]Source
drop n xs returns the suffix of xs
 after the first n elements, or [] if n > :
length xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general Data.List.genericDrop,
 in which n may be of any integral type.
splitAt :: Int -> [a] -> ([a], [a])Source
splitAt n xs returns a tuple where first element is xs prefix of
 length n and second element is the remainder of the list:
 splitAt 6 "Hello World!" == ("Hello ","World!")
 splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5])
 splitAt 1 [1,2,3] == ([1],[2,3])
 splitAt 3 [1,2,3] == ([1,2,3],[])
 splitAt 4 [1,2,3] == ([1,2,3],[])
 splitAt 0 [1,2,3] == ([],[1,2,3])
 splitAt (-1) [1,2,3] == ([],[1,2,3])
It is equivalent to ( when take n xs, drop n xs)n is not _|_
 (splitAt _|_ xs = _|_).
 splitAt is an instance of the more general Data.List.genericSplitAt,
 in which n may be of any integral type.
takeWhile :: (a -> Bool) -> [a] -> [a]Source
takeWhile, applied to a predicate p and a list xs, returns the
 longest prefix (possibly empty) of xs of elements that satisfy p:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
span :: (a -> Bool) -> [a] -> ([a], [a])Source
span, applied to a predicate p and a list xs, returns a tuple where
 first element is longest prefix (possibly empty) of xs of elements that
 satisfy p and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
break :: (a -> Bool) -> [a] -> ([a], [a])Source
break, applied to a predicate p and a list xs, returns a tuple where
 first element is longest prefix (possibly empty) of xs of elements that
 do not satisfy p and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]Source
The stripPrefix function drops the given prefix from a list.
 It returns Nothing if the list did not start with the prefix
 given, or Just the list after the prefix, if it does.
stripPrefix "foo" "foobar" == Just "bar" stripPrefix "foo" "foo" == Just "" stripPrefix "foo" "barfoo" == Nothing stripPrefix "foo" "barfoobaz" == Nothing
group :: Eq a => [a] -> [[a]]Source
The group function takes a list and returns a list of lists such
 that the concatenation of the result is equal to the argument.  Moreover,
 each sublist in the result contains only equal elements.  For example,
group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
It is a special case of groupBy, which allows the programmer to supply
 their own equality test.
Predicates
isPrefixOf :: Eq a => [a] -> [a] -> BoolSource
The isPrefixOf function takes two lists and returns True
 iff the first list is a prefix of the second.
isSuffixOf :: Eq a => [a] -> [a] -> BoolSource
The isSuffixOf function takes two lists and returns True
 iff the first list is a suffix of the second.
 Both lists must be finite.
Searching lists
Searching by equality
lookup :: Eq a => a -> [(a, b)] -> Maybe bSource
lookup key assocs looks up a key in an association list.
Searching with a predicate
filter :: (a -> Bool) -> [a] -> [a]Source
filter, applied to a predicate and a list, returns the list of
 those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
partition :: (a -> Bool) -> [a] -> ([a], [a])Source
The partition function takes a predicate a list and returns
 the pair of lists of elements which do and do not satisfy the
 predicate, respectively; i.e.,
partition p xs == (filter p xs, filter (not . p) xs)
Indexing lists
These functions treat a list xs as a indexed collection,
 with indices ranging from 0 to length xs - 1
List index (subscript) operator, starting from 0.
 It is an instance of the more general Data.List.genericIndex,
 which takes an index of any integral type.
elemIndices :: Eq a => a -> [a] -> [Int]Source
The elemIndices function extends elemIndex, by returning the
 indices of all elements equal to the query element, in ascending order.
findIndices :: (a -> Bool) -> [a] -> [Int]Source
The findIndices function extends findIndex, by returning the
 indices of all elements satisfying the predicate, in ascending order.
Zipping and unzipping lists
zip :: [a] -> [b] -> [(a, b)]Source
zip takes two lists and returns a list of corresponding pairs.
 If one input list is short, excess elements of the longer list are
 discarded.
zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]Source
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]Source
unzip :: [(a, b)] -> ([a], [b])Source
unzip transforms a list of pairs into a list of first components
 and a list of second components.
Special lists
Functions on strings
lines :: String -> [String]Source
lines breaks a string up into a list of strings at newline
 characters.  The resulting strings do not contain newlines.
words :: String -> [String]Source
words breaks a string up into a list of words, which were delimited
 by white space.
"Set" operations
(\\) :: Eq a => [a] -> [a] -> [a]Source
The \\ function is list difference ((non-associative).
 In the result of xs \\ ys, the first occurrence of each element of
 ys in turn (if any) has been removed from xs.  Thus
(xs ++ ys) \\ xs == ys.
It is a special case of deleteFirstsBy, which allows the programmer
 to supply their own equality test.
union :: Eq a => [a] -> [a] -> [a]Source
The union function returns the list union of the two lists.
 For example,
"dog" `union` "cow" == "dogcw"
Duplicates, and elements of the first list, are removed from the
 the second list, but if the first list contains duplicates, so will
 the result.
 It is a special case of unionBy, which allows the programmer to supply
 their own equality test.
intersect :: Eq a => [a] -> [a] -> [a]Source
The intersect function takes the list intersection of two lists.
 For example,
[1,2,3,4] `intersect` [2,4,6,8] == [2,4]
If the first list contains duplicates, so will the result.
[1,2,2,3,4] `intersect` [6,4,4,2] == [2,2,4]
It is a special case of intersectBy, which allows the programmer to
 supply their own equality test.
Ordered lists
insert :: Ord a => a -> [a] -> [a]Source
The insert function takes an element and a list and inserts the
 element into the list at the last position where it is still less
 than or equal to the next element.  In particular, if the list
 is sorted before the call, the result will also be sorted.
 It is a special case of insertBy, which allows the programmer to
 supply their own comparison function.
Generalized functions
The "By" operations
By convention, overloaded functions have a non-overloaded
 counterpart whose name is suffixed with `By'.
It is often convenient to use these functions together with
 Data.Function.on, for instance sortBy (compare
 `on` fst)
User-supplied equality (replacing an Eq context)
The predicate is assumed to define an equivalence.
deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]Source
The deleteFirstsBy function takes a predicate and two lists and
 returns the first list with the first occurrence of each element of
 the second list removed.
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]Source
The intersectBy function is the non-overloaded version of intersect.
User-supplied comparison (replacing an Ord context)
The function is assumed to define a total ordering.
maximumBy :: (a -> a -> Ordering) -> [a] -> aSource
The maximumBy function takes a comparison function and a list
 and returns the greatest element of the list by the comparison function.
 The list must be finite and non-empty.
minimumBy :: (a -> a -> Ordering) -> [a] -> aSource
The minimumBy function takes a comparison function and a list
 and returns the least element of the list by the comparison function.
 The list must be finite and non-empty.
The "generic" operations
The prefix `generic' indicates an overloaded function that
 is a generalized version of a Prelude function.
genericLength :: Num i => [b] -> iSource
The genericLength function is an overloaded version of length.  In
 particular, instead of returning an Int, it returns any type which is
 an instance of Num.  It is, however, less efficient than length.
genericTake :: Integral i => i -> [a] -> [a]Source
The genericTake function is an overloaded version of take, which
 accepts any Integral value as the number of elements to take.
genericDrop :: Integral i => i -> [a] -> [a]Source
The genericDrop function is an overloaded version of drop, which
 accepts any Integral value as the number of elements to drop.
genericSplitAt :: Integral i => i -> [b] -> ([b], [b])Source
The genericSplitAt function is an overloaded version of splitAt, which
 accepts any Integral value as the position at which to split.
genericIndex :: Integral a => [b] -> a -> bSource
The genericIndex function is an overloaded version of !!, which
 accepts any Integral value as the index.
genericReplicate :: Integral i => i -> a -> [a]Source
The genericReplicate function is an overloaded version of replicate,
 which accepts any Integral value as the number of repetitions to make.