semigroups-0.9: Haskell 98 semigroups

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Inferred

Data.List.NonEmpty

Contents

Description

A NonEmpty list forms a monad as per list, but always contains at least one element.

Synopsis

The type of non-empty streams

Non-empty stream transformations

map :: (a -> b) -> NonEmpty a -> NonEmpty bSource

Map a function over a NonEmpty stream.

intersperse :: a -> NonEmpty a -> NonEmpty aSource

'intersperse x xs' alternates elements of the list with copies of x.

 intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]

scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty bSource

scanl is similar to foldl, 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.

scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty bSource

scanr is the right-to-left dual of scanl. Note that

 head (scanr f z xs) == foldr f z xs.

scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty aSource

scanl1 is a variant of scanl that has no starting value argument:

 scanl1 f [x1, x2, ...] == x1 :| [x1 `f` x2, x1 `f` (x2 `f` x3), ...]

scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty aSource

scanr1 is a variant of scanr that has no starting value argument.

Basic functions

head :: NonEmpty a -> aSource

Extract the first element of the stream.

tail :: NonEmpty a -> [a]Source

Extract the possibly-empty tail of the stream.

last :: NonEmpty a -> aSource

Extract the last element of the stream.

init :: NonEmpty a -> [a]Source

Extract everything except the last element of the stream.

(<|) :: a -> NonEmpty a -> NonEmpty aSource

Prepend an element to the stream.

cons :: a -> NonEmpty a -> NonEmpty aSource

Synonym for <|.

uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))Source

uncons produces the first element of the stream, and a stream of the remaining elements, if any.

sort :: Ord a => NonEmpty a -> NonEmpty aSource

Sort a stream.

reverse :: NonEmpty a -> NonEmpty aSource

reverse a finite NonEmpty stream.

inits :: Foldable f => f a -> NonEmpty [a]Source

The inits function takes a stream xs and returns all the finite prefixes of xs.

tails :: Foldable f => f a -> NonEmpty [a]Source

The tails function takes a stream xs and returns all the suffixes of xs.

Building streams

iterate :: (a -> a) -> a -> NonEmpty aSource

iterate f x produces the infinite sequence of repeated applications of f to x.

 iterate f x = x :| [f x, f (f x), ..]

repeat :: a -> NonEmpty aSource

repeat x returns a constant stream, where all elements are equal to x.

cycle :: NonEmpty a -> NonEmpty aSource

cycle xs returns the infinite repetition of xs:

 cycle [1,2,3] = 1 :| [2,3,1,2,3,...]

unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty bSource

unfold 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 instead of a new seed value, the stream ends.

insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty aSource

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

Extracting sublists

take :: Int -> NonEmpty a -> [a]Source

take n xs returns the first n elements of xs.

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

drop n xs drops the first n elements off the front of the sequence xs.

splitAt :: Int -> NonEmpty a -> ([a], [a])Source

splitAt 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

takeWhile :: (a -> Bool) -> NonEmpty a -> [a]Source

takeWhile p xs returns the longest prefix of the stream xs for which the predicate p holds.

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

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

span :: (a -> Bool) -> NonEmpty a -> ([a], [a])Source

span p xs returns the longest prefix of xs that satisfies p, 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

break :: (a -> Bool) -> NonEmpty a -> ([a], [a])Source

The break p function is equivalent to span (not . p).

filter :: (a -> Bool) -> NonEmpty a -> [a]Source

filter p xs removes any elements from xs that do not satisfy p.

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

The partition function takes a predicate p and a stream xs, 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 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" : ...

groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]Source

groupBy operates like group, but uses the provided equality predicate instead of ==.

group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)Source

group1 operates like group, but uses the knowledge that its input is non-empty to produce guaranteed non-empty output.

groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)Source

groupBy1 is to group1 as groupBy is to group.

Sublist predicates

isPrefixOf :: Eq a => [a] -> NonEmpty a -> BoolSource

The isPrefix function returns True if the first argument is a prefix of the second.

Indexing streams

(!!) :: NonEmpty a -> Int -> aSource

xs !! n returns the element of the stream xs at index n. Note that the head of the stream has index 0.

Beware: a negative or out-of-bounds index will cause an error.

Zipping and unzipping streams

zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)Source

The zip function takes two streams and returns a stream of corresponding pairs.

zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty cSource

The zipWith function generalizes zip. Rather than tupling the elements, the elements are combined using the function passed as the first argument.

unzip :: Functor f => f (a, b) -> (f a, f b)Source

The unzip function is the inverse of the zip function.

Functions on streams of characters

words :: NonEmpty Char -> NonEmpty StringSource

The words function breaks a stream of characters into a stream of words, which were delimited by white space.

Beware: if the input contains no words (i.e. is entirely whitespace), this will cause an error.

unwords :: NonEmpty String -> NonEmpty CharSource

The unwords function is an inverse operation to words. It joins words with separating spaces.

Beware: the input ("" :| []) will cause an error.

lines :: NonEmpty Char -> NonEmpty StringSource

The lines function breaks a stream of characters into a stream of strings at newline characters. The resulting strings do not contain newlines.

unlines :: NonEmpty String -> NonEmpty CharSource

The unlines function is an inverse operation to lines. It joins lines, after appending a terminating newline to each.

Converting to and from a list

fromList :: [a] -> NonEmpty aSource

Converts a normal list to a NonEmpty stream.

Raises an error if given an empty list.

toList :: NonEmpty a -> [a]Source

Convert a stream to a normal list efficiently.

nonEmpty :: [a] -> Maybe (NonEmpty a)Source

nonEmpty efficiently turns a normal list into a NonEmpty stream, producing Nothing if the input is empty.