![]() |
CS 535 Object-Oriented Programming & Design Fall Semester, 2001 Assignment 4 Comments |
|
---|---|---|
© 2001, All Rights Reserved, SDSU & Roger Whitney San Diego State University -- This page last updated 30-Oct-01 |
positives ^(self select: [:each | each > 0]) size
Smalltalk.CS535 defineClass: #Node superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'key value left right ' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment' key ^key key: aMagnitude key := aMagnitude left ^left left: aNode left := aNode right ^right right: aNode right := aNode value ^value value: anObject value := anObject
Node>>printOn: aStream aStream nextPutAll: '('; print: left; print: key; print: right; nextPutAll: ')'
Node class>>key: aMagnitude value: anObject ^super new setKey: aMagnitude setValue: anObject
newNode := Node new. newNode key: aKey; value: aValue. currentNode left: newNode.This can now be replaced by:
newNode := Node key: aKey value: aValue. currentNode left: newNode.
currentNode left: (Node key: aKey value: aValue).
Smalltalk.CS535 defineClass: #Node superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'key value left right parent classInstanceVariableNames: '' imports: '' category: 'Course-Assignment'
left: aNode left := aNode. aNode parent: self right: aNode right := aNode aNode parent: selfNow one can forget about setting parent pointers in nodes
currentNode left: aNode. aNode parent: currentNodeWith
currentNode left: aNode.
Smalltalk.CS535 defineClass: #Node superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'key value left right ' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment'
Category |
Methods |
accessing |
at: at:put: |
enumeration |
keysAndValuesDo: |
initialize |
setKey:setValue: |
printing |
printOn: |
private |
keyNotFoundError: |
key: aKey value: anObject ^super new setKey: aKey setValue: anObject
keyNotFoundException ^KeyedCollection keyNotFoundSignal
CS535.Node methodsFor: 'initialize'
setKey: aKey setValue: anObject key := aKey. value := anObject
at: aKey aKey = key ifTrue: [^value]. aKey < key ifTrue: [left isNil ifTrue: [self keyNotFoundError: aKey]. ^left at: aKey]. aKey > key ifTrue: [right isNil ifTrue: [self keyNotFoundError: aKey]. ^right at: aKey].
at: aKey put: anObject aKey = key ifTrue: [^value := anObject]. aKey < key ifTrue: [left isNil ifTrue: [left := self class key: aKey value: anObject. ^anObject]. ^left at: aKey put: anObject]. aKey > key ifTrue: [right isNil ifTrue: [right := self class key: aKey value: anObject. ^anObject]. ^right at: aKey put: anObject]
keysAndValuesDo: aBlock "Block has two parameters - key then value" left notNil ifTrue:[left keysAndValuesDo: aBlock]. aBlock value: key value: value. right notNil ifTrue: [right keysAndValuesDo: aBlock]
CS535.Node methodsFor: 'printing'
printOn: aStream aStream nextPut: $(; print: left; print: key; print: right; nextPut: $)CS535.Node methodsFor: 'private'
keyNotFoundError: missingKey "Raise a signal indicating that the key was not found." ^self class keyNotFoundException raiseWith: missingKey
Smalltalk.CS535 defineClass: #BinarySearchTree superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'root ' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment' CS535.BinarySearchTree class methodsFor: 'constants'
keyNotFoundException ^KeyedCollection keyNotFoundSignal
CS535.BinarySearchTree class methodsFor: 'instance creation'
keys: keyCollection values: objectCollection | tree | tree := super new. tree addKeys: keyCollection withValues: objectCollection. ^tree
CS535.BinarySearchTree methodsFor: 'accessing'
addKeys: keyCollection withValues: objectCollection keyCollection with: objectCollection do: [:key :value | self at: key put: value]
at: aKey root isNil ifTrue: [self keyNotFoundError: aKey]. ^root at: aKey
at: aKey put: anObject aKey isNil ifTrue: [^self subscriptBoundsError: aKey]. root isNil ifTrue: [root := Node key: aKey value: anObject. ^anObject]. ^root at: aKey put: anObject
size | nodeCount | nodeCount := 0. self do: [:each | nodeCount := nodeCount + 1]. ^nodeCount.
CS535.BinarySearchTree methodsFor: 'enumeration'
detect: aBlock ^self detect: aBlock ifNone: [self notFoundError]
detect: aBlock ifNone: exceptionBlock self do: [:each | (aBlock value: each) ifTrue: [^each]]. ^exceptionBlock value
do: aBlock "Block has one parameter - value of each node" root isNil ifTrue:[^nil]. root keysAndValuesDo: [:key :value | aBlock value: value]
CS535.BinarySearchTree methodsFor: 'printing'
printOn: aStream aStream nextPutAll: 'BST('; print: root; nextPut: $)
CS535.BinarySearchTree methodsFor: 'private'
keyNotFoundError: missingKey "Raise a signal indicating that the key was not found."
^self class keyNotFoundException raiseWith: missingKey
notFoundError "Raise a signal indicating that an object is not in the collection."
^self class notFoundSignal raise
Smalltalk.CS535 defineClass: #NilNode superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'parent ' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment'
keyNotFoundException ^KeyedCollection keyNotFoundSignal
new self error: 'Use parent: to create an instance of ' , self name
parent: aNodeOrTree ^super new setParent: aNodeOrTree
at: aKey self keyNotFoundError: aKey
at: aKey put: anObject parent replaceNode: self with: (Node key: aKey value: anObject). ^anObject
keysAndValuesDo: aBlock "Block has two parameters - key then value"
setParent: aNodeOrTree parent := aNodeOrTree
printOn: aStream
keyNotFoundError: missingKey "Raise a signal indicating that the key was not found." ^self class keyNotFoundException raiseWith: missingKey
Smalltalk.CS535 defineClass: #Node superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'key value left right ' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment'
key: aKey value: anObject ^super new setKey: aKey setValue: anObject
setKey: aKey setValue: anObject key := aKey. value := anObject. left := NilNode parent: self. right := NilNode parent: self.
at: aKey aKey = key ifTrue: [^value]. aKey < key ifTrue: [^left at: aKey]. aKey > key ifTrue: [^right at: aKey].
at: aKey put: anObject aKey = key ifTrue: [^value := anObject]. aKey < key ifTrue: [^left at: aKey put: anObject]. aKey > key ifTrue: [^right at: aKey put: anObject]
keysAndValuesDo: aBlock "Block has two parameters - key then value" left keysAndValuesDo: aBlock. aBlock value: key value: value. right keysAndValuesDo: aBlock
printOn: aStream aStream nextPut: $(; print: left; print: key; print: right; nextPut: $)
replaceNode: existingNode with: newNode existingNode == left ifTrue:[left := newNode]. existingNode == right ifTrue:[right := newNode].
Smalltalk.CS535 defineClass: #BinarySearchTree superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'root ' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment'
keys: keyCollection values: objectCollection | tree | tree := self new. tree addKeys: keyCollection withValues: objectCollection. ^tree
new ^super new initialize
addKeys: keyCollection withValues: objectCollection keyCollection with: objectCollection do: [:key :value | self at: key put: value]
at: aKey ^root at: aKey
at: aKey put: anObject aKey isNil ifTrue: [^self subscriptBoundsError: aKey]. ^root at: aKey put: anObject
size | nodeCount | nodeCount := 0. self do: [:each | nodeCount := nodeCount + 1]. ^nodeCount.
notFoundError "Raise a signal indicating that an object is not in the collection."
^self class notFoundSignal raise
replaceNode: existingNode with: newNode root := newNode
detect: aBlock ^self detect: aBlock ifNone: [self notFoundError]
detect: aBlock ifNone: exceptionBlock self do: [:each | (aBlock value: each) ifTrue: [^each]]. ^exceptionBlock value
do: aBlock "Block has one parameter - value of each node" root keysAndValuesDo: [:key :value | aBlock value: value]
printOn: aStream aStream nextPutAll: 'BST('; print: root; nextPut: $)
initialize root := NilNode parent: self
(currentNode isNil) ifTrue: [^nil] ifFalse: [^currentNode value]
(currentNode isNil) ifTrue: [^nil] ifFalse: [^currentNode value]
(currentNode isNil) ifTrue: [^nil] ifFalse: [^currentNode value] at: aKey put: aValue "store aValue at aKey" root isNil ifTrue:[ root := blah] ifFalse: [more blah]
message selector and argument names "comment stating purpose of message" | temporary variable names | statements
insert: aKey data: aValue | treeNode found saveNode | found := false. treeNode := root. [treeNode ~= nil and: [found = false]] whileTrue: [saveNode := treeNode. (aKey = treeNode key) ifTrue: [found := true] ifFalse: [(aKey < treeNode key) ifTrue: [treeNode := treeNode leftChild] ifFalse: [treeNode := treeNode rightChild]. ]. ]. (found = false) ifTrue: [treeNode := Node key: aKey data: aValue. size := size + 1. (aKey < saveNode key) ifTrue: [saveNode leftChild: treeNode] ifFalse: [saveNode rightChild: treeNode]. ].
insert: aKey data: aValue | treeNode saveNode | treeNode := root. [treeNode notNil] whileTrue: [saveNode := treeNode. (aKey = treeNode key) ifTrue: [^nil]. (aKey < treeNode key) ifTrue: [treeNode := treeNode leftChild] ifFalse: [treeNode := treeNode rightChild]. ]. treeNode := Node key: aKey data: aValue. size := size + 1. (aKey < saveNode key) ifTrue: [saveNode leftChild: treeNode] ifFalse: [saveNode rightChild: treeNode].
insert: aKey data: aValue | child parent | child := root. parent := child. [child notNil] whileTrue: [(aKey = child key) ifTrue: [^nil]. parent := child. child := parent nextNodeFor: aKey]. ]. parent addToSelf: (Node key: aKey data: aValue).
checkFrom: aNode toFind: aKey aNode isNil ifFalse: [aNode key = aKey ifTrue: [^aNode value] ifFalse: aKey < aNode key ifTrue: [^self checkFrom: aNode leftChild toFind: aKey] ifTrue: [^self checkFrom: aNode rightChild toFind: aKey]]] ifTrue: [^nil]
checkFrom: aNode toFind: aKey aNode isNil ifTrue: [^nil]. aNode key = aKey ifTrue: [^aNode value] aKey < aNode key ifTrue: [^self checkFrom: aNode leftChild toFind: aKey] ifTrue: [^self checkFrom: aNode rightChild toFind: aKey]]]
Smalltalk.CS535 defineClass: #BinarySearchTree superclass: #{Core.Object} indexedType: #none private: false instanceVariableNames: 'root nodesInOrderedCollection' classInstanceVariableNames: '' imports: '' category: 'Course-Assignment'