| Portability | portable | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
Data.List.NonEmpty
Contents
Description
A NonEmpty list forms a monad as per list, but always contains at least one element.
- data NonEmpty a = a :| [a]
 - map :: (a -> b) -> NonEmpty a -> NonEmpty b
 - intersperse :: a -> NonEmpty a -> NonEmpty a
 - scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
 - scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
 - scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
 - scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
 - head :: NonEmpty a -> a
 - tail :: NonEmpty a -> [a]
 - last :: NonEmpty a -> a
 - init :: NonEmpty a -> [a]
 - (<|) :: a -> NonEmpty a -> NonEmpty a
 - cons :: a -> NonEmpty a -> NonEmpty a
 - uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
 - sort :: Ord a => NonEmpty a -> NonEmpty a
 - reverse :: NonEmpty a -> NonEmpty a
 - inits :: Foldable f => f a -> NonEmpty [a]
 - tails :: Foldable f => f a -> NonEmpty [a]
 - iterate :: (a -> a) -> a -> NonEmpty a
 - repeat :: a -> NonEmpty a
 - cycle :: NonEmpty a -> NonEmpty a
 - unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
 - insert :: Foldable f => Ord a => a -> f a -> NonEmpty a
 - take :: Int -> NonEmpty a -> [a]
 - drop :: Int -> NonEmpty a -> [a]
 - splitAt :: Int -> NonEmpty a -> ([a], [a])
 - takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
 - dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
 - span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
 - break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
 - filter :: (a -> Bool) -> NonEmpty a -> [a]
 - partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
 - group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
 - groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
 - group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
 - groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
 - isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
 - (!!) :: NonEmpty a -> Int -> a
 - zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
 - zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
 - unzip :: Functor f => f (a, b) -> (f a, f b)
 - words :: NonEmpty Char -> NonEmpty String
 - unwords :: NonEmpty String -> NonEmpty Char
 - lines :: NonEmpty Char -> NonEmpty String
 - unlines :: NonEmpty String -> NonEmpty Char
 - fromList :: [a] -> NonEmpty a
 - toList :: NonEmpty a -> [a]
 - nonEmpty :: [a] -> Maybe (NonEmpty a)
 
The type of streams
Constructors
| a :| [a] | 
non-empty stream transformations
intersperse :: a -> NonEmpty a -> NonEmpty aSource
Basic functions
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
 produces the infinite sequence
 of repeated applications of iterate f xf to x.
iterate f x = [x, f x, f (f x), ..]
repeat :: a -> NonEmpty aSource
 returns a constant stream, where all elements are
 equal to repeat xx.
cycle :: NonEmpty a -> NonEmpty aSource
 returns the infinite repetition of cycle xsxs:
cycle [1,2,3] = 1 :| [2,3,1,2,3,...]
Extracting sublists
take :: Int -> NonEmpty a -> [a]Source
 returns the first take n xsn elements of xs.
Beware: passing a negative integer as the first argument will cause an error.
drop :: Int -> NonEmpty a -> [a]Source
 drops the first drop n xsn elements off the front of
 the sequence xs.
Beware: passing a negative integer as the first argument will cause an error.
splitAt :: Int -> NonEmpty a -> ([a], [a])Source
 returns a pair consisting of the prefix of splitAt n xsxs 
 of length n and the remaining stream immediately following this prefix.
Beware: passing a negative integer as the first argument will cause an error.
takeWhile :: (a -> Bool) -> NonEmpty a -> [a]Source
 returns the longest prefix of the stream
 takeWhile p xsxs for which the predicate p holds.
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.
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 streams. The first stream corresponds
 to the elements of xs for which p holds; the second stream
 corresponds to the elements of xs for which p does not hold.
group :: (Foldable f, Eq a) => f a -> [NonEmpty a]Source
The group function takes a stream and returns a stream of
 lists such that flattening the resulting stream is equal to the
 argument.  Moreover, each sublist in the resulting stream
 contains only equal elements.  For example,
group $ cycle "Mississippi" = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...
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: passing a negative integer as the first argument 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 list of
 corresponding pairs.
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.
lines :: NonEmpty Char -> NonEmpty StringSource
The lines function breaks a stream of characters into a list
 of strings at newline characters. The resulting strings do not
 contain newlines.