tagged-list-1.0: Lists tagged with a type-level natural number representing their length.

Data.List.Tagged

Contents

Synopsis

Tagged lists

data TaggedList n α whereSource

TaggedList is a data structure that represents a linked-list tagged with a phantom type-level natural number representing the length of the list.

Constructors

E :: TaggedList Zero α 
:. :: α -> TaggedList n α -> TaggedList (SuccessorTo n) α 

data UntaggedList α Source

UntaggedList is a wrapper around TaggedList that lets you hide the length tag; the purpose of this is to allow for situations in which you have a tagged list with an unknown length.

Constructors

forall n . UntaggedList (TaggedList n α) 

newtype TL α n Source

TL is a newtype wrapper around a TaggedList which flips the two type arguments; this type was introduced to make it easier to define inductive operations on TaggedLists.

Constructors

TL 

Fields

unwrapTL :: TaggedList n α
 

newtype ATL t α n Source

ATL is a newtype wrapper around some functor of TaggedList which flips the two type arguments; this type was introduced to make it easier to define inductive operations on functors of TaggedLists.

Constructors

ATL 

Fields

unwrapATL :: t (TaggedList n α)
 

Utility functions

append :: TaggedList m α -> TaggedList n α -> TaggedList (Plus m n) αSource

Appends two tagged lists.

(Note: The order of the arguments to Plus is important since append is defined recursively over its *first* argument.)

eqLists :: Eq α => TaggedList m α -> TaggedList n α -> BoolSource

Compares two lists, which may be of different sizes; False is returned if the lists do not have the same size.

extractRightsOrLefts :: TaggedList n (Either α β) -> Either [α] (TaggedList n β)Source

If the input list of Either values has only Rights, then this function returns a tagged list of the same length with the values contained in each Right. Otherwise, this function returns an ordinary list with the values contained in each Left.

fromList :: Induction n => [α] -> TaggedList n αSource

Converts a list to a TaggedList, returning _|_ if the length of the list does not match the length tag of the return type.

fromListAsUntagged :: [α] -> UntaggedList αSource

Converts an arbitrary list to an UntaggedList.

head :: TaggedList (SuccessorTo n) α -> αSource

Returns the head of a tagged list.

Note that unlike its List counterpart, this function never returns _|_ since the existence of at least one element is guaranteed by the type system.

join :: TaggedList m α -> TaggedList n α -> (TaggedList (Plus m n) α, TaggedList (Plus m n) β -> (TaggedList m β, TaggedList n β))Source

Appends two lists together, and returns both the result and a splitter function that allows you to take another list of the same size as the result (though possible of a different type) and split it back into two lists of the sizes of the arguments to this function.

length :: NaturalNumber n => TaggedList n α -> N nSource

Returns the length of the list as a value-level natural number.

map :: (α -> β) -> TaggedList n α -> TaggedList n βSource

Applies a function to every element of the list.

mapM_ :: Monad m => (α -> m β) -> TaggedList n α -> m ()Source

Performs an action for every element in the list and returns ().

replace :: [α] -> TaggedList n β -> TaggedList n αSource

Replaces all of the elements in a given tagged list with the members of an ordinary list, returning _|_ if the length of the list does not match the length tag.

tail :: TaggedList (SuccessorTo n) α -> TaggedList n αSource

Returns the tail of a tagged list.

Note that unlike its List counterpart, this function never returns _|_ since the existence of at least one element is guaranteed by the type system.

toList :: TaggedList n α -> [α]Source

Converts a tagged list to an ordinary list.

withTL :: (TL α n -> TL β n) -> TaggedList n α -> TaggedList n βSource

This is a convenience function for lifting a function on TL to a function on TaggedList.

(Note: TL is just a newtype wrapper around TaggedList that swaps the two type arguments to make it easier to perform inductive operations.)

zipf :: TaggedList n (α -> β) -> TaggedList n α -> TaggedList n βSource

Applies a list of functions to a list of inputs.

Tuple conversion

type family TupleOf n α Source

TupleOf is a type family that maps type-level natural numbers (from N0 to N15) to tuples with the corresponding number of entries.