multi-trie-0.1: Trie of sets, as a model for compound names having multiple values

Safe HaskellSafe
LanguageHaskell98

Data.MultiTrie

Contents

Description

A MultiTrie v d is a trie (i.e. a tree whose child nodes have distinct labels, or atomic names, of type v) with each node containing a list of values of type d that could be considered as a set or a multiset. It represents a multivalued naming with compound names: each path, or a compound name (i.e. a chain of labels) has a (possibly empty) list of values.

The simplest possible MultiTrie is empty that has an empty list of values and no child nodes. Since the only essential feature of a MultiTrie is carrying values, the empty MultiTrie could be equated with an absense of a MultiTrie. In particular, instead of saying that there is no sub-trie under some path in a MultiTrie, let us say that the path points to an empty node. Therefore, every MultiTrie could be considered as infinite, having child nodes under all possible names - and some of the nodes are empty.

Some operations could be defined for MultiTries in a natural way, including filter, union, intersection, cartesian. Obviously, empty is a neutral element of union. Cartesian product is empty if any of the two operands is empty.

A unary function f can be applied to each value in each node of a MultiTrie that results in a map function. Moreover, a MultiTrie can contain not only ordinary values but also functions that makes it possible to apply a MultiTrie of functions to a MultiTrie of argument values, combining results with cartesian. A MultiTrie whose values are, in their turn, MultiTries, can be flattened. This makes MultiTries an instance of Functor, Applicative' and Monad classes.

For a detailed description of the multivalued naming with compound names as a a mathematical notion, its operations and properties, see an article distributed with this package as a LaTeX source.

Synopsis

Type

data MultiTrie v d Source #

A trie consists of a list of values and labelled child tries.

Instances

Ord v => Monad (MultiTrie v) Source # 

Methods

(>>=) :: MultiTrie v a -> (a -> MultiTrie v b) -> MultiTrie v b #

(>>) :: MultiTrie v a -> MultiTrie v b -> MultiTrie v b #

return :: a -> MultiTrie v a #

fail :: String -> MultiTrie v a #

Ord v => Functor (MultiTrie v) Source # 

Methods

fmap :: (a -> b) -> MultiTrie v a -> MultiTrie v b #

(<$) :: a -> MultiTrie v b -> MultiTrie v a #

Ord v => Applicative (MultiTrie v) Source # 

Methods

pure :: a -> MultiTrie v a #

(<*>) :: MultiTrie v (a -> b) -> MultiTrie v a -> MultiTrie v b #

(*>) :: MultiTrie v a -> MultiTrie v b -> MultiTrie v b #

(<*) :: MultiTrie v a -> MultiTrie v b -> MultiTrie v a #

(Ord v, Eq d) => Eq (MultiTrie v d) Source # 

Methods

(==) :: MultiTrie v d -> MultiTrie v d -> Bool #

(/=) :: MultiTrie v d -> MultiTrie v d -> Bool #

(Show v, Show d) => Show (MultiTrie v d) Source # 

Methods

showsPrec :: Int -> MultiTrie v d -> ShowS #

show :: MultiTrie v d -> String #

showList :: [MultiTrie v d] -> ShowS #

Simple constructors

empty :: MultiTrie v d Source #

An empty MultiTrie constant. A neutral element of union and zero of cartesian.

singleton :: d -> MultiTrie v d Source #

A MultiTrie containing just one value in its root and no child nodes.

leaf :: [d] -> MultiTrie v d Source #

A MultiTrie containing the given list in its root and no child nodes.

repeat :: Ord v => [v] -> [d] -> MultiTrie v d Source #

An infinite MultiTrie that has in each node the same list of values and, under each name from the given set, a child identical to the root.

updateValues :: ([d] -> [d]) -> MultiTrie v d -> MultiTrie v d Source #

Change a list in the root node with a function and leave children intact.

addValue :: d -> MultiTrie v d -> MultiTrie v d Source #

Add a new value to the root node's list of values.

Simple selectors

values :: MultiTrie v d -> [d] Source #

List of values in the root node.

children :: MultiTrie v d -> MultiTrieMap v d Source #

Map of atomic names to child sub-tries.

null :: MultiTrie v d -> Bool Source #

Check if a MultiTrie is empty.

size :: MultiTrie v d -> Int Source #

A total number of values in all nodes.

Comparison

areEqualStrict :: (Ord v, Eq d) => MultiTrie v d -> MultiTrie v d -> Bool Source #

Check for equality counting the order of elements.

areEqualWeak :: (Ord v, Eq d) => MultiTrie v d -> MultiTrie v d -> Bool Source #

Check for equality ignoring the order of elements.

areEquivalentUpTo :: (Ord v, Eq d) => ([d] -> [d] -> Bool) -> MultiTrie v d -> MultiTrie v d -> Bool Source #

Check if two MultiTries, t1 and t2, are equivalent up to a custom list equivalence predicate p. True if and only if (1) both MultiTries have non-empty nodes at the same paths and (2) for each such path w, value lists from t1 and t2 under w are equivalent, i.e. satisfy p.

Subnode access

subnode :: Ord v => [v] -> MultiTrie v d -> MultiTrie v d Source #

Select a MultiTrie subnode identified by the given path, or empty if there is no such path.

subnodeUpdate :: Ord v => [v] -> (MultiTrie v d -> MultiTrie v d) -> MultiTrie v d -> MultiTrie v d Source #

Perform the given transformation on a subnode identified by the path.

subnodeAddValue :: Ord v => [v] -> d -> MultiTrie v d -> MultiTrie v d Source #

Add a value to a list of values in a subnode identified by the path.

subnodeReplace :: Ord v => [v] -> MultiTrie v d -> MultiTrie v d -> MultiTrie v d Source #

Replace a subnode identified by the path with a new MultiTrie.

subnodeDelete :: Ord v => [v] -> MultiTrie v d -> MultiTrie v d Source #

Delete a subnode identified by the given path.

subnodeUnite :: Ord v => [v] -> MultiTrie v d -> MultiTrie v d -> MultiTrie v d Source #

Unite a subnode identified by the path with another MultiTrie.

subnodeIntersect :: (Ord v, Eq d) => [v] -> MultiTrie v d -> MultiTrie v d -> MultiTrie v d Source #

Intersect a subnode identified by the path with another MultiTrie.

Filtration

filter :: Ord v => (d -> Bool) -> MultiTrie v d -> MultiTrie v d Source #

Leave only those values that satisfy the predicate p.

project :: Ord v => [[v]] -> MultiTrie v d -> MultiTrie v d Source #

Leave only the nodes whose compound names are in the given list.

filterOnNames :: Ord v => ([v] -> Bool) -> MultiTrie v d -> MultiTrie v d Source #

Leave only those nodes whose compound names satisfy the predicate p.

filterWithNames :: Ord v => ([v] -> d -> Bool) -> MultiTrie v d -> MultiTrie v d Source #

Leave only those values that, with their compound names, satisfy the predicate p.

Mappings

map :: Ord v => (d1 -> d2) -> MultiTrie v d1 -> MultiTrie v d2 Source #

Map a function over all values in a MultiTrie.

mapWithName :: Ord v => ([v] -> d1 -> d2) -> MultiTrie v d1 -> MultiTrie v d2 Source #

Map a function over all values with their compound names.

mapMany :: Ord v => [d1 -> d2] -> MultiTrie v d1 -> MultiTrie v d2 Source #

Apply a list of functions to all values in a MultiTrie.

mapManyWithName :: Ord v => [[v] -> d1 -> d2] -> MultiTrie v d1 -> MultiTrie v d2 Source #

Apply a list of functions to each value and its compound name.

mapOnLists :: Ord v => ([d1] -> [d2]) -> MultiTrie v d1 -> MultiTrie v d2 Source #

Map a function over entire lists contained in nodes.

mapOnListsWithName :: Ord v => ([v] -> [d1] -> [d2]) -> MultiTrie v d1 -> MultiTrie v d2 Source #

Map a function over entire lists in all nodes, with their compound names.

High-level operations

cartesian :: Ord v => MultiTrie v d1 -> MultiTrie v d2 -> MultiTrie v (d1, d2) Source #

Cartesian product of two MultiTries, t1 and t2. The resulting MultiTrie consists of all possible pairs (x1, x2) under a concatenated name v1 ++ v2 where x1 is a value in t1 under a name v1, and x2 is a value from t2 under the name v2.

union :: Ord v => MultiTrie v d -> MultiTrie v d -> MultiTrie v d Source #

Union of MultiTries.

unions :: Ord v => [MultiTrie v d] -> MultiTrie v d Source #

Union of a list of MultiTries.

intersection :: (Ord v, Eq d) => MultiTrie v d -> MultiTrie v d -> MultiTrie v d Source #

Intersection of MultiTries.

intersections1 :: (Ord v, Eq d) => [MultiTrie v d] -> MultiTrie v d Source #

Intersection of a non-empty list of MultiTries.

flatten :: Ord v => MultiTrie v (MultiTrie v d) -> MultiTrie v d Source #

Flatten a MultiTrie whose values are, in their turn, MultiTries.

Applications

apply :: Ord v => MultiTrie v (d1 -> d2) -> MultiTrie v d1 -> MultiTrie v d2 Source #

Given a MultiTrie t1 of functions and a MultiTrie t2 of values, for all compound names v1 and v2, apply each function named by v1 in t1 to each value named by v2 in t2 and put the result into a new MultiTrie under a name v1 ++ v2.

bind :: Ord v => MultiTrie v d1 -> (d1 -> MultiTrie v d2) -> MultiTrie v d2 Source #

Given a MultiTrie t of values and a function f that maps an arbitrary value to a MultiTrie, apply the function f to each value from t and flatten the result.

Conversions

toMap :: Ord v => MultiTrie v d -> Map [v] [d] Source #

Convert a MultiTrie t to a Map of compound names into value lists.

toList :: Ord v => MultiTrie v d -> [([v], d)] Source #

Convert a MultiTrie to a list of path-value pairs.

fromList :: Ord v => [([v], d)] -> MultiTrie v d Source #

Convert a list of path-value pairs to a MultiTrie.

fromMaybe :: Maybe (MultiTrie v d) -> MultiTrie v d Source #

Map Nothing to empty and Just t to t.

toMaybe :: MultiTrie v d -> Maybe (MultiTrie v d) Source #

Map empty to Nothing and a non-empty t to Just t.

Debug

draw :: (Show v, Show [d]) => MultiTrie v d -> String Source #

Convert a MultiTrie into an ASCII-drawn tree.

Other

listAsMultiSetEquals :: Eq a => [a] -> [a] -> Bool Source #

Check if two lists are equal as multisets, i.e. if they have equal numbers of equal values.

areMapsEquivalentUpTo :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool Source #

Decide if maps are equivalent up to a custom value equivalence predicate. True if and only if the maps have exactly the same names and, for each name, its values in the two maps are equivalent. Map is missing this.