BinaryTreeNode.st
changeset 2778 7f379c407160
child 2781 bf6e167105ee
equal deleted inserted replaced
2777:06c0bd66713f 2778:7f379c407160
       
     1 "
       
     2     Public domain (1996 published in c.l.s) no limitation on use.
       
     3 
       
     4     This class is provided as-is, without any warranty. 
       
     5     It is not part of or covered by the ST/X copyright.
       
     6 "
       
     7 'From Smalltalk/X, Version:6.2.2 on 05-08-2012 at 18:49:10'                     !
       
     8 
       
     9 "{ Package: 'stx:libbasic2' }"
       
    10 
       
    11 Object subclass:#BinaryTreeNode
       
    12 	instanceVariableNames:'data leftSubtree rightSubtree'
       
    13 	classVariableNames:''
       
    14 	poolDictionaries:''
       
    15 	category:'Collections-Ordered-Trees'
       
    16 !
       
    17 
       
    18 !BinaryTreeNode class methodsFor:'documentation'!
       
    19 
       
    20 copyright
       
    21 "
       
    22     Public domain (1996 published in c.l.s) no limitation on use.
       
    23 
       
    24     This class is provided as-is, without any warranty. 
       
    25     It is not part of or covered by the ST/X copyright.
       
    26 "
       
    27 !
       
    28 
       
    29 documentation
       
    30 "
       
    31     goody from comp.lang.smalltalk;
       
    32     original header:
       
    33 
       
    34         Here's a complete implementation of a binary tree class:
       
    35 
       
    36 
       
    37     [organization:]
       
    38         The National Capital FreeNet, Ottawa, Ontario, Canada
       
    39 
       
    40     [author:]
       
    41         al938@FreeNet.Carleton.CA (Steve Chepurny)
       
    42 
       
    43     [see also:]
       
    44         LinkedList Chain
       
    45         Link ValueLink ChainLink
       
    46 "
       
    47 !
       
    48 
       
    49 examples
       
    50 "
       
    51   manual building of a tree (but see BinaryTree for a collection-facade):
       
    52                                                                         [exBegin]
       
    53     |tree|
       
    54 
       
    55     tree := BinaryTreeNode data:2.
       
    56     tree leftSubtree:(BinaryTreeNode new data:1).
       
    57     tree rightSubtree:(BinaryTreeNode new data:3).
       
    58     tree printOn:Transcript.
       
    59                                                                         [exEnd]
       
    60 
       
    61   insertion:
       
    62                                                                         [exBegin]
       
    63     |tree|
       
    64 
       
    65     tree := BinaryTreeNode data:'hello'.
       
    66     #('the' 'quick' 'brown' 'fox' 'jumps' 'over' 'the' 'lazy' 'dogs')
       
    67     do:[:word |
       
    68         tree insert:(BinaryTreeNode data:word).
       
    69     ].
       
    70     tree inOrderDo:[:node |
       
    71         Transcript showCR:node data
       
    72     ]
       
    73                                                                         [exEnd]
       
    74 "
       
    75 ! !
       
    76 
       
    77 !BinaryTreeNode class methodsFor:'instance creation'!
       
    78 
       
    79 data:data
       
    80     "Returns a new binary tree node, holding data"
       
    81 
       
    82     ^ self basicNew data:data
       
    83 
       
    84     "Modified: 10.5.1996 / 15:00:13 / cg"
       
    85     "Created: 10.5.1996 / 15:00:35 / cg"
       
    86 !
       
    87 
       
    88 empty
       
    89     "Returns a new binary tree with subtrees as binary tree nodes"
       
    90 
       
    91     ^ self new
       
    92 	    leftSubtree: self new;
       
    93 	    rightSubtree: self new
       
    94 
       
    95     "Modified: 10.5.1996 / 15:00:02 / cg"
       
    96 ! !
       
    97 
       
    98 !BinaryTreeNode methodsFor:'accessing'!
       
    99 
       
   100 data
       
   101     ^ data
       
   102 !
       
   103 
       
   104 data:anObject 
       
   105     data := anObject
       
   106 !
       
   107 
       
   108 leftSubtree
       
   109     ^leftSubtree
       
   110 !
       
   111 
       
   112 leftSubtree: aBinaryTree
       
   113     leftSubtree := aBinaryTree
       
   114 !
       
   115 
       
   116 nextNodeInOrder
       
   117     "return the node holding the next value"
       
   118 
       
   119     ^ rightSubtree leftMostNode
       
   120 !
       
   121 
       
   122 predecessor
       
   123     "return the previous value"
       
   124 
       
   125     ^ self prevNodeInOrder data
       
   126 !
       
   127 
       
   128 prevNodeInOrder
       
   129     "return the node holding the previous value"
       
   130 
       
   131     ^ leftSubtree rightMostNode
       
   132 !
       
   133 
       
   134 rightSubtree
       
   135     ^rightSubtree
       
   136 !
       
   137 
       
   138 rightSubtree: aBinaryTree
       
   139     rightSubtree := aBinaryTree
       
   140 !
       
   141 
       
   142 successor
       
   143     "return the next value"
       
   144 
       
   145     ^ self nextNodeInOrder data
       
   146 ! !
       
   147 
       
   148 !BinaryTreeNode methodsFor:'enumeration'!
       
   149 
       
   150 do: aBlock
       
   151     "applies aBlock to each element's data in the binary tree in inorder"
       
   152 
       
   153     self inOrderDo:[:eachNode | aBlock value:eachNode data]
       
   154 !
       
   155 
       
   156 inOrderDo:aBlock
       
   157     "Traverses the elements of the binary tree in
       
   158         LEFT - ROOT - RIGHT order, 
       
   159      applying a block to each node.
       
   160 
       
   161      We use an interative approach here, to avoid VM stack overflow"
       
   162 
       
   163     |nextNode stack|
       
   164 
       
   165     stack := Stack new.
       
   166     nextNode := self.
       
   167     [
       
   168         |left|
       
   169 
       
   170         stack push:nextNode.
       
   171         left := nextNode leftSubtree.
       
   172         left isNil ifTrue:[
       
   173             [
       
   174                 stack isEmpty ifTrue:[
       
   175                     ^ self
       
   176                 ].
       
   177                 nextNode := stack pop.
       
   178                 aBlock value:nextNode.
       
   179                 nextNode := nextNode rightSubtree.
       
   180             ] doWhile:[nextNode isNil]
       
   181         ] ifFalse:[
       
   182             nextNode := left.
       
   183         ].
       
   184     ] loop.
       
   185 
       
   186     "
       
   187       BinaryTree withAll:#(2 16 3 1 0 4 7 9)
       
   188     "
       
   189 !
       
   190 
       
   191 postOrderDo: aBlock
       
   192     "Traverses the elements of the binary tree in
       
   193         LEFT - RIGHT - ROOT order, 
       
   194      applying a block to each node"
       
   195 
       
   196     leftSubtree notNil ifTrue:[
       
   197         leftSubtree postOrderDo: aBlock
       
   198     ].
       
   199     rightSubtree notNil ifTrue:[
       
   200         rightSubtree postOrderDo: aBlock
       
   201     ].
       
   202 
       
   203     aBlock value: self.
       
   204 !
       
   205 
       
   206 preOrderDo: aBlock
       
   207     "Traverses the elements of the binary tree in
       
   208         ROOT - LEFT - RIGHT order, 
       
   209      applying a block to each node"
       
   210 
       
   211     aBlock value: self.
       
   212 
       
   213     leftSubtree notNil ifTrue:[
       
   214         leftSubtree preOrderDo: aBlock
       
   215     ].
       
   216     rightSubtree notNil ifTrue:[
       
   217         rightSubtree preOrderDo: aBlock
       
   218     ].
       
   219 ! !
       
   220 
       
   221 !BinaryTreeNode methodsFor:'insert & delete'!
       
   222 
       
   223 insert:aBinaryTreeNode
       
   224     "insert a node, comparing nodes using a default sort rule"
       
   225 
       
   226     ^ self
       
   227         insert:aBinaryTreeNode
       
   228         sortBlock:[:a :b | a < b]
       
   229 
       
   230     "Modified: 10.5.1996 / 15:08:30 / cg"
       
   231     "Created: 10.5.1996 / 15:09:44 / cg"
       
   232 !
       
   233 
       
   234 insert:newBinaryTreeNode sortBlock:sortBlock
       
   235     "insert a node, comparing nodes using sortBlock"
       
   236 
       
   237     |node newValue left right|
       
   238 
       
   239     "/ the following might be ugly - however, it it slightly faster than the stuff below.
       
   240     "/ AND it does not suffer stack exhaustion....
       
   241     "/ (we MUST have LCO in smalltalk for this to be automatically faster
       
   242 
       
   243     node := self.
       
   244     newValue := newBinaryTreeNode data.
       
   245     [true] whileTrue:[
       
   246         "newValue is less the node data"
       
   247         (sortBlock value:newValue value:node data) ifTrue:[
       
   248             left := node leftSubtree.
       
   249             left isNil ifTrue:[
       
   250                 node leftSubtree:newBinaryTreeNode.
       
   251                 ^ self
       
   252             ].
       
   253             node := left
       
   254         ] ifFalse:[
       
   255             "newValue is larger or equal than node data"
       
   256             right := node rightSubtree.
       
   257             "if right data is less than node, we would be jumping back..."
       
   258             right isNil ifTrue:[
       
   259                 node rightSubtree:newBinaryTreeNode.
       
   260                 ^ self
       
   261             ].
       
   262             node := right
       
   263         ]
       
   264     ].
       
   265     "not reached"
       
   266 
       
   267 "/    (sortBlock value:newBinaryTreeNode data value:data) ifTrue:[
       
   268 "/        leftSubtree isNil ifTrue:[
       
   269 "/            leftSubtree := newBinaryTreeNode.
       
   270 "/        ] ifFalse:[
       
   271 "/            leftSubtree insert:newBinaryTreeNode sortBlock:sortBlock
       
   272 "/        ]
       
   273 "/    ] ifFalse:[
       
   274 "/        rightSubtree isNil ifTrue:[
       
   275 "/            rightSubtree := newBinaryTreeNode.
       
   276 "/        ] ifFalse:[
       
   277 "/            rightSubtree insert:newBinaryTreeNode sortBlock:sortBlock
       
   278 "/        ]
       
   279 "/    ]
       
   280 
       
   281     "
       
   282      BinaryTree withAll:#(16 3 1 0 4 7 9)             
       
   283     "
       
   284 ! !
       
   285 
       
   286 !BinaryTreeNode methodsFor:'printing'!
       
   287 
       
   288 printOn: aStream
       
   289     "Append the ascii representation to aStream"
       
   290 
       
   291     data isNil
       
   292         ifTrue: [aStream nextPutAll: '--']
       
   293         ifFalse: [
       
   294             aStream nextPut: $(.
       
   295             data printOn: aStream. aStream nextPut: $ .
       
   296             leftSubtree printOn: aStream. aStream nextPut: $ .
       
   297             rightSubtree printOn: aStream.
       
   298             aStream nextPut: $)]
       
   299 !
       
   300 
       
   301 printOn:aStream indent:i
       
   302     "Append the graphical ascii representation to aStream"
       
   303 
       
   304     data isNil
       
   305         ifTrue: [aStream spaces:i. aStream nextPutAll: '--']
       
   306         ifFalse: [
       
   307             aStream spaces:i. aStream nextPut: $(.
       
   308             data printOn: aStream. 
       
   309             aStream cr.
       
   310             leftSubtree isNil 
       
   311                 ifTrue:[ aStream spaces:i+2. '--' printOn: aStream]
       
   312                 ifFalse:[ leftSubtree printOn: aStream indent:i+2 ]. 
       
   313             aStream cr.
       
   314             rightSubtree isNil 
       
   315                 ifTrue:[ aStream spaces:i+2. '--' printOn: aStream]
       
   316                 ifFalse:[ rightSubtree printOn: aStream indent:i+2 ]. 
       
   317             aStream nextPut: $)
       
   318         ]
       
   319 ! !
       
   320 
       
   321 !BinaryTreeNode methodsFor:'private helpers'!
       
   322 
       
   323 removeLeftRightMostNode
       
   324     |rightMost|
       
   325 
       
   326     leftSubtree rightSubtree isNil ifTrue:[
       
   327         rightMost := leftSubtree.
       
   328         leftSubtree := leftSubtree leftSubtree.
       
   329         ^ rightMost.
       
   330     ].
       
   331 
       
   332     ^ leftSubtree removeRightMostNode
       
   333 
       
   334     "
       
   335      |tree|
       
   336 
       
   337      tree := BinaryTreeNode data:4.
       
   338      #(2 6 1 3 5 7)
       
   339      do:[:word |
       
   340          tree insert:(BinaryTreeNode data:word).
       
   341      ].
       
   342      tree printOn:Transcript indent:0. Transcript cr.
       
   343      '---------------------------' printOn:Transcript. Transcript cr.
       
   344      tree removeLeftRightMostNode.
       
   345      tree printOn:Transcript indent:0. Transcript cr.
       
   346     "
       
   347 !
       
   348 
       
   349 removeRightMostNode
       
   350     |right rr parent|
       
   351 
       
   352     rightSubtree isNil ifTrue:[
       
   353         self error:'should not happen'
       
   354     ].
       
   355 
       
   356     parent := self.
       
   357     right := rightSubtree.
       
   358     [ (rr := right rightSubtree) notNil ] whileTrue:[
       
   359         parent := right.
       
   360         right := rr.
       
   361     ].
       
   362     parent rightSubtree:(right leftSubtree).
       
   363     ^ right.
       
   364 
       
   365     "
       
   366      |tree|
       
   367 
       
   368      tree := BinaryTreeNode data:4.
       
   369      #(2 6 1 3 5 7)
       
   370      do:[:word |
       
   371          tree insert:(BinaryTreeNode data:word).
       
   372      ].
       
   373      Transcript showCR:tree.
       
   374      Transcript showCR:(tree removeLeftRightMostNode). 
       
   375      Transcript showCR:tree.
       
   376     "
       
   377 !
       
   378 
       
   379 removeValue:oldValue using:compareOp sortBlock:sortBlock
       
   380     "remove a value - returns a new treeNode, or nil if the value is not in the tree"
       
   381 
       
   382     |thisIsMyNode newTop newLeft newRight|
       
   383 
       
   384     "/ speed hack - avoids message sends (and also better inline caching)
       
   385     compareOp == #== ifTrue:[
       
   386         thisIsMyNode := (data == oldValue).
       
   387     ] ifFalse:[
       
   388         compareOp == #= ifTrue:[
       
   389             thisIsMyNode := (data = oldValue).
       
   390         ] ifFalse:[
       
   391             thisIsMyNode := data perform:compareOp with:oldValue.
       
   392         ].
       
   393     ].
       
   394 
       
   395     thisIsMyNode ifTrue:[
       
   396         leftSubtree isNil ifTrue:[
       
   397             ^ rightSubtree
       
   398         ].
       
   399         rightSubtree isNil ifTrue:[
       
   400             ^ leftSubtree
       
   401         ].
       
   402         newTop := self removeLeftRightMostNode.
       
   403         newTop leftSubtree:leftSubtree.
       
   404         newTop rightSubtree:rightSubtree.
       
   405         ^ newTop.
       
   406     ].
       
   407 
       
   408     (sortBlock value:oldValue value:data) ifTrue:[
       
   409         "/ the value should be in the left part.
       
   410         leftSubtree isNil ifTrue:[
       
   411             ^ nil
       
   412         ].
       
   413         newLeft := leftSubtree removeValue:oldValue using:compareOp sortBlock:sortBlock.
       
   414         newLeft isNil ifTrue:[
       
   415             (leftSubtree data perform:compareOp with:oldValue) ifFalse:[
       
   416                 ^ nil
       
   417             ].
       
   418         ].
       
   419         leftSubtree := newLeft.
       
   420     ] ifFalse:[
       
   421         "/ the value should be in the right part.
       
   422         rightSubtree isNil ifTrue:[
       
   423             ^ nil
       
   424         ].
       
   425         newRight := rightSubtree removeValue:oldValue using:compareOp sortBlock:sortBlock.
       
   426         newRight isNil ifTrue:[
       
   427             (rightSubtree data perform:compareOp with:oldValue) ifFalse:[
       
   428                 ^ nil
       
   429             ].
       
   430         ].
       
   431         rightSubtree := newRight.
       
   432     ].
       
   433     ^ self. 
       
   434 ! !
       
   435 
       
   436 !BinaryTreeNode methodsFor:'queries'!
       
   437 
       
   438 depth
       
   439     "Returns the depth of the binary tree (0 for leafs)"
       
   440 
       
   441     ^ self level - 1.
       
   442 !
       
   443 
       
   444 getTreeWithAnInteger: anInteger
       
   445     "Private - Returns the BinaryTree with data anInteger.  
       
   446      If anInteger not in the tree it returns nil."
       
   447 
       
   448     self inOrderDo: [:each| each data = anInteger ifTrue:[^each]].
       
   449     ^nil.
       
   450 !
       
   451 
       
   452 inOrderSuccessor
       
   453     "Returns the in-order successor the of receiver.
       
   454      (that is the leftMost node on the right side)
       
   455      If receiver is empty then returns the receiver."
       
   456 
       
   457     rightSubtree isNil ifTrue:[^ self].
       
   458     ^ rightSubtree leftMostNode
       
   459 !
       
   460 
       
   461 includesIdenticalValue:aValue sortBlock:sortBlock
       
   462     "return true, if aValue is contained as some node's data"
       
   463 
       
   464     data == aValue ifTrue:[ ^ true ].
       
   465     (sortBlock value:aValue value:data) ifTrue:[
       
   466         leftSubtree isNil ifTrue:[
       
   467             ^ false
       
   468         ].
       
   469         ^ leftSubtree includesIdenticalValue:aValue sortBlock:sortBlock.
       
   470     ].
       
   471     rightSubtree isNil ifTrue:[
       
   472         ^ false
       
   473     ].
       
   474     ^ rightSubtree includesIdenticalValue:aValue sortBlock:sortBlock.
       
   475 !
       
   476 
       
   477 includesValue:aValue sortBlock:sortBlock
       
   478     "return true, if some node's data is equal to aValue"
       
   479 
       
   480     data = aValue ifTrue:[ ^ true ].
       
   481 
       
   482     (sortBlock value:aValue value:data) ifTrue:[
       
   483         leftSubtree isNil ifTrue:[
       
   484             ^ false
       
   485         ].
       
   486         ^ leftSubtree includesValue:aValue sortBlock:sortBlock.
       
   487     ].
       
   488     rightSubtree isNil ifTrue:[
       
   489         ^ false
       
   490     ].
       
   491     ^ rightSubtree includesValue:aValue sortBlock:sortBlock.
       
   492 !
       
   493 
       
   494 isEmpty
       
   495     "returns true if the binary tree is empty and false otherwise"
       
   496 
       
   497     ^ data isNil
       
   498 !
       
   499 
       
   500 isLeaf
       
   501     "Returns true if self is a leaf"
       
   502 
       
   503     ^ ((leftSubtree isNil) and: [rightSubtree isNil])
       
   504 !
       
   505 
       
   506 leftMostNode
       
   507     "Returns the leftMost (smallest-valued) node"
       
   508 
       
   509     leftSubtree isNil ifTrue:[^ self].
       
   510     ^ leftSubtree leftMostNode
       
   511 !
       
   512 
       
   513 level
       
   514     "Returns the level of the binary tree (1 for leafs)"
       
   515 
       
   516     |l|
       
   517 
       
   518     l := 0.
       
   519     leftSubtree notNil ifTrue:[
       
   520         l := leftSubtree level
       
   521     ].
       
   522     rightSubtree notNil ifTrue:[
       
   523         l := l max:(rightSubtree level)
       
   524     ].
       
   525     ^ l + 1
       
   526 !
       
   527 
       
   528 rightMostNode
       
   529     "Returns the rightMost (largest-valued) node"
       
   530 
       
   531     rightSubtree isNil ifTrue:[^ self].
       
   532     ^ rightSubtree rightMostNode
       
   533 !
       
   534 
       
   535 size
       
   536     "Returns the size of the binary tree"
       
   537 
       
   538     ^ 1
       
   539     + (leftSubtree isNil ifTrue: [0] ifFalse:[leftSubtree size])
       
   540     + (rightSubtree isNil ifTrue: [0] ifFalse:[rightSubtree size])
       
   541 ! !
       
   542 
       
   543 !BinaryTreeNode class methodsFor:'documentation'!
       
   544 
       
   545 version
       
   546     ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTreeNode.st,v 1.6 2012-08-05 16:49:40 cg Exp $'
       
   547 !
       
   548 
       
   549 version_CVS
       
   550     ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTreeNode.st,v 1.6 2012-08-05 16:49:40 cg Exp $'
       
   551 ! !