home *** CD-ROM | disk | FTP | other *** search
/ NetNews Usenet Archive 1992 #20 / NN_1992_20.iso / spool / comp / lang / prolog / 1661 < prev    next >
Encoding:
Text File  |  1992-09-08  |  4.2 KB  |  174 lines

  1. Newsgroups: comp.lang.prolog
  2. 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
  3. From: awenn@matilda.vut.edu.au (Andrew Wenn)
  4. Subject: AVL trees - improving an implementation of:
  5. Message-ID: <Bu6w2w.IBF@matilda.vut.edu.au>
  6. Organization: Victoria University of Technology
  7. Date: Mon, 7 Sep 1992 03:52:07 GMT
  8. Lines: 164
  9.  
  10. Dear Prolog Users,
  11.  
  12. I have implemented (almost entirely thanks to Ivan Bratko's book) 
  13. a program for AVL trees. However, it has a problem, which I 
  14. suspect is mainly due to the lack of tail recursion optimisation 
  15. in the prolog that I am using in that if I try to insert a large 
  16. number of items into it I run out of local stack space. For 
  17. various reasons, I cannot increase the size of the stack and 
  18. besides I feel this is the incorrect approach. By the way if I 
  19. use a simple binary dictionary, I can insert all the records I 
  20. wish into it.
  21.  
  22. Before you ask, this is not an assignment!
  23.  
  24. I have taught myself all the prolog that I know but I feel that 
  25. it may be beneficial to myself and others in a similar situation 
  26. if we could discuss various approaches for improving the program 
  27. here. 
  28.  
  29. There are some quite talented and experienced prolog users
  30. who read this news; let's hope they rise to the challenge of 
  31. passing on their knowledge to the less experienced ones.
  32.  
  33. For those who are unfamiliar with Bratko's book, the code for avl 
  34. trees is attached below. 
  35.  
  36. cut here
  37. ----------------------------------------------------------
  38. %%%   A program for constructing and searching an avl tree.
  39.  
  40. /* Based on Bratko pp 244ff. */
  41.  
  42. /* Build the tree. */
  43.  
  44. % The root of the tree is Key.
  45.  
  46. addavl( nil/0, Key, avl(nil/0, Key, nil/0)/1 ).    
  47.  
  48. addavl( avl(Left, Y, Right)/Hy, Key, NewTree):-
  49.     eq(Y, Key), 
  50.     !,
  51.     NewTree = avl(Left, Y, Right)/Hy.
  52.  
  53. addavl( avl(Left, Y, Right)/Hy, Key, NewTree):-
  54.     gt(Y, Key),
  55.     addavl(Left, Key, avl(Left1, Z, Left2)/_ ),
  56.     combine(Left1, Z, Left2, Y, Right, NewTree).  
  57.  
  58. addavl( avl(Left, Y, Right)/Hy, Key, NewTree):- 
  59.     gt(Key, Y),
  60.     addavl(Right, Key, avl(Right1, Z, Right2)/_ ),
  61.     combine(Left, Y, Right1, Z, Right2, NewTree).  
  62.  
  63. combine(T1/H1, A, avl(T21, B, T22)/H2 , C, T3/H3,
  64.         avl(avl(T1/H1, A, T21)/Ha, B, avl(T22, C, T3/H3)/Hc)/Hb ):-
  65.     H2 > H1, 
  66.     H2 > H3,
  67.     Ha is H1 + 1,
  68.     Hc is H3 + 1,
  69.     Hb is Ha + 1.
  70.  
  71. combine(T1/H1, A, T2/H2, C, T3/H3,
  72.         avl(T1/H1, A, avl(T2/H2, C, T3/H3)/Hc)/Ha ):-
  73.     H1 >= H2,
  74.     H1 >= H3,
  75.     max1(H2, H3, Hc),
  76.     max1(H1, Hc, Ha).
  77.  
  78. combine(T1/H1, A, T2/H2, C, T3/H3,
  79.         avl(avl(T1/H1, A, T2/H2)/Ha, C, T3/H3)/Hc ):-
  80.     H3 >= H2,
  81.     H3 >= H1,
  82.     max1(H1, H2, Ha),
  83.     max1(Ha, H3, Hc).
  84.  
  85. max1(U, V, Max):-
  86.     (  U > V, 
  87.        !,
  88.        Max is U + 1
  89.     ;  Max is V + 1
  90.     ).
  91.  
  92. /* Display a tree. */
  93.  
  94. show(T):-
  95.     show2(T,0).
  96.  
  97. show2(nil/0,_).
  98. show2(avl(Left, X, Right)/_, Indent):-
  99.     Ind2 is Indent + 2,
  100.     show2(Right, Ind2),
  101.     tab(Indent),
  102.     write(X),
  103.     nl,
  104.     show2(Left, Ind2).
  105.  
  106. /* Find an item in a binary tree. */
  107.  
  108. intree(X):-
  109.     clause(tree(T), true),
  110.     in(X, T).
  111.  
  112. in(X, avl(_,X,_)/_ ):-!.
  113. in(X, avl(Left, Root, _)/_ ):-
  114.     gt(Root, X),
  115.     in(X, Left).
  116. in(X, avl(_, Root, Right)/_ ):-
  117.     gt(X, Root),
  118.     in(X, Right).
  119.  
  120. build(File):-
  121.     see(File),
  122.     write('Loading dictionary.\n'),
  123.     build_tree(Tree),
  124.     seen,
  125.     write('Complete.\n'),
  126.     show(Tree).
  127.  
  128. build_tree(Final):-
  129.     build_tree_next(nil/0, Final).
  130.  
  131. build_tree_next(Tree, NewTree):- 
  132.     read(Item),
  133.     (  Item = end_of_file -> true,
  134.        NewTree = Tree
  135.     ;  addavl(Tree, Item, Tree1), 
  136.        build_tree_next(Tree1, NewTree), 
  137.        ! 
  138.     ).
  139.  
  140. /* Test to see where item is to be put. */
  141.  
  142. gt(X, Y):-
  143.     X @>  Y.        
  144.  
  145. eq(X, Y):-
  146.     X == Y,
  147.     !,
  148.     write(X),
  149.     write(' Item already in tree\n').
  150.  
  151. --------------------------------------------------------------
  152. A sample (the whole file has about 500 of them) of the data that 
  153. I am testing my implementation with are facts with the following 
  154. format:
  155.  
  156. cut here
  157. ------------------------------------------------------------------
  158. item(ant).
  159. item(a).
  160. item(zak).
  161. item(john).
  162. item(queen).
  163. item(harry).
  164. item(harvey).
  165. item(jane).
  166. item(james).
  167. item(robert).
  168. item(zoo).
  169. item(felicity).
  170. item(queen0).
  171. item(ant1).
  172.  
  173.  
  174.