| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
GHC.Data.List.NonEmpty
Synopsis
- (!!) :: HasCallStack => NonEmpty a -> Int -> a
- (<|) :: a -> NonEmpty a -> NonEmpty a
- append :: NonEmpty a -> NonEmpty a -> NonEmpty a
- appendList :: NonEmpty a -> [a] -> NonEmpty a
- break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- compareLength :: NonEmpty a -> Int -> Ordering
- cons :: a -> NonEmpty a -> NonEmpty a
- cycle :: NonEmpty a -> NonEmpty a
- drop :: Int -> NonEmpty a -> [a]
- dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
- filter :: (a -> Bool) -> NonEmpty a -> [a]
- fromList :: HasCallStack => [a] -> NonEmpty a
- group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
- group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
- groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a]
- groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
- groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
- groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- head :: NonEmpty a -> a
- init :: NonEmpty a -> [a]
- inits :: Foldable f => f a -> NonEmpty [a]
- inits1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
- intersperse :: a -> NonEmpty a -> NonEmpty a
- isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
- iterate :: (a -> a) -> a -> NonEmpty a
- last :: NonEmpty a -> a
- length :: NonEmpty a -> Int
- mapMaybe :: (a -> Maybe b) -> NonEmpty a -> [b]
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- nub :: Eq a => NonEmpty a -> NonEmpty a
- nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
- partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- permutations :: [a] -> NonEmpty [a]
- permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- prependList :: [a] -> NonEmpty a -> NonEmpty a
- repeat :: a -> NonEmpty a
- reverse :: NonEmpty a -> NonEmpty a
- scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
- scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
- scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- singleton :: a -> NonEmpty a
- some1 :: Alternative f => f a -> f (NonEmpty a)
- sort :: Ord a => NonEmpty a -> NonEmpty a
- sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
- sortOn :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty a
- sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- splitAt :: Int -> NonEmpty a -> ([a], [a])
- tail :: NonEmpty a -> [a]
- tails :: Foldable f => f a -> NonEmpty [a]
- tails1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- take :: Int -> NonEmpty a -> [a]
- takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
- transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
- uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
- unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- xor :: NonEmpty Bool -> Bool
- zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
- zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
- map :: (a -> b) -> NonEmpty a -> NonEmpty b
- data NonEmpty a = a :| [a]
- isSingleton :: NonEmpty a -> Bool
- mapAndUnzip :: (a -> (b, c)) -> NonEmpty a -> (NonEmpty b, NonEmpty c)
- mapAndUnzip3 :: (a -> (b, c, d)) -> NonEmpty a -> (NonEmpty b, NonEmpty c, NonEmpty d)
- unzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
- unzip3 :: NonEmpty (a, b, c) -> (NonEmpty a, NonEmpty b, NonEmpty c)
- zipWithM :: Applicative f => (a -> b -> f c) -> NonEmpty a -> NonEmpty b -> f (NonEmpty c)
- toList :: Foldable t => t a -> [a]
Documentation
(!!) :: 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.
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
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
cycle :: NonEmpty a -> NonEmpty a Source #
returns the infinite repetition of cycle xsxs:
cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]
drop :: Int -> NonEmpty a -> [a] Source #
drops the first drop n xsn elements off the front of
the sequence xs.
filter :: (a -> Bool) -> NonEmpty a -> [a] Source #
removes any elements from filter p xsxs that do not satisfy p.
fromList :: HasCallStack => [a] -> NonEmpty a Source #
Converts a normal list to a NonEmpty stream.
Raises an error if given an empty list.
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
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) Source #
groupAllWith1 is to groupWith1 as groupAllWith is to groupWith
groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) Source #
groupWith1 is to group1 as groupWith is to group
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a Source #
inserts 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.
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]
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool Source #
The isPrefixOf function returns True if the first argument is
a prefix of the second.
iterate :: (a -> a) -> a -> NonEmpty a Source #
produces the infinite sequence
of repeated applications of iterate f xf to x.
iterate f x = x :| [f x, f (f x), ..]
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)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
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
repeat :: a -> NonEmpty a Source #
returns a constant stream, where all elements are
equal to repeat xx.
singleton :: a -> NonEmpty a Source #
Construct a NonEmpty list from a single element.
Since: base-4.15
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)]
However, sortOn may still be faster for instances with a more efficient
implementation of (>) than compare.
sortWith is an alias for `sortBy . comparing`.
Since: base-4.20.0.0
span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) Source #
returns the longest prefix of 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 xssplitAt :: 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.
'splitAt' n xs == ('take' n xs, 'drop' n xs)
xs == ys ++ zs where (ys, zs) = 'splitAt' n xstakeWhile :: (a -> Bool) -> NonEmpty a -> [a] Source #
returns the longest prefix of the stream
takeWhile p xsxs for which the predicate p holds.
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.
zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) Source #
The zip function takes two streams and returns a stream of
corresponding pairs.
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
Constructors
| a :| [a] infixr 5 |
Instances
isSingleton :: NonEmpty a -> Bool Source #
toList :: Foldable t => t a -> [a] Source #
List of elements of a structure, from left to right. If the entire list is intended to be reduced via a fold, just fold the structure directly bypassing the list.
Examples
Basic usage:
>>>toList Nothing[]
>>>toList (Just 42)[42]
>>>toList (Left "foo")[]
>>>toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))[5,17,12,8]
For lists, toList is the identity:
>>>toList [1, 2, 3][1,2,3]
Since: base-4.8.0.0