| 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
- (++) :: [a] -> [a] -> [a]
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- map :: (a -> b) -> [a] -> [b]
- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
- transpose :: [[a]] -> [[a]]
- tails :: [a] -> [[a]]
- subsequences :: [a] -> [[a]]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- permutations :: [a] -> [[a]]
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- intersperse :: a -> [a] -> [a]
- intercalate :: [a] -> [[a]] -> [a]
- inits :: [a] -> [[a]]
- group :: Eq a => [a] -> [[a]]
- genericTake :: Integral i => i -> [a] -> [a]
- genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
- genericReplicate :: Integral i => i -> a -> [a]
- genericLength :: Num i => [a] -> i
- genericDrop :: Integral i => i -> [a] -> [a]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip :: [(a, b)] -> ([a], [b])
- uncons :: [a] -> Maybe (a, [a])
- takeWhile :: (a -> Bool) -> [a] -> [a]
- take :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanl' :: (b -> a -> b) -> b -> [a] -> [b]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- reverse :: [a] -> [a]
- replicate :: Int -> a -> [a]
- repeat :: a -> [a]
- iterate :: (a -> a) -> a -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- break :: (a -> Bool) -> [a] -> ([a], [a])
- cycle :: [a] -> [a]
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
List
(++) :: [a] -> [a] -> [a] infixr 5 #
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.
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]
>>>filter odd [1, 2, 3][1,3]
zip :: [a] -> [b] -> [(a, b)] #
\(\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 [] 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.
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, ...]
>>>map (+1) [1, 2, 3][2,3,4]
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
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]
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]] #
The subsequences function returns the list of all subsequences of the argument.
>>>subsequences "abc"["","a","b","ab","c","ac","bc","abc"]
sortOn :: Ord b => (a -> b) -> [a] -> [a] #
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
permutations :: [a] -> [[a]] #
The permutations function returns the list of all permutations of the argument.
>>>permutations "abc"["abc","bac","cba","bca","cab","acb"]
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.
>>>"Hello" `isPrefixOf` "Hello World!"True
>>>"Hello" `isPrefixOf` "Wello Horld!"False
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. For
example,
>>>intersperse ',' "abcde""a,b,c,d,e"
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.
>>>intercalate ", " ["Lorem", "ipsum", "dolor"]"Lorem, ipsum, dolor"
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 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.
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.
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.
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.
>>>genericLength [1, 2, 3] :: Int3>>>genericLength [1, 2, 3] :: Float3.0
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.
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..]
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:
>>>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.
unzip :: [(a, b)] -> ([a], [b]) #
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")
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.
>>>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
>>>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.
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 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.
span :: (a -> Bool) -> [a] -> ([a], [a]) #
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])
scanr1 :: (a -> a -> a) -> [a] -> [a] #
\(\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]>>>force $ scanr1 (+) [1..]*** Exception: stack overflow
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.
>>>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
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, ...]
>>>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 *
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
>>>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 *
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 *
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.
>>>replicate 0 True[]>>>replicate (-1) True[]>>>replicate 4 True[True,True,True,True]
repeat x is an infinite list, with x the value of every element.
>>>take 20 $ repeat 17[17,17,17,17,17,17,17,17,17...
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), ...]
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 10 $ iterate not True[True,False,True,False...>>>take 10 $ iterate (+3) 42[42,45,48,51,54,57,60,63...
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.
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 (> 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],[])
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]