YAP 7.1.0
All Classes Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
avl.yap
Go to the documentation of this file.
1/*************************************************************************
2* *
3* YAP Prolog *
4* *
5* Yap Prolog was developed at NCCUP - Universidade do Porto *
6* *
7* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
8* *
9**************************************************************************
10* *
11* File: regexp.yap *
12* Last rev: 5/15/2000 *
13* mods: *
14* comments: AVL trees in YAP (from code by M. van Emden, P. Vasey) *
15* *
16*************************************************************************/
17
18/**
19 * @file avl.yap
20 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
21 * @date Tue Nov 17 00:59:28 2015
22 *
23 * @brief Support for constructing AVL trees
24 *
25 *
26*/
27
28
29
30/**
31* @defgroup avl AVL Trees
32* @ingroup YAPLibrary
33
34@brief Supports constructing AVL trees.
35
36@long available through the directive:
37
38```
39:- use_module(library(avl)).
40```
41
42 It includes the following predicates:
43
44 - avl_insert/4
45 - avl_lookup/3
46 - avl_new/1
47
48AVL trees are balanced search binary trees. They are named after their
49inventors, Adelson-Velskii and Landis, and they were the first
50dynamically balanced trees to be proposed. The YAP AVL tree manipulation
51predicates library uses code originally written by Martin van Emdem and
52published in the Logic Programming Newsletter, Autumn 1981. A bug in
53this code was fixed by Philip Vasey, in the Logic Programming
54Newsletter, Summer 1982. The library currently only includes routines to
55insert and lookup elements in the tree. Please try red-black trees if
56you need deletion.
57
58@{
59
60 */
61
62:- module(avl, [
66 ]).
67
68
69/** @pred avl_new(+ _T_)
70
71
72Create a new tree.
73
74
75*/
76avl_new([]).
77
78/** @pred avl_insert(+ _Key_,? _Value_,+ _T0_,- _TF_)
79
80
81Add an element with key _Key_ and _Value_ to the AVL tree
82 _T0_ creating a new AVL tree _TF_. Duplicated elements are
83allowed.
84
85
86*/
87avl_insert(Key, Value, T0, TF) :-
88 insert(T0, Key, Value, TF, _).
89
90insert([], Key, Value, avl([],Key,Value,-,[]), yes).
91insert(avl(L,Root,RVal,Bl,R), E, Value, NewTree, WhatHasChanged) :-
92 E @< Root, insert,
93 insert(L, E, Value, NewL, LeftHasChanged),
94 adjust(avl(NewL,Root,RVal,Bl,R), LeftHasChanged, left, NewTree, WhatHasChanged).
95insert(avl(L,Root,RVal,Bl,R), E, Val, NewTree, WhatHasChanged) :-
96% E @>= Root, currently we allow duplicated values, although
97% lookup will only fetch the first.
98 insert(R, E, Val,NewR, RightHasChanged),
99 adjust(avl(L,Root,RVal,Bl,NewR), RightHasChanged, right, NewTree, WhatHasChanged).
100
101adjust(Oldtree, no, _, Oldtree, no).
102adjust(avl(L,Root,RVal,Bl,R), yes, Lor, NewTree, WhatHasChanged) :-
103 table(Bl, Lor, Bl1, WhatHasChanged, ToBeRebalanced),
104 rebalance(avl(L, Root, RVal, Bl, R), Bl1, ToBeRebalanced, NewTree).
105
106% balance where balance whole tree to be
107% before inserted after increased rebalanced
108table(- , left , < , yes , no ).
109table(- , right , > , yes , no ).
110table(< , left , - , no , yes ).
111table(< , right , - , no , no ).
112table(> , left , - , no , no ).
113table(> , right , - , no , yes ).
114
115rebalance(avl(Lst, Root, RVal, _Bl, Rst), Bl1, no, avl(Lst, Root, RVal, Bl1,Rst)).
116rebalance(OldTree, _, yes, NewTree) :-
117 avl_geq(OldTree,NewTree).
118
119avl_geq(avl(Alpha,A,VA,>,avl(Beta,B,VB,>,Gamma)),
120 avl(avl(Alpha,A,VA,-,Beta),B,VB,-,Gamma)).
121avl_geq(avl(avl(Alpha,A,VA,<,Beta),B,VB,<,Gamma),
122 avl(Alpha,A,VA,-,avl(Beta,B,VB,-,Gamma))).
123avl_geq(avl(Alpha,A,VA,>,avl(avl(Beta,X,VX,Bl1,Gamma),B,VB,<,Delta)),
124 avl(avl(Alpha,A,VA,Bl2,Beta),X,VX,-,avl(Gamma,B,VB,Bl3,Delta))) :-
125 table2(Bl1,Bl2,Bl3).
126avl_geq(avl(avl(Alpha,A,VA,>,avl(Beta,X,VX,Bl1,Gamma)),B,VB,<,Delta),
127 avl(avl(Alpha,A,VA,Bl2,Beta),X,VX,-,avl(Gamma,B,VB,Bl3,Delta))) :-
128 table2(Bl1,Bl2,Bl3).
129
130table2(< ,- ,> ).
131table2(> ,< ,- ).
132table2(- ,- ,- ).
133
134/** @pred avl_lookup(+ _Key_,- _Value_,+ _T_)
135
136
137Lookup an element with key _Key_ in the AVL tree
138 _T_, returning the value _Value_.
139
140*/
141
142avl_lookup(Key, Value, avl(L,Key0,KVal,_,R)) :-
143 compare(Cmp, Key, Key0),
144 avl_lookup(Cmp, Value, L, R, Key, KVal).
145
146avl_lookup(=, Value, _, _, _, Value).
147avl_lookup(<, Value, L, _, Key, _) :-
148 avl_lookup(Key, Value, L).
149avl_lookup(>, Value, _, R, Key, _) :-
150 avl_lookup(Key, Value, R).
151
152
153/**
154@}
155*/
156
avl_insert(+ Key,? Value,+ T0,- TF)
avl_lookup(+ Key,- Value,+ T)
avl_new(+ T)