home *** CD-ROM | disk | FTP | other *** search
- Newsgroups: comp.lang.prolog
- Path: sparky!uunet!munnari.oz.au!cs.mu.OZ.AU!mundil.cs.mu.OZ.AU!fjh
- From: fjh@mundil.cs.mu.OZ.AU (Fergus James HENDERSON)
- Subject: Re: AVL trees - improving an implementation of:
- Message-ID: <9225217.13465@mulga.cs.mu.OZ.AU>
- Sender: news@cs.mu.OZ.AU
- Organization: Computer Science, University of Melbourne, Australia
- References: <Bu6w2w.IBF@matilda.vut.edu.au>
- Date: Tue, 8 Sep 1992 07:12:37 GMT
- Lines: 100
-
- awenn@matilda.vut.edu.au (Andrew Wenn) writes:
-
- >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.
-
- A good reference which covers this sort of thing is "The Craft of Prolog"
- by Richard O'Keefe, in particular chapter 3, "Where Does All The Space Go?".
-
- >----------------------------------------------------------
- >%%% 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 ).
-
- Using '/' in this way is convenient, but most Prolog compilers
- are not smart enough to avoid using extra space if you do so.
- The following is likely to be more space-efficient:
-
- addavl( nil(0), Key, avl(nil(0), Key, nil(0), 1) ).
-
- Ie. replace nil/H with nil(H) and avl(L,K,R)/H with avl(L,K,R,H).
- [You will need to change all the rest of the code too :-( ]
-
- >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).
-
- The basic problem is likely to be that although the above code
- is deterministic, most Prolog compilers are not going to be smart
- enough to detect this, and you are going to get unnecessary choice
- points on the stack. You could improve things by putting a cut after the
- call gt(Y, Key), which would remove the choice point from the stack,
- but it is better to avoid pushing the choice point in the first place.
-
- Most Prolog compilers "index" clauses on the top-level functor of the
- first argument, and will detect determinism if the top-level functors
- of the first argument of each clause are different (and avoid pushing
- choice points). Thus the following code may be much more efficient:
-
- % top-lvl functors of 1st arg are nil/1 and avl/4.
- addavl( nil(0), Key, avl(nil(0), Key, nil(0), 1)).
- addavl( avl(Left, Y, Right, Hy), Key, NewTree):-
- termCompare(Y, Key, Result),
- addavl_2(Result, Left, Y, Right, Hy, Key, NewTree).
-
- % Using termCompare/3 above allows us to index on 1st arg here,
- % thus avoiding creating choice points
- addavl_2(=, Left, Y, Right, Hy, _Key, avl(Left, Y, Right, Hy)):-
- write(Y), % don't hide these writes in eq/2 - put them
- % here in addavl so they're obvious.
- % eq/2 might be used for other purposes.
- write(' Item already in tree\n').
- addavl_2(>, Left, Y, Right, Hy, Key, NewTree):-
- addavl(Left, Key, avl(Left1, Z, Left2, _),
- combine(Left1, Z, Left2, Y, Right, NewTree).
- addavl_2(<, Left, Y, Right, Hy, Key, NewTree):-
- addavl(Right, Key, avl(Right1, Z, Right2, _),
- combine(Left, Y, Right1, Z, Right2, NewTree).
-
- You should use the same trick with termCompare and an auxiliary predicate
- for searching the AVL tree.
-
- >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 ):-
-
- As far as I know, most Prolog compilers don't seem to do common subexpression
- elimination, so repeating the terms T1/H1 and T3/H3 will cost you both time
- and heap space. (Another reason to avoid using '/'/2 in this way.)
-
- Hope all this helps,
- Fergus.
-
- --
- Fergus Henderson fjh@munta.cs.mu.OZ.AU
- This .signature virus is a self-referential statement that is true - but
- you will only be able to consistently believe it if you copy it to your own
- .signature file!
-