% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(rbtrees): Red black trees} \label{sec:rbtrees} \begin{tags} \tag{author} Vitor Santos Costa, Jan Wielemaker, Samer Abdallah, Peter Ludemann.\mtag{See also}- \file{library(pairs)}, \file{library(assoc)} \\- "Introduction to Algorithms", Second Edition Cormen, Leiserson, Rivest, and Stein, MIT Press \end{tags} Red-Black trees are balanced search binary trees. They are named because nodes can be classified as either red or black. The code we include is based on "Introduction to Algorithms", second edition, by Cormen, Leiserson, Rivest and Stein. The library includes routines to insert, lookup and delete elements in the tree. A Red black tree is represented as a term \verb$t(Nil, Tree)$, where Nil is the Nil-node, a node shared for each nil-node in the tree. Any node has the form \verb$colour(Left, Key, Value, Right)$, where \textit{colour} is one of \const{red} or \const{black}. \textbf{Warning: instantiation of keys} Red-Black trees depend on the Prolog \textit{standard order of terms} to organize the keys as a (balanced) binary tree. This implies that any term may be used as a key. The tree may produce wrong results, such as not being able to find a key, if the ordering of keys changes after the key has been inserted into the tree. The user is responsible to ensure that variables used as keys or appearing in a term used as key that may affect ordering are not unified, with the exception of unification against new fresh variables. For this reason, \textit{ground} terms are safe keys. When using non-ground terms, either make sure the variables appear in places that do not affect the standard order relative to other keys in the tree or make sure to not unify against these variables as long as the tree is being used.\vspace{0.7cm} \begin{description} \predicate[det]{rb_new}{1}{-Tree} Create a new Red-Black tree \arg{Tree}. \begin{tags} \tag{deprecated} Use \predref{rb_empty}{1}. \end{tags} \predicate[semidet]{rb_empty}{1}{?Tree} Succeeds if \arg{Tree} is an empty Red-Black tree. \predicate[semidet]{rb_lookup}{3}{+Key, -Value, +Tree} True when \arg{Value} is associated with \arg{Key} in the Red-Black tree \arg{Tree}. The given \arg{Key} may include variables, in which case the RB tree is searched for a key with equivalent variables (using (\Sequal{})/2). Time complexity is O(log N) in the number of elements in the tree. \begin{tags} \tag{See also} \predref{rb_in}{3} for backtracking over keys. \end{tags} \predicate[semidet]{rb_min}{3}{+Tree, -Key, -Value} \arg{Key} is the minimum key in \arg{Tree}, and is associated with Val. \predicate[semidet]{rb_max}{3}{+Tree, -Key, -Value} \arg{Key} is the maximal key in \arg{Tree}, and is associated with Val. \predicate[semidet]{rb_next}{4}{+Tree, +Key, -Next, -Value} \arg{Next} is the next element after \arg{Key} in \arg{Tree}, and is associated with Val. Fails if \arg{Key} isn't in \arg{Tree} or if \arg{Key} is the maximum key. \predicate[semidet]{rb_previous}{4}{+Tree, +Key, -Previous, -Value} \arg{Previous} is the previous element after \arg{Key} in \arg{Tree}, and is associated with Val. Fails if \arg{Key} isn't in \arg{Tree} or if \arg{Key} is the minimum key. \predicate[semidet]{rb_update}{4}{+Tree, +Key, ?NewVal, -NewTree} \arg{Tree} \arg{NewTree} is tree \arg{Tree}, but with value for \arg{Key} associated with \arg{NewVal}. Fails if \arg{Key} is not in \arg{Tree} (using (\Sequal{})/2). This predicate may fail or give unexpected results if \arg{Key} is not sufficiently instantiated. \begin{tags} \tag{See also} \predref{rb_in}{3} for backtracking over keys. \end{tags} \predicate[semidet]{rb_update}{5}{+Tree, +Key, -OldVal, ?NewVal, -NewTree} Same as \verb$rb_update(Tree, Key, NewVal, NewTree)$ but also unifies \arg{OldVal} with the value associated with \arg{Key} in \arg{Tree}. \predicate[semidet]{rb_apply}{4}{+Tree, +Key, :G, -NewTree} If the value associated with key \arg{Key} is Val0 in \arg{Tree}, and if \verb$call(G,Val0,ValF)$ holds, then \arg{NewTree} differs from \arg{Tree} only in that \arg{Key} is associated with value ValF in tree \arg{NewTree}. Fails if it cannot find \arg{Key} in \arg{Tree}, or if \verb$call(G,Val0,ValF)$ is not satisfiable. \predicate[nondet]{rb_in}{3}{?Key, ?Value, +Tree} True when \arg{Key}-\arg{Value} is a key-value pair in red-black tree \arg{Tree}. Same as below, but does not materialize the pairs. \begin{code} rb_visit(Tree, Pairs), member(Key-Value, Pairs) \end{code} Leaves a choicepoint even if \arg{Key} is instantiated; to avoid a choicepoint, use \predref{rb_lookup}{3}. \predicate[det]{rb_insert}{4}{+Tree, +Key, ?Value, -NewTree} Add an element with key \arg{Key} and \arg{Value} to the tree \arg{Tree} creating a new red-black tree \arg{NewTree}. If \arg{Key} is a key in \arg{Tree}, the associated value is replaced by \arg{Value}. See also \predref{rb_insert_new}{4}. Does \textit{not} validate that \arg{Key} is sufficiently instantiated to ensure the tree remains valid if a key is further instantiated. \predicate[semidet]{rb_insert_new}{4}{+Tree, +Key, ?Value, -NewTree} Add a new element with key \arg{Key} and \arg{Value} to the tree \arg{Tree} creating a new red-black tree \arg{NewTree}. Fails if \arg{Key} is a key in \arg{Tree}. Does \textit{not} validate that \arg{Key} is sufficiently instantiated to ensure the tree remains valid if a key is further instantiated. \predicate{rb_delete}{3}{+Tree, +Key, -NewTree} Delete element with key \arg{Key} from the tree \arg{Tree}, returning the value Val associated with the key and a new tree \arg{NewTree}. Fails if \arg{Key} is not in \arg{Tree} (using (\Sequal{})/2). \begin{tags} \tag{See also} \predref{rb_in}{3} for backtracking over keys. \end{tags} \predicate{rb_delete}{4}{+Tree, +Key, -Val, -NewTree} Same as \verb$rb_delete(Tree, Key, NewTree)$, but also unifies \arg{Val} with the value associated with \arg{Key} in \arg{Tree}. \predicate{rb_del_min}{4}{+Tree, -Key, -Val, -NewTree} Delete the least element from the tree \arg{Tree}, returning the key \arg{Key}, the value \arg{Val} associated with the key and a new tree \arg{NewTree}. Fails if \arg{Tree} is empty. \predicate{rb_del_max}{4}{+Tree, -Key, -Val, -NewTree} Delete the largest element from the tree \arg{Tree}, returning the key \arg{Key}, the value \arg{Val} associated with the key and a new tree \arg{NewTree}. Fails if \arg{Tree} is empty. \predicate[det]{rb_visit}{2}{+Tree, -Pairs} \arg{Pairs} is an infix visit of tree \arg{Tree}, where each element of \arg{Pairs} is of the form Key-Value. \predicate[semidet]{rb_map}{2}{+T, :Goal} True if \verb$call(Goal, Value)$ is true for all nodes in \arg{T}. \predicate[semidet]{rb_map}{3}{+Tree, :G, -NewTree} For all nodes Key in the tree \arg{Tree}, if the value associated with key Key is Val0 in tree \arg{Tree}, and if \verb$call(G,Val0,ValF)$ holds, then the value associated with Key in \arg{NewTree} is ValF. Fails if \verb$call(G,Val0,ValF)$ is not satisfiable for all Val0. If \arg{G} is non-deterministic, \predref{rb_map}{3} will backtrack over all possible values from \verb$call(G,Val0,ValF)$. You should not depend on the order of tree traversal (currently: key order). \predicate{rb_fold}{4}{:Goal, +Tree, +State0, -State} Fold the given predicate over all the key-value pairs in \arg{Tree}, starting with initial state \arg{State0} and returning the final state \arg{State}. Pred is called as \begin{code} call(Pred, Key-Value, State1, State2) \end{code} Determinism depends on \arg{Goal}. \predicate[det]{rb_clone}{3}{+TreeIn, -TreeOut, -Pairs} `Clone' the red-back tree \arg{TreeIn} into a new tree \arg{TreeOut} with the same keys as the original but with all values set to unbound values. \arg{Pairs} is a list containing all new nodes as pairs K-V. \predicate{rb_partial_map}{4}{+Tree, +Keys, :G, -NewTree} For all nodes Key in \arg{Keys}, if the value associated with key Key is Val0 in tree \arg{Tree}, and if \verb$call(G,Val0,ValF)$ holds, then the value associated with Key in \arg{NewTree} is ValF, otherwise it is the value associated with the key in \arg{Tree}. Fails if Key isn't in \arg{Tree} or if \verb$call(G,Val0,ValF)$ is not satisfiable for all Val0 in \arg{Keys}. Assumes keys are sorted and not repeated (fails if this is not true). \predicate[det]{rb_keys}{2}{+Tree, -Keys} \arg{Keys} is unified with an ordered list of all keys in the Red-Black tree \arg{Tree}. \predicate[det]{list_to_rbtree}{2}{+List, -Tree} \arg{Tree} is the red-black tree corresponding to the mapping in \arg{List}, which should be a list of Key-Value pairs. \arg{List} should not contain more than one entry for each distinct key, but this is not validated by \predref{list_to_rbtree}{2}. \predicate[det]{ord_list_to_rbtree}{2}{+List, -Tree} \arg{Tree} is the red-black tree corresponding to the mapping in list \arg{List}, which should be a list of Key-Value pairs. \arg{List} should not contain more than one entry for each distinct key, but this is not validated by \predref{ord_list_to_rbtree}{2}. \arg{List} is assumed to be sorted according to the standard order of terms. \predicate[det]{rb_size}{2}{+Tree, -Size} \arg{Size} is the number of elements in \arg{Tree}. \predicate[semidet]{is_rbtree}{1}{@Term} True if \arg{Term} is a valid Red-Black tree. Processes the entire tree, checking the coloring of the nodes, the balance and the ordering of keys. Does \textit{not} validate that keys are sufficiently instantiated to ensure the tree remains valid if a key is further instantiated. \end{description}