BinaryTree.st
author Claus Gittinger <cg@exept.de>
Mon, 28 Sep 2009 18:16:39 +0200
changeset 2264 8407f28876f1
parent 2262 b9a5edc20d13
child 2374 3530cb215730
permissions -rw-r--r--
*** empty log message ***

"
 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'
!

!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
"
                                                                [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]

"
!

performance
"
    Time to insert random 100000 individually into SortedCollection: 6037ms
    Time to insert random 100000 en-bloque into SortedCollection: 172ms
    Time to insert in order 100000 individually into SortedCollection: 31ms
    Time to insert in order 100000 en-bloque into SortedCollection: 125ms
    Time to insert in reverse order 100000 individually into SortedCollection: 93ms
    Time to insert in reverse order 100000 en-bloque into SortedCollection: 125ms
    Time to remove in random order 100000 from SortedCollection: 6380ms
    Time to remove in order 100000 from SortedCollection: 109ms
    Time to remove in reverse order 100000 from SortedCollection: 125ms

    Time to insert random 100000 individually into AATree: 281ms
    Time to insert random 100000 en-bloque into AATree: 265ms
    Time to insert in order 100000 individually into AATree: 281ms
    Time to insert in order 100000 en-bloque into AATree: 328ms
    Time to insert in reverse order 100000 individually into AATree: 203ms
    Time to insert in reverse order 100000 en-bloque into AATree: 218ms
    Time to remove in random order 100000 from AATree: 452ms
    Time to remove in order 100000 from AATree: 312ms
    TSourceCodeManager [warning]: class `CollectionBenchmarks' has neither source nor compiled-in info
    ime to remove in reverse order 100000 from AATree: 499ms

    Time to insert random 100000 individually into BinaryTree: 156ms
    Time to insert random 100000 en-bloque into BinaryTree: 156ms
    Time to insert in order 100000 individually into BinaryTree: 195921ms
    Time to insert in order 100000 en-bloque into BinaryTree: 205266ms
    Time to insert in reverse order 100000 individually into BinaryTree: 202271ms
    Time to insert in reverse order 100000 en-bloque into BinaryTree: 197684ms
    Time to remove in random order 100000 from BinaryTree: 234ms
    Time to remove in order 100000 from BinaryTree: 78ms
    Time to remove in reverse order 100000 from BinaryTree: 78ms
"
! !

!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 := BinaryTreeNode 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
    "
!

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
! !

!BinaryTree class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/BinaryTree.st,v 1.9 2009-09-28 16:16:39 cg Exp $'
! !

BinaryTree initialize!