home *** CD-ROM | disk | FTP | other *** search
- Newsgroups: comp.lang.prolog
- Path: sparky!uunet!spool.mu.edu!wupost!usc!rpi!batcomputer!munnari.oz.au!bruce.cs.monash.edu.au!monu6!minyos.xx.rmit.oz.au!matilda.vut.edu.au!awenn
- From: awenn@matilda.vut.edu.au (Andrew Wenn)
- Subject: AVL trees - improving an implementation of:
- Message-ID: <Bu6w2w.IBF@matilda.vut.edu.au>
- Organization: Victoria University of Technology
- Date: Mon, 7 Sep 1992 03:52:07 GMT
- Lines: 164
-
- Dear Prolog Users,
-
- I have implemented (almost entirely thanks to Ivan Bratko's book)
- a program for AVL trees. However, it has a problem, which I
- suspect is mainly due to the lack of tail recursion optimisation
- in the prolog that I am using in that if I try to insert a large
- number of items into it I run out of local stack space. For
- various reasons, I cannot increase the size of the stack and
- besides I feel this is the incorrect approach. By the way if I
- use a simple binary dictionary, I can insert all the records I
- wish into it.
-
- Before you ask, this is not an assignment!
-
- I have taught myself all the prolog that I know but I feel that
- it may be beneficial to myself and others in a similar situation
- if we could discuss various approaches for improving the program
- here.
-
- There are some quite talented and experienced prolog users
- who read this news; let's hope they rise to the challenge of
- passing on their knowledge to the less experienced ones.
-
- For those who are unfamiliar with Bratko's book, the code for avl
- trees is attached below.
-
- cut here
- ----------------------------------------------------------
- %%% A program for constructing and searching an avl tree.
-
- /* Based on Bratko pp 244ff. */
-
- /* Build the tree. */
-
- % The root of the tree is Key.
-
- addavl( nil/0, Key, avl(nil/0, Key, nil/0)/1 ).
-
- addavl( avl(Left, Y, Right)/Hy, Key, NewTree):-
- eq(Y, Key),
- !,
- NewTree = avl(Left, Y, Right)/Hy.
-
- addavl( avl(Left, Y, Right)/Hy, Key, NewTree):-
- gt(Y, Key),
- addavl(Left, Key, avl(Left1, Z, Left2)/_ ),
- combine(Left1, Z, Left2, Y, Right, NewTree).
-
- addavl( avl(Left, Y, Right)/Hy, Key, NewTree):-
- gt(Key, Y),
- addavl(Right, Key, avl(Right1, Z, Right2)/_ ),
- combine(Left, Y, Right1, Z, Right2, NewTree).
-
- combine(T1/H1, A, avl(T21, B, T22)/H2 , C, T3/H3,
- avl(avl(T1/H1, A, T21)/Ha, B, avl(T22, C, T3/H3)/Hc)/Hb ):-
- H2 > H1,
- H2 > H3,
- Ha is H1 + 1,
- Hc is H3 + 1,
- Hb is Ha + 1.
-
- combine(T1/H1, A, T2/H2, C, T3/H3,
- avl(T1/H1, A, avl(T2/H2, C, T3/H3)/Hc)/Ha ):-
- H1 >= H2,
- H1 >= H3,
- max1(H2, H3, Hc),
- max1(H1, Hc, Ha).
-
- combine(T1/H1, A, T2/H2, C, T3/H3,
- avl(avl(T1/H1, A, T2/H2)/Ha, C, T3/H3)/Hc ):-
- H3 >= H2,
- H3 >= H1,
- max1(H1, H2, Ha),
- max1(Ha, H3, Hc).
-
- max1(U, V, Max):-
- ( U > V,
- !,
- Max is U + 1
- ; Max is V + 1
- ).
-
- /* Display a tree. */
-
- show(T):-
- show2(T,0).
-
- show2(nil/0,_).
- show2(avl(Left, X, Right)/_, Indent):-
- Ind2 is Indent + 2,
- show2(Right, Ind2),
- tab(Indent),
- write(X),
- nl,
- show2(Left, Ind2).
-
- /* Find an item in a binary tree. */
-
- intree(X):-
- clause(tree(T), true),
- in(X, T).
-
- in(X, avl(_,X,_)/_ ):-!.
- in(X, avl(Left, Root, _)/_ ):-
- gt(Root, X),
- in(X, Left).
- in(X, avl(_, Root, Right)/_ ):-
- gt(X, Root),
- in(X, Right).
-
- build(File):-
- see(File),
- write('Loading dictionary.\n'),
- build_tree(Tree),
- seen,
- write('Complete.\n'),
- show(Tree).
-
- build_tree(Final):-
- build_tree_next(nil/0, Final).
-
- build_tree_next(Tree, NewTree):-
- read(Item),
- ( Item = end_of_file -> true,
- NewTree = Tree
- ; addavl(Tree, Item, Tree1),
- build_tree_next(Tree1, NewTree),
- !
- ).
-
- /* Test to see where item is to be put. */
-
- gt(X, Y):-
- X @> Y.
-
- eq(X, Y):-
- X == Y,
- !,
- write(X),
- write(' Item already in tree\n').
-
- --------------------------------------------------------------
- A sample (the whole file has about 500 of them) of the data that
- I am testing my implementation with are facts with the following
- format:
-
- cut here
- ------------------------------------------------------------------
- item(ant).
- item(a).
- item(zak).
- item(john).
- item(queen).
- item(harry).
- item(harvey).
- item(jane).
- item(james).
- item(robert).
- item(zoo).
- item(felicity).
- item(queen0).
- item(ant1).
-
-
-