| Copyright | (C) 2011-2014 Edward Kmett, (C) 2010 Tony Morris, Oliver Taylor, Eelis van der Weegen | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
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
- transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
- sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
- sortOn :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- length :: NonEmpty a -> Int
- 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))
- unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- 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
- some1 :: Alternative f => f a -> f (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
- nub :: Eq a => NonEmpty a -> NonEmpty a
- nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
- (!!) :: 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)
- xor :: NonEmpty Bool -> Bool
The type of non-empty streams
Constructors
| a :| [a] infixr 5 | 
Instances
| Monad NonEmpty | |
| Functor NonEmpty | |
| Applicative NonEmpty | |
| Foldable NonEmpty | |
| Traversable NonEmpty | |
| IsList (NonEmpty a) | |
| Eq a => Eq (NonEmpty a) | |
| Data a => Data (NonEmpty a) | |
| Ord a => Ord (NonEmpty a) | |
| Read a => Read (NonEmpty a) | |
| Show a => Show (NonEmpty a) | |
| Generic (NonEmpty a) | |
| NFData a => NFData (NonEmpty a) | |
| Hashable a => Hashable (NonEmpty a) | |
| Semigroup (NonEmpty a) | |
| Typeable (* -> *) NonEmpty | |
| type Rep (NonEmpty a) | |
| type Item (NonEmpty a) = a | 
Non-empty stream transformations
intersperse :: a -> NonEmpty a -> NonEmpty a Source
'intersperse x xs' alternates elements of the list with copies of x.
intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]
Basic functions
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.
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 a Source
iterate f xf to x.
iterate f x = x :| [f x, f (f x), ..]
repeat :: a -> NonEmpty a Source
repeat xx.
cycle :: NonEmpty a -> NonEmpty a Source
cycle xsxs:
cycle [1,2,3] = 1 :| [2,3,1,2,3,...]
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a Source
insert x xsx 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.
some1 :: Alternative f => f a -> f (NonEmpty a) Source
some1 xx one or more times.
Extracting sublists
drop :: Int -> NonEmpty a -> [a] Source
drop n xsn elements off the front of
 the sequence xs.
splitAt :: Int -> NonEmpty a -> ([a], [a]) Source
splitAt n xsxs
 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 xstakeWhile :: (a -> Bool) -> NonEmpty a -> [a] Source
takeWhile p xsxs for which the predicate p holds.
span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) Source
span p xsxs 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 xsfilter :: (a -> Bool) -> NonEmpty a -> [a] Source
filter p xsxs 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" : ...
Sublist predicates
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool Source
The isPrefix function returns True if the first argument is
 a prefix of the second.
"Set" operations
Indexing streams
(!!) :: NonEmpty a -> Int -> a Source
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.
Functions on streams of characters
words :: NonEmpty Char -> NonEmpty String Source
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.
lines :: NonEmpty Char -> NonEmpty String Source
The lines function breaks a stream of characters into a stream
 of strings at newline characters. The resulting strings do not
 contain newlines.
Converting to and from a list
fromList :: [a] -> NonEmpty a Source
Converts a normal list to a NonEmpty stream.
Raises an error if given an empty list.