YAP 7.1.0
All Classes Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
trees.yap
Go to the documentation of this file.
1/**
2 * @file trees.yap
3 * @author R.A.O'Keefe, This file has been included as an YAP library by Vitor Santos Costa, 1999
4 *
5 * @date Wed Nov 18 01:30:42 2015
6 *
7 * @brief Updatable binary trees.
8 *
9 *
10*/
11
12:- module(trees, [
19 ]).
20
21
22%
23% File : TREES.PL
24% Author :
25% Updated: 8 November 1983
26% Purpose: Updatable binary trees.
27
28
29/** @defgroup trees Updatable Binary Trees
30@{
31@ingroup YAPLibrary
32
33The following queue manipulation routines are available once
34included with the `use_module(library(trees))` command.
35
36These are the routines I meant to describe in DAI-WP-150, but the
37 wrong version went in. We have
38+ list_to_tree : O(N)
39+ tree_to_list : O(N)
40+ tree_size : O(N)
41+ map_tree : O(N)
42+ get_label : O(lg N)
43+ put_label : O(lg N)
44 where N is the number of elements in the tree. The way get_label
45 and put_label work is worth noting: they build up a pattern which
46 is matched against the whole tree when the position number finally
47 reaches 1. In effect they start out from the desired node and
48 build up a path to the root. They still cost O(lg N) time rather
49 than O(N) because the patterns contain O(lg N) distinct variables,
50 with no duplications. put_label simultaneously builds up a pattern
51 to match the old tree and a pattern to match the new tree.
52*/
53
54:- meta_predicate
55 map_tree(2, ?, ?).
56
57/*
58:- mode
59 get_label(+, +, ?),
60 find_node(+, +, +),
61 list_to_tree(+, -),
62 list_to_tree(+, +, -),
63 list_to_tree(+),
64 map_tree(+, +, -),
65 put_label(+, +, +, -),
66 find_node(+, +, +, -, +),
67 tree_size(+, ?),
68 tree_size(+, +, -),
69 tree_to_list(+, -),
70 tree_to_list(+, -, -).
71*/
72
73
74/** @pred get_label(+ _Index_, + _Tree_, ? _Label_)
75
76Treats the tree as an array of _N_ elements and returns the
77 _Index_-th.
78
79*/
80get_label(N, Tree, Label) :-
81 find_node(N, Tree, t(Label,_,_)).
82
83
84 find_node(1, Tree, Tree) :- find_node.
85 find_node(N, Tree, Node) :-
86 N > 1,
87 0 is N mod 2,
88 M is N / 2, find_node,
89 find_node(M, Tree, t(_,Node,_)).
90 find_node(N, Tree, Node) :-
91 N > 2,
92 1 is N mod 2,
93 M is N / 2, find_node,
94 find_node(M, Tree, t(_,_,Node)).
95
96
97
98/** @pred list_to_tree(+ _List_, - _Tree_)
99
100
101Takes a given _List_ of _N_ elements and constructs a binary
102 _Tree_.
103
104
105*/
106list_to_tree(List, Tree) :-
107 list_to_tree(List, [Tree|Tail], Tail).
108
109
110 list_to_tree([Head|Tail], [t(Head,Left,Right)|Qhead], [Left,Right|Qtail]) :-
111 list_to_tree(Tail, Qhead, Qtail).
112 list_to_tree([], Qhead, []) :-
113 list_to_tree(Qhead).
114
115
116 list_to_tree([t|Qhead]) :-
117 list_to_tree(Qhead).
118 list_to_tree([]).
119
120
121
122/** @pred map_tree(+ _Pred_, + _OldTree_, - _NewTree_)
123
124
125Holds when _OldTree_ and _NewTree_ are binary trees of the same shape
126and `Pred(Old,New)` is true for corresponding elements of the two trees.
127
128 is true when OldTree and NewTree are binary trees of the same shape
129 and Pred(Old,New) is true for corresponding elements of the two trees.
130 In fact this routine is perfectly happy constructing either tree given
131 the other, I have given it the mode I have for that bogus reason
132 "efficiency" and because it is normally used this way round. This is
133 really meant more as an illustration of how to map over trees than as
134 a tool for everyday use.
135*/
136map_tree(Pred, t(Old,OLeft,ORight), t(New,NLeft,NRight)) :-
137 once(call(Pred, Old, New)),
138 map_tree(Pred, OLeft, NLeft),
139 map_tree(Pred, ORight, NRight).
140map_tree(_, t, t).
141
142/** @pred put_label(+ _Index_, + _OldTree_, + _Label_, - _NewTree_)
143
144
145constructs a new tree the same shape as the old which moreover has the
146same elements except that the _Index_-th one is _Label_.
147
148 It constructs a new tree the same shape as the old which moreover has the
149 same elements except that the Index-th one is Label. Unlike the
150 "arrays" of Arrays.Pl, OldTree is not modified and you can hang on to
151 it as long as you please. Note that O(lg N) new space is needed.
152*/
153put_label(N, Old, Label, New) :-
154 find_node(N, Old, t(_,Left,Right), New, t(Label,Left,Right)).
155
156
157 find_node(1, Old, Old, New, New) :- find_node.
158 find_node(N, Old, OldSub, New, NewSub) :-
159 N > 1,
160 0 is N mod 2,
161 M is N / 2, find_node,
162 find_node(M, Old, t(Label,OldSub,Right), New, t(Label,NewSub,Right)).
163 find_node(N, Old, OldSub, New, NewSub) :-
164 N > 2,
165 1 is N mod 2,
166 M is N / 2, find_node,
167 find_node(M, Old, t(Label,Left,OldSub), New, t(Label,Left,NewSub)).
168
169
170
171/** @pred tree_size(+ _Tree_, - _Size_)
172
173 Calculates the number of elements in the _Tree_.
174
175 All trees made by list_to_tree that are the same size have the same shape.
176*/
177tree_size(Tree, Size) :-
178 tree_size(Tree, 0, Total), tree_size,
179 Size = Total.
180
181
182 tree_size(t(_,Left,Right), SoFar, Total) :-
183 tree_size(Right, SoFar, M),
184 N is M+1, tree_size,
185 tree_size(Left, N, Total).
186 tree_size(t, Accum, Accum).
187
188
189
190/** @pred tree_to_list(+ _Tree_, - _List_)
191
192
193 Is the converse operation to list_to_tree.. Any mapping or checking
194 operation can be done by converting the tree to a list, mapping or
195 checking the list, and converting the result, if any, back to a tree.
196 It is also easier for a human to read a list than a tree, as the
197 order in the tree goes all over the place.
198 */
199tree_to_list(Tree, List) :-
200 tree_to_list([Tree|Tail], Tail, List).
201
202
203 tree_to_list([], [], []) :- tree_to_list.
204 tree_to_list([t|_], _, []) :- tree_to_list.
205 tree_to_list([t(Head,Left,Right)|Qhead], [Left,Right|Qtail], [Head|Tail]) :-
206 tree_to_list(Qhead, Qtail, Tail).
207
208
209
210list(0, []).
211list(N, [N|L]) :- M is N-1, list(M, L).
212
213%% @}
214
215
216
217
once( 0:G)
get_label(+ Index, + Tree, ? Label)
list_to_tree(+ List, - Tree)
map_tree(+ Pred, + OldTree, - NewTree)
put_label(+ Index, + OldTree, + Label, - NewTree)
tree_size(+ Tree, - Size)
tree_to_list(+ Tree, - List)