|
|
|
@@ -63,6 +63,29 @@ form colour(Left, Key, Value, Right), where _colour_ is one of =red= or
|
|
|
|
|
|
|
|
|
|
:- meta_predicate rb_map(+,:,-), rb_partial_map(+,+,:,-), rb_apply(+,+,:,-).
|
|
|
|
|
|
|
|
|
|
/*
|
|
|
|
|
:- use_module(library(type_check)).
|
|
|
|
|
|
|
|
|
|
:- type rbtree(K,V) ---> t(tree(K,V),tree(K,V)).
|
|
|
|
|
:- type tree(K,V) ---> black(tree(K,V),K,V,tree(K,V))
|
|
|
|
|
; red(tree(K,V),K,V,tree(K,V))
|
|
|
|
|
; ''.
|
|
|
|
|
:- type cmp ---> (=) ; (<) ; (>).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
:- pred rb_new(rbtree(_K,_V)).
|
|
|
|
|
:- pred rb_empty(rbtree(_K,_V)).
|
|
|
|
|
:- pred rb_lookup(K,V,rbtree(K,V)).
|
|
|
|
|
:- pred lookup(K,V, tree(K,V)).
|
|
|
|
|
:- pred lookup(cmp, K, V, tree(K,V)).
|
|
|
|
|
:- pred rb_min(rbtree(K,V),K,V).
|
|
|
|
|
:- pred min(tree(K,V),K,V).
|
|
|
|
|
:- pred rb_max(rbtree(K,V),K,V).
|
|
|
|
|
:- pred max(tree(K,V),K,V).
|
|
|
|
|
:- pred rb_next(rbtree(K,V),K,pair(K,V),V).
|
|
|
|
|
:- pred next(tree(K,V),K,pair(K,V),V,tree(K,V)).
|
|
|
|
|
*/
|
|
|
|
|
|
|
|
|
|
% create an empty tree.
|
|
|
|
|
%% rb_new(-T) is det.
|
|
|
|
|
%
|
|
|
|
@@ -70,15 +93,15 @@ form colour(Left, Key, Value, Right), where _colour_ is one of =red= or
|
|
|
|
|
%
|
|
|
|
|
% @deprecated Use rb_empty/1.
|
|
|
|
|
|
|
|
|
|
rb_new(t(Nil,Nil)) :- Nil = black([],[],[],[]).
|
|
|
|
|
rb_new(t(Nil,Nil)) :- Nil = black('',_,_,'').
|
|
|
|
|
|
|
|
|
|
rb_new(K,V,t(Nil,black(Nil,K,V,Nil))) :- Nil = black('',_,_,'').
|
|
|
|
|
|
|
|
|
|
%% rb_empty(?T) is semidet.
|
|
|
|
|
%
|
|
|
|
|
% Succeeds if T is an empty Red-Black tree.
|
|
|
|
|
|
|
|
|
|
rb_empty(t(Nil,Nil)) :- Nil = black([],[],[],[]).
|
|
|
|
|
|
|
|
|
|
rb_new(K,V,t(Nil,black(Nil,K,V,Nil))) :- Nil = black([],[],[],[]).
|
|
|
|
|
rb_empty(t(Nil,Nil)) :- Nil = black('',_,_,'').
|
|
|
|
|
|
|
|
|
|
%% rb_lookup(+Key, -Value, +T) is semidet.
|
|
|
|
|
%
|
|
|
|
@@ -88,7 +111,7 @@ rb_new(K,V,t(Nil,black(Nil,K,V,Nil))) :- Nil = black([],[],[],[]).
|
|
|
|
|
rb_lookup(Key, Val, t(_,Tree)) :-
|
|
|
|
|
lookup(Key, Val, Tree).
|
|
|
|
|
|
|
|
|
|
lookup(_, _, black([],_,_,[])) :- !, fail.
|
|
|
|
|
lookup(_, _, black('',_,_,'')) :- !, fail.
|
|
|
|
|
lookup(Key, Val, Tree) :-
|
|
|
|
|
arg(2,Tree,KA),
|
|
|
|
|
compare(Cmp,KA,Key),
|
|
|
|
@@ -110,8 +133,8 @@ lookup(=, _, V, Tree) :-
|
|
|
|
|
rb_min(t(_,Tree), Key, Val) :-
|
|
|
|
|
min(Tree, Key, Val).
|
|
|
|
|
|
|
|
|
|
min(red(black([],_,_,_),Key,Val,_), Key, Val) :- !.
|
|
|
|
|
min(black(black([],_,_,_),Key,Val,_), Key, Val) :- !.
|
|
|
|
|
min(red(black('',_,_,_),Key,Val,_), Key, Val) :- !.
|
|
|
|
|
min(black(black('',_,_,_),Key,Val,_), Key, Val) :- !.
|
|
|
|
|
min(red(Right,_,_,_), Key, Val) :-
|
|
|
|
|
min(Right,Key,Val).
|
|
|
|
|
min(black(Right,_,_,_), Key, Val) :-
|
|
|
|
@@ -124,8 +147,8 @@ min(black(Right,_,_,_), Key, Val) :-
|
|
|
|
|
rb_max(t(_,Tree), Key, Val) :-
|
|
|
|
|
max(Tree, Key, Val).
|
|
|
|
|
|
|
|
|
|
max(red(_,Key,Val,black([],_,_,_)), Key, Val) :- !.
|
|
|
|
|
max(black(_,Key,Val,black([],_,_,_)), Key, Val) :- !.
|
|
|
|
|
max(red(_,Key,Val,black('',_,_,_)), Key, Val) :- !.
|
|
|
|
|
max(black(_,Key,Val,black('',_,_,_)), Key, Val) :- !.
|
|
|
|
|
max(red(_,_,_,Left), Key, Val) :-
|
|
|
|
|
max(Left,Key,Val).
|
|
|
|
|
max(black(_,_,_,Left), Key, Val) :-
|
|
|
|
@@ -139,7 +162,7 @@ max(black(_,_,_,Left), Key, Val) :-
|
|
|
|
|
rb_next(t(_,Tree), Key, Next, Val) :-
|
|
|
|
|
next(Tree, Key, Next, Val, []).
|
|
|
|
|
|
|
|
|
|
next(black([],_,_,[]), _, _, _, _) :- !, fail.
|
|
|
|
|
next(black('',_,_,''), _, _, _, _) :- !, fail.
|
|
|
|
|
next(Tree, Key, Next, Val, Candidate) :-
|
|
|
|
|
arg(2,Tree,KA),
|
|
|
|
|
arg(3,Tree,VA),
|
|
|
|
@@ -169,7 +192,7 @@ next(=, _, _, _, NK, Val, Tree, Candidate) :-
|
|
|
|
|
rb_previous(t(_,Tree), Key, Previous, Val) :-
|
|
|
|
|
previous(Tree, Key, Previous, Val, []).
|
|
|
|
|
|
|
|
|
|
previous(black([],_,_,[]), _, _, _, _) :- !, fail.
|
|
|
|
|
previous(black('',_,_,''), _, _, _, _) :- !, fail.
|
|
|
|
|
previous(Tree, Key, Previous, Val, Candidate) :-
|
|
|
|
|
arg(2,Tree,KA),
|
|
|
|
|
arg(3,Tree,VA),
|
|
|
|
@@ -241,7 +264,7 @@ update(red(Left,Key0,Val0,Right), Key, OldVal, Val, NewTree) :-
|
|
|
|
|
rb_apply(t(Nil,OldTree), Key, Goal, t(Nil,NewTree)) :-
|
|
|
|
|
apply(OldTree, Key, Goal, NewTree).
|
|
|
|
|
|
|
|
|
|
%apply(black([],_,_,[]), _, _, _) :- !, fail.
|
|
|
|
|
%apply(black('',_,_,''), _, _, _) :- !, fail.
|
|
|
|
|
apply(black(Left,Key0,Val0,Right), Key, Goal,
|
|
|
|
|
black(NewLeft,Key0,Val,NewRight)) :-
|
|
|
|
|
Left \= [],
|
|
|
|
@@ -288,7 +311,7 @@ rb_in(Key, Val, t(_,T)) :-
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
enum(Key, Val, black(L,K,V,R)) :-
|
|
|
|
|
L \= [],
|
|
|
|
|
L \= '',
|
|
|
|
|
enum_cases(Key, Val, L, K, V, R).
|
|
|
|
|
enum(Key, Val, red(L,K,V,R)) :-
|
|
|
|
|
enum_cases(Key, Val, L, K, V, R).
|
|
|
|
@@ -309,7 +332,7 @@ rb_lookupall(Key, Val, t(_,Tree)) :-
|
|
|
|
|
lookupall(Key, Val, Tree).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
lookupall(_, _, black([],_,_,[])) :- !, fail.
|
|
|
|
|
lookupall(_, _, black('',_,_,'')) :- !, fail.
|
|
|
|
|
lookupall(Key, Val, Tree) :-
|
|
|
|
|
arg(2,Tree,KA),
|
|
|
|
|
compare(Cmp,KA,Key),
|
|
|
|
@@ -369,7 +392,7 @@ insert(Tree0,Key,Val,Nil,Tree) :-
|
|
|
|
|
%
|
|
|
|
|
% actual insertion
|
|
|
|
|
%
|
|
|
|
|
insert2(black([],[],[],[]), K, V, Nil, T, Status) :- !,
|
|
|
|
|
insert2(black('',_,_,''), K, V, Nil, T, Status) :- !,
|
|
|
|
|
T = red(Nil,K,V,Nil),
|
|
|
|
|
Status = not_done.
|
|
|
|
|
insert2(red(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
@@ -414,7 +437,7 @@ insert_new(Tree0,Key,Val,Nil,Tree) :-
|
|
|
|
|
%
|
|
|
|
|
% actual insertion, copied from insert2
|
|
|
|
|
%
|
|
|
|
|
insert_new_2(black([],[],[],[]), K, V, Nil, T, Status) :- !,
|
|
|
|
|
insert_new_2(black('',_,_,''), K, V, Nil, T, Status) :- !,
|
|
|
|
|
T = red(Nil,K,V,Nil),
|
|
|
|
|
Status = not_done.
|
|
|
|
|
insert_new_2(red(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
@@ -520,7 +543,7 @@ fix_right(T,T,done).
|
|
|
|
|
pretty_print(t(_,T)) :-
|
|
|
|
|
pretty_print(T,6).
|
|
|
|
|
|
|
|
|
|
pretty_print(black([],[],[],[]),_) :- !.
|
|
|
|
|
pretty_print(black('',_,_,''),_) :- !.
|
|
|
|
|
pretty_print(red(L,K,_,R),D) :-
|
|
|
|
|
DN is D+6,
|
|
|
|
|
pretty_print(L,DN),
|
|
|
|
@@ -580,12 +603,12 @@ delete(black(L,_,V,R), _, V, OUT, Flag) :-
|
|
|
|
|
rb_del_min(t(Nil,T), K, Val, t(Nil,NT)) :-
|
|
|
|
|
del_min(T, K, Val, Nil, NT, _).
|
|
|
|
|
|
|
|
|
|
del_min(red(black([],_,_,_),K,V,R), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
del_min(red(black('',_,_,_),K,V,R), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
delete_red_node(Nil,R,OUT,Flag).
|
|
|
|
|
del_min(red(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
|
del_min(L, K, V, Nil, NL, Flag0),
|
|
|
|
|
fixup_left(Flag0,red(NL,K0,V0,R), NT, Flag).
|
|
|
|
|
del_min(black(black([],_,_,_),K,V,R), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
del_min(black(black('',_,_,_),K,V,R), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
delete_black_node(Nil,R,OUT,Flag).
|
|
|
|
|
del_min(black(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
|
del_min(L, K, V, Nil, NL, Flag0),
|
|
|
|
@@ -600,12 +623,12 @@ del_min(black(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
|
rb_del_max(t(Nil,T), K, Val, t(Nil,NT)) :-
|
|
|
|
|
del_max(T, K, Val, Nil, NT, _).
|
|
|
|
|
|
|
|
|
|
del_max(red(L,K,V,black([],_,_,_)), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
del_max(red(L,K,V,black('',_,_,_)), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
delete_red_node(L,Nil,OUT,Flag).
|
|
|
|
|
del_max(red(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
|
del_max(R, K, V, Nil, NR, Flag0),
|
|
|
|
|
fixup_right(Flag0,red(L,K0,V0,NR),NT, Flag).
|
|
|
|
|
del_max(black(L,K,V,black([],_,_,_)), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
del_max(black(L,K,V,black('',_,_,_)), K, V, Nil, OUT, Flag) :- !,
|
|
|
|
|
delete_black_node(L,Nil,OUT,Flag).
|
|
|
|
|
del_max(black(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
|
del_max(R, K, V, Nil, NR, Flag0),
|
|
|
|
@@ -614,27 +637,27 @@ del_max(black(L,K0,V0,R), K, V, Nil, NT, Flag) :-
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
delete_red_node(L1,L2,L1,done) :- L1 == L2, !.
|
|
|
|
|
delete_red_node(black([],[],[],[]),R,R,done) :- !.
|
|
|
|
|
delete_red_node(L,black([],[],[],[]),L,done) :- !.
|
|
|
|
|
delete_red_node(black('',_,_,''),R,R,done) :- !.
|
|
|
|
|
delete_red_node(L,black('',_,_,''),L,done) :- !.
|
|
|
|
|
delete_red_node(L,R,OUT,Done) :-
|
|
|
|
|
delete_next(R,NK,NV,NR,Done0),
|
|
|
|
|
fixup_right(Done0,red(L,NK,NV,NR),OUT,Done).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
delete_black_node(L1,L2,L1,not_done) :- L1 == L2, !.
|
|
|
|
|
delete_black_node(black([],[],[],[]),red(L,K,V,R),black(L,K,V,R),done) :- !.
|
|
|
|
|
delete_black_node(black([],[],[],[]),R,R,not_done) :- !.
|
|
|
|
|
delete_black_node(red(L,K,V,R),black([],[],[],[]),black(L,K,V,R),done) :- !.
|
|
|
|
|
delete_black_node(L,black([],[],[],[]),L,not_done) :- !.
|
|
|
|
|
delete_black_node(black('',_,_,''),red(L,K,V,R),black(L,K,V,R),done) :- !.
|
|
|
|
|
delete_black_node(black('',_,_,''),R,R,not_done) :- !.
|
|
|
|
|
delete_black_node(red(L,K,V,R),black('',_,_,''),black(L,K,V,R),done) :- !.
|
|
|
|
|
delete_black_node(L,black('',_,_,''),L,not_done) :- !.
|
|
|
|
|
delete_black_node(L,R,OUT,Done) :-
|
|
|
|
|
delete_next(R,NK,NV,NR,Done0),
|
|
|
|
|
fixup_right(Done0,black(L,NK,NV,NR),OUT,Done).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
delete_next(red(black([],[],[],[]),K,V,R),K,V,R,done) :- !.
|
|
|
|
|
delete_next(black(black([],[],[],[]),K,V,red(L1,K1,V1,R1)),
|
|
|
|
|
delete_next(red(black('',_,_,''),K,V,R),K,V,R,done) :- !.
|
|
|
|
|
delete_next(black(black('',_,_,''),K,V,red(L1,K1,V1,R1)),
|
|
|
|
|
K,V,black(L1,K1,V1,R1),done) :- !.
|
|
|
|
|
delete_next(black(black([],[],[],[]),K,V,R),K,V,R,not_done) :- !.
|
|
|
|
|
delete_next(black(black('',_,_,''),K,V,R),K,V,R,not_done) :- !.
|
|
|
|
|
delete_next(red(L,K,V,R),K0,V0,OUT,Done) :-
|
|
|
|
|
delete_next(L,K0,V0,NL,Done0),
|
|
|
|
|
fixup_left(Done0,red(NL,K,V,R),OUT,Done).
|
|
|
|
@@ -742,7 +765,7 @@ rb_visit(t(_,T),Lf) :-
|
|
|
|
|
rb_visit(t(_,T),L0,Lf) :-
|
|
|
|
|
visit(T,L0,Lf).
|
|
|
|
|
|
|
|
|
|
visit(black([],_,_,_),L,L) :- !.
|
|
|
|
|
visit(black('',_,_,_),L,L) :- !.
|
|
|
|
|
visit(red(L,K,V,R),L0,Lf) :-
|
|
|
|
|
visit(L,[K-V|L1],Lf),
|
|
|
|
|
visit(R,L0,L1).
|
|
|
|
@@ -755,9 +778,19 @@ visit(black(L,K,V,R),L0,Lf) :-
|
|
|
|
|
% True if call(Goal, Value) is true for all nodes in T.
|
|
|
|
|
|
|
|
|
|
rb_map(t(Nil,Tree),Goal,t(Nil,NewTree)) :-
|
|
|
|
|
map(Tree,Goal,NewTree).
|
|
|
|
|
map(Tree,Goal,NewTree,Nil).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
map(black('',_,_,''),_,Nil,Nil) :- !.
|
|
|
|
|
map(red(L,K,V,R),Goal,red(NL,K,NV,NR),Nil) :-
|
|
|
|
|
call(Goal,V,NV), !,
|
|
|
|
|
map(L,Goal,NL,Nil),
|
|
|
|
|
map(R,Goal,NR,Nil).
|
|
|
|
|
map(black(L,K,V,R),Goal,black(NL,K,NV,NR),Nil) :-
|
|
|
|
|
call(Goal,V,NV), !,
|
|
|
|
|
map(L,Goal,NL,Nil),
|
|
|
|
|
map(R,Goal,NR,Nil).
|
|
|
|
|
|
|
|
|
|
%% rb_map(+T, :G, -TN) is semidet.
|
|
|
|
|
%
|
|
|
|
|
% For all nodes Key in the tree T, if the value associated with
|
|
|
|
@@ -765,21 +798,11 @@ rb_map(t(Nil,Tree),Goal,t(Nil,NewTree)) :-
|
|
|
|
|
% the value associated with Key in TN is ValF. Fails if
|
|
|
|
|
% call(G,Val0,ValF) is not satisfiable for all Var0.
|
|
|
|
|
|
|
|
|
|
map(black([],[],[],[]),_,black([],[],[],[])) :- !.
|
|
|
|
|
map(red(L,K,V,R),Goal,red(NL,K,NV,NR)) :-
|
|
|
|
|
call(Goal,V,NV), !,
|
|
|
|
|
map(L,Goal,NL),
|
|
|
|
|
map(R,Goal,NR).
|
|
|
|
|
map(black(L,K,V,R),Goal,black(NL,K,NV,NR)) :-
|
|
|
|
|
call(Goal,V,NV), !,
|
|
|
|
|
map(L,Goal,NL),
|
|
|
|
|
map(R,Goal,NR).
|
|
|
|
|
|
|
|
|
|
rb_map(t(_,Tree),Goal) :-
|
|
|
|
|
map(Tree,Goal).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
map(black([],[],[],[]),_) :- !.
|
|
|
|
|
map(black('',_,_,''),_) :- !.
|
|
|
|
|
map(red(L,_,V,R),Goal) :-
|
|
|
|
|
call(Goal,V), !,
|
|
|
|
|
map(L,Goal),
|
|
|
|
@@ -796,26 +819,26 @@ map(black(L,_,V,R),Goal) :-
|
|
|
|
|
% a list containing all new nodes as pairs K-V.
|
|
|
|
|
|
|
|
|
|
rb_clone(t(Nil,T),t(Nil,NT),Ns) :-
|
|
|
|
|
clone(T,NT,Ns,[]).
|
|
|
|
|
clone(T,Nil,NT,Ns,[]).
|
|
|
|
|
|
|
|
|
|
clone(black([],[],[],[]),black([],[],[],[]),Ns,Ns) :- !.
|
|
|
|
|
clone(red(L,K,_,R),red(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,NR,Ns1,Ns0).
|
|
|
|
|
clone(black(L,K,_,R),black(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,NR,Ns1,Ns0).
|
|
|
|
|
clone(black('',_,_,''),Nil,Nil,Ns,Ns) :- !.
|
|
|
|
|
clone(red(L,K,_,R),Nil,red(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,Nil,NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,Nil,NR,Ns1,Ns0).
|
|
|
|
|
clone(black(L,K,_,R),Nil,black(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,Nil,NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,Nil,NR,Ns1,Ns0).
|
|
|
|
|
|
|
|
|
|
rb_clone(t(Nil,T),ONs,t(Nil,NT),Ns) :-
|
|
|
|
|
clone(T,ONs,[],NT,Ns,[]).
|
|
|
|
|
clone(T,Nil,ONs,[],NT,Ns,[]).
|
|
|
|
|
|
|
|
|
|
clone(black([],[],[],[]),ONs,ONs,black([],[],[],[]),Ns,Ns) :- !.
|
|
|
|
|
clone(red(L,K,V,R),ONsF,ONs0,red(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,ONsF,[K-V|ONs1],NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,ONs1,ONs0,NR,Ns1,Ns0).
|
|
|
|
|
clone(black(L,K,V,R),ONsF,ONs0,black(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,ONsF,[K-V|ONs1],NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,ONs1,ONs0,NR,Ns1,Ns0).
|
|
|
|
|
clone(black('',_,_,''),Nil,ONs,ONs,Nil,Ns,Ns) :- !.
|
|
|
|
|
clone(red(L,K,V,R),Nil,ONsF,ONs0,red(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,Nil,ONsF,[K-V|ONs1],NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,Nil,ONs1,ONs0,NR,Ns1,Ns0).
|
|
|
|
|
clone(black(L,K,V,R),Nil,ONsF,ONs0,black(NL,K,NV,NR),NsF,Ns0) :-
|
|
|
|
|
clone(L,Nil,ONsF,[K-V|ONs1],NL,NsF,[K-NV|Ns1]),
|
|
|
|
|
clone(R,Nil,ONs1,ONs0,NR,Ns1,Ns0).
|
|
|
|
|
|
|
|
|
|
%% rb_partial_map(+T, +Keys, :G, -TN)
|
|
|
|
|
%
|
|
|
|
@@ -832,7 +855,7 @@ rb_partial_map(t(Nil,T0), Map, Map0, Goal, t(Nil,TF)) :-
|
|
|
|
|
rb_partial_map(T0, Map, Map0, Nil, Goal, TF).
|
|
|
|
|
|
|
|
|
|
partial_map(T,[],[],_,_,T) :- !.
|
|
|
|
|
partial_map(black([],_,_,_),Map,Map,Nil,_,Nil) :- !.
|
|
|
|
|
partial_map(black('',_,_,_),Map,Map,Nil,_,Nil) :- !.
|
|
|
|
|
partial_map(red(L,K,V,R),Map,MapF,Nil,Goal,red(NL,K,NV,NR)) :-
|
|
|
|
|
partial_map(L,Map,MapI,Nil,Goal,NL),
|
|
|
|
|
(
|
|
|
|
@@ -885,7 +908,7 @@ rb_keys(t(_,T),Lf) :-
|
|
|
|
|
rb_keys(t(_,T),L0,Lf) :-
|
|
|
|
|
keys(T,L0,Lf).
|
|
|
|
|
|
|
|
|
|
keys(black([],[],[],[]),L,L) :- !.
|
|
|
|
|
keys(black('',_,_,''),L,L) :- !.
|
|
|
|
|
keys(red(L,K,_,R),L0,Lf) :-
|
|
|
|
|
keys(L,[K|L1],Lf),
|
|
|
|
|
keys(R,L0,L1).
|
|
|
|
@@ -908,11 +931,11 @@ list_to_rbtree(List, T) :-
|
|
|
|
|
% list L.
|
|
|
|
|
|
|
|
|
|
ord_list_to_rbtree([], t(Nil,Nil)) :- !,
|
|
|
|
|
Nil = black([], [], [], []).
|
|
|
|
|
Nil = black('', _, _, '').
|
|
|
|
|
ord_list_to_rbtree([K-V], t(Nil,black(Nil,K,V,Nil))) :- !,
|
|
|
|
|
Nil = black([], [], [], []).
|
|
|
|
|
Nil = black('', _, _, '').
|
|
|
|
|
ord_list_to_rbtree(List, t(Nil,Tree)) :-
|
|
|
|
|
Nil = black([], [], [], []),
|
|
|
|
|
Nil = black('', _, _, ''),
|
|
|
|
|
Ar =.. [seq|List],
|
|
|
|
|
functor(Ar,_,L),
|
|
|
|
|
Height is integer(log(L)/log(2)),
|
|
|
|
@@ -943,7 +966,7 @@ build_node( _, Left, K, Val, Right, black(Left, K, Val, Right)).
|
|
|
|
|
rb_size(t(_,T),Size) :-
|
|
|
|
|
size(T,0,Size).
|
|
|
|
|
|
|
|
|
|
size(black([],_,_,_),Sz,Sz) :- !.
|
|
|
|
|
size(black('',_,_,_),Sz,Sz) :- !.
|
|
|
|
|
size(red(L,_,_,R),Sz0,Szf) :-
|
|
|
|
|
Sz1 is Sz0+1,
|
|
|
|
|
size(L,Sz1,Sz2),
|
|
|
|
@@ -974,7 +997,7 @@ is_rbtree(T,Goal) :-
|
|
|
|
|
% This code checks if a tree is ordered and a rbtree
|
|
|
|
|
%
|
|
|
|
|
%
|
|
|
|
|
rbtree(t(_,black([],[],[],[]))) :- !.
|
|
|
|
|
rbtree(t(_,black('',_,_,''))) :- !.
|
|
|
|
|
rbtree(t(_,T)) :-
|
|
|
|
|
catch(rbtree1(T),msg(S,Args),format(S,Args)).
|
|
|
|
|
|
|
|
|
@@ -986,14 +1009,14 @@ rbtree1(red(_,_,_,_)) :-
|
|
|
|
|
throw(msg("root should be black",[])).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
find_path_blacks(black([],[],[],[]), Bls, Bls) :- !.
|
|
|
|
|
find_path_blacks(black('',_,_,''), Bls, Bls) :- !.
|
|
|
|
|
find_path_blacks(black(L,_,_,_), Bls0, Bls) :-
|
|
|
|
|
Bls1 is Bls0+1,
|
|
|
|
|
find_path_blacks(L, Bls1, Bls).
|
|
|
|
|
find_path_blacks(red(L,_,_,_), Bls0, Bls) :-
|
|
|
|
|
find_path_blacks(L, Bls0, Bls).
|
|
|
|
|
|
|
|
|
|
check_rbtree(black([],[],[],[]),Min,Max,Bls0) :- !,
|
|
|
|
|
check_rbtree(black('',_,_,''),Min,Max,Bls0) :- !,
|
|
|
|
|
check_height(Bls0,Min,Max).
|
|
|
|
|
check_rbtree(red(L,K,_,R),Min,Max,Bls) :-
|
|
|
|
|
check_val(K,Min,Max),
|
|
|
|
@@ -1061,11 +1084,11 @@ clean_tree(X1,X,T0,TF) :-
|
|
|
|
|
clean_tree(X2,X,TI,TF).
|
|
|
|
|
|
|
|
|
|
bclean_tree(X,X,T0,TF) :- !,
|
|
|
|
|
% format("cleaning ~d~n", [X]),
|
|
|
|
|
format("cleaning ~d~n", [X]),
|
|
|
|
|
rb_delete(T0,X,TF),
|
|
|
|
|
( rbtree(TF) -> true ; abort).
|
|
|
|
|
bclean_tree(X1,X,T0,TF) :-
|
|
|
|
|
% format("cleaning ~d~n", [X1]),
|
|
|
|
|
format("cleaning ~d~n", [X1]),
|
|
|
|
|
rb_delete(T0,X1,TI),
|
|
|
|
|
X2 is X1-1,
|
|
|
|
|
( rbtree(TI) -> true ; abort),
|
|
|
|
|