| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Data.NonEmpty
Synopsis
- 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
- foldl1Map :: Foldable f => (b -> b -> b) -> (a -> b) -> T f a -> b
- foldBalanced :: (a -> a -> a) -> T [] a -> a
- foldBalancedStrict :: (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
- chop :: (a -> Bool) -> [a] -> T [] [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
- tails :: (Traversable f, Cons g, Empty g) => f a -> T f (g a)
- inits :: (Traversable f, Snoc g, Empty g) => f a -> T f (g a)
- initsRev :: (Traversable f, Cons g, Empty g, Reverse g) => f a -> T f (g a)
- removeEach :: Traversable f => T f a -> T f (a, f a)
- partitionEithersLeft :: T [] (Either a b) -> Either (T [] a) ([a], T [] b)
- partitionEithersRight :: T [] (Either a b) -> Either (T [] a, [b]) (T [] b)
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 to- Optional 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) Source # | |
| Functor f => Functor (T f) Source # | |
| (Applicative f, Empty f, Cons f, Append f) => Applicative (T f) Source # | |
| Foldable f => Foldable (T f) Source # | |
| Defined in Data.NonEmptyPrivate Methods fold :: Monoid m => T f m -> m # foldMap :: Monoid m => (a -> m) -> T f a -> m # foldMap' :: Monoid m => (a -> m) -> T f a -> m # foldr :: (a -> b -> b) -> b -> T f a -> b # foldr' :: (a -> b -> b) -> b -> T f a -> b # foldl :: (b -> a -> b) -> b -> T f a -> b # foldl' :: (b -> a -> b) -> b -> T f a -> b # foldr1 :: (a -> a -> a) -> T f a -> a # foldl1 :: (a -> a -> a) -> T f a -> a # elem :: Eq a => a -> T f a -> Bool # maximum :: Ord a => T f a -> a # | |
| Traversable f => Traversable (T f) Source # | |
| NFData f => NFData (T f) Source # | |
| Gen f => Gen (T f) Source # | |
| Arbitrary f => Arbitrary (T f) Source # | |
| Show f => Show (T f) Source # | |
| (Traversable f, Reverse f) => Reverse (T f) Source # | |
| (SortBy f, InsertBy f) => SortBy (T f) Source # | |
| (Sort f, InsertBy f) => Sort (T f) Source # | 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) Source # | |
| Defined in Data.NonEmptyPrivate | |
| Repeat f => Repeat (T f) Source # | |
| Defined in Data.NonEmptyPrivate | |
| Zip f => Zip (T f) Source # | |
| (Cons f, Append f) => Append (T f) Source # | |
| Empty f => Singleton (T f) Source # | |
| Defined in Data.NonEmptyPrivate | |
| ViewL f => ViewL (T f) Source # | Caution:
 This instance mainly exist to allow cascaded applications of  | 
| Snoc f => Snoc (T f) Source # | |
| Cons f => Cons (T f) Source # | |
| InsertBy f => InsertBy (T f) Source # | |
| Insert f => Insert (T f) Source # | |
| Choose f => Choose (T f) Source # | |
| Defined in Data.NonEmpty.Mixed | |
| (Eq a, Eq (f a)) => Eq (T f a) Source # | |
| (Ord a, Ord (f a)) => Ord (T f a) Source # | |
| (Show f, Show a) => Show (T f a) Source # | |
| (Arbitrary a, Arbitrary f) => Arbitrary (T f a) Source # | |
| (NFData f, NFData a) => NFData (T f a) Source # | |
| Defined in Data.NonEmptyPrivate | |
snoc :: Traversable f => f a -> a -> T f a Source #
viewR :: Traversable f => T f a -> (f a, a) Source #
init :: Traversable f => T f a -> f a Source #
foldBalanced :: (a -> a -> a) -> T [] a -> a Source #
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.
foldBalancedStrict :: (a -> a -> a) -> T [] a -> a Source #
appendLeft :: (Append f, Traversable f) => f a -> T f a -> T f a infixr 5 Source #
cycle :: (Cons f, Append f) => T f a -> T f a Source #
generic variants:
cycle or better Semigroup.cycle
mapAdjacent :: Traversable f => (a -> a -> b) -> T f a -> f b Source #
Methods
insert :: Ord a => a -> f a -> T f a Source #
Insert an element into an ordered list while preserving the order.
scanl :: Traversable f => (b -> a -> b) -> b -> f a -> T f b Source #
scanr :: Traversable f => (a -> b -> b) -> b -> f a -> T f b Source #
inits :: (Traversable f, Snoc g, Empty g) => f a -> T f (g a) Source #
Only advised for structures with efficient appending of single elements
like Sequence.
Alternatively you may consider initsRev.
removeEach :: Traversable f => T f a -> T f (a, f a) Source #
partitionEithersLeft :: T [] (Either a b) -> Either (T [] a) ([a], T [] b) Source #
\xs -> mapMaybe EitherHT.maybeLeft (NonEmpty.flatten xs) == either NonEmpty.flatten fst (NonEmpty.partitionEithersLeft (xs::NonEmpty.T[](Either Char Int)))
\xs -> mapMaybe EitherHT.maybeRight (NonEmpty.flatten xs) == either (const []) (NonEmpty.flatten . snd) (NonEmpty.partitionEithersLeft (xs::NonEmpty.T[](Either Char Int)))
\xs -> NonEmpty.partitionEithersRight (fmap EitherHT.swap xs) == EitherHT.mapLeft swap (EitherHT.swap (NonEmpty.partitionEithersLeft (xs::NonEmpty.T[](Either Char Int))))