BinaryTree.st
author Claus Gittinger <cg@exept.de>
Sun, 05 Aug 2012 11:42:31 +0200
changeset 2770 24caf488ddc1
parent 2763 e4b1ecc6a263
child 2776 f15140d07975
permissions -rw-r--r--
tree node class is private

"
 COPYRIGHT (c) 2003 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic2' }"

Collection subclass:#BinaryTree
	instanceVariableNames:'treeRoot sortBlock'
	classVariableNames:'DefaultSortBlock'
	poolDictionaries:''
	category:'Collections-Ordered-Trees'
!

Object subclass:#BinaryTreeNode
	instanceVariableNames:'data leftSubtree rightSubtree'
	classVariableNames:''
	poolDictionaries:''
	privateIn:BinaryTree
!

!BinaryTree class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2003 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    Loosely based on the Public Domain BinaryTreeNode class from Steve Chepurny.

    WARNING:
        This tree does not reorganize itself. 
        Thus, its performance might degenerate to that of a linked list (see performance).
        The performance is OK, if elements are added in random order and the tree is therefore balanced.
        The worst case is to add elements in order, reverseOrder or zig-zag order.
        Use instances of my subclasses, which balance the tree if in doubt.

    Changes:
        Changed to be Collection-protocol compatible.
        Slight speedup in insert-code.

    [author:]
        Steve Chepurny (original BinaryTreeNode implementation)
        Claus Gittinger (cg@alan)

    [instance variables:]

    [class variables:]

    [see also:]

"
!

examples
"
  a degenerated tree:
                                                                [exBegin]
    |coll|

    coll := BinaryTree new.
    (1 to:10) do:[:i | coll add:i].
    coll addAll:(20 to:30).
    coll inspect   
                                                                [exEnd]

                                                                [exBegin]
    |tree|

    tree := self new.
    tree add:'hello'.
    tree add:'aaaa'.
    tree add:'AAAb'.
    tree add:'aaaC'.
    tree add:'world'.
    tree asOrderedCollection     
                                                                [exEnd]

                                                                [exBegin]
    |tree|

    tree := self sortBlock:[:a :b | a asLowercase < b asLowercase].
    tree add:'hello'.
    tree add:'aaaa'.
    tree add:'AAAb'.
    tree add:'aaaC'.
    tree add:'world'.
    tree asOrderedCollection     
                                                                [exEnd]

  timing examples and benchmarks: see examples in AATree:  


  A functional example of a UCB-CS61A lecture's example.
  The task is to extract all values within a given range (min..max) from
  a binary tree.
  The range 'function' below does this; given a binary tree, a min and max value,
      range(bst, min, max)
  returns an array of all values which are within that range.
  Only the relevant branches of the binary tree are to be visited, of course.
                                                                [exBegin]
    |t rangeNode range|

    t := BinaryTree new.
    t add:54; add:37; add:19; add:45; add:80; add:65; add:91; add:57.

    rangeNode := [:node :min :max |
                |nodeValue leftTree rightTree left right middle|

                leftTree := node leftSubtree.
                rightTree := node rightSubtree.
                nodeValue := node data.

                left := (leftTree notNil and:[nodeValue > min]) 
                            ifTrue:[ rangeNode value:leftTree value:min value:max ]
                            ifFalse:[ #() ].

                right := (rightTree notNil and:[nodeValue < max]) 
                            ifTrue:[ rangeNode value:rightTree value:min value:max ]
                            ifFalse:[ #() ].

                middle := (nodeValue between:min and:max)
                            ifTrue:[ (Array with:nodeValue) ]    
                            ifFalse:[ #() ].

                left, middle, right
        ].
    range := [:tree :min :max |
                rangeNode value:tree rootNode value:min value:max
        ].
    range value:t value:30 value:60.                
                                                                [exEnd]

"
! !

!BinaryTree class methodsFor:'initialization'!

initialize
    "setup the default sortBlock.
     Use #<, since this is the base method in Magnitude."

    "/ only do this once at early startup
    DefaultSortBlock isNil ifTrue:[
        DefaultSortBlock := [:a :b | a < b]
    ]

    "
     BinaryTree initialize
    "
! !

!BinaryTree class methodsFor:'instance creation'!

new
    "return a new instance using the default sortOrder (which is a < b)"

    ^ self basicNew sortBlock:DefaultSortBlock
!

new:n
    "return a new instance using the default sortOrder (which is a < b)"

    ^ self new
!

sortBlock:aTwoArgBlock
    "return a new instance using the given sortBlock (which returns true if a < b)"

    ^ self basicNew sortBlock:aTwoArgBlock

    "
     |tree|

     tree := self sortBlock:[:a :b | a asLowercase < b asLowercase].
     tree add:'hello'.
     tree add:'aaaa'.
     tree add:'AAAb'.
     tree add:'aaaC'.
     tree add:'world'.
     tree asOrderedCollection
    "
! !

!BinaryTree methodsFor:'accessing'!

rootNode
    "return the rootNode of the tree"

    ^ treeRoot
!

sortBlock:something
    "set the sort block.
     This is allowed only before any elements are stored in the tree"

    self assert:treeRoot isNil message:'changing sortBlock in BinaryTree'.
    sortBlock := something.
! !

!BinaryTree methodsFor:'adding & removing'!

add:anObject
    "add anObject to the collection. The object is inserted as defined by the sortBlock"

    |newNode|

    newNode := self treeNodeClass data:anObject.
    treeRoot isNil ifTrue:[
        treeRoot := newNode.
    ] ifFalse:[
        treeRoot insert:newNode sortBlock:sortBlock
    ].
    ^ anObject "sigh - collection protocol"

    "
     BinaryTree withAll:#(16 3 1 0 4 7 9)
     BinaryTree new add:1; add:2; yourself
     BinaryTree with:1 with:2 with:3
    "

    "Modified: / 05-08-2012 / 11:36:42 / cg"
!

includes:anElement
    "return true, if the argument, anObject is contained in the collection.
     Uses #= when comparing; i.e. the search is for an equal object."

    treeRoot isNil ifTrue:[
        ^ false.
    ].
    ^ treeRoot includesValue:anElement sortBlock:sortBlock.

    "
     BinaryTree new 
        addAll:#( 2 1 4.0 3 6 5 7); 
        includes:4           
    "
    "
     BinaryTree new 
        addAll:#( 2 1 4.0 3 6 5 7); 
        includes:4.0           
    "

    "
     BinaryTree new 
        addAll:#(2 1 4 3 6 5 7); 
        includesIdentical:4           
    "

    "
     BinaryTree new 
        addAll:#( 2 1 4.0 3 6 5 7); 
        includesIdentical:4           
    "
!

includesIdentical:anElement
    "return true, if the argument, anObject is contained in the collection.
     Uses #== (instead of #=) when comparing; 
     i.e. the search is for the object itself, not some object being just equal."

    treeRoot isNil ifTrue:[
        ^ false.
    ].
    ^ treeRoot includesIdenticalValue:anElement sortBlock:sortBlock.

    "
     BinaryTree new 
        addAll:#(4 2 1 4.0 3 6 5 7); 
        includesIdentical:4           
    "

    "
     BinaryTree new 
        addAll:#( 2 1 4.0 3 6 5 7); 
        includesIdentical:4           
    "

    "
     BinaryTree new 
        addAll:#(4 2 1 3 6 5 7); 
        includesIdentical:8
    "

    "
     BinaryTree new 
        addAll:#( 2 1 4.0 3 6 5 7); 
        includes:4           
    "
    "
     BinaryTree new 
        addAll:#( 2 1 4.0 3 6 5 7); 
        includes:4.0           
    "
!

remove:oldObject ifAbsent:exceptionValue
    |newRoot|

    treeRoot isNil ifTrue:[
        ^ exceptionValue value.
    ].
    newRoot := treeRoot removeValue:oldObject using:#= sortBlock:sortBlock.
    newRoot isNil ifTrue:[
        treeRoot data = oldObject ifFalse:[
            ^ exceptionValue value.
        ].
    ].
    treeRoot := newRoot.    
    ^ oldObject "sigh - collection protocol"

    "
     BinaryTree new 
        addAll:#(4 2 1 3 6 5 7); 
        removeIdentical:4;
        yourself   
    "

    "
     BinaryTree new 
        addAll:#(4 2 1 3 6 5 7); 
        removeIdentical:7;
        yourself      
    "
!

removeIdentical:oldObject ifAbsent:exceptionValue
    |newRoot|

    treeRoot isNil ifTrue:[
        ^ exceptionValue value.
    ].
    newRoot := treeRoot removeValue:oldObject using:#== sortBlock:sortBlock.
    newRoot isNil ifTrue:[
        treeRoot data == oldObject ifFalse:[
            ^ exceptionValue value.
        ].
    ].
    treeRoot := newRoot.    
    ^ oldObject "sigh - collection protocol"

    "
     BinaryTree new 
        addAll:#(4 2 1 3 6 5 7); 
        removeIdentical:4;
        yourself   
    "

    "
     BinaryTree new 
        addAll:#(4 2 1 3 6 5 7); 
        removeIdentical:7;
        yourself      
    "
! !

!BinaryTree methodsFor:'enumerating'!

do:aBlock
    "enumerate the tree in order"

    treeRoot notNil ifTrue:[
        treeRoot inOrderDo:[:eachNode | aBlock value:(eachNode data)].
    ].

    "
     |coll|

     coll:= OrderedCollection new.
     (BinaryTree withAll:#(5 4 3 2 1 6 7 8 9 0)) do:[:each| coll add:each].
     coll
    "

    "
     |coll|

     coll:= OrderedCollection new.
     (BinaryTree withAll:#(5 4 3 2 1 6 7 8 9 0)) preOrderDo:[:each| coll add:each].
     coll
    "

    "
     |coll|

     coll:= OrderedCollection new.
     (BinaryTree withAll:#(5 4 3 2 1 6 7 8 9 0)) postOrderDo:[:each| coll add:each].
     coll
    "
!

postOrderDo:aBlock
    "enumerate in postOrder - Left, Right, Root"

    treeRoot notNil ifTrue:[
        treeRoot postOrderDo:[:eachNode | aBlock value:(eachNode data)].
    ].
!

preOrderDo:aBlock
    "enumerate in preOrder - Root, Left, Right"

    treeRoot notNil ifTrue:[
        treeRoot preOrderDo:[:eachNode | aBlock value:(eachNode data)].
    ].
! !

!BinaryTree methodsFor:'queries'!

size
    "return the number of tree elements"

    ^ treeRoot size
!

treeNodeClass
    ^ BinaryTreeNode

    "Created: / 05-08-2012 / 11:36:26 / cg"
! !

!BinaryTree::BinaryTreeNode class methodsFor:'documentation'!

copyright
"
    Public domain (1996 published in c.l.s) no limitation on use.

    This class is provided as-is, without any warranty. 
    It is not part of or covered by the ST/X copyright.
"
!

documentation
"
    goody from comp.lang.smalltalk;
    original header:

        Here's a complete implementation of a binary tree class:


    [organization:]
        The National Capital FreeNet, Ottawa, Ontario, Canada

    [author:]
        al938@FreeNet.Carleton.CA (Steve Chepurny)

    [see also:]
        LinkedList Chain
        Link ValueLink ChainLink
"
!

examples
"
  manual building of a tree (but see BinaryTree for a collection-facade):
                                                                        [exBegin]
    |tree|

    tree := BinaryTreeNode data:2.
    tree leftSubtree:(BinaryTreeNode new data:1).
    tree rightSubtree:(BinaryTreeNode new data:3).
    tree printOn:Transcript.
                                                                        [exEnd]

  insertion:
                                                                        [exBegin]
    |tree|

    tree := BinaryTreeNode data:'hello'.
    #('the' 'quick' 'brown' 'fox' 'jumps' 'over' 'the' 'lazy' 'dogs')
    do:[:word |
        tree insert:(BinaryTreeNode data:word).
    ].
    tree inOrderDo:[:node |
        Transcript showCR:node data
    ]
                                                                        [exEnd]
"
!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTree.st,v 1.12 2012-08-05 09:42:31 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTree.st,v 1.12 2012-08-05 09:42:31 cg Exp $'
! !

!BinaryTree::BinaryTreeNode class methodsFor:'instance creation'!

data:data
    "Returns a new binary tree node, holding data"

    ^ self basicNew data:data

    "Modified: 10.5.1996 / 15:00:13 / cg"
    "Created: 10.5.1996 / 15:00:35 / cg"
!

empty
    "Returns a new binary tree with subtrees as binary tree nodes"

    ^ self new
	    leftSubtree: self new;
	    rightSubtree: self new

    "Modified: 10.5.1996 / 15:00:02 / cg"
! !

!BinaryTree::BinaryTreeNode methodsFor:'accessing'!

data
    ^ data
!

data:anObject 
    data := anObject
!

leftSubtree
    ^leftSubtree
!

leftSubtree: aBinaryTree
    leftSubtree := aBinaryTree
!

nextNodeInOrder
    "return the node holding the next value"

    ^ rightSubtree leftMostNode
!

predecessor
    "return the previous value"

    ^ self prevNodeInOrder data
!

prevNodeInOrder
    "return the node holding the previous value"

    ^ leftSubtree rightMostNode
!

rightSubtree
    ^rightSubtree
!

rightSubtree: aBinaryTree
    rightSubtree := aBinaryTree
!

successor
    "return the next value"

    ^ self nextNodeInOrder data
! !

!BinaryTree::BinaryTreeNode methodsFor:'enumeration'!

do: aBlock
    "applies aBlock to each element's data in the binary tree in inorder"

    self inOrderDo:[:eachNode | aBlock value:eachNode data]
!

inOrderDo:aBlock
    "Traverses the elements of the binary tree in
        LEFT - ROOT - RIGHT order, 
     applying a block to each node.

     We use an interative approach here, to avoid VM stack overflow"

    |nextNode stack|

    stack := Stack new.
    nextNode := self.
    [
        |left|

        stack push:nextNode.
        left := nextNode leftSubtree.
        left isNil ifTrue:[
            [
                stack isEmpty ifTrue:[
                    ^ self
                ].
                nextNode := stack pop.
                aBlock value:nextNode.
                nextNode := nextNode rightSubtree.
            ] doWhile:[nextNode isNil]
        ] ifFalse:[
            nextNode := left.
        ].
    ] loop.

    "
      BinaryTree withAll:#(2 16 3 1 0 4 7 9)
    "
!

postOrderDo: aBlock
    "Traverses the elements of the binary tree in
        LEFT - RIGHT - ROOT order, 
     applying a block to each node"

    leftSubtree notNil ifTrue:[
        leftSubtree postOrderDo: aBlock
    ].
    rightSubtree notNil ifTrue:[
        rightSubtree postOrderDo: aBlock
    ].

    aBlock value: self.
!

preOrderDo: aBlock
    "Traverses the elements of the binary tree in
        ROOT - LEFT - RIGHT order, 
     applying a block to each node"

    aBlock value: self.

    leftSubtree notNil ifTrue:[
        leftSubtree preOrderDo: aBlock
    ].
    rightSubtree notNil ifTrue:[
        rightSubtree preOrderDo: aBlock
    ].
! !

!BinaryTree::BinaryTreeNode methodsFor:'insert & delete'!

insert:aBinaryTreeNode
    "insert a node, comparing nodes using a default sort rule"

    ^ self
        insert:aBinaryTreeNode
        sortBlock:[:a :b | a < b]

    "Modified: 10.5.1996 / 15:08:30 / cg"
    "Created: 10.5.1996 / 15:09:44 / cg"
!

insert:newBinaryTreeNode sortBlock:sortBlock
    "insert a node, comparing nodes using sortBlock"

    |node newValue left right|

    "/ the following might be ugly - however, it it slightly faster than the stuff below.
    "/ AND it does not suffer stack exhaustion....
    "/ (we MUST have LCO in smalltalk for this to be automatically faster

    node := self.
    newValue := newBinaryTreeNode data.
    [true] whileTrue:[
        "newValue is less the node data"
        (sortBlock value:newValue value:node data) ifTrue:[
            left := node leftSubtree.
            left isNil ifTrue:[
                node leftSubtree:newBinaryTreeNode.
                ^ self
            ].
            node := left
        ] ifFalse:[
            "newValue is larger or equal than node data"
            right := node rightSubtree.
            "if right data is less than node, we would be jumping back..."
            right isNil ifTrue:[
                node rightSubtree:newBinaryTreeNode.
                ^ self
            ].
            node := right
        ]
    ].
    "not reached"

"/    (sortBlock value:newBinaryTreeNode data value:data) ifTrue:[
"/        leftSubtree isNil ifTrue:[
"/            leftSubtree := newBinaryTreeNode.
"/        ] ifFalse:[
"/            leftSubtree insert:newBinaryTreeNode sortBlock:sortBlock
"/        ]
"/    ] ifFalse:[
"/        rightSubtree isNil ifTrue:[
"/            rightSubtree := newBinaryTreeNode.
"/        ] ifFalse:[
"/            rightSubtree insert:newBinaryTreeNode sortBlock:sortBlock
"/        ]
"/    ]

    "
     BinaryTree withAll:#(16 3 1 0 4 7 9)             
    "
! !

!BinaryTree::BinaryTreeNode methodsFor:'printing'!

printOn: aStream
    "Append the ascii representation to aStream"

    data isNil
        ifTrue: [aStream nextPutAll: '--']
        ifFalse: [
            aStream nextPut: $(.
            data printOn: aStream. aStream nextPut: $ .
            leftSubtree printOn: aStream. aStream nextPut: $ .
            rightSubtree printOn: aStream.
            aStream nextPut: $)]
!

printOn:aStream indent:i
    "Append the graphical ascii representation to aStream"

    data isNil
        ifTrue: [aStream spaces:i. aStream nextPutAll: '--']
        ifFalse: [
            aStream spaces:i. aStream nextPut: $(.
            data printOn: aStream. 
            aStream cr.
            leftSubtree isNil 
                ifTrue:[ aStream spaces:i+2. '--' printOn: aStream]
                ifFalse:[ leftSubtree printOn: aStream indent:i+2 ]. 
            aStream cr.
            rightSubtree isNil 
                ifTrue:[ aStream spaces:i+2. '--' printOn: aStream]
                ifFalse:[ rightSubtree printOn: aStream indent:i+2 ]. 
            aStream nextPut: $)
        ]
! !

!BinaryTree::BinaryTreeNode methodsFor:'private helpers'!

removeLeftRightMostNode
    |rightMost|

    leftSubtree rightSubtree isNil ifTrue:[
        rightMost := leftSubtree.
        leftSubtree := leftSubtree leftSubtree.
        ^ rightMost.
    ].

    ^ leftSubtree removeRightMostNode

    "
     |tree|

     tree := BinaryTreeNode data:4.
     #(2 6 1 3 5 7)
     do:[:word |
         tree insert:(BinaryTreeNode data:word).
     ].
     tree printOn:Transcript indent:0. Transcript cr.
     '---------------------------' printOn:Transcript. Transcript cr.
     tree removeLeftRightMostNode.
     tree printOn:Transcript indent:0. Transcript cr.
    "
!

removeRightMostNode
    |right rr parent|

    rightSubtree isNil ifTrue:[
        self error:'should not happen'
    ].

    parent := self.
    right := rightSubtree.
    [ (rr := right rightSubtree) notNil ] whileTrue:[
        parent := right.
        right := rr.
    ].
    parent rightSubtree:(right leftSubtree).
    ^ right.

    "
     |tree|

     tree := BinaryTreeNode data:4.
     #(2 6 1 3 5 7)
     do:[:word |
         tree insert:(BinaryTreeNode data:word).
     ].
     Transcript showCR:tree.
     Transcript showCR:(tree removeLeftRightMostNode). 
     Transcript showCR:tree.
    "
!

removeValue:oldValue using:compareOp sortBlock:sortBlock
    "remove a value - returns a new treeNode, or nil if the value is not in the tree"

    |thisIsMyNode newTop newLeft newRight|

    "/ speed hack - avoids message sends (and also better inline caching)
    compareOp == #== ifTrue:[
        thisIsMyNode := (data == oldValue).
    ] ifFalse:[
        compareOp == #= ifTrue:[
            thisIsMyNode := (data = oldValue).
        ] ifFalse:[
            thisIsMyNode := data perform:compareOp with:oldValue.
        ].
    ].

    thisIsMyNode ifTrue:[
        leftSubtree isNil ifTrue:[
            ^ rightSubtree
        ].
        rightSubtree isNil ifTrue:[
            ^ leftSubtree
        ].
        newTop := self removeLeftRightMostNode.
        newTop leftSubtree:leftSubtree.
        newTop rightSubtree:rightSubtree.
        ^ newTop.
    ].

    (sortBlock value:oldValue value:data) ifTrue:[
        "/ the value should be in the left part.
        leftSubtree isNil ifTrue:[
            ^ nil
        ].
        newLeft := leftSubtree removeValue:oldValue using:compareOp sortBlock:sortBlock.
        newLeft isNil ifTrue:[
            (leftSubtree data perform:compareOp with:oldValue) ifFalse:[
                ^ nil
            ].
        ].
        leftSubtree := newLeft.
    ] ifFalse:[
        "/ the value should be in the right part.
        rightSubtree isNil ifTrue:[
            ^ nil
        ].
        newRight := rightSubtree removeValue:oldValue using:compareOp sortBlock:sortBlock.
        newRight isNil ifTrue:[
            (rightSubtree data perform:compareOp with:oldValue) ifFalse:[
                ^ nil
            ].
        ].
        rightSubtree := newRight.
    ].
    ^ self. 
! !

!BinaryTree::BinaryTreeNode methodsFor:'queries'!

depth
    "Returns the depth of the binary tree (0 for leafs)"

    ^ self level - 1.
!

getTreeWithAnInteger: anInteger
    "Private - Returns the BinaryTree with data anInteger.  
     If anInteger not in the tree it returns nil."

    self inOrderDo: [:each| each data = anInteger ifTrue:[^each]].
    ^nil.
!

inOrderSuccessor
    "Returns the in-order successor the of receiver.
     (that is the leftMost node on the right side)
     If receiver is empty then returns the receiver."

    rightSubtree isNil ifTrue:[^ self].
    ^ rightSubtree leftMostNode
!

includesIdenticalValue:aValue sortBlock:sortBlock
    "return true, if aValue is contained as some node's data"

    data == aValue ifTrue:[ ^ true ].
    (sortBlock value:aValue value:data) ifTrue:[
        leftSubtree isNil ifTrue:[
            ^ false
        ].
        ^ leftSubtree includesIdenticalValue:aValue sortBlock:sortBlock.
    ].
    rightSubtree isNil ifTrue:[
        ^ false
    ].
    ^ rightSubtree includesIdenticalValue:aValue sortBlock:sortBlock.
!

includesValue:aValue sortBlock:sortBlock
    "return true, if some node's data is equal to aValue"

    data = aValue ifTrue:[ ^ true ].

    (sortBlock value:aValue value:data) ifTrue:[
        leftSubtree isNil ifTrue:[
            ^ false
        ].
        ^ leftSubtree includesValue:aValue sortBlock:sortBlock.
    ].
    rightSubtree isNil ifTrue:[
        ^ false
    ].
    ^ rightSubtree includesValue:aValue sortBlock:sortBlock.
!

isEmpty
    "returns true if the binary tree is empty and false otherwise"

    ^ data isNil
!

isLeaf
    "Returns true if self is a leaf"

    ^ ((leftSubtree isNil) and: [rightSubtree isNil])
!

leftMostNode
    "Returns the leftMost (smallest-valued) node"

    leftSubtree isNil ifTrue:[^ self].
    ^ leftSubtree leftMostNode
!

level
    "Returns the level of the binary tree (1 for leafs)"

    |l|

    l := 0.
    leftSubtree notNil ifTrue:[
        l := leftSubtree level
    ].
    rightSubtree notNil ifTrue:[
        l := l max:(rightSubtree level)
    ].
    ^ l + 1
!

rightMostNode
    "Returns the rightMost (largest-valued) node"

    rightSubtree isNil ifTrue:[^ self].
    ^ rightSubtree rightMostNode
!

size
    "Returns the size of the binary tree"

    ^ 1
    + (leftSubtree isNil ifTrue: [0] ifFalse:[leftSubtree size])
    + (rightSubtree isNil ifTrue: [0] ifFalse:[rightSubtree size])
! !

!BinaryTree class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTree.st,v 1.12 2012-08-05 09:42:31 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTree.st,v 1.12 2012-08-05 09:42:31 cg Exp $'
! !

BinaryTree initialize!