base-4.19.1.0: Basic libraries
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.List

Description

Operations on lists.

Synopsis

Basic functions

(++) :: [a] -> [a] -> [a] infixr 5 Source #

(++) appends 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.

Performance considerations

Expand

This function takes linear time in the number of elements of the first list. Thus it is better to associate repeated applications of (++) to the right (which is the default behaviour): xs ++ (ys ++ zs) or simply xs ++ ys ++ zs, but not (xs ++ ys) ++ zs. For the same reason concat = foldr (++) [] has linear performance, while foldl (++) [] is prone to quadratic slowdown

Examples

Expand
>>> [1, 2, 3] ++ [4, 5, 6]
[1,2,3,4,5,6]
>>> [] ++ [1, 2, 3]
[1,2,3]
>>> [3, 2, 1] ++ []
[3,2,1]

head :: HasCallStack => [a] -> a Source #

Warning: This is a partial function, it throws an error on empty lists. Use pattern matching or Data.List.uncons instead. Consider refactoring to use Data.List.NonEmpty.

\(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.

Examples
Expand
>>> head [1, 2, 3]
1
>>> head [1..]
1
>>> head []
*** Exception: Prelude.head: empty list

last :: HasCallStack => [a] -> a Source #

\(\mathcal{O}(n)\). Extract the last element of a list, which must be finite and non-empty.

WARNING: This function is partial. Consider using unsnoc instead.

Examples

Expand
>>> last [1, 2, 3]
3
>>> last [1..]
* Hangs forever *
>>> last []
*** Exception: Prelude.last: empty list

tail :: HasCallStack => [a] -> [a] Source #

Warning: This is a partial function, it throws an error on empty lists. Replace it with drop 1, or use pattern matching or Data.List.uncons instead. Consider refactoring to use Data.List.NonEmpty.

\(\mathcal{O}(1)\). Extract the elements after the head of a list, which must be non-empty.

Examples

Expand
>>> tail [1, 2, 3]
[2,3]
>>> tail [1]
[]
>>> tail []
*** Exception: Prelude.tail: empty list

init :: HasCallStack => [a] -> [a] Source #

\(\mathcal{O}(n)\). Return all the elements of a list except the last one. The list must be non-empty.

WARNING: This function is partial. Consider using unsnoc instead.

Examples

Expand
>>> init [1, 2, 3]
[1,2]
>>> init [1]
[]
>>> init []
*** Exception: Prelude.init: empty list

uncons :: [a] -> Maybe (a, [a]) Source #

\(\mathcal{O}(1)\). Decompose a list into its head and tail.

  • If the list is empty, returns Nothing.
  • If the list is non-empty, returns Just (x, xs), where x is the head of the list and xs its tail.

Examples

Expand
>>> uncons []
Nothing
>>> uncons [1]
Just (1,[])
>>> uncons [1, 2, 3]
Just (1,[2,3])

Since: base-4.8.0.0

unsnoc :: [a] -> Maybe ([a], a) Source #

\(\mathcal{O}(n)\). Decompose a list into init and last.

  • If the list is empty, returns Nothing.
  • If the list is non-empty, returns Just (xs, x), where xs is the initial part of the list and x is its last element.

unsnoc is dual to uncons: for a finite list xs

unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)

Examples

Expand
>>> unsnoc []
Nothing
>>> unsnoc [1]
Just ([],1)
>>> unsnoc [1, 2, 3]
Just ([1,2],3)

Laziness

Expand
>>> fst <$> unsnoc [undefined]
Just []
>>> head . fst <$> unsnoc (1 : undefined)
Just *** Exception: Prelude.undefined
>>> head . fst <$> unsnoc (1 : 2 : undefined)
Just 1

Since: base-4.19.0.0

singleton :: a -> [a] Source #

Construct a list from a single element.

Examples

Expand
>>> singleton True
[True]
>>> singleton [1, 2, 3]
[[1,2,3]]
>>> singleton 'c'
"c"

Since: base-4.15.0.0

null :: Foldable t => t a -> Bool Source #

Test whether the structure is empty. The default implementation is Left-associative and lazy in both the initial element and the accumulator. Thus optimised for structures where the first element can be accessed in constant time. Structures where this is not the case should have a non-default implementation.

Examples

Expand

Basic usage:

>>> null []
True
>>> null [1]
False

null is expected to terminate even for infinite structures. The default implementation terminates provided the structure is bounded on the left (there is a leftmost element).

>>> 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 just counts elements starting with the leftmost. Instances for structures that can compute the element count faster than via element-by-element counting, should provide a specialised implementation.

Examples

Expand

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, ...]

this means that map id == id

Examples

Expand
>>> map (+1) [1, 2, 3]
[2,3,4]
>>> map id [1, 2, 3]
[1,2,3]
>>> map (\n -> 3 * n + 1) [1, 2, 3]
[4,7,10]

reverse :: [a] -> [a] Source #

\(\mathcal{O}(n)\). reverse xs returns the elements of xs in reverse order. xs must be finite.

Laziness

Expand

reverse is lazy in its elements.

>>> head (reverse [undefined, 1])
1
>>> reverse (1 : 2 : undefined)
*** Exception: Prelude.undefined

Examples

Expand
>>> 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.

Laziness

Expand

intersperse has the following properties

>>> take 1 (intersperse undefined ('a' : undefined))
"a"
>>> take 2 (intersperse ',' ('a' : undefined))
"a*** Exception: Prelude.undefined

Examples

Expand
>>> intersperse ',' "abcde"
"a,b,c,d,e"
>>> intersperse 1 [3, 4, 5]
[3,1,4,1,5]

intercalate :: [a] -> [[a]] -> [a] Source #

intercalate xs xss is equivalent to (concat (intersperse xs xss)). It inserts the list xs in between the lists in xss and concatenates the result.

Laziness

Expand

intercalate has the following properties:

>>> take 5 (intercalate undefined ("Lorem" : undefined))
"Lorem"
>>> take 6 (intercalate ", " ("Lorem" : undefined))
"Lorem*** Exception: Prelude.undefined

Examples

Expand
>>> intercalate ", " ["Lorem", "ipsum", "dolor"]
"Lorem, ipsum, dolor"
>>> intercalate [0, 1] [[2, 3], [4, 5, 6], []]
[2,3,0,1,4,5,6,0,1]
>>> intercalate [1, 2, 3] [[], []]
[1,2,3]

transpose :: [[a]] -> [[a]] Source #

The transpose function transposes the rows and columns of its argument.

Laziness

Expand

transpose is lazy in its elements

>>> take 1 (transpose ['a' : undefined, 'b' : undefined])
["ab"]

Examples

Expand
>>> 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]]

For this reason the outer list must be finite; otherwise transpose hangs:

>>> transpose (repeat [])
* Hangs forever *

subsequences :: [a] -> [[a]] Source #

The subsequences function returns the list of all subsequences of the argument.

Laziness

Expand

subsequences does not look ahead unless it must:

>>> take 1 (subsequences undefined)
[[]]
>>> take 2 (subsequences ('a' : undefined))
["","a"]

Examples

Expand
>>> subsequences "abc"
["","a","b","ab","c","ac","bc","abc"]

This function is productive on infinite inputs:

>>> take 8 $ subsequences ['a'..]
["","a","b","ab","c","ac","bc","abc"]

permutations :: [a] -> [[a]] Source #

The permutations function returns the list of all permutations of the argument.

Note that the order of permutations is not lexicographic. It satisfies the following property:

map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]

Laziness

Expand

The permutations function is maximally lazy: for each n, the value of permutations xs starts with those permutations that permute take n xs and keep drop n xs.

Examples

Expand
>>> permutations "abc"
["abc","bac","cba","bca","cab","acb"]
>>> permutations [1, 2]
[[1,2],[2,1]]
>>> permutations []
[[]]

This function is productive on infinite inputs:

>>> take 6 $ map (take 3) $ permutations ['a'..]
["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, lazy in the accumulator. This is rarely what you want, but can work well for structures with efficient right-to-left sequencing and an operator that is lazy in its left argument.

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. Like all left-associative folds, foldl will diverge if given an infinite list.

If you want an efficient strict left-fold, you probably want to use foldl' instead of foldl. The reason for this is that the 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 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

Expand

The first example is a strict fold, which in practice is best performed with foldl'.

>>> foldl (+) 42 [1,2,3,4]
52

Though the result below is lazy, the input is reversed before prepending it to the initial accumulator, so corecursion begins only after traversing the entire input string.

>>> foldl (\acc c -> c : acc) "abcd" "efgh"
"hgfeabcd"

A left fold of a structure that is infinite on the right cannot terminate, even when for any finite input the fold just returns the initial accumulator:

>>> foldl (\a _ -> a) 0 $ repeat 1
* Hangs forever *

WARNING: When it comes to lists, you always want to use either foldl' or foldr instead.

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 structure to a single strict result (e.g. sum).

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

Expand

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 *

foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a Source #

A strict version of foldl1.

foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b Source #

Right-associative fold of a structure, lazy in the accumulator.

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, given an operator lazy in its right argument, foldr can produce a terminating expression from an unbounded list.

For a general Foldable structure this should be semantically identical to,

foldr f z = foldr f z . toList

Examples

Expand

Basic usage:

>>> foldr (||) False [False, True, False]
True
>>> foldr (||) False []
False
>>> foldr (\c acc -> acc ++ [c]) "foo" ['a', 'b', 'c', 'd']
"foodcba"
Infinite structures

⚠️ Applying foldr to infinite structures usually doesn't terminate.

It may still terminate under 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 operator is lazy in its second argument (the initial accumulator is never used in this case, and so could be left undefined, but [] is more clear):

>>> take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (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

Expand

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

Expand

Basic usage:

>>> concat (Just [1, 2, 3])
[1,2,3]
>>> concat (Left 42)
[]
>>> concat [[1, 2, 3], [4, 5], [6], []]
[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

Expand

Basic usage:

>>> concatMap (take 3) [[1..], [10..], [100..], [1000..]]
[1,2,3,10,11,12,100,101,102,1000,1001,1002]
>>> concatMap (take 3) (Just [1..])
[1,2,3]

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

Expand

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,...
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

Expand

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,...
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

Expand

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

Expand

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

Expand

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

Expand

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 :: (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. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the maximum in faster than linear time.

Examples

Expand

Basic usage:

>>> maximum [1..10]
10
>>> maximum []
*** Exception: Prelude.maximum: empty list
>>> maximum Nothing
*** Exception: maximum: empty structure

WARNING: This function is partial for possibly-empty structures like lists.

Since: base-4.8.0.0

minimum :: (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. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the minimum in faster than linear time.

Examples

Expand

Basic usage:

>>> minimum [1..10]
1
>>> minimum []
*** Exception: Prelude.minimum: empty list
>>> minimum Nothing
*** Exception: minimum: empty structure

WARNING: This function is partial for possibly-empty structures like lists.

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

Examples

Expand
>>> 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"]
>>> take 10 (scanl (+) 0 [1..])
[0,1,3,6,10,15,21,28,36,45]
>>> take 1 (scanl undefined 'a' undefined)
"a"

scanl' :: (b -> a -> b) -> b -> [a] -> [b] Source #

\(\mathcal{O}(n)\). A strict version of scanl.

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, ...]

Examples

Expand
>>> 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]
>>> take 10 (scanl1 (+) [1..])
[1,3,6,10,15,21,28,36,45,55]
>>> take 1 (scanl1 undefined ('a' : undefined))
"a"

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.

Examples

Expand
>>> 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"]
>>> force $ scanr (+) 0 [1..]
*** Exception: stack overflow

scanr1 :: (a -> a -> a) -> [a] -> [a] Source #

\(\mathcal{O}(n)\). scanr1 is a variant of scanr that has no starting value argument.

Examples

Expand
>>> 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]
>>> force $ scanr1 (+) [1..]
*** Exception: stack overflow

Accumulating maps

mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) 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

Expand

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 => (s -> a -> (s, b)) -> s -> t a -> (s, t b) 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

Expand

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), ...]

Laziness

Expand

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.

>>> take 1 $ iterate undefined 42
[42]

Examples

Expand
>>> take 10 $ iterate not True
[True,False,True,False,True,False,True,False,True,False]
>>> take 10 $ iterate (+3) 42
[42,45,48,51,54,57,60,63,66,69]

iterate id == repeat:

>>> take 10 $ iterate id 1
[1,1,1,1,1,1,1,1,1,1]

iterate' :: (a -> a) -> a -> [a] Source #

iterate' is the strict version of iterate.

It forces the result of each application of the function to weak head normal form (WHNF) before proceeding.

>>> take 1 $ iterate' undefined 42
*** Exception: Prelude.undefined

repeat :: a -> [a] Source #

repeat x is an infinite list, with x the value of every element.

Examples

Expand
>>> take 10 $ repeat 17
[17,17,17,17,17,17,17,17,17, 17]
>>> repeat undefined
[*** Exception: Prelude.undefined

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.

Examples

Expand
>>> replicate 0 True
[]
>>> replicate (-1) True
[]
>>> replicate 4 True
[True,True,True,True]

cycle :: HasCallStack => [a] -> [a] Source #

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.

Examples

Expand
>>> cycle []
*** Exception: Prelude.cycle: empty list
>>> take 10 (cycle [42])
[42,42,42,42,42,42,42,42,42,42]
>>> take 10 (cycle [2, 5, 7])
[2,5,7,2,5,7,2,5,7,2]
>>> take 1 (cycle (42 : undefined))
[42]

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

Laziness

Expand
>>> take 1 (unfoldr (\x -> Just (x, undefined)) 'a')
"a"

Examples

Expand
>>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
[10,9,8,7,6,5,4,3,2,1]
>>> take 10 $ unfoldr (\(x, y) -> Just (x, (y, x + y))) (0, 1)
[0,1,1,2,3,5,8,13,21,54]

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.

It is an instance of the more general genericTake, in which n may be of any integral type.

Laziness

Expand
>>> take 0 undefined
[]
>>> take 2 (1 : 2 : undefined)
[1,2]

Examples

Expand
>>> 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]
[]

drop :: Int -> [a] -> [a] Source #

drop n xs returns the suffix of xs after the first n elements, or [] if n >= length xs.

It is an instance of the more general genericDrop, in which n may be of any integral type.

Examples

Expand
>>> 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]

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 is an instance of the more general genericSplitAt, in which n may be of any integral type.

Laziness

Expand

It is equivalent to (take n xs, drop n xs) unless n is _|_: splitAt _|_ xs = _|_, not (_|_, _|_)).

The first component of the tuple is produced lazily:

>>> fst (splitAt 0 undefined)
[]
>>> take 1 (fst (splitAt 10 (1 : undefined)))
[1]

Examples

Expand
>>> 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])

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.

Laziness

Expand
>>> takeWhile (const False) undefined
*** Exception: Prelude.undefined
>>> takeWhile (const False) (undefined : undefined)
[]
>>> take 1 (takeWhile (const True) (1 : undefined))
[1]

Examples

Expand
>>> 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]
[]

dropWhile :: (a -> Bool) -> [a] -> [a] Source #

dropWhile p xs returns the suffix remaining after takeWhile p xs.

Examples

Expand
>>> dropWhile (< 3) [1,2,3,4,5,1,2,3]
[3,4,5,1,2,3]
>>> dropWhile (< 9) [1,2,3]
[]
>>> dropWhile (< 0) [1,2,3]
[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.

Laziness

Expand

This function is lazy in spine, but strict in elements, which makes it different from reverse . dropWhile p . reverse, which is strict in spine, but lazy in elements. For instance:

>>> take 1 (dropWhileEnd (< 0) (1 : undefined))
[1]
>>> take 1 (reverse $ dropWhile (< 0) $ reverse (1 : undefined))
*** Exception: Prelude.undefined

but on the other hand

>>> last (dropWhileEnd (< 0) [undefined, 1])
*** Exception: Prelude.undefined
>>> last (reverse $ dropWhile (< 0) $ reverse [undefined, 1])
1

Examples

Expand
>>> dropWhileEnd isSpace "foo\n"
"foo"
>>> dropWhileEnd isSpace "foo bar"
"foo bar"
>>> dropWhileEnd (> 10) [1..20]
[1,2,3,4,5,6,7,8,9,10]

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 the longest prefix (possibly empty) of xs of elements that satisfy p and second element is the remainder of the list:

span p xs is equivalent to (takeWhile p xs, dropWhile p xs), even if p is _|_.

Laziness

Expand
>>> span undefined []
([],[])
>>> fst (span (const False) undefined)
*** Exception: Prelude.undefined
>>> fst (span (const False) (undefined : undefined))
[]
>>> take 1 (fst (span (const True) (1 : undefined)))
[1]

span produces the first component of the tuple lazily:

>>> take 10 (fst (span (const True) [1..]))
[1,2,3,4,5,6,7,8,9,10]

Examples

Expand
>>> 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 p is equivalent to span (not . p) and consequently to (takeWhile (not . p) xs, dropWhile (not . p) xs), even if p is _|_.

Laziness

Expand
>>> break undefined []
([],[])
>>> fst (break (const True) undefined)
*** Exception: Prelude.undefined
>>> fst (break (const True) (undefined : undefined))
[]
>>> take 1 (fst (break (const False) (1 : undefined)))
[1]

break produces the first component of the tuple lazily:

>>> take 10 (fst (break (const False) [1..]))
[1,2,3,4,5,6,7,8,9,10]

Examples

Expand
>>> 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.

Examples
Expand
>>> 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 is non-empty and all elements are equal to the first one.

group is a special case of groupBy, which allows the programmer to supply their own equality test.

It's often preferable to use Data.List.NonEmpty.group, which provides type-level guarantees of non-emptiness of inner lists.

Examples

Expand
>>> group "Mississippi"
["M","i","ss","i","ss","i","pp","i"]
>>> group [1, 1, 1, 2, 2, 3, 4, 5, 5]
[[1,1,1],[2,2],[3],[4],[5,5]]

inits :: [a] -> [[a]] Source #

The inits function returns all initial segments of the argument, shortest first.

inits is semantically equivalent to map reverse . scanl (flip (:)) [], but under the hood uses a queue to amortize costs of reverse.

Laziness

Expand

Note that inits has the following strictness property: inits (xs ++ _|_) = inits xs ++ _|_

In particular, inits _|_ = [] : _|_

Examples

Expand
>>> inits "abc"
["","a","ab","abc"]
>>> inits []
[[]]

inits is productive on infinite lists:

>>> take 5 $ inits [1..]
[[],[1],[1,2],[1,2,3],[1,2,3,4]]

tails :: [a] -> [[a]] Source #

\(\mathcal{O}(n)\). The tails function returns all final segments of the argument, longest first.

Laziness

Expand

Note that tails has the following strictness property: tails _|_ = _|_ : _|_

>>> tails undefined
[*** Exception: Prelude.undefined
>>> drop 1 (tails [undefined, 1, 2])
[[1, 2], [2], []]

Examples

Expand
>>> tails "abc"
["abc","bc","c",""]
>>> tails [1, 2, 3]
[[1,2,3],[2,3],[3],[]]
>>> tails []
[[]]

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.

Examples

Expand
>>> "Hello" `isPrefixOf` "Hello World!"
True
>>> "Hello" `isPrefixOf` "Wello Horld!"
False

For the result to be True, the first list must be finite; False, however, results from any mismatch:

>>> [0..] `isPrefixOf` [1..]
False
>>> [0..] `isPrefixOf` [0..99]
False
>>> [0..99] `isPrefixOf` [0..]
True
>>> [0..] `isPrefixOf` [0..]
* Hangs forever *

isPrefixOf shortcuts when the first argument is empty:

>>> isPrefixOf [] undefined
True

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.

Examples

Expand
>>> "ld!" `isSuffixOf` "Hello World!"
True
>>> "World" `isSuffixOf` "Hello World!"
False

The second list must be finite; however the first list may be infinite:

>>> [0..] `isSuffixOf` [0..99]
False
>>> [0..99] `isSuffixOf` [0..]
* Hangs forever *

isInfixOf :: Eq a => [a] -> [a] -> Bool Source #

The isInfixOf function takes two lists and returns True iff the first list is contained, wholly and intact, anywhere within the second.

Examples

Expand
>>> isInfixOf "Haskell" "I really like Haskell."
True
>>> isInfixOf "Ial" "I really like Haskell."
False

For the result to be True, the first list must be finite; for the result to be False, the second list must be finite:

>>> [20..50] `isInfixOf` [0..]
True
>>> [0..] `isInfixOf` [20..50]
False
>>> [0..] `isInfixOf` [0..]
* Hangs forever *

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.

isSubsequenceOf x y is equivalent to x `elem` (subsequences y).

Note: isSubsequenceOf is often used in infix form.

Examples

Expand
>>> "GHC" `isSubsequenceOf` "The Glorious Haskell Compiler"
True
>>> ['a','d'..'z'] `isSubsequenceOf` ['a'..'z']
True
>>> [1..10] `isSubsequenceOf` [10,9..0]
False

For the result to be True, the first list must be finite; for the result to be False, the second list must be finite:

>>> [0,2..10] `isSubsequenceOf` [0..]
True
>>> [0..] `isSubsequenceOf` [0,2..10]
False
>>> [0,2..] `isSubsequenceOf` [0..]
* Hangs forever*

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

Expand

Basic usage:

>>> 3 `elem` []
False
>>> 3 `elem` [1,2]
False
>>> 3 `elem` [1,2,3,4,5]
True

For infinite structures, the default implementation of elem terminates if the sought-after 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

Expand

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. For the result to be Nothing, the list must be finite.

Examples

Expand
>>> 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

Expand

Basic usage:

>>> find (> 42) [0, 5..]
Just 45
>>> 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]

Examples

Expand
>>> filter odd [1, 2, 3]
[1,3]
>>> filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]
["Hello","World"]
>>> filter (/= 3) [1, 2, 3, 4, 3, 2, 1]
[1,2,4,2,1]

partition :: (a -> Bool) -> [a] -> ([a], [a]) Source #

The partition function takes a predicate and 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)

Examples

Expand
>>> partition (`elem` "aeiou") "Hello World!"
("eoo","Hll Wrld!")
>>> partition even [1..10]
([2,4,6,8,10],[1,3,5,7,9])
>>> partition (< 5) [1..10]
([1,2,3,4],[5,6,7,8,9,10])

Indexing lists

These functions treat a list xs as an indexed collection, with indices ranging from 0 to length xs - 1.

(!?) :: [a] -> Int -> Maybe a infixl 9 Source #

List index (subscript) operator, starting from 0. Returns Nothing if the index is out of bounds

This is the total variant of the partial !! operator.

WARNING: This function takes linear time in the index.

Examples

Expand
>>> ['a', 'b', 'c'] !? 0
Just 'a'
>>> ['a', 'b', 'c'] !? 2
Just 'c'
>>> ['a', 'b', 'c'] !? 3
Nothing
>>> ['a', 'b', 'c'] !? (-1)
Nothing

(!!) :: HasCallStack => [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.

WARNING: This function is partial, and should only be used if you are sure that the indexing will not fail. Otherwise, use !?.

WARNING: This function takes linear time in the index.

Examples

Expand
>>> ['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

elemIndex :: Eq a => a -> [a] -> Maybe Int Source #

The elemIndex function returns the index of the first element in the given list which is equal (by ==) to the query element, or Nothing if there is no such element. For the result to be Nothing, the list must be finite.

Examples

Expand
>>> elemIndex 4 [0..]
Just 4
>>> elemIndex 'o' "haskell"
Nothing
>>> elemIndex 0 [1..]
* hangs forever *

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.

Examples

Expand
>>> elemIndices 'o' "Hello World"
[4,7]
>>> elemIndices 1 [1, 2, 3, 1, 2, 3]
[0,3]

findIndex :: (a -> Bool) -> [a] -> Maybe Int Source #

The findIndex function takes a predicate and a list and returns the index of the first element in the list satisfying the predicate, or Nothing if there is no such element. For the result to be Nothing, the list must be finite.

Examples

Expand
>>> findIndex isSpace "Hello World!"
Just 5
>>> findIndex odd [0, 2, 4, 6]
Nothing
>>> findIndex even [1..]
Just 1
>>> findIndex odd [0, 2 ..]
* hangs forever *

findIndices :: (a -> Bool) -> [a] -> [Int] Source #

The findIndices function extends findIndex, by returning the indices of all elements satisfying the predicate, in ascending order.

Examples

Expand
>>> findIndices (`elem` "aeiou") "Hello World!"
[1,4,7]
>>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"]
[1,3]

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 is right-lazy:

>>> zip [] undefined
[]
>>> zip undefined []
*** Exception: Prelude.undefined
...

zip is capable of list fusion, but it is restricted to its first list argument and its resulting list.

Examples

Expand
>>> zip [1, 2, 3] ['a', 'b', 'c']
[(1,'a'),(2,'b'),(3,'c')]

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..] []
[]

zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] Source #

zip3 takes three lists and returns a list of triples, analogous to zip. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)] Source #

The zip4 function takes four lists and returns a list of quadruples, analogous to zip. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)] Source #

The zip5 function takes five lists and returns a list of five-tuples, analogous to zip. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)] Source #

The zip6 function takes six lists and returns a list of six-tuples, analogous to zip. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] Source #

The zip7 function takes seven lists and returns a list of seven-tuples, analogous to zip. It 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..]

zipWith is right-lazy:

>>> let f = undefined
>>> zipWith f [] undefined
[]

zipWith is capable of list fusion, but it is restricted to its first list argument and its resulting list.

Examples

Expand

zipWith (+) can be applied to two lists to produce the list of corresponding sums:

>>> zipWith (+) [1, 2, 3] [4, 5, 6]
[5,7,9]
>>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
["hello world!","foobar"]

zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #

\(\mathcal{O}(\min(l,m,n))\). 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..]

Examples

Expand
>>> zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"
["1ax","2by","3cz"]
>>> zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9]
[11,18,27]

zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] Source #

The zipWith4 function takes a function which combines four elements, as well as four lists and returns a list of their point-wise combination, analogous to zipWith. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] Source #

The zipWith5 function takes a function which combines five elements, as well as five lists and returns a list of their point-wise combination, analogous to zipWith. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] Source #

The zipWith6 function takes a function which combines six elements, as well as six lists and returns a list of their point-wise combination, analogous to zipWith. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] Source #

The zipWith7 function takes a function which combines seven elements, as well as seven lists and returns a list of their point-wise combination, analogous to zipWith. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

unzip :: [(a, b)] -> ([a], [b]) Source #

unzip transforms a list of pairs into a list of first components and a list of second components.

Examples

Expand
>>> unzip []
([],[])
>>> unzip [(1, 'a'), (2, 'b')]
([1,2],"ab")

unzip3 :: [(a, b, c)] -> ([a], [b], [c]) Source #

The unzip3 function takes a list of triples and returns three lists of the respective components, analogous to unzip.

Examples

Expand
>>> unzip3 []
([],[],[])
>>> unzip3 [(1, 'a', True), (2, 'b', False)]
([1,2],"ab",[True,False])

unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) Source #

The unzip4 function takes a list of quadruples and returns four lists, analogous to unzip.

unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e]) Source #

The unzip5 function takes a list of five-tuples and returns five lists, analogous to unzip.

unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) Source #

The unzip6 function takes a list of six-tuples and returns six lists, analogous to unzip.

unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) Source #

The unzip7 function takes a list of seven-tuples and returns seven lists, analogous to unzip.

Special lists

Functions on strings

lines :: String -> [String] Source #

Splits the argument into a list of lines stripped of their terminating \n characters. The \n terminator is optional in a final non-empty line of the argument string.

When the argument string is empty, or ends in a \n character, it can be recovered by passing the result of lines to the unlines function. Otherwise, unlines appends the missing terminating \n. This makes unlines . lines idempotent:

(unlines . lines) . (unlines . lines) = (unlines . lines)

Examples

Expand
>>> lines ""           -- empty input contains no lines
[]
>>> lines "\n"         -- single empty line
[""]
>>> lines "one"        -- single unterminated line
["one"]
>>> lines "one\n"      -- single non-empty line
["one"]
>>> lines "one\n\n"    -- second line is empty
["one",""]
>>> lines "one\ntwo"   -- second line is unterminated
["one","two"]
>>> lines "one\ntwo\n" -- two non-empty lines
["one","two"]

words :: String -> [String] Source #

words breaks a string up into a list of words, which were delimited by white space (as defined by isSpace). This function trims any white spaces at the beginning and at the end.

Examples

Expand
>>> words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
>>> words " foo bar "
["foo","bar"]

unlines :: [String] -> String Source #

Appends a \n character to each input string, then concatenates the results. Equivalent to foldMap (s -> s ++ "\n").

Examples

Expand
>>> unlines ["Hello", "World", "!"]
"Hello\nWorld\n!\n"

Note that unlines . lines /= id when the input is not \n-terminated:

>>> unlines . lines $ "foo\nbar"
"foo\nbar\n"

unwords :: [String] -> String Source #

unwords joins words with separating spaces (U+0020 SPACE).

unwords is neither left nor right inverse of words:

>>> words (unwords [" "])
[]
>>> unwords (words "foo\nbar")
"foo bar"

Examples

Expand
>>> unwords ["Lorem", "ipsum", "dolor"]
"Lorem ipsum dolor"
>>> unwords ["foo", "bar", "", "baz"]
"foo bar  baz"

"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.

If there exists instance Ord a, it's faster to use nubOrd from the containers package (link to the latest online documentation), which takes only \(\mathcal{O}(n \log d)\) time where d is the number of distinct elements in the list.

Another approach to speed up nub is to use map Data.List.NonEmpty.head . Data.List.NonEmpty.group . sort, which takes \(\mathcal{O}(n \log n)\) time, requires instance Ord a and doesn't preserve the order.

Examples

Expand
>>> nub [1,2,3,4,3,2,1,2,4,3,5]
[1,2,3,4,5]
>>> nub "hello, world!"
"helo, wrd!"

delete :: Eq a => a -> [a] -> [a] Source #

\(\mathcal{O}(n)\). delete x removes the first occurrence of x from its list argument.

It is a special case of deleteBy, which allows the programmer to supply their own equality test.

Examples

Expand
>>> delete 'a' "banana"
"bnana"
>>> delete "not" ["haskell", "is", "not", "awesome"]
["haskell","is","awesome"]

(\\) :: 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.

It is a special case of deleteFirstsBy, which allows the programmer to supply their own equality test.

Examples

Expand
>>> "Hello World!" \\ "ell W"
"Hoorld!"

The second list must be finite, but the first may be infinite.

>>> take 5 ([0..] \\ [2..4])
[0,1,5,6,7]
>>> take 5 ([0..] \\ [2..])
* Hangs forever *

union :: Eq a => [a] -> [a] -> [a] Source #

The union function returns the list union of the two lists. It is a special case of unionBy, which allows the programmer to supply their own equality test.

Examples

Expand
>>> "dog" `union` "cow"
"dogcw"

If equal elements are present in both lists, an element from the first list will be used. If the second list contains equal elements, only the first one will be retained:

>>> import Data.Semigroup(Arg(..))
>>> union [Arg () "dog"] [Arg () "cow"]
[Arg () "dog"]
>>> union [] [Arg () "dog", Arg () "cow"]
[Arg () "dog"]

However if the first list contains duplicates, so will the result:

>>> "coot" `union` "duck"
"cootduk"
>>> "duck" `union` "coot"
"duckot"

union is productive even if both arguments are infinite.

>>> [0, 2 ..] `union` [1, 3 ..]
[0,2,4,6,8,10,12..

intersect :: Eq a => [a] -> [a] -> [a] Source #

The intersect function takes the list intersection of two lists. It is a special case of intersectBy, which allows the programmer to supply their own equality test.

Examples
Expand
>>> [1,2,3,4] `intersect` [2,4,6,8]
[2,4]

If equal elements are present in both lists, an element from the first list will be used, and all duplicates from the second list quashed:

>>> import Data.Semigroup
>>> intersect [Arg () "dog"] [Arg () "cow", Arg () "cat"]
[Arg () "dog"]

However if the first list contains duplicates, so will the result.

>>> "coot" `intersect` "heron"
"oo"
>>> "heron" `intersect` "coot"
"o"

If the second list is infinite, intersect either hangs or returns its first argument in full. Otherwise if the first list is infinite, intersect might be productive:

>>> intersect [100..] [0..]
[100,101,102,103...
>>> intersect [0] [1..]
* Hangs forever *
>>> intersect [1..] [0]
* Hangs forever *
>>> intersect (cycle [1..3]) [2]
[2,2,2,2...

Ordered lists

sort :: Ord a => [a] -> [a] Source #

The sort function implements a stable sorting algorithm. It is a special case of sortBy, which allows the programmer to supply their own comparison function.

Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.

The argument must be finite.

Examples

Expand
>>> sort [1,6,4,3,2,5]
[1,2,3,4,5,6]
>>> sort "haskell"
"aehklls"
>>> import Data.Semigroup(Arg(..))
>>> sort [Arg ":)" 0, Arg ":D" 0, Arg ":)" 1, Arg ":3" 0, Arg ":D" 1]
[Arg ":)" 0,Arg ":)" 1,Arg ":3" 0,Arg ":D" 0,Arg ":D" 1]

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.

The argument must be finite.

Examples

Expand
>>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
>>> sortOn length ["jim", "creed", "pam", "michael", "dwight", "kevin"]
["jim","pam","creed","kevin","dwight","michael"]

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.

Examples

Expand
>>> insert (-1) [1, 2, 3]
[-1,1,2,3]
>>> insert 'd' "abcefg"
"abcdefg"
>>> 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.

nubBy :: (a -> a -> Bool) -> [a] -> [a] Source #

The nubBy function behaves just like nub, except it uses a user-supplied equality predicate instead of the overloaded (==) function.

Examples

Expand
>>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6]
[1,2,6]
>>> nubBy (/=) [2, 7, 1, 8, 2, 8, 1, 8, 2, 8]
[2,2,2]
>>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2]
[1,2,3,5,5]

deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] Source #

\(\mathcal{O}(n)\). The deleteBy function behaves like delete, but takes a user-supplied equality predicate.

Examples

Expand
>>> deleteBy (<=) 4 [1..10]
[1,2,3,5,6,7,8,9,10]
>>> deleteBy (/=) 5 [5, 5, 4, 3, 5, 2]
[5,5,3,5,2]

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. This is the non-overloaded version of (\\).

(\\) == deleteFirstsBy (==)

The second list must be finite, but the first may be infinite.

Examples

Expand
>>> deleteFirstsBy (>) [1..10] [3, 4, 5]
[4,5,6,7,8,9,10]
>>> deleteFirstsBy (/=) [1..10] [1, 3, 5]
[4,5,6,7,8,9,10]

unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #

The unionBy function is the non-overloaded version of union. Both arguments may be infinite.

Examples

Expand
>>> unionBy (>) [3, 4, 5] [1, 2, 3, 4, 5, 6]
[3,4,5,4,5,6]
>>> import Data.Semigroup (Arg(..))
>>> unionBy (/=) [Arg () "Saul"] [Arg () "Kim"]
[Arg () "Saul", Arg () "Kim"]

intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #

The intersectBy function is the non-overloaded version of intersect. It is productive for infinite arguments only if the first one is a subset of the second.

groupBy :: (a -> a -> Bool) -> [a] -> [[a]] Source #

The groupBy function is the non-overloaded version of group.

When a supplied relation is not transitive, it is important to remember that equality is checked against the first element in the group, not against the nearest neighbour:

>>> groupBy (\a b -> b - a < 5) [0..19]
[[0,1,2,3,4],[5,6,7,8,9],[10,11,12,13,14],[15,16,17,18,19]]

It's often preferable to use Data.List.NonEmpty.groupBy, which provides type-level guarantees of non-emptiness of inner lists.

Examples

Expand
>>> groupBy (/=) [1, 1, 1, 2, 3, 1, 4, 4, 5]
[[1],[1],[1,2,3],[1,4,4,5]]
>>> groupBy (>) [1, 3, 5, 1, 4, 2, 6, 5, 4]
[[1],[3],[5,1,4,2],[6,5,4]]
>>> groupBy (const not) [True, False, True, False, False, False, True]
[[True,False],[True,False,False,False],[True]]

User-supplied comparison (replacing an Ord context)

The function is assumed to define a total ordering.

sortBy :: (a -> a -> Ordering) -> [a] -> [a] Source #

The sortBy function is the non-overloaded version of sort. The argument must be finite.

The supplied comparison relation is supposed to be reflexive and antisymmetric, otherwise, e. g., for _ _ -> GT, the ordered list simply does not exist. The relation is also expected to be transitive: if it is not then sortBy might fail to find an ordered permutation, even if it exists.

Examples

Expand
>>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]

insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] Source #

\(\mathcal{O}(n)\). The non-overloaded version of insert.

Examples

Expand
>>> insertBy (\x y -> compare (length x) (length y)) [1, 2] [[1], [1, 2, 3], [1, 2, 3, 4]]
[[1],[1,2],[1,2,3],[1,2,3,4]]

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

Expand

Basic usage:

>>> maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
"Longest"

WARNING: This function is partial for possibly-empty structures like lists.

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

Expand

Basic usage:

>>> minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]
"!"

WARNING: This function is partial for possibly-empty structures like lists.

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.

Examples

Expand
>>> genericLength [1, 2, 3] :: Int
3
>>> genericLength [1, 2, 3] :: Float
3.0

Users should take care to pick a return type that is wide enough to contain the full length of the list. If the width is insufficient, the overflow behaviour will depend on the (+) implementation in the selected Num instance. The following example overflows because the actual list length of 200 lies outside of the Int8 range of -128..127.

>>> genericLength [1..200] :: Int8
-56

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.