Data.List.NonEmpty (original) (raw)
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
Non-empty stream transformations
scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b Source #
[scanl](Data-List-NonEmpty.html#v:scanl "Data.List.NonEmpty") is similar to [foldl](Data-List.html#v:foldl "Data.List"), but returns a stream 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.
prependList :: [a] -> NonEmpty a -> NonEmpty a Source #
Attach a list at the beginning of a [NonEmpty](Data-List-NonEmpty.html#t:NonEmpty "Data.List.NonEmpty").
>>> **prependList [] (1 :| [2,3])** ****1 :| [2,3]
>>> prependList [negate 1, 0] (1 :| [2, 3])** **-1 :| [0,1,2,3]
Since: base-4.16
iterate :: (a -> a) -> a -> NonEmpty a Source #
`[iterate](Data-List-NonEmpty.html#v:iterate "Data.List.NonEmpty")` f x produces the infinite sequence of repeated applications of f to x.
iterate f x = x :| [f x, f (f x), ..]
unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b Source #
Deprecated: Use unfoldr
[unfold](Data-List-NonEmpty.html#v:unfold "Data.List.NonEmpty") produces a new stream by repeatedly applying the unfolding function to the seed value to produce an element of type b and a new seed value. When the unfolding function returns [Nothing](Data-Maybe.html#v:Nothing "Data.Maybe") instead of a new seed value, the stream ends.
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a Source #
`[insert](Data-List-NonEmpty.html#v:insert "Data.List.NonEmpty")` x xs inserts x into the last position in xs where it is still less than or equal to the next element. In particular, if the list is sorted beforehand, the result will also be sorted.
splitAt :: Int -> NonEmpty a -> ([a], [a]) Source #
`[splitAt](Data-List-NonEmpty.html#v:splitAt "Data.List.NonEmpty")` n xs returns a pair consisting of the prefix of xs of length n and the remaining stream immediately following this prefix.
'splitAt' n xs == ('take' n xs, 'drop' n xs) xs == ys ++ zs where (ys, zs) = 'splitAt' n xs
span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) Source #
`[span](Data-List-NonEmpty.html#v:span "Data.List.NonEmpty")` p xs returns the longest prefix of xs that satisfiesp, together with the remainder of the stream.
'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs) xs == ys ++ zs where (ys, zs) = 'span' p xs
partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) Source #
The [partition](Data-List-NonEmpty.html#v:partition "Data.List.NonEmpty") function takes a predicate p and a streamxs, and returns a pair of lists. The first list corresponds to the elements of xs for which p holds; the second corresponds to the elements of xs for which p does not hold.
'partition' p xs = ('filter' p xs, 'filter' (not . p) xs)
group :: (Foldable f, Eq a) => f a -> [NonEmpty a] Source #
The [group](Data-List-NonEmpty.html#v:group "Data.List.NonEmpty") function takes a stream and returns a list of streams such that flattening the resulting list is equal to the argument. Moreover, each stream in the resulting list contains only equal elements. For example, in list notation:
'group' $ 'cycle' "Mississippi" = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...
Sublist predicates"Set" operations
nub :: Eq a => NonEmpty a -> NonEmpty a Source #
The [nub](Data-List-NonEmpty.html#v:nub "Data.List.NonEmpty") function removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element. (The name [nub](Data-List-NonEmpty.html#v:nub "Data.List.NonEmpty") means 'essence'.) It is a special case of [nubBy](Data-List-NonEmpty.html#v:nubBy "Data.List.NonEmpty"), which allows the programmer to supply their own inequality test.
(!!) :: NonEmpty a -> Int -> a infixl 9 Source #
xs !! n returns the element of the stream xs at indexn. Note that the head of the stream has index 0.
Beware: a negative or out-of-bounds index will cause an error.