non-empty-0.1.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 maximm 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) 
Show f => Show (T f) 
(Traversable f, Reverse f) => Reverse (T f) 
(Sort f, Insert f) => Sort (T f) 
Repeat f => Repeat (T f) 
Zip f => Zip (T f) 
(Cons f, Append f) => Append (T f) 
Empty f => Singleton (T f) 
Cons f => Cons (T f) 
Tails f => Tails (T f) 
RemoveEach f => RemoveEach (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 :: View f => f a -> Maybe (T f a)Source

cons :: Cons f => a -> T f 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

init :: (Zip f, Cons f) => T f a -> f aSource

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

foldl1 :: Foldable f => (a -> a -> a) -> T f a -> aSource

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 :: (Cons f, Append f) => T f a -> T f a -> T f aSource

appendLeft :: (Append f, View f, Cons 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

sortBy :: (Sort f, Insert f) => (a -> a -> Ordering) -> T f a -> T f aSource

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

sort :: (Ord a, Sort f, Insert f) => T f a -> T f aSource

class Insert f whereSource

Methods

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

Instances

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

insert :: (Ord a, Insert f, Sort f) => a -> f a -> T f aSource

Insert an element into an ordered list while preserving the order. The first element of the resulting list is returned individually. We need this for construction of a non-empty list.

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

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

transposeClip :: (Traversable f, Zip g, Repeat g) => f (g a) -> g (f a)Source

Always returns a rectangular list by clipping all dimensions to the shortest slice. Be aware that transpose [] == repeat [].

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