Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Operations on lists.
Synopsis
- (++) :: [a] -> [a] -> [a]
- head :: [a] -> a
- last :: [a] -> a
- tail :: [a] -> [a]
- init :: [a] -> [a]
- uncons :: [a] -> Maybe (a, [a])
- singleton :: a -> [a]
- null :: Foldable t => t a -> Bool
- length :: Foldable t => t 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 :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- foldl1' :: (a -> a -> a) -> [a] -> a
- foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
- concat :: Foldable t => t [a] -> [a]
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- sum :: (Foldable t, Num a) => t a -> a
- product :: (Foldable t, Num a) => t a -> a
- maximum :: forall a. (Foldable t, Ord a) => t a -> a
- minimum :: forall a. (Foldable t, Ord a) => t a -> a
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl' :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- iterate :: (a -> a) -> a -> [a]
- 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]
- dropWhileEnd :: (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
- isSubsequenceOf :: Eq a => [a] -> [a] -> Bool
- elem :: (Foldable t, Eq a) => a -> t a -> Bool
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- find :: Foldable t => (a -> Bool) -> t 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]
- sortOn :: Ord b => (a -> b) -> [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 :: Foldable t => (a -> a -> Ordering) -> t a -> a
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- genericLength :: Num i => [a] -> i
- genericTake :: Integral i => i -> [a] -> [a]
- genericDrop :: Integral i => i -> [a] -> [a]
- genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
- genericIndex :: Integral i => [a] -> i -> a
- genericReplicate :: Integral i => i -> a -> [a]
Basic functions
(++) :: [a] -> [a] -> [a] infixr 5 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.
\(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.
>>>
head [1, 2, 3]
1>>>
head [1..]
1>>>
head []
Exception: Prelude.head: empty list
\(\mathcal{O}(n)\). Extract the last element of a list, which must be finite and non-empty.
>>>
last [1, 2, 3]
3>>>
last [1..]
* Hangs forever *>>>
last []
Exception: Prelude.last: empty list
\(\mathcal{O}(1)\). Extract the elements after the head of a list, which must be non-empty.
>>>
tail [1, 2, 3]
[2,3]>>>
tail [1]
[]>>>
tail []
Exception: Prelude.tail: empty list
\(\mathcal{O}(n)\). Return all the elements of a list except the last one. The list must be non-empty.
>>>
init [1, 2, 3]
[1,2]>>>
init [1]
[]>>>
init []
Exception: Prelude.init: empty list
null :: Foldable t => t a -> Bool Source #
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
Examples
Basic usage:
>>>
null []
True
>>>
null [1]
False
null
terminates even for infinite structures:
>>>
null [1..]
False
Since: base-4.8.0.0
length :: Foldable t => t a -> Int Source #
Returns the size/length of a finite structure as an Int
. The
default implementation is optimized for structures that are similar to
cons-lists, because there is no general way to do better.
Examples
Basic usage:
>>>
length []
0
>>>
length ['a', 'b', 'c']
3>>>
length [1..]
* Hangs forever *
Since: base-4.8.0.0
List transformations
map :: (a -> b) -> [a] -> [b] Source #
\(\mathcal{O}(n)\). 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, ...]
>>>
map (+1) [1, 2, 3]
[2,3,4]
reverse :: [a] -> [a] Source #
reverse
xs
returns the elements of xs
in reverse order.
xs
must be finite.
>>>
reverse []
[]>>>
reverse [42]
[42]>>>
reverse [2,5,7]
[7,5,2]>>>
reverse [1..]
* Hangs forever *
intersperse :: a -> [a] -> [a] Source #
\(\mathcal{O}(n)\). 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.
>>>
intercalate ", " ["Lorem", "ipsum", "dolor"]
"Lorem, ipsum, dolor"
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]]
If some of the rows are shorter than the following rows, their elements are skipped:
>>>
transpose [[10,11],[20],[],[30,31,32]]
[[10,20,30],[11,31],[32]]
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 :: Foldable t => (b -> a -> b) -> b -> t a -> b Source #
Left-associative fold of a structure.
In the case of lists, foldl
, when 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
Note that to produce the outermost application of the operator the
entire input list must be traversed. This means that foldl'
will
diverge if given an infinite list.
Also note that if you want an efficient left-fold, you probably want to
use foldl'
instead of foldl
. The reason for this is that latter does
not force the "inner" results (e.g. z `f` x1
in the above example)
before applying them to the operator (e.g. to (`f` x2)
). This results
in a thunk chain \(\mathcal{O}(n)\) elements long, which then must be
evaluated from the outside-in.
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl
f z .toList
Examples
Basic usage:
>>>
foldl (+) 42 (Node (Leaf 1) 3 (Node Empty 4 (Leaf 2)))
52
>>>
foldl (+) 42 Empty
42
>>>
foldl (\string nextElement -> nextElement : string) "abcd" (Node (Leaf 'd') 'e' (Node Empty 'f' (Leaf 'g')))
"gfedabcd"
Left-folding infinite structures never terminates:
>>>
let infiniteNode = Node Empty 1 infiniteNode in foldl (+) 42 infiniteNode
* Hangs forever *
Evaluating the head of the result (when applicable) does not terminate, unlike foldr
:
>>>
let infiniteNode = Node Empty 'd' infiniteNode in take 5 (foldl (\string nextElement -> nextElement : string) "abc" infiniteNode)
* Hangs forever *
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b Source #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to weak head normal
form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a finite
list to a single, monolithic result (e.g. length
).
For a general Foldable
structure this should be semantically identical
to,
foldl' f z =foldl'
f z .toList
Since: base-4.6.0.0
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a Source #
A variant of foldl
that has no base case,
and thus may only be applied to non-empty structures.
⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
foldl1
f =foldl1
f .toList
Examples
Basic usage:
>>>
foldl1 (+) [1..4]
10
>>>
foldl1 (+) []
*** Exception: Prelude.foldl1: empty list
>>>
foldl1 (+) Nothing
*** Exception: foldl1: empty structure
>>>
foldl1 (-) [1..4]
-8
>>>
foldl1 (&&) [True, False, True, True]
False
>>>
foldl1 (||) [False, False, True, True]
True
>>>
foldl1 (+) [1..]
* Hangs forever *
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b Source #
Right-associative fold of a structure.
In the case of lists, foldr
, when 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)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
foldr
can produce a terminating expression from an infinite list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
Examples
Basic usage:
>>>
foldr (||) False [False, True, False]
True
>>>
foldr (||) False []
False
>>>
foldr (\nextChar reversedString -> reversedString ++ [nextChar]) "foo" ['a', 'b', 'c', 'd']
"foodcba"
Infinite structures
⚠️ Applying foldr
to infinite structures usually doesn't terminate.
It may still terminate in one of the following conditions:
- the folding function is short-circuiting
- the folding function is lazy on its second argument
Short-circuiting
'(||)' short-circuits on True
values, so the following terminates because there is a True
value finitely far from the left side:
>>>
foldr (||) False (True : repeat False)
True
But the following doesn't terminate:
>>>
foldr (||) False (repeat False ++ [True])
* Hangs forever *
Laziness in the second argument
Applying foldr
to infinite structures terminates when the folding function is lazy on its second argument:
>>>
foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1)
[1,4,7,10,13,16,19,22,25,28,31,34,37,40,43...
>>>
take 5 $ foldr (\nextElement accumulator -> nextElement : fmap (+3) accumulator) [42] (repeat 1)
[1,4,7,10,13]
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a Source #
A variant of foldr
that has no base case,
and thus may only be applied to non-empty structures.
⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
Examples
Basic usage:
>>>
foldr1 (+) [1..4]
10
>>>
foldr1 (+) []
Exception: Prelude.foldr1: empty list
>>>
foldr1 (+) Nothing
*** Exception: foldr1: empty structure
>>>
foldr1 (-) [1..4]
-2
>>>
foldr1 (&&) [True, False, True, True]
False
>>>
foldr1 (||) [False, False, True, True]
True
>>>
foldr1 (+) [1..]
* Hangs forever *
Special folds
concat :: Foldable t => t [a] -> [a] Source #
The concatenation of all the elements of a container of lists.
Examples
Basic usage:
>>>
concat (Just [1, 2, 3])
[1,2,3]
>>>
concat (Node (Leaf [1, 2, 3]) [4, 5] (Node Empty [6] (Leaf [])))
[1,2,3,4,5,6]
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] Source #
Map a function over all the elements of a container and concatenate the resulting lists.
Examples
Basic usage:
>>>
concatMap (take 3) [[1..], [10..], [100..], [1000..]]
[1,2,3,10,11,12,100,101,102,1000,1001,1002]
>>>
concatMap (take 3) (Node (Leaf [1..]) [10..] Empty)
[1,2,3,10,11,12]
and :: Foldable t => t Bool -> Bool Source #
and
returns the conjunction of a container of Bools. For the
result to be True
, the container must be finite; False
, however,
results from a False
value finitely far from the left end.
Examples
Basic usage:
>>>
and []
True
>>>
and [True]
True
>>>
and [False]
False
>>>
and [True, True, False]
False
>>>
and (False : repeat True) -- Infinite list [False,True,True,True,True,True,True...
False
>>>
and (repeat True)
* Hangs forever *
or :: Foldable t => t Bool -> Bool Source #
or
returns the disjunction of a container of Bools. For the
result to be False
, the container must be finite; True
, however,
results from a True
value finitely far from the left end.
Examples
Basic usage:
>>>
or []
False
>>>
or [True]
True
>>>
or [False]
False
>>>
or [True, True, False]
True
>>>
or (True : repeat False) -- Infinite list [True,False,False,False,False,False,False...
True
>>>
or (repeat False)
* Hangs forever *
any :: Foldable t => (a -> Bool) -> t a -> Bool Source #
Determines whether any element of the structure satisfies the predicate.
Examples
Basic usage:
>>>
any (> 3) []
False
>>>
any (> 3) [1,2]
False
>>>
any (> 3) [1,2,3,4,5]
True
>>>
any (> 3) [1..]
True
>>>
any (> 3) [0, -1..]
* Hangs forever *
all :: Foldable t => (a -> Bool) -> t a -> Bool Source #
Determines whether all elements of the structure satisfy the predicate.
Examples
Basic usage:
>>>
all (> 3) []
True
>>>
all (> 3) [1,2]
False
>>>
all (> 3) [1,2,3,4,5]
False
>>>
all (> 3) [1..]
False
>>>
all (> 3) [4..]
* Hangs forever *
sum :: (Foldable t, Num a) => t a -> a Source #
The sum
function computes the sum of the numbers of a structure.
Examples
Basic usage:
>>>
sum []
0
>>>
sum [42]
42
>>>
sum [1..10]
55
>>>
sum [4.1, 2.0, 1.7]
7.8
>>>
sum [1..]
* Hangs forever *
Since: base-4.8.0.0
product :: (Foldable t, Num a) => t a -> a Source #
The product
function computes the product of the numbers of a
structure.
Examples
Basic usage:
>>>
product []
1
>>>
product [42]
42
>>>
product [1..10]
3628800
>>>
product [4.1, 2.0, 1.7]
13.939999999999998
>>>
product [1..]
* Hangs forever *
Since: base-4.8.0.0
maximum :: forall a. (Foldable t, Ord a) => t a -> a Source #
The largest element of a non-empty structure.
⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
Examples
Basic usage:
>>>
maximum [1..10]
10
>>>
maximum []
*** Exception: Prelude.maximum: empty list
>>>
maximum Nothing
*** Exception: maximum: empty structure
Since: base-4.8.0.0
minimum :: forall a. (Foldable t, Ord a) => t a -> a Source #
The least element of a non-empty structure.
⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty
Examples
Basic usage:
>>>
minimum [1..10]
1
>>>
minimum []
*** Exception: Prelude.minimum: empty list
>>>
minimum Nothing
*** Exception: minimum: empty structure
Since: base-4.8.0.0
Building lists
Scans
scanl :: (b -> a -> b) -> b -> [a] -> [b] Source #
\(\mathcal{O}(n)\). scanl
is similar to foldl
, but returns a list of
successive reduced values from the left:
scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
Note that
last (scanl f z xs) == foldl f z xs
>>>
scanl (+) 0 [1..4]
[0,1,3,6,10]>>>
scanl (+) 42 []
[42]>>>
scanl (-) 100 [1..4]
[100,99,97,94,90]>>>
scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
["foo","afoo","bafoo","cbafoo","dcbafoo"]>>>
scanl (+) 0 [1..]
* Hangs forever *
scanl1 :: (a -> a -> a) -> [a] -> [a] Source #
\(\mathcal{O}(n)\). scanl1
is a variant of scanl
that has no starting
value argument:
scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
>>>
scanl1 (+) [1..4]
[1,3,6,10]>>>
scanl1 (+) []
[]>>>
scanl1 (-) [1..4]
[1,-1,-4,-8]>>>
scanl1 (&&) [True, False, True, True]
[True,False,False,False]>>>
scanl1 (||) [False, False, True, True]
[False,False,True,True]>>>
scanl1 (+) [1..]
* Hangs forever *
scanr :: (a -> b -> b) -> b -> [a] -> [b] Source #
\(\mathcal{O}(n)\). scanr
is the right-to-left dual of scanl
. Note that the order of parameters on the accumulating function are reversed compared to scanl
.
Also note that
head (scanr f z xs) == foldr f z xs.
>>>
scanr (+) 0 [1..4]
[10,9,7,4,0]>>>
scanr (+) 42 []
[42]>>>
scanr (-) 100 [1..4]
[98,-97,99,-96,100]>>>
scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]>>>
scanr (+) 0 [1..]
* Hangs forever *
scanr1 :: (a -> a -> a) -> [a] -> [a] Source #
\(\mathcal{O}(n)\). scanr1
is a variant of scanr
that has no starting
value argument.
>>>
scanr1 (+) [1..4]
[10,9,7,4]>>>
scanr1 (+) []
[]>>>
scanr1 (-) [1..4]
[-2,3,-1,4]>>>
scanr1 (&&) [True, False, True, True]
[False,False,True,True]>>>
scanr1 (||) [True, True, False, False]
[True,True,False,False]>>>
scanr1 (+) [1..]
* Hangs forever *
Accumulating maps
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) Source #
The mapAccumL
function behaves like a combination of fmap
and foldl
; it applies a function to each element of a structure,
passing an accumulating parameter from left to right, and returning
a final value of this accumulator together with the new structure.
Examples
Basic usage:
>>>
mapAccumL (\a b -> (a + b, a)) 0 [1..10]
(55,[0,1,3,6,10,15,21,28,36,45])
>>>
mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]
("012345",["0","01","012","0123","01234"])
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) Source #
The mapAccumR
function behaves like a combination of fmap
and foldr
; it applies a function to each element of a structure,
passing an accumulating parameter from right to left, and returning
a final value of this accumulator together with the new structure.
Examples
Basic usage:
>>>
mapAccumR (\a b -> (a + b, a)) 0 [1..10]
(55,[54,52,49,45,40,34,27,19,10,0])
>>>
mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]
("054321",["05432","0543","054","05","0"])
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), ...]
Note that iterate
is lazy, potentially leading to thunk build-up if
the consumer doesn't force each iterate. See iterate'
for a strict
variant of this function.
>>>
iterate not True
[True,False,True,False...>>>
iterate (+3) 42
[42,45,48,51,54,57,60,63...
repeat
x
is an infinite list, with x
the value of every element.
>>>
repeat 17
[17,17,17,17,17,17,17,17,17...
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 genericReplicate
,
in which n
may be of any integral type.
>>>
replicate 0 True
[]>>>
replicate (-1) True
[]>>>
replicate 4 True
[True,True,True,True]
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.
>>>
cycle []
Exception: Prelude.cycle: empty list>>>
cycle [42]
[42,42,42,42,42,42,42,42,42,42...>>>
cycle [2, 5, 7]
[2,5,7,2,5,7,2,5,7,2,5,7...
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 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 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 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]
[]
dropWhileEnd :: (a -> Bool) -> [a] -> [a] Source #
The dropWhileEnd
function drops the largest suffix of a list
in which the given predicate holds for all elements. For example:
>>>
dropWhileEnd isSpace "foo\n"
"foo"
>>>
dropWhileEnd isSpace "foo bar"
"foo bar"
dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined
Since: base-4.5.0.0
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 #
\(\mathcal{O}(\min(m,n))\). 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] -> Bool Source #
\(\mathcal{O}(\min(m,n))\). The isPrefixOf
function takes two lists and
returns True
iff the first list is a prefix of the second.
>>>
"Hello" `isPrefixOf` "Hello World!"
True
>>>
"Hello" `isPrefixOf` "Wello Horld!"
False
isSuffixOf :: Eq a => [a] -> [a] -> Bool Source #
The isSuffixOf
function takes two lists and returns True
iff
the first list is a suffix of the second. The second list must be
finite.
>>>
"ld!" `isSuffixOf` "Hello World!"
True
>>>
"World" `isSuffixOf` "Hello World!"
False
isSubsequenceOf :: Eq a => [a] -> [a] -> Bool Source #
The isSubsequenceOf
function takes two lists and returns True
if all
the elements of the first list occur, in order, in the second. The
elements do not have to occur consecutively.
is equivalent to isSubsequenceOf
x y
.elem
x (subsequences
y)
Examples
>>>
isSubsequenceOf "GHC" "The Glorious Haskell Compiler"
True>>>
isSubsequenceOf ['a','d'..'z'] ['a'..'z']
True>>>
isSubsequenceOf [1..10] [10,9..0]
False
Since: base-4.8.0.0
Searching lists
Searching by equality
elem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 Source #
Does the element occur in the structure?
Note: elem
is often used in infix form.
Examples
Basic usage:
>>>
3 `elem` []
False
>>>
3 `elem` [1,2]
False
>>>
3 `elem` [1,2,3,4,5]
True
For infinite structures, elem
terminates if the value exists at a
finite distance from the left side of the structure:
>>>
3 `elem` [1..]
True
>>>
3 `elem` ([4..] ++ [3])
* Hangs forever *
Since: base-4.8.0.0
notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 Source #
notElem
is the negation of elem
.
Examples
Basic usage:
>>>
3 `notElem` []
True
>>>
3 `notElem` [1,2]
True
>>>
3 `notElem` [1,2,3,4,5]
False
For infinite structures, notElem
terminates if the value exists at a
finite distance from the left side of the structure:
>>>
3 `notElem` [1..]
False
>>>
3 `notElem` ([4..] ++ [3])
* Hangs forever *
lookup :: Eq a => a -> [(a, b)] -> Maybe b Source #
\(\mathcal{O}(n)\). lookup
key assocs
looks up a key in an association
list.
>>>
lookup 2 []
Nothing>>>
lookup 2 [(1, "first")]
Nothing>>>
lookup 2 [(1, "first"), (2, "second"), (3, "third")]
Just "second"
Searching with a predicate
find :: Foldable t => (a -> Bool) -> t a -> Maybe a Source #
The find
function takes a predicate and a structure and returns
the leftmost element of the structure matching the predicate, or
Nothing
if there is no such element.
Examples
Basic usage:
>>>
find (> 42) [0, 5..]
Just 45
>>>
find (> 4) (Node (Leaf 3) 17 (Node Empty 12 (Leaf 8)))
Just 17
>>>
find (> 12) [1..7]
Nothing
filter :: (a -> Bool) -> [a] -> [a] Source #
\(\mathcal{O}(n)\). 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]
>>>
filter odd [1, 2, 3]
[1,3]
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)
>>>
partition (`elem` "aeiou") "Hello World!"
("eoo","Hll Wrld!")
Indexing lists
These functions treat a list xs
as a indexed collection,
with indices ranging from 0 to
.length
xs - 1
(!!) :: [a] -> Int -> a infixl 9 Source #
List index (subscript) operator, starting from 0.
It is an instance of the more general genericIndex
,
which takes an index of any integral type.
>>>
['a', 'b', 'c'] !! 0
'a'>>>
['a', 'b', 'c'] !! 2
'c'>>>
['a', 'b', 'c'] !! 3
Exception: Prelude.!!: index too large>>>
['a', 'b', 'c'] !! (-1)
Exception: Prelude.!!: negative index
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.
>>>
elemIndices 'o' "Hello World"
[4,7]
findIndices :: (a -> Bool) -> [a] -> [Int] Source #
The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending order.
>>>
findIndices (`elem` "aeiou") "Hello World!"
[1,4,7]
Zipping and unzipping lists
zip :: [a] -> [b] -> [(a, b)] Source #
\(\mathcal{O}(\min(m,n))\). zip
takes two lists and returns a list of
corresponding pairs.
>>>
zip [1, 2] ['a', 'b']
[(1, 'a'), (2, 'b')]
If one input list is shorter than the other, excess elements of the longer list are discarded, even if one of the lists is infinite:
>>>
zip [1] ['a', 'b']
[(1, 'a')]>>>
zip [1, 2] ['a']
[(1, 'a')]>>>
zip [] [1..]
[]>>>
zip [1..] []
[]
zip
is right-lazy:
>>>
zip [] _|_
[]>>>
zip _|_ []
_|_
zip
is capable of list fusion, but it is restricted to its
first list argument and its resulting list.
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #
\(\mathcal{O}(\min(m,n))\). zipWith
generalises zip
by zipping with the
function given as the first argument, instead of a tupling function.
zipWith (,) xs ys == zip xs ys zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
For example,
is applied to two lists to produce the list of
corresponding sums:zipWith
(+)
>>>
zipWith (+) [1, 2, 3] [4, 5, 6]
[5,7,9]
zipWith
is right-lazy:
>>>
zipWith f [] _|_
[]
zipWith
is capable of list fusion, but it is restricted to its
first list argument and its resulting list.
zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #
The zipWith3
function takes a function which combines three
elements, as well as three lists and returns a list of the function applied
to corresponding elements, analogous to zipWith
.
It is capable of list fusion, but it is restricted to its
first list argument and its resulting list.
zipWith3 (,,) xs ys zs == zip3 xs ys zs zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
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.
>>>
unzip []
([],[])>>>
unzip [(1, 'a'), (2, 'b')]
([1,2],"ab")
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.
Note that after splitting the string at newline characters, the last part of the string is considered a line even if it doesn't end with a newline. For example,
>>>
lines ""
[]
>>>
lines "\n"
[""]
>>>
lines "one"
["one"]
>>>
lines "one\n"
["one"]
>>>
lines "one\n\n"
["one",""]
>>>
lines "one\ntwo"
["one","two"]
>>>
lines "one\ntwo\n"
["one","two"]
Thus
contains at least as many elements as newlines in lines
ss
.
words :: String -> [String] Source #
words
breaks a string up into a list of words, which were delimited
by white space.
>>>
words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
"Set" operations
nub :: Eq a => [a] -> [a] Source #
\(\mathcal{O}(n^2)\). The nub
function removes duplicate elements from a
list. In particular, it keeps only the first occurrence of each element. (The
name nub
means `essence'.) It is a special case of nubBy
, which allows
the programmer to supply their own equality test.
>>>
nub [1,2,3,4,3,2,1,2,4,3,5]
[1,2,3,4,5]
(\\) :: Eq a => [a] -> [a] -> [a] infix 5 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.
>>>
"Hello World!" \\ "ell W"
"Hoorld!"
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. If the element is found in both the first
and the second list, the element from the first list will be used.
Ordered lists
sortOn :: Ord b => (a -> b) -> [a] -> [a] Source #
Sort a list by comparing the results of a key function applied to each
element. sortOn f
is equivalent to sortBy (comparing f)
, but has the
performance advantage of only evaluating f
once for each element in the
input list. This is called the decorate-sort-undecorate paradigm, or
Schwartzian transform.
Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
Since: base-4.8.0.0
insert :: Ord a => a -> [a] -> [a] Source #
\(\mathcal{O}(n)\). The insert
function takes an element and a list and
inserts the element into the list at the first position where it is 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.
>>>
insert 4 [1,2,3,5,6,7]
[1,2,3,4,5,6,7]
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
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.
insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] Source #
\(\mathcal{O}(n)\). The non-overloaded version of insert
.
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a Source #
The largest element of a non-empty structure with respect to the given comparison function.
Examples
Basic usage:
>>>
maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
"Longest"
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a Source #
The least element of a non-empty structure with respect to the given comparison function.
Examples
Basic usage:
>>>
minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
"!"
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
genericLength :: Num i => [a] -> i Source #
\(\mathcal{O}(n)\). 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
.
>>>
genericLength [1, 2, 3] :: Int
3>>>
genericLength [1, 2, 3] :: Float
3.0
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 -> [a] -> ([a], [a]) Source #
The genericSplitAt
function is an overloaded version of splitAt
, which
accepts any Integral
value as the position at which to split.
genericIndex :: Integral i => [a] -> i -> a Source #
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.