
% File: bstree.pl
% Author: Dave Wessels
%
% Purpose: to represent and manipulate binary search trees
%    of unique keys that are positive integers 
%    paired with any kind of associated data values
%
% Representation:
%    bstree(Key,Value,Left,Right)
%
% Rules:
%    Left and Right are the left and right subtrees, nil if the subtrees are empty,
%    Left is a valid bstree and keys in Left must be < Key
%    Right is a valid bstree and keys in Right must be > Key
%
% Supported query set:
%    binTree(T):            succeeds iff T is a valid binary tree with integer keys
%    validKeys(T,Min,Max):  succeeds iff T's key structure is valid for binary search trees
%    bstree(T):             succeeds iff T is a valid binary search tree
%    bstInsert(K,V,T,NewT): succeeds iff K,V can be inserted into T to create NewT,
%                              fails if K is already in T
%    bstLookup(K,V,T):      succeeds iff T contains K and V is K's associated data value
%    bstPrint(T):           succeeds iff an inorder traversal of T can be performed,
%                              printing each key,value pair on a line of its own


% binTree(T)
% -----------
% succeeds iff T is a valid binary tree with integer keys
%    and instantiated values
binTree(nil).
binTree(bstree(K,V,L,R)) :-
   integer(K), nonvar(V),
   binTree(L), binTree(R).


% validKeys(T,Min,Max)
% --------------------
% succeeds iff  either T is nil or T has the form bstree(K,V,L,R)
%    such that all of the following apply:
%       (1) T's key, K, is in the range Min..Max (inclusive)
%       (2) validKeys(L,Min,K-1) succeeds
%       (3) validKeys(R,K+1,Max) succeeds
% IMPORTANT NOTE:
%    validKey assumes binTree(T) has already been checked and succeeded
validKeys(nil, _, _).
validKeys(bstree(K,_,L,R), Min, Max) :- 
     integer(Min), integer(Max), Min =< K, K =< Max,
     newMax is K - 1, newMin is K + 1,
     validKeys(L, Min, newMax),
     validKeys(R, newMin, Max). 
     

% bstree(T)
% ---------
% succeeds iff T is a valid binary search tree,
%    i.e. it has valid structure and valid keys
bstree(nil).
bstree(T) :- binTree(T), current_prolog_flag(max_integer,Max), validKeys(T,1,Max).


% bstInsert(K,V,T,NewT)
% ---------------------
% succeeds iff K,V can be inserted into T to create NewT,
%    fails if K is already in T

% can insert any valid K,V pair into an empty tree
bstInsert(K, V, nil, bstree(K,V,nil,nil)) :-
   nonvar(V), integer(K), K > 0.

% if K is less than the root's key then
%    attempt an insert in the left subtree
bstInsert(K, V, bstree(Kr,Vr,L,R), bstree(Kr,Vr,L1,R)) :-
   integer(K), nonvar(V), K < Kr, bstInsert(K,V,L,L1).

% if K is greater than the root's key then
%    attempt an insert in the right subtree
bstInsert(K,V, bstree(Kr,Vr,L,R), bstree(Kr,Vr,L,R1)) :-
   integer(K), nonvar(V), Kr < K, bstInsert(K,V,R,R1).


% bstLookup(K,V,T)
% ----------------
% succeeds iff T contains K and V is K's associated data value

% find it in the root
bstLookup(K,V,bstree(K,V,_,_)).

% if K is less than the root's key then search the left subtree
bstLookup(K,V,bstree(Kr,_,L,_)) :-
   integer(K), K < Kr, bstLookup(K,V,L).

% if K is greater than the root's key then search the right subtree
bstLookup(K,V,bstree(Kr,_,_,R)) :- 
   integer(K), Kr < K, bstLookup(K,V,R).


% bstPrint(T)
% -----------
% succeeds iff an inorder traversal of T can be performed,
%    printing each key,value pair on a line of its own
bstPrint(nil).
bstPrint(bstree(K,V,L,R)) :-
   bstPrint(L),
   write(K), put(0':), write(V), nl,
   bstPrint(R).

% -------------------------------------------------------------
%   Collection of test trees

testcase(t00,nil).
testcase(t01,bstree(8,1, nil, nil)).
testcase(t02,bstree(8,1,
                        bstree(4,2,nil,nil),
                        nil)).
testcase(t03,bstree(8,1,
                        bstree(4,2,nil,nil),
                        bstree(12,3,nil,nil))).
testcase(t04,bstree(8,1,bstree(4,2,
                                    bstree(2,4,nil,nil), 
                                    nil),
                        bstree(12,3,
                                    nil,
                                    bstree(14,5,nil,nil)))).
testcase(t05,bstree(8,1,bstree(4,2,
                                    bstree(2,4,nil,nil),
                                    nil),
                        bstree(12,3,
                                    nil,
                                    bstree(14,5,nil,nil)))).

