Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2023 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Relude.List.Reexport
Contents
Description
Reexports most of the Data.List.
Synopsis
- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- transpose :: [[a]] -> [[a]]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- (++) :: [a] -> [a] -> [a]
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- map :: (a -> b) -> [a] -> [b]
- uncons :: [a] -> Maybe (a, [a])
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanl' :: (b -> a -> b) -> b -> [a] -> [b]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- iterate :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- reverse :: [a] -> [a]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- intersperse :: a -> [a] -> [a]
- intercalate :: [a] -> [[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])
- genericReplicate :: Integral i => i -> a -> [a]
- group :: Eq a => [a] -> [[a]]
- inits :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- subsequences :: [a] -> [[a]]
- permutations :: [a] -> [[a]]
- sort :: Ord a => [a] -> [a]
- cycle :: [a] -> [a]
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
List
unfoldr :: (b -> Maybe (a, b)) -> b -> [a] #
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
>>>
take 1 (unfoldr (\x -> Just (x, undefined)) 'a')
"a"
Examples
>>>
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]
sortOn :: Ord b => (a -> b) -> [a] -> [a] #
Sort a list by comparing the results of a key function applied to each
element.
is equivalent to sortOn
f
, but has the
performance advantage of only evaluating sortBy
(comparing
f)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
>>>
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"]
Performance notes
This function minimises the projections performed, by materialising the projections in an intermediate list.
For trivial projections, you should prefer using sortBy
with
comparing
, for example:
>>>
sortBy (comparing fst) [(3, 1), (2, 2), (1, 3)]
[(1,3),(2,2),(3,1)]
Or, for the exact same API as sortOn
, you can use `sortBy . comparing`:
>>>
(sortBy . comparing) fst [(3, 1), (2, 2), (1, 3)]
[(1,3),(2,2),(3,1)]
@since base-4.8.0.0
The transpose
function transposes the rows and columns of its argument.
Laziness
transpose
is lazy in its elements
>>>
take 1 (transpose ['a' : undefined, 'b' : undefined])
["ab"]
Examples
>>>
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 *
sortBy :: (a -> a -> Ordering) -> [a] -> [a] #
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
>>>
sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
(++) :: [a] -> [a] -> [a] infixr 5 #
(++)
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
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
>>>
[1, 2, 3] ++ [4, 5, 6]
[1,2,3,4,5,6]
>>>
[] ++ [1, 2, 3]
[1,2,3]
>>>
[3, 2, 1] ++ []
[3,2,1]
filter :: (a -> Bool) -> [a] -> [a] #
\(\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
>>>
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]
zip :: [a] -> [b] -> [(a, b)] #
\(\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
>>>
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..] []
[]
map :: (a -> b) -> [a] -> [b] #
\(\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
>>>
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]
uncons :: [a] -> Maybe (a, [a]) #
\(\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
, whereJust
(x, xs)x
is thehead
of the list andxs
itstail
.
@since base-4.8.0.0
Examples
>>>
uncons []
Nothing
>>>
uncons [1]
Just (1,[])
>>>
uncons [1, 2, 3]
Just (1,[2,3])
scanl :: (b -> a -> b) -> b -> [a] -> [b] #
\(\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
>>>
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"
scanl1 :: (a -> a -> a) -> [a] -> [a] #
\(\mathcal{O}(n)\). scanl1
is a variant of scanl
that has no starting
value argument:
scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
Examples
>>>
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] #
\(\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
>>>
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] #
\(\mathcal{O}(n)\). scanr1
is a variant of scanr
that has no starting
value argument.
Examples
>>>
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
iterate :: (a -> a) -> a -> [a] #
iterate
f x
returns an infinite list of repeated applications
of f
to x
:
iterate f x == [x, f x, f (f x), ...]
Laziness
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
>>>
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]
repeat
x
is an infinite list, with x
the value of every element.
Examples
>>>
take 10 $ repeat 17
[17,17,17,17,17,17,17,17,17, 17]
>>>
repeat undefined
[*** Exception: Prelude.undefined
replicate :: Int -> a -> [a] #
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
>>>
replicate 0 True
[]
>>>
replicate (-1) True
[]
>>>
replicate 4 True
[True,True,True,True]
takeWhile :: (a -> Bool) -> [a] -> [a] #
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
.
Laziness
>>>
takeWhile (const False) undefined
*** Exception: Prelude.undefined
>>>
takeWhile (const False) (undefined : undefined)
[]
>>>
take 1 (takeWhile (const True) (1 : undefined))
[1]
Examples
>>>
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]
[]
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
>>>
take 0 undefined
[]>>>
take 2 (1 : 2 : undefined)
[1,2]
Examples
>>>
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
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
>>>
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]) #
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
It is equivalent to (
unless take
n xs, drop
n xs)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
>>>
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])
span :: (a -> Bool) -> [a] -> ([a], [a]) #
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 (
, even if takeWhile
p xs, dropWhile
p xs)p
is _|_
.
Laziness
>>>
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
>>>
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]) #
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
and consequently to span
(not
. p)(
,
even if takeWhile
(not
. p) xs, dropWhile
(not
. p) xs)p
is _|_
.
Laziness
>>>
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
>>>
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],[])
\(\mathcal{O}(n)\). reverse
xs
returns the elements of xs
in reverse order.
xs
must be finite.
Laziness
reverse
is lazy in its elements.
>>>
head (reverse [undefined, 1])
1
>>>
reverse (1 : 2 : undefined)
*** Exception: Prelude.undefined
Examples
>>>
reverse []
[]
>>>
reverse [42]
[42]
>>>
reverse [2,5,7]
[7,5,2]
>>>
reverse [1..]
* Hangs forever *
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] #
\(\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
unzip :: [(a, b)] -> ([a], [b]) #
unzip
transforms a list of pairs into a list of first components
and a list of second components.
Examples
>>>
unzip []
([],[])
>>>
unzip [(1, 'a'), (2, 'b')]
([1,2],"ab")
isPrefixOf :: Eq a => [a] -> [a] -> Bool #
\(\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
>>>
"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
intersperse :: a -> [a] -> [a] #
\(\mathcal{O}(n)\). The intersperse
function takes an element and a list
and `intersperses' that element between the elements of the list.
Laziness
intersperse
has the following properties
>>>
take 1 (intersperse undefined ('a' : undefined))
"a"
>>>
take 2 (intersperse ',' ('a' : undefined))
"a*** Exception: Prelude.undefined
Examples
>>>
intersperse ',' "abcde"
"a,b,c,d,e"
>>>
intersperse 1 [3, 4, 5]
[3,1,4,1,5]
intercalate :: [a] -> [[a]] -> [a] #
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.
Laziness
intercalate
has the following properties:
>>>
take 5 (intercalate undefined ("Lorem" : undefined))
"Lorem"
>>>
take 6 (intercalate ", " ("Lorem" : undefined))
"Lorem*** Exception: Prelude.undefined
Examples
>>>
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]
genericLength :: Num i => [a] -> i #
\(\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
>>>
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] #
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] #
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]) #
The genericSplitAt
function is an overloaded version of splitAt
, which
accepts any Integral
value as the position at which to split.
genericReplicate :: Integral i => i -> a -> [a] #
The genericReplicate
function is an overloaded version of replicate
,
which accepts any Integral
value as the number of repetitions to make.
group :: Eq a => [a] -> [[a]] #
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, all elements are equal to the
first one, and consecutive equal elements of the input end up in the
same element of the output list.
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.
A common idiom to squash repeating elements map
head
.
group
is better served by
map
Data.List.NonEmpty.
head
.
Data.List.NonEmpty.
group
because it avoids partial functions.
Examples
>>>
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]]
The inits
function returns all initial segments of the argument,
shortest first.
inits
is semantically equivalent to
,
but under the hood uses a queue to amortize costs of map
reverse
. scanl
(flip
(:)) []reverse
.
Laziness
Note that inits
has the following strictness property:
inits (xs ++ _|_) = inits xs ++ _|_
In particular,
inits _|_ = [] : _|_
Examples
>>>
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]]
\(\mathcal{O}(n)\). The tails
function returns all final segments of the
argument, longest first.
Laziness
Note that tails
has the following strictness property:
tails _|_ = _|_ : _|_
>>>
tails undefined
[*** Exception: Prelude.undefined
>>>
drop 1 (tails [undefined, 1, 2])
[[1, 2], [2], []]
Examples
>>>
tails "abc"
["abc","bc","c",""]
>>>
tails [1, 2, 3]
[[1,2,3],[2,3],[3],[]]
>>>
tails []
[[]]
subsequences :: [a] -> [[a]] #
The subsequences
function returns the list of all subsequences of the argument.
Laziness
subsequences
does not look ahead unless it must:
>>>
take 1 (subsequences undefined)
[[]]>>>
take 2 (subsequences ('a' : undefined))
["","a"]
Examples
>>>
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]] #
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
The permutations
function is maximally lazy:
for each n
, the value of
starts with those permutations
that permute permutations
xs
and keep take
n xs
.drop
n xs
Examples
>>>
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"]
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
>>>
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]
Creates an infinite list from a finite list by appending the list
to itself infinite times (i.e. by cycling the list). Unlike cycle
from Data.List, this implementation doesn't throw error on empty
lists, but returns an empty list instead.
>>>
cycle []
[]>>>
take 10 $ cycle [1,2,3]
[1,2,3,1,2,3,1,2,3,1]
sortWith :: Ord b => (a -> b) -> [a] -> [a] #
The sortWith
function sorts a list of elements using the
user supplied function to project something out of each element
In general if the user supplied function is expensive to compute then
you should probably be using sortOn
, as it only needs
to compute it once for each element. sortWith
, on the other hand
must compute the mapping function for every comparison that it performs.