Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2019 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Reexports most of the Data.List and Data.List.NonEmpty.
Note, that Relude reexports head
, tail
, init
, last
from
"Data,List.NonEmpty" instead of the Data.List, so these functions are safe to
use.
relude
also provides custom type error for better experience with transition
from lists to NonEmpty
with those functions.
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]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- permutations :: [a] -> [[a]]
- subsequences :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- inits :: [a] -> [[a]]
- group :: Eq a => [a] -> [[a]]
- genericReplicate :: Integral i => i -> a -> [a]
- genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
- genericDrop :: Integral i => i -> [a] -> [a]
- genericTake :: Integral i => i -> [a] -> [a]
- genericLength :: Num i => [a] -> i
- transpose :: [[a]] -> [[a]]
- intercalate :: [a] -> [[a]] -> [a]
- intersperse :: a -> [a] -> [a]
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip :: [(a, b)] -> ([a], [b])
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- reverse :: [a] -> [a]
- break :: (a -> Bool) -> [a] -> ([a], [a])
- splitAt :: Int -> [a] -> ([a], [a])
- drop :: Int -> [a] -> [a]
- take :: Int -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- replicate :: Int -> a -> [a]
- repeat :: a -> [a]
- iterate :: (a -> a) -> a -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- uncons :: [a] -> Maybe (a, [a])
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
- data NonEmpty a = a :| [a]
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- head :: IsNonEmpty f a a "head" => f a -> a
- init :: IsNonEmpty f a [a] "init" => f a -> [a]
- last :: IsNonEmpty f a a "last" => f a -> a
- tail :: IsNonEmpty f a [a] "tail" => f 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] #
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)] #
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 short, excess elements of the longer list are discarded:
zip [1] ['a', 'b'] = [(1, 'a')] zip [1, 2] ['a'] = [(1, 'a')]
zip
is right-lazy:
zip [] _|_ = [] zip _|_ [] = _|_
zip
is capable of list fusion, but it is restricted to its
first list argument and its resulting list.
map :: (a -> b) -> [a] -> [b] #
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]
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]
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 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
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 from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sort [1,6,4,3,2,5]
[1,2,3,4,5,6]
permutations :: [a] -> [[a]] #
The permutations
function returns the list of all permutations of the argument.
>>>
permutations "abc"
["abc","bac","cba","bca","cab","acb"]
subsequences :: [a] -> [[a]] #
The subsequences
function returns the list of all subsequences of the argument.
>>>
subsequences "abc"
["","a","b","ab","c","ac","bc","abc"]
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.
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.
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.
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.
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.
genericLength :: Num i => [a] -> i #
O(n). The genericLength
function is an overloaded version of length
.
In particular, instead of returning an Int
, it returns any type which is an
instance of Num
. It is, however, less efficient than length
.
>>>
genericLength [1, 2, 3] :: Int
3>>>
genericLength [1, 2, 3] :: Float
3.0
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]]
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"
intersperse :: a -> [a] -> [a] #
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"
isPrefixOf :: Eq a => [a] -> [a] -> Bool #
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
unzip :: [(a, b)] -> ([a], [b]) #
unzip
transforms a list of pairs into a list of first components
and a list of second components.
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] #
O(min(m,n)). zipWith
generalises zip
by zipping with the function
given as the first argument, instead of a tupling function. For example,
is applied to two lists to produce the list of corresponding
sums:zipWith
(+)
>>>
zipWith (+) [1, 2, 3] [4, 5, 6]
[5,7,9]
zipWith
is right-lazy:
zipWith f [] _|_ = []
zipWith
is capable of list fusion, but it is restricted to its
first list argument and its resulting list.
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],[])
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.
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.
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.
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] == []
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.
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.
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
NonEmpty List
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
a :| [a] infixr 5 |
Instances
Monad NonEmpty | Since: base-4.9.0.0 |
Functor NonEmpty | Since: base-4.9.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Traversable NonEmpty | Since: base-4.9.0.0 |
Eq1 NonEmpty | Since: base-4.10.0.0 |
Ord1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Read1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Show1 NonEmpty | Since: base-4.10.0.0 |
NFData1 NonEmpty | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Foldable1 NonEmpty Source # | |
Defined in Relude.Extra.Foldable1 | |
IsList (NonEmpty a) | Since: base-4.9.0.0 |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
Data a => Data (NonEmpty a) | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) # toConstr :: NonEmpty a -> Constr # dataTypeOf :: NonEmpty a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) # gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r # gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # | |
Ord a => Ord (NonEmpty a) | Since: base-4.9.0.0 |
Read a => Read (NonEmpty a) | Since: base-4.11.0.0 |
Show a => Show (NonEmpty a) | Since: base-4.11.0.0 |
Generic (NonEmpty a) | Since: base-4.6.0.0 |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
Lift a => Lift (NonEmpty a) | Since: template-haskell-2.15.0.0 |
NFData a => NFData (NonEmpty a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable (NonEmpty a) | |
Defined in Data.Hashable.Class | |
One (NonEmpty a) Source # | Allows to create singleton
length (one @(NonEmpty Int) x) == 1 |
Generic1 NonEmpty | Since: base-4.6.0.0 |
type Rep (NonEmpty a) | |
Defined in GHC.Generics type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |
type Item (NonEmpty a) | |
type OneItem (NonEmpty a) Source # | |
Defined in Relude.Container.One | |
type Rep1 NonEmpty | |
Defined in GHC.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) |
head :: IsNonEmpty f a a "head" => f a -> a Source #
O(1)
. Extracts the first element of a NonEmpty
list.
Actual type of this function is the following:
head :: NonEmpty
a -> a
but it was given a more complex type to provide friendlier compile time errors.
>>>
head ('a' :| "bcde")
'a'>>>
head [0..5 :: Int]
... ... 'head' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'head' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty head (yourList) Note, that this will return 'Maybe Int' therefore it is a safe function unlike 'head' from the standard Prelude ...>>>
head (Just 'a')
... ... 'head' works with 'NonEmpty Char' lists But given: Maybe Char ...
init :: IsNonEmpty f a [a] "init" => f a -> [a] Source #
O(n)
. Return all the elements of a NonEmpty
list except the last one
element.
Actual type of this function is the following:
init :: NonEmpty
a -> [a]
but it was given a more complex type to provide friendlier compile time errors.
>>>
init ('a' :| "bcde")
"abcd">>>
init [0..5 :: Int]
... ... 'init' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'init' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty init (yourList) Note, that this will return 'Maybe [Int]' therefore it is a safe function unlike 'init' from the standard Prelude ...>>>
init (Just 'a')
... ... 'init' works with 'NonEmpty Char' lists But given: Maybe Char ...
last :: IsNonEmpty f a a "last" => f a -> a Source #
O(n)
. Extracts the last element of a NonEmpty
list.
Actual type of this function is the following:
last :: NonEmpty
a -> a
but it was given a more complex type to provide friendlier compile time errors.
>>>
last ('a' :| "bcde")
'e'>>>
last [0..5 :: Int]
... ... 'last' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'last' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty last (yourList) Note, that this will return 'Maybe Int' therefore it is a safe function unlike 'last' from the standard Prelude ...>>>
last (Just 'a')
... ... 'last' works with 'NonEmpty Char' lists But given: Maybe Char ...
tail :: IsNonEmpty f a [a] "tail" => f a -> [a] Source #
O(1)
. Return all the elements of a NonEmpty
list after the head
element.
Actual type of this function is the following:
tail :: NonEmpty
a -> [a]
but it was given a more complex type to provide friendlier compile time errors.
>>>
tail ('a' :| "bcde")
"bcde">>>
tail [0..5 :: Int]
... ... 'tail' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'tail' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty tail (yourList) Note, that this will return 'Maybe [Int]' therefore it is a safe function unlike 'tail' from the standard Prelude ...>>>
tail (Just 'a')
... ... 'tail' works with 'NonEmpty Char' lists But given: Maybe Char ...