| Safe Haskell | None |
|---|
Data.NonEmpty
- data T f a = Cons {}
- (!:) :: a -> f a -> T f a
- force :: T f a -> T f a
- apply :: (Applicative f, Cons f, Append f) => T f (a -> b) -> T f a -> T f b
- bind :: (Monad f, Cons f, Append f) => T f a -> (a -> T f b) -> T f b
- toList :: Foldable f => T f a -> [a]
- flatten :: Cons f => T f a -> f a
- fetch :: ViewL f => f a -> Maybe (T f a)
- cons :: a -> f a -> T f a
- snoc :: Traversable f => f a -> a -> T f a
- singleton :: Empty f => a -> T f a
- reverse :: (Traversable f, Reverse f) => T f a -> T f a
- mapHead :: (a -> a) -> T f a -> T f a
- mapTail :: (f a -> g a) -> T f a -> T g a
- viewL :: T f a -> (a, f a)
- viewR :: Traversable f => T f a -> (f a, a)
- init :: Traversable f => T f a -> f a
- last :: Foldable f => T f a -> a
- foldl1 :: Foldable f => (a -> a -> a) -> T f a -> a
- foldBalanced :: (a -> a -> a) -> T [] a -> a
- maximum :: (Ord a, Foldable f) => T f a -> a
- maximumBy :: Foldable f => (a -> a -> Ordering) -> T f a -> a
- maximumKey :: (Ord b, Foldable f) => (a -> b) -> T f a -> a
- minimum :: (Ord a, Foldable f) => T f a -> a
- minimumBy :: Foldable f => (a -> a -> Ordering) -> T f a -> a
- minimumKey :: (Ord b, Foldable f) => (a -> b) -> T f a -> a
- sum :: (Num a, Foldable f) => T f a -> a
- product :: (Num a, Foldable f) => T f a -> a
- append :: (Append f, Traversable f) => T f a -> T f a -> T (T f) a
- appendLeft :: (Append f, Traversable f) => f a -> T f a -> T f a
- appendRight :: Append f => T f a -> f a -> T f a
- cycle :: (Cons f, Append f) => T f a -> T f a
- zipWith :: Zip f => (a -> b -> c) -> T f a -> T f b -> T f c
- mapAdjacent :: Traversable f => (a -> a -> b) -> T f a -> f b
- class Insert f where
- insertDefault :: (Ord a, InsertBy f, SortBy f) => a -> f a -> T f a
- class Insert f => InsertBy f where
- scanl :: Traversable f => (b -> a -> b) -> b -> f a -> T f b
- scanr :: Traversable f => (a -> b -> b) -> b -> f a -> T f b
- class Tails f where
- class Functor f => RemoveEach f where
- removeEach :: T f a -> T f (a, f a)
Documentation
The type T can be used for many kinds of list-like structures
with restrictions on the size.
-
T [] ais a lazy list containing at least one element. -
T (T []) ais a lazy list containing at least two elements. -
T Vector ais a vector with at least one element. You may also use unboxed vectors but the first element will be stored in a box and you will not be able to use many functions from this module. -
T Maybe ais a list that contains one or two elements. -
Maybeis isomorphic toOptional Empty. -
T Empty ais a list that contains exactly one element. -
T (T Empty) ais a list that contains exactly two elements. -
Optional (T Empty) ais a list that contains zero or two elements. - You can create a list type for every finite set of allowed list length
by nesting Optional and NonEmpty constructors.
If list length
nis allowed, then placeOptionalat depthn, if it is disallowed then placeNonEmpty. The maximum length is marked byEmpty.
Instances
| (Monad f, Empty f, Cons f, Append f) => Monad (T f) | |
| Functor f => Functor (T f) | |
| (Applicative f, Empty f, Cons f, Append f) => Applicative (T f) | |
| Foldable f => Foldable (T f) | |
| Traversable f => Traversable (T f) | |
| Arbitrary f => Arbitrary (T f) | |
| Show f => Show (T f) | |
| (Traversable f, Reverse f) => Reverse (T f) | |
| (SortBy f, InsertBy f) => SortBy (T f) | |
| (Sort f, InsertBy f) => Sort (T f) | If you nest too many non-empty lists then the efficient merge-sort (linear-logarithmic runtime) will degenerate to an inefficient insert-sort (quadratic runtime). |
| Iterate f => Iterate (T f) | |
| Repeat f => Repeat (T f) | |
| Zip f => Zip (T f) | |
| (Cons f, Append f) => Append (T f) | |
| Empty f => Singleton (T f) | |
| Snoc f => Snoc (T f) | |
| Cons f => Cons (T f) | |
| Tails f => Tails (T f) | |
| RemoveEach f => RemoveEach (T f) | |
| InsertBy f => InsertBy (T f) | |
| Insert f => Insert (T f) | |
| (Eq a, Eq (f a)) => Eq (T f a) | |
| (Ord a, Ord (f a)) => Ord (T f a) | |
| (Show f, Show a) => Show (T f a) | |
| (Arbitrary a, Arbitrary f) => Arbitrary (T f a) |
snoc :: Traversable f => f a -> a -> T f aSource
viewR :: Traversable f => T f a -> (f a, a)Source
init :: Traversable f => T f a -> f aSource
foldBalanced :: (a -> a -> a) -> T [] a -> aSource
Fold a non-empty list in a balanced way.
Balanced means that each element
has approximately the same depth in the operator tree.
Approximately the same depth means
that the difference between maximum and minimum depth is at most 1.
The accumulation operation must be associative and commutative
in order to get the same result as foldl1 or foldr1.
maximumKey :: (Ord b, Foldable f) => (a -> b) -> T f a -> aSource
maximumKey is a total function
minimumKey :: (Ord b, Foldable f) => (a -> b) -> T f a -> aSource
minimumKey is a total function
appendLeft :: (Append f, Traversable f) => f a -> T f a -> T f aSource
appendRight :: Append f => T f a -> f a -> T f aSource
cycle :: (Cons f, Append f) => T f a -> T f aSource
generic variants:
cycle or better Semigroup.cycle
mapAdjacent :: Traversable f => (a -> a -> b) -> T f a -> f bSource
scanl :: Traversable f => (b -> a -> b) -> b -> f a -> T f bSource
scanr :: Traversable f => (a -> b -> b) -> b -> f a -> T f bSource
class Functor f => RemoveEach f whereSource
Methods
removeEach :: T f a -> T f (a, f a)Source
Instances
| RemoveEach [] | |
| RemoveEach Maybe | |
| RemoveEach T | |
| RemoveEach f => RemoveEach (T f) | |
| RemoveEach f => RemoveEach (T f) |