| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Papa.Base.Export.Data.List.NonEmpty
- data NonEmpty a :: * -> * = a :| [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
- inits :: Foldable f => f a -> NonEmpty [a]
- tails :: Foldable f => f a -> NonEmpty [a]
- iterate :: (a -> a) -> a -> NonEmpty a
- repeat :: 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)
- 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)
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- xor :: NonEmpty Bool -> Bool
Documentation
Non-empty (and non-strict) list type.
Since: 4.9.0.0
Constructors
| a :| [a] infixr 5 |
Instances
| Monad NonEmpty | Since: 4.9.0.0 |
| Functor NonEmpty | Since: 4.9.0.0 |
| MonadFix NonEmpty | Since: 4.9.0.0 |
| Applicative NonEmpty | Since: 4.9.0.0 |
| Foldable NonEmpty | Since: 4.9.0.0 |
| Traversable NonEmpty | Since: 4.9.0.0 |
| Eq1 NonEmpty | Since: 4.10.0.0 |
| Ord1 NonEmpty | Since: 4.10.0.0 |
| Read1 NonEmpty | Since: 4.10.0.0 |
| Show1 NonEmpty | Since: 4.10.0.0 |
| MonadZip NonEmpty | Since: 4.9.0.0 |
| IsList (NonEmpty a) | Since: 4.9.0.0 |
| 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) | |
| Semigroup (NonEmpty a) | Since: 4.9.0.0 |
| Generic1 * NonEmpty | |
| type Rep (NonEmpty a) | |
| type Item (NonEmpty a) | |
| type Rep1 * NonEmpty | |
inits :: Foldable f => f a -> NonEmpty [a] #
The inits function takes a stream xs and returns all the
finite prefixes of xs.
tails :: Foldable f => f a -> NonEmpty [a] #
The tails function takes a stream xs and returns all the
suffixes of xs.
iterate :: (a -> a) -> a -> NonEmpty a #
produces the infinite sequence
of repeated applications of iterate f xf to x.
iterate f x = x :| [f x, f (f x), ..]
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a #
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.
some1 :: Alternative f => f a -> f (NonEmpty a) #
sequences some1 xx one or more times.
group :: (Foldable f, Eq a) => f a -> [NonEmpty a] #
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" : ...
groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] #
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) #
groupWith1 is to group1 as groupWith is to group
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupAllWith1 is to groupWith1 as groupAllWith is to groupWith