| Copyright | (C) 2011-2015 Edward Kmett (C) 2010 Tony Morris Oliver Taylor Eelis van der Weegen | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.List.NonEmpty
Description
A NonEmpty list is one which always has at least one element, but
 is otherwise identical to the traditional list type in complexity
 and in terms of API. You will almost certainly want to import this
 module qualified.
Since: base-4.9.0.0
Synopsis
- 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
- sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- length :: NonEmpty a -> Int
- compareLength :: NonEmpty a -> Int -> Ordering
- head :: NonEmpty a -> a
- tail :: NonEmpty a -> [a]
- last :: NonEmpty a -> a
- init :: NonEmpty a -> [a]
- singleton :: a -> NonEmpty 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
- sortOn :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty a
- reverse :: NonEmpty a -> NonEmpty a
- inits :: Foldable f => f a -> NonEmpty [a]
- inits1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- tails :: Foldable f => f a -> NonEmpty [a]
- tails1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- append :: NonEmpty a -> NonEmpty a -> NonEmpty a
- appendList :: NonEmpty a -> [a] -> NonEmpty a
- prependList :: [a] -> NonEmpty 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]
- groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
- groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a]
- group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
- groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- permutations :: [a] -> NonEmpty [a]
- permutations1 :: 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
- (!!) :: HasCallStack => 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)
- fromList :: HasCallStack => [a] -> NonEmpty a
- toList :: NonEmpty a -> [a]
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- xor :: NonEmpty Bool -> Bool
The type of non-empty streams
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
Constructors
| a :| [a] infixr 5 | 
Instances
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
compareLength :: NonEmpty a -> Int -> Ordering Source #
Use compareLength xs n as a safer and faster alternative
 to compare (length xs) n. Similarly, it's better
 to write compareLength xs 10 == LT instead of length xs < 10.
While length would force and traverse
 the entire spine of xs (which could even diverge if xs is infinite),
 compareLength traverses at most n elements to determine its result.
>>>compareLength ('a' :| []) 1EQ>>>compareLength ('a' :| ['b']) 3LT>>>compareLength (0 :| [1..]) 100GT>>>compareLength undefined 0GT>>>compareLength ('a' :| 'b' : undefined) 1GT
Since: base-4.21.0.0
singleton :: a -> NonEmpty a Source #
Construct a NonEmpty list from a single element.
Since: base-4.15
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.
sortOn :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty a Source #
Sort a NonEmpty on a user-supplied projection of its elements.
 See sortOn for more detailed information.
Examples
>>>sortOn fst $ (2, "world") :| [(4, "!"), (1, "Hello")](1,"Hello") :| [(2,"world"),(4,"!")]
>>>sortOn List.length ("jim" :| ["creed", "pam", "michael", "dwight", "kevin"])"jim" :| ["pam","creed","kevin","dwight","michael"]
Performance notes
This function minimises the projections performed, by materialising the projections in an intermediate list.
For trivial projections, you should prefer using sortBy with
 comparing, for example:
>>>sortBy (comparing fst) $ (3, 1) :| [(2, 2), (1, 3)](1,3) :| [(2,2),(3,1)]
Or, for the exact same API as sortOn, you can use `sortBy . comparing`:
>>>(sortBy . comparing) fst $ (3, 1) :| [(2, 2), (1, 3)](1,3) :| [(2,2),(3,1)]
sortWith is an alias for `sortBy . comparing`.
Since: base-4.20.0.0
appendList :: NonEmpty a -> [a] -> NonEmpty a Source #
Attach a list at the end of a NonEmpty.
>>>appendList (1 :| [2,3]) []1 :| [2,3]
>>>appendList (1 :| [2,3]) [4,5]1 :| [2,3,4,5]
Since: base-4.16
prependList :: [a] -> NonEmpty a -> NonEmpty a Source #
Attach a list at the beginning of a NonEmpty.
>>>prependList [] (1 :| [2,3])1 :| [2,3]
>>>prependList [negate 1, 0] (1 :| [2, 3])-1 :| [0,1,2,3]
Since: base-4.16
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.
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, and consecutive equal elements
 of the input end up in the same stream of the output list.
 For example, in list notation:
>>>group "Mississippi"['M' :| "",'i' :| "",'s' :| "s",'i' :| "",'s' :| "s",'i' :| "",'p' :| "p",'i' :| ""]
groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] Source #
groupAllWith operates like groupWith, but sorts the list
 first so that each equivalence class has, at most, one list in the
 output
groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) Source #
groupWith1 is to group1 as groupWith is to group
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) Source #
groupAllWith1 is to groupWith1 as groupAllWith is to groupWith
permutations :: [a] -> NonEmpty [a] Source #
The permutations function returns the list of all permutations of the argument.
Since: base-4.20.0.0
permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a) Source #
permutations1 operates like permutations, but uses the knowledge that its input is
 non-empty to produce output where every element is non-empty.
permutations1 = fmap fromList . permutations . toList
Since: base-4.20.0.0
Sublist predicates
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool Source #
The isPrefixOf function returns True if the first argument is
 a prefix of the second.
"Set" operations
Indexing streams
(!!) :: HasCallStack => NonEmpty a -> Int -> a infixl 9 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.
Converting to and from a list
fromList :: HasCallStack => [a] -> NonEmpty a Source #
Converts a normal list to a NonEmpty stream.
Raises an error if given an empty list.