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

Safe HaskellNone

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) 
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) 

(!:) :: a -> f a -> T f aSource

force :: T f a -> T f aSource

Force immediate generation of Cons.

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

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 bSource

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 aSource

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

cons :: a -> f a -> T f aSource

Synonym for Cons. For symmetry to snoc.

snoc :: Traversable f => f a -> a -> T f aSource

singleton :: Empty f => a -> T f aSource

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

mapHead :: (a -> a) -> T f a -> T f aSource

mapTail :: (f a -> g a) -> T f a -> T g aSource

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 aSource

last :: Foldable f => T f a -> aSource

foldl1 :: Foldable f => (a -> a -> a) -> T f a -> 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.

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

maximum is a total function

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

maximumBy is a total function

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

maximumKey is a total function

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

minimum is a total function

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

minimumBy is a total function

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

minimumKey is a total function

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

sum does not need a zero for initialization

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

product does not need a one for initialization

append :: (Append f, Traversable f) => T f a -> T f a -> T (T f) aSource

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

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

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

class Insert f whereSource

Methods

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

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 aSource

Default implementation for insert based on insertBy.

class Insert f => InsertBy f whereSource

Methods

insertBy :: (a -> a -> Ordering) -> a -> f a -> T f aSource

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 Tails f whereSource

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) 

class Functor f => RemoveEach f whereSource

Methods

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