| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.NonEmpty
Contents
Description
This package extends NonEmpty from semigroups to arbitrary
Alternative types. The method is the same as for lists, by
separating an element from the rest.
There are two natural ways to merge an element x to the rest of the
structure xs. The first gives rise to NonEmptyL:
flattenL :: NonEmptyL f a -> f a flattenL (x :<: xs) = pure x <|> xs
The second gives rise to NonEmptyR:
flattenR :: NonEmptyR f a -> f a flattenR (xs :>: x) = xs <|> pure x
The instances are made so that flattenL gives a type class morphism
between NonEmptyL List and List, and flattenR gives the same for
NonEmptyR RList and RList from the package rlist.
- data NonEmptyL f a = a :<: (f a)
- headL :: NonEmptyL f a -> a
- tailL :: NonEmptyL f a -> f a
- flattenL :: Alternative f => NonEmptyL f a -> f a
- joinL :: (Alternative f, Monad f) => NonEmptyL f (NonEmptyL f a) -> NonEmptyL f a
- budgeL :: (Alternative f, Alternative g) => NonEmptyL f (g a) -> NonEmptyL f (g a)
- data NonEmptyR f a = (f a) :>: a
- lastR :: NonEmptyR f a -> a
- initR :: NonEmptyR f a -> f a
- flattenR :: Alternative f => NonEmptyR f a -> f a
- joinR :: (Alternative f, Monad f) => NonEmptyR f (NonEmptyR f a) -> NonEmptyR f a
- budgeR :: (Alternative f, Alternative g) => NonEmptyR f (g a) -> NonEmptyR f (g a)
Left Non-Empty Alternatives
The type NonEmptyL is well suited for cons structures.
Constructors
| a :<: (f a) infixr 5 |
Instances
| (Alternative f, Monad f) => Monad (NonEmptyL f) Source | |
| Functor f => Functor (NonEmptyL f) Source | |
| Alternative f => Applicative (NonEmptyL f) Source | |
| Foldable f => Foldable (NonEmptyL f) Source | |
| (Functor f, Traversable f) => Traversable (NonEmptyL f) Source | |
| Generic1 (NonEmptyL f) Source | |
| Alternative f => Comonad (NonEmptyL f) Source | |
| (Eq a, Eq (f a)) => Eq (NonEmptyL f a) Source | |
| (Data a, Data (f a), Typeable (* -> *) f) => Data (NonEmptyL f a) Source | |
| (Ord a, Ord (f a)) => Ord (NonEmptyL f a) Source | |
| (Read a, Read (f a)) => Read (NonEmptyL f a) Source | |
| (Show a, Show (f a)) => Show (NonEmptyL f a) Source | |
| Generic (NonEmptyL f a) Source | |
| Alternative f => Semigroup (NonEmptyL f a) Source | |
| type Rep1 (NonEmptyL f) Source | |
| type Rep (NonEmptyL f a) Source |
Basic functions for NonEmptyL
headL :: NonEmptyL f a -> a Source
Extracts the structure's singular element. This function is total
and equivalent to extract from Comonad.
tailL :: NonEmptyL f a -> f a Source
Extracts the structure's remaining data. This function is total.
flattenL :: Alternative f => NonEmptyL f a -> f a Source
Flattens the structure to its base type from the left.
joinL :: (Alternative f, Monad f) => NonEmptyL f (NonEmptyL f a) -> NonEmptyL f a Source
This is equivalent to join for Monad.
budgeL :: (Alternative f, Alternative g) => NonEmptyL f (g a) -> NonEmptyL f (g a) Source
Budge the head into the remaining structure from the left, adding an empty head.
Right Non-Empty Alternatives
The type NonEmptyR is well suited for snoc structures.
Constructors
| (f a) :>: a infixl 5 |
Instances
| Functor f => Functor (NonEmptyR f) Source | |
| Alternative f => Applicative (NonEmptyR f) Source | |
| Foldable f => Foldable (NonEmptyR f) Source | |
| (Functor f, Traversable f) => Traversable (NonEmptyR f) Source | |
| Generic1 (NonEmptyR f) Source | |
| Alternative f => Comonad (NonEmptyR f) Source | |
| (Eq a, Eq (f a)) => Eq (NonEmptyR f a) Source | |
| (Data a, Data (f a), Typeable (* -> *) f) => Data (NonEmptyR f a) Source | |
| (Ord a, Ord (f a)) => Ord (NonEmptyR f a) Source | |
| (Read a, Read (f a)) => Read (NonEmptyR f a) Source | |
| (Show a, Show (f a)) => Show (NonEmptyR f a) Source | |
| Generic (NonEmptyR f a) Source | |
| Alternative f => Semigroup (NonEmptyR f a) Source | |
| type Rep1 (NonEmptyR f) Source | |
| type Rep (NonEmptyR f a) Source |
Basic functions for NonEmptyR
lastR :: NonEmptyR f a -> a Source
Extracts the structure's singular element. This function is total
and equivalent to extract from Comonad.
initR :: NonEmptyR f a -> f a Source
Extracts the structure's remaining data. This function is total.
flattenR :: Alternative f => NonEmptyR f a -> f a Source
Flattens the structure to its base type from the right.
joinR :: (Alternative f, Monad f) => NonEmptyR f (NonEmptyR f a) -> NonEmptyR f a Source
This is equivalent to join for Monad.
budgeR :: (Alternative f, Alternative g) => NonEmptyR f (g a) -> NonEmptyR f (g a) Source
Budge the head into the remaining structure from the right, adding an empty head.