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

Safe HaskellSafe-Inferred
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

head :: a
 
tail :: f a
 

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) 
ViewL f => ViewL (T f)

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.

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) 
Choose f => Choose (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) 

(!:) :: 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.

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

Methods

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

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

Instances

Insert [] 
Insert Maybe 
Insert Seq 
Insert T 
Insert f => Insert (T f) 
Insert f => Insert (T f) 

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

Methods

insertBy :: (a -> a -> Ordering) -> a -> f a -> 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

class Tails f where Source

Methods

tails :: (Cons g, Empty g) => f a -> T f (g a) Source

Instances

Tails [] 
Tails Maybe 
Tails Seq 
Tails T 
Tails f => Tails (T f) 
Tails f => Tails (T f) 

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

class Functor f => RemoveEach f where Source

Methods

removeEach :: T f a -> T f (a, f a) Source