non-empty-0.3: List-like structures with static restrictions on the number of elements

Safe HaskellSafe
LanguageHaskell98

Data.NonEmpty

Synopsis

Documentation

data T f a Source #

The type T can be used for many kinds of list-like structures with restrictions on the size.

  • T [] a is a lazy list containing at least one element.
  • T (T []) a is a lazy list containing at least two elements.
  • T Vector a is 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 a is a list that contains one or two elements.
  • Maybe is isomorphic to Optional Empty.
  • T Empty a is a list that contains exactly one element.
  • T (T Empty) a is a list that contains exactly two elements.
  • Optional (T Empty) a is 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 n is allowed, then place Optional at depth n, if it is disallowed then place NonEmpty. The maximum length is marked by Empty.

Constructors

Cons 

Fields

Instances

(Monad f, Empty f, Cons f, Append f) => Monad (T f) Source # 

Methods

(>>=) :: T f a -> (a -> T f b) -> T f b #

(>>) :: T f a -> T f b -> T f b #

return :: a -> T f a #

fail :: String -> T f a #

Functor f => Functor (T f) Source # 

Methods

fmap :: (a -> b) -> T f a -> T f b #

(<$) :: a -> T f b -> T f a #

(Applicative f, Empty f, Cons f, Append f) => Applicative (T f) Source # 

Methods

pure :: a -> T f a #

(<*>) :: T f (a -> b) -> T f a -> T f b #

(*>) :: T f a -> T f b -> T f b #

(<*) :: T f a -> T f b -> T f a #

Foldable f => Foldable (T f) Source # 

Methods

fold :: Monoid m => T f m -> 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 #

toList :: T f a -> [a] #

null :: T f a -> Bool #

length :: T f a -> Int #

elem :: Eq a => a -> T f a -> Bool #

maximum :: Ord a => T f a -> a #

minimum :: Ord a => T f a -> a #

sum :: Num a => T f a -> a #

product :: Num a => T f a -> a #

Traversable f => Traversable (T f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> T f a -> f (T f b) #

sequenceA :: Applicative f => T f (f a) -> f (T f a) #

mapM :: Monad m => (a -> m b) -> T f a -> m (T f b) #

sequence :: Monad m => T f (m a) -> m (T f a) #

NFData f => NFData (T f) Source # 

Methods

rnf :: NFData a => T f a -> () Source #

Arbitrary f => Arbitrary (T f) Source # 

Methods

arbitrary :: Arbitrary a => Gen (T f a) Source #

shrink :: Arbitrary a => T f a -> [T f a] Source #

Show f => Show (T f) Source # 

Methods

showsPrec :: Show a => Int -> T f a -> ShowS Source #

(Traversable f, Reverse f) => Reverse (T f) Source # 

Methods

reverse :: T f a -> T f a Source #

(SortBy f, InsertBy f) => SortBy (T f) Source # 

Methods

sortBy :: (a -> a -> Ordering) -> T f a -> T f a 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).

Methods

sort :: Ord a => T f a -> T f a Source #

Iterate f => Iterate (T f) Source # 

Methods

iterate :: (a -> a) -> a -> T f a Source #

Repeat f => Repeat (T f) Source # 

Methods

repeat :: a -> T f a Source #

Zip f => Zip (T f) Source # 

Methods

zipWith :: (a -> b -> c) -> T f a -> T f b -> T f c Source #

(Cons f, Append f) => Append (T f) Source # 

Methods

append :: T f a -> T f a -> T f a Source #

Empty f => Singleton (T f) Source # 

Methods

singleton :: a -> T f a Source #

ViewL f => ViewL (T f) Source #

Caution: viewL (NonEmpty.Cons x []) = Nothing because the tail is empty, and thus cannot be NonEmpty!

This instance mainly exist to allow cascaded applications of fetch.

Methods

viewL :: T f a -> Maybe (a, T f a) Source #

Snoc f => Snoc (T f) Source # 

Methods

snoc :: T f a -> a -> T f a Source #

Cons f => Cons (T f) Source # 

Methods

cons :: a -> T f a -> T f a Source #

InsertBy f => InsertBy (T f) Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> T f a -> T (T f) a Source #

Insert f => Insert (T f) Source # 

Methods

insert :: Ord a => a -> T f a -> T (T f) a Source #

Choose f => Choose (T f) Source # 

Methods

choose :: [a] -> [T f a] Source #

(Eq a, Eq (f a)) => Eq (T f a) Source # 

Methods

(==) :: T f a -> T f a -> Bool #

(/=) :: T f a -> T f a -> Bool #

(Ord a, Ord (f a)) => Ord (T f a) Source # 

Methods

compare :: T f a -> T f a -> Ordering #

(<) :: T f a -> T f a -> Bool #

(<=) :: T f a -> T f a -> Bool #

(>) :: T f a -> T f a -> Bool #

(>=) :: T f a -> T f a -> Bool #

max :: T f a -> T f a -> T f a #

min :: T f a -> T f a -> T f a #

(Show f, Show a) => Show (T f a) Source # 

Methods

showsPrec :: Int -> T f a -> ShowS #

show :: T f a -> String #

showList :: [T f a] -> ShowS #

(Arbitrary a, Arbitrary f) => Arbitrary (T f a) Source # 

Methods

arbitrary :: Gen (T f a) #

shrink :: T f a -> [T f a] #

(NFData f, NFData a) => NFData (T f a) Source # 

Methods

rnf :: T f a -> () #

(!:) :: a -> f a -> T f a infixr 5 Source #

force :: T f a -> T f a Source #

Force immediate generation of Cons.

apply :: (Applicative f, Cons f, Append f) => T f (a -> b) -> T f a -> T f b Source #

Implementation of <*> without the Empty constraint that is needed for pure.

bind :: (Monad f, Cons f, Append f) => T f a -> (a -> T f b) -> T f b Source #

Implementation of >>= without the Empty constraint that is needed for return.

toList :: Foldable f => T f a -> [a] Source #

flatten :: Cons f => T f a -> f a Source #

fetch :: ViewL f => f a -> Maybe (T f a) Source #

cons :: a -> f a -> T f a Source #

Synonym for Cons. For symmetry to snoc.

snoc :: Traversable f => f a -> a -> T f a Source #

singleton :: Empty f => a -> T f a Source #

reverse :: (Traversable f, Reverse f) => T f a -> T f a Source #

mapHead :: (a -> a) -> T f a -> T f a Source #

mapTail :: (f a -> g a) -> T f a -> T g a Source #

viewL :: T f a -> (a, f a) Source #

viewR :: Traversable f => T f a -> (f a, a) Source #

init :: Traversable f => T f a -> f a Source #

last :: Foldable f => T f a -> a Source #

foldl1 :: Foldable f => (a -> a -> a) -> T f a -> a Source #

foldl1Map :: Foldable f => (b -> b -> b) -> (a -> b) -> T f a -> b Source #

It holds:

foldl1Map f g = foldl1 f . fmap g

but foldl1Map does not need a Functor instance.

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 #

maximum :: (Ord a, Foldable f) => T f a -> a Source #

maximum is a total function

maximumBy :: Foldable f => (a -> a -> Ordering) -> T f a -> a Source #

maximumBy is a total function

maximumKey :: (Ord b, Foldable f) => (a -> b) -> T f a -> a Source #

maximumKey is a total function

minimum :: (Ord a, Foldable f) => T f a -> a Source #

minimum is a total function

minimumBy :: Foldable f => (a -> a -> Ordering) -> T f a -> a Source #

minimumBy is a total function

minimumKey :: (Ord b, Foldable f) => (a -> b) -> T f a -> a Source #

minimumKey is a total function

sum :: (Num a, Foldable f) => T f a -> a Source #

sum does not need a zero for initialization

product :: (Num a, Foldable f) => T f a -> a Source #

product does not need a one for initialization

append :: (Append f, Traversable f) => T f a -> T f a -> T (T f) a infixr 5 Source #

appendLeft :: (Append f, Traversable f) => f a -> T f a -> T f a infixr 5 Source #

appendRight :: Append f => T f a -> 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

zipWith :: Zip f => (a -> b -> c) -> T f a -> T f b -> T f c Source #

mapAdjacent :: Traversable f => (a -> a -> b) -> T f a -> f b Source #

class Insert f where Source #

Minimal complete definition

insert

Methods

insert :: Ord a => a -> f a -> T f a Source #

Insert an element into an ordered list while preserving the order.

Instances

Insert [] Source # 

Methods

insert :: Ord a => a -> [a] -> T [] a Source #

Insert Maybe Source # 

Methods

insert :: Ord a => a -> Maybe a -> T Maybe a Source #

Insert Seq Source # 

Methods

insert :: Ord a => a -> Seq a -> T Seq a Source #

Insert T Source # 

Methods

insert :: Ord a => a -> T a -> T T a Source #

Insert f => Insert (T f) Source # 

Methods

insert :: Ord a => a -> T f a -> T (T f) a Source #

Insert f => Insert (T f) Source # 

Methods

insert :: Ord a => a -> T f a -> T (T f) a Source #

insertDefault :: (Ord a, InsertBy f, SortBy f) => a -> f a -> T f a Source #

Default implementation for insert based on insertBy.

class Insert f => InsertBy f where Source #

Minimal complete definition

insertBy

Methods

insertBy :: (a -> a -> Ordering) -> a -> f a -> T f a Source #

Instances

InsertBy [] Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> [a] -> T [] a Source #

InsertBy Maybe Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> Maybe a -> T Maybe a Source #

InsertBy Seq Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> Seq a -> T Seq a Source #

InsertBy T Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> T a -> T T a Source #

InsertBy f => InsertBy (T f) Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> T f a -> T (T f) a Source #

InsertBy f => InsertBy (T f) Source # 

Methods

insertBy :: (a -> a -> Ordering) -> a -> T f a -> T (T f) a Source #

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 #

tails :: (Traversable f, Cons g, Empty g) => f a -> T f (g a) 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.

initsRev :: (Traversable f, Cons g, Empty g, Reverse g) => f a -> T f (g a) Source #

removeEach :: Traversable f => T f a -> T f (a, f a) Source #