SystemOrganization addCategory: #'Container-Core'! SystemOrganization addCategory: #'Container-Core-Iterators'! SystemOrganization addCategory: #'Container-Core-Comparators'! SystemOrganization addCategory: #'Container-Core-Exceptions'! SystemOrganization addCategory: #'Container-Core-Lists'! SystemOrganization addCategory: #'Container-Core-Sets'! SystemOrganization addCategory: #'Container-Core-Maps'! SystemOrganization addCategory: #'Container-Core-Misc'! SystemOrganization addCategory: #'Container-Core-Private'! Error subclass: #CTElementNotFoundError instanceVariableNames: 'element' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTElementNotFoundError commentStamp: 'lr 5/13/2012 18:07' prior: 0! Exception thrown when a requested element cannot be found.! !CTElementNotFoundError methodsFor: 'accessing' stamp: 'lr 12/28/2011 16:04'! element ^ element! ! !CTElementNotFoundError methodsFor: 'accessing' stamp: 'lr 12/28/2011 16:04'! element: anObject element := anObject! ! Error subclass: #CTIllegalArgumentError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTIllegalArgumentError commentStamp: 'lr 5/13/2012 18:21' prior: 0! Exception thrown when a method invocation cannot handle one ore more arguments passed in.! Error subclass: #CTIndexOutOfBoundsError instanceVariableNames: 'index' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTIndexOutOfBoundsError commentStamp: 'lr 5/13/2012 18:09' prior: 0! Exception thrown when an index is not within the valid bounds.! !CTIndexOutOfBoundsError methodsFor: 'accessing' stamp: 'lr 12/28/2011 16:04'! index ^ index! ! !CTIndexOutOfBoundsError methodsFor: 'accessing' stamp: 'lr 12/28/2011 16:04'! index: anInteger index := anInteger! ! Error subclass: #CTKeyNotFoundError instanceVariableNames: 'key' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTKeyNotFoundError commentStamp: 'lr 5/13/2012 18:09' prior: 0! Exception thrown when a given key cannot be found.! !CTKeyNotFoundError methodsFor: 'accessing' stamp: 'lr 1/1/2012 17:20'! key ^ key! ! !CTKeyNotFoundError methodsFor: 'accessing' stamp: 'lr 1/1/2012 17:20'! key: anObject key := anObject! ! Error subclass: #CTNoSuchElementError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTNoSuchElementError commentStamp: 'lr 5/13/2012 18:10' prior: 0! Exception thrown when the requested element cannot be found.! Error subclass: #CTUnsupportedOperationError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTUnsupportedOperationError commentStamp: 'lr 5/13/2012 18:10' prior: 0! Exception thrown when invoked functionality is not supported in the given context.! !SequenceableCollection methodsFor: '*container-core-iterators' stamp: 'lr 4/21/2012 21:12'! iterator "Answer a default iterator over the elements in this collection." ^ CTListIterator on: self! ! !Symbol methodsFor: '*container-core-comparators' stamp: 'lr 1/26/2012 13:52'! asComparator ^ self asComparator: CTNaturalComparator new! ! !Symbol methodsFor: '*container-core-comparators' stamp: 'lr 1/26/2012 13:52'! asComparator: aComparator ^ aComparator transform: self! ! Object subclass: #CTComparator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTComparator commentStamp: '' prior: 0! Abstract strategy to encapsulates the behavior of comparing elements (equality, order and hash).! CTComparator subclass: #CTCombinedComparator instanceVariableNames: 'comparators' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTCombinedComparator commentStamp: '' prior: 0! Combines multiple comparators together. This means an element is equal to another one only if it is equal using all its comparators; the hash is the combination of the hashes of all its comparators; and an element is less than another one if the first comparator not being equal is less.! !CTCombinedComparator class methodsFor: 'instance creation' stamp: 'lr 1/24/2012 19:21'! on: aCollection ^ self basicNew initializeOn: aCollection! ! !CTCombinedComparator methodsFor: 'operators' stamp: 'lr 2/11/2012 23:18'! , aComparator ^ self class on: (comparators copyWith: aComparator)! ! !CTCombinedComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 18:34'! equals: leftObject to: rightObject 1 to: comparators size do: [ :index | ((comparators at: index) equals: leftObject to: rightObject) ifFalse: [ ^ false ] ]. ^ true! ! !CTCombinedComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:21'! hashOf: anObject | hash | hash := 0. 1 to: comparators size do: [ :index | hash := 31 * hash + (((comparators at: index) hashOf: anObject) bitAnd: 16r0FFFFFFF) ]. ^ hash! ! !CTCombinedComparator methodsFor: 'initialization' stamp: 'lr 2/12/2012 15:15'! initializeOn: aCollection comparators := aCollection asArray! ! !CTCombinedComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 18:34'! less: leftObject than: rightObject | order | 1 to: comparators size do: [ :index | ((order := comparators at: index) equals: leftObject to: rightObject) ifFalse: [ ^ order less: leftObject than: rightObject ] ]. ^ false! ! !CTCombinedComparator methodsFor: 'printing' stamp: 'lr 1/24/2012 18:34'! printOn: aStream aStream nextPut: $(. comparators do: [ :each | aStream print: each ] separatedBy: [ aStream nextPutAll: ' , ' ]. aStream nextPut: $)! ! !CTComparator methodsFor: 'operators' stamp: 'lr 3/30/2012 11:24'! , aComparator "Combine the comparator of the receiver with the comparator of the argument." ^ CTCombinedComparator on: (Array with: self with: aComparator)! ! !CTComparator methodsFor: 'comparing' stamp: 'lr 1/27/2012 14:29'! equals: leftObject to: rightObject "Returns true if the left-object and the right-object are equal." self subclassResponsibility! ! !CTComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 18:31'! hashOf: anObject "Returns the hash of anObject." self subclassResponsibility! ! !CTComparator methodsFor: 'searching' stamp: 'lr 2/11/2012 14:49'! indexOf: anObject in: anArray "Finds the index of anObject sorted by the receiving comparator. Answer 0 if the element cannot be found." ^ self indexOf: anObject in: anArray from: 1 to: anArray size! ! !CTComparator methodsFor: 'searching' stamp: 'lr 2/11/2012 14:49'! indexOf: anObject in: anArray from: aStartIndex to: aStopIndex "Finds the index of anObject sorted by the receiving comparator within the range from aStartIndex to aStopIndex. Answer 0 if the element cannot be found." | start stop | start := aStartIndex. stop := aStopIndex. [ stop < start ] whileFalse: [ | index value | index := start + stop // 2. value := anArray at: index. (self equals: anObject to: value) ifTrue: [ ^ index ]. (self less: anObject than: value) ifTrue: [ stop := index - 1 ] ifFalse: [ start := index + 1 ] ]. ^ 0! ! !CTComparator methodsFor: 'searching' stamp: 'lr 2/11/2012 14:49'! insertionIndexOf: anObject in: anArray "Finds the insertion index of anObject sorted by the receiving comparator in anArray ." ^ self insertionIndexOf: anObject in: anArray from: 1 to: anArray size! ! !CTComparator methodsFor: 'searching' stamp: 'lr 2/11/2012 14:49'! insertionIndexOf: anObject in: anArray from: aStartIndex to: aStopIndex "Finds the insertion index of anObject sorted by the receiving comparator in anArray within the range from aStartIndex to aStopIndex." | start stop | start := aStartIndex. stop := aStopIndex. [ stop < start ] whileFalse: [ | index | index := start + stop // 2. (self less: anObject than: (anArray at: index)) ifTrue: [ stop := index - 1 ] ifFalse: [ start := index + 1 ] ]. ^ start! ! !CTComparator methodsFor: 'private' stamp: 'lr 2/7/2012 19:49'! insertionSort: anArray from: startInteger to: stopInteger "In-place insertion sort algorithm, very efficient for almost sorted data." startInteger + 1 to: stopInteger do: [ :outer | | key value inner | key := anArray at: (inner := outer). [ startInteger < inner and: [ self less: key than: (value := anArray at: inner - 1) ] ] whileTrue: [ anArray at: inner put: value. inner := inner - 1 ]. anArray at: inner put: key ]. ^ anArray! ! !CTComparator methodsFor: 'testing' stamp: 'lr 1/21/2012 10:53'! isPartial: anIterable "Answer true if the argument is partially ordered, that is each element is bigger or equal to the previous." | iterator | iterator := anIterable iterator. [ iterator hasNext ] whileTrue: [ | previous | previous := iterator next. [ iterator hasNext ] whileTrue: [ | next | (self less: (next := iterator next) than: previous) ifTrue: [ ^ false ]. previous := next ] ]. ^ true! ! !CTComparator methodsFor: 'testing' stamp: 'lr 1/27/2012 14:30'! isStrict: anIterable "Answer true if the argument is strictly ordered, that is each element is bigger than the previous." | iterator | iterator := anIterable iterator. [ iterator hasNext ] whileTrue: [ | previous | previous := iterator next. [ iterator hasNext ] whileTrue: [ | next | (self less: previous than: (next := iterator next)) ifFalse: [ ^ false ]. previous := next ] ]. ^ true! ! !CTComparator methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:56'! less: leftObject than: rightObject "Returns true if the left-object is less than the right-object." self subclassResponsibility! ! !CTComparator methodsFor: 'sorting' stamp: 'lr 1/20/2012 19:39'! maximum: anIterable "Answer the maximum of the argument." | iterator maximum | iterator := anIterable iterator. maximum := iterator next. [ iterator hasNext ] whileTrue: [ | current | (self less: maximum than: (current := iterator next)) ifTrue: [ maximum := current ] ]. ^ maximum! ! !CTComparator methodsFor: 'sorting' stamp: 'lr 1/20/2012 19:40'! minimum: anIterable "Answer the minimum of the argument." | iterator minimum | iterator := anIterable iterator. minimum := iterator next. [ iterator hasNext ] whileTrue: [ | current | (self less: (current := iterator next) than: minimum) ifTrue: [ minimum := current ] ]. ^ minimum! ! !CTComparator methodsFor: 'private' stamp: 'lr 5/13/2012 18:20'! quickPartition: anArray from: startIndex to: endIndex | pivot leftIndex rightIndex left right | startIndex = endIndex ifTrue: [ ^ startIndex ]. pivot := anArray at: startIndex. leftIndex := startIndex. rightIndex := endIndex. [ leftIndex < rightIndex ] whileTrue: [ [ (self less: pivot than: (left := anArray at: leftIndex)) or: [ leftIndex >= rightIndex ] ] whileFalse: [ leftIndex := leftIndex + 1 ]. [ self less: pivot than: (right := anArray at: rightIndex) ] whileTrue: [ rightIndex := rightIndex - 1 ]. leftIndex < rightIndex ifTrue: [ anArray at: rightIndex put: left. anArray at: leftIndex put: right ] ]. anArray at: rightIndex put: pivot. anArray at: startIndex put: right. ^ rightIndex! ! !CTComparator methodsFor: 'private' stamp: 'lr 5/13/2012 18:21'! quickSort: anArray from: startInteger to: stopInteger "Approximative in-place implementation of quick-sort, very efficient for large random data." | pivot index | startInteger + 10 < stopInteger ifFalse: [ ^ self ]. pivot := anArray at: (index := startInteger + stopInteger // 2). anArray at: index put: (anArray at: startInteger). anArray at: startInteger put: pivot. index := self quickPartition: anArray from: startInteger to: stopInteger. self quickSort: anArray from: startInteger to: index - 1. self quickSort: anArray from: index + 1 to: stopInteger! ! !CTComparator methodsFor: 'operators' stamp: 'lr 3/30/2012 11:24'! reverse "Reverses the comparator of the receiver." ^ CTReverseComparator on: self! ! !CTComparator methodsFor: 'sorting' stamp: 'lr 1/27/2012 14:30'! sort: anArray "Sorts anArray in-place using the order of the receiver." self sort: anArray from: 1 to: anArray size! ! !CTComparator methodsFor: 'sorting' stamp: 'lr 5/13/2012 18:22'! sort: anArray from: startInteger to: stopInteger "Sorts anArray in-place from startInteger to stopInteger. We do so by first applying an approximative ordering using quick-sort that brings elements close to their final position, and then we fix up the final order with insertion-sort (as recommended by Robert Sedgewick)." self quickSort: anArray from: startInteger to: stopInteger. self insertionSort: anArray from: startInteger to: stopInteger! ! !CTComparator methodsFor: 'operators' stamp: 'lr 3/30/2012 11:24'! transform: aSymbol "Transform the element of the comparator by performing aSymbol on the object." ^ CTMutatingComparator on: self selector: aSymbol! ! CTComparator subclass: #CTDelegateComparator instanceVariableNames: 'comparator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTDelegateComparator commentStamp: '' prior: 0! Wrapper around another comparator.! !CTDelegateComparator class methodsFor: 'instance creation' stamp: 'lr 2/11/2012 23:22'! on: aComparator ^ self basicNew initializeOn: aComparator! ! !CTDelegateComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! equals: leftObject to: rightObject ^ comparator equals: leftObject to: rightObject! ! !CTDelegateComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! hashOf: anObject ^ comparator hashOf: anObject! ! !CTDelegateComparator methodsFor: 'initialization' stamp: 'lr 2/12/2012 15:15'! initializeOn: aComparator comparator := aComparator! ! !CTDelegateComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! less: leftObject than: rightObject ^ comparator less: leftObject than: rightObject! ! !CTDelegateComparator methodsFor: 'printing' stamp: 'lr 1/24/2012 19:13'! printOn: aStream aStream print: comparator! ! CTDelegateComparator subclass: #CTMutatingComparator instanceVariableNames: 'selector' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTMutatingComparator commentStamp: '' prior: 0! Mutates the elements to be compared with the given selector.! !CTMutatingComparator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 15:15'! on: aComparator selector: aSymbol ^ self basicNew initializeOn: aComparator selector: aSymbol! ! !CTMutatingComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! equals: leftObject to: rightObject ^ comparator equals: (leftObject perform: selector) to: (rightObject perform: selector)! ! !CTMutatingComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:14'! hashOf: anObject ^ comparator hashOf: (anObject perform: selector)! ! !CTMutatingComparator methodsFor: 'initialization' stamp: 'lr 2/12/2012 15:15'! initializeOn: aComparator selector: aSymbol self initializeOn: aComparator. selector := aSymbol! ! !CTMutatingComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! less: leftObject than: rightObject ^ comparator less: (leftObject perform: selector) than: (rightObject perform: selector)! ! !CTMutatingComparator methodsFor: 'printing' stamp: 'lr 1/22/2012 10:20'! printOn: aStream aStream nextPut: $(. super printOn: aStream. aStream nextPutAll: ' transform: '; print: selector; nextPut: $)! ! CTDelegateComparator subclass: #CTReverseComparator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTReverseComparator commentStamp: '' prior: 0! Reverses the order of the wrapped comparator.! !CTReverseComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! equals: leftObject to: rightObject ^ comparator equals: rightObject to: leftObject! ! !CTReverseComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:13'! less: leftObject than: rightObject ^ comparator less: rightObject than: leftObject! ! !CTReverseComparator methodsFor: 'sorting' stamp: 'lr 1/24/2012 19:13'! maximum: anIterable ^ comparator minimum: anIterable! ! !CTReverseComparator methodsFor: 'sorting' stamp: 'lr 1/24/2012 19:13'! minimum: anIterable ^ comparator maximum: anIterable! ! !CTReverseComparator methodsFor: 'printing' stamp: 'lr 1/24/2012 19:13'! printOn: aStream aStream print: comparator; nextPutAll: ' reverse'! ! !CTReverseComparator methodsFor: 'operators' stamp: 'lr 1/24/2012 19:13'! reverse ^ comparator! ! CTComparator subclass: #CTNaturalComparator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! CTNaturalComparator class instanceVariableNames: 'instance'! !CTNaturalComparator commentStamp: '' prior: 0! The natural comparator for Smalltalk objects, using #=, #hash and #< on the involved objects.! CTNaturalComparator class instanceVariableNames: 'instance'! CTNaturalComparator subclass: #CTIdentityComparator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTIdentityComparator commentStamp: '' prior: 0! The identity comparator for Smalltalk objects, using #==, #identityHash and #< on the involved objects.! !CTIdentityComparator class methodsFor: 'class initialization' stamp: 'lr 4/21/2012 23:50'! initialize instance := self basicNew! ! !CTIdentityComparator methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:57'! equals: leftObject to: rightObject ^ leftObject == rightObject! ! !CTIdentityComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:15'! hashOf: anObject ^ anObject identityHash! ! !CTNaturalComparator class methodsFor: 'class initialization' stamp: 'lr 4/21/2012 23:50'! initialize instance := self basicNew! ! !CTNaturalComparator class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 10:09'! new ^ instance! ! !CTNaturalComparator methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:58'! equals: leftObject to: rightObject ^ leftObject = rightObject! ! !CTNaturalComparator methodsFor: 'comparing' stamp: 'lr 1/24/2012 19:15'! hashOf: anObject ^ anObject hash! ! !CTNaturalComparator methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:57'! less: leftObject than: rightObject ^ leftObject < rightObject! ! !CTNaturalComparator methodsFor: 'printing' stamp: 'lr 1/22/2012 09:22'! printOn: aStream aStream print: self class; nextPutAll: ' new'! ! CTComparator subclass: #CTPluggableComparator instanceVariableNames: 'equals less hash' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTPluggableComparator commentStamp: 'lr 2/12/2012 15:16' prior: 0! A fully pluggable comparator with blocks. Use sparingly, useful mostly for testing.! !CTPluggableComparator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 15:14'! equals: anEqualBlock ^ self equals: anEqualBlock less: nil hash: nil! ! !CTPluggableComparator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 15:04'! equals: anEqualBlock less: aLessBlock hash: aHashBlock ^ self basicNew initializeEquals: anEqualBlock less: aLessBlock hash: aHashBlock! ! !CTPluggableComparator methodsFor: 'comparing' stamp: 'lr 2/12/2012 15:05'! equals: leftObject to: rightObject ^ equals value: leftObject value: rightObject! ! !CTPluggableComparator methodsFor: 'comparing' stamp: 'lr 2/12/2012 15:05'! hashOf: anObject ^ hash value: anObject! ! !CTPluggableComparator methodsFor: 'initialization' stamp: 'lr 2/12/2012 15:07'! initializeEquals: anEqualBlock less: aLessBlock hash: aHashBlock self initialize. equals := anEqualBlock. less := aLessBlock. hash := aHashBlock! ! !CTPluggableComparator methodsFor: 'comparing' stamp: 'lr 2/12/2012 15:06'! less: leftObject than: rightObject ^ less value: leftObject value: rightObject! ! Object subclass: #CTHashMapNode instanceVariableNames: 'key object next' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! key ^ key! ! !CTHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! key: anObject key := anObject! ! !CTHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! next ^ next! ! !CTHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! next: aNode next := aNode! ! !CTHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! object ^ object! ! !CTHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! object: anObject object := anObject! ! CTHashMapNode subclass: #CTLinkedHashMapNode instanceVariableNames: 'before after' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTLinkedHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! after ^ after! ! !CTLinkedHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! after: aNode after := aNode! ! !CTLinkedHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! before ^ before! ! !CTLinkedHashMapNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:09'! before: aNode before := aNode! ! Object subclass: #CTHashSetNode instanceVariableNames: 'key next' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:44'! key ^ key! ! !CTHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:44'! key: anObject key := anObject! ! !CTHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:44'! next ^ next! ! !CTHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:44'! next: aNode next := aNode! ! CTHashSetNode subclass: #CTLinkedHashSetNode instanceVariableNames: 'before after' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTLinkedHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:45'! after ^ after! ! !CTLinkedHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:45'! after: aNode after := aNode! ! !CTLinkedHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:45'! before ^ before! ! !CTLinkedHashSetNode methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:45'! before: aNode before := aNode! ! Object subclass: #CTHashTable instanceVariableNames: 'array size threshold comparator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTHashTable class methodsFor: 'instance creation' stamp: 'lr 1/24/2012 19:31'! new: anInteger comparator: aComparator ^ self basicNew initialize: anInteger comparator: aComparator! ! !CTHashTable methodsFor: 'adding' stamp: 'lr 2/7/2012 21:40'! add: aNode | index | index := self indexFor: (comparator hashOf: aNode key). aNode next: (array at: index). array at: index put: aNode. threshold < (size := size + 1) ifTrue: [ self grow: (self capacityFor: array size + 1) ]! ! !CTHashTable methodsFor: 'accessing' stamp: 'lr 1/24/2012 19:32'! at: aKey | node | node := array at: (self indexFor: (comparator hashOf: aKey)). [ node isNil or: [ comparator equals: aKey to: node key ] ] whileFalse: [ node := node next ]. ^ node! ! !CTHashTable methodsFor: 'private' stamp: 'lr 10/24/2012 18:36'! capacityFor: anInteger | index | index := CTNaturalComparator new insertionIndexOf: anInteger in: self capacityValues. ^ self capacityValues at: index! ! !CTHashTable methodsFor: 'private' stamp: 'lr 2/7/2012 21:20'! capacityValues ^ #(7 13 31 61 127 251 509 1021 2039 4093 8191 16381 32749 65521 131071 262139 524287 1048573 2097143 4194301 8388593 16777213 33554393 67108859 134217689 268435399 536870909 1073741789 2147483647)! ! !CTHashTable methodsFor: 'copying' stamp: 'lr 1/24/2012 19:52'! copyEmpty ^ self shallowCopy postCopyEmpty! ! !CTHashTable methodsFor: 'private' stamp: 'lr 1/24/2012 19:34'! grow: anInteger | previousArray | previousArray := array. array := Array new: anInteger. threshold := (self loadFactor * anInteger) truncated. 1 to: previousArray size do: [ :previousIndex | | node | node := previousArray at: previousIndex. [ node isNil ] whileFalse: [ | nextNode index | nextNode := node next. index := self indexFor: (comparator hashOf: node key). node next: (array at: index). array at: index put: node. node := nextNode ] ]! ! !CTHashTable methodsFor: 'private' stamp: 'lr 1/13/2012 23:17'! indexFor: anInteger ^ (anInteger \\ array size) + 1! ! !CTHashTable methodsFor: 'initialization' stamp: 'lr 1/24/2012 19:31'! initialize: anInteger comparator: aComparator | capacity | capacity := self capacityFor: (anInteger / self loadFactor) truncated. threshold := (self loadFactor * capacity) truncated. array := Array new: capacity. size := 0. comparator := aComparator! ! !CTHashTable methodsFor: 'converting' stamp: 'lr 1/13/2012 23:17'! iterator ^ CTHashTableIterator on: array! ! !CTHashTable methodsFor: 'private' stamp: 'lr 1/13/2012 09:57'! loadFactor ^ 0.75! ! !CTHashTable methodsFor: 'copying' stamp: 'pmm 2/6/2012 20:39'! postCopy array := array copy. 1 to: array size do: [ :index | | node prev | prev := nil. node := array at: index. [ node isNil ] whileFalse: [ prev isNil ifTrue: [ array at: index put: (prev := node copy) ] ifFalse: [ prev next: (prev := node copy) ]. node := prev next ] ]! ! !CTHashTable methodsFor: 'copying' stamp: 'lr 1/24/2012 19:53'! postCopyEmpty array := Array new: array size. size := 0! ! !CTHashTable methodsFor: 'removing' stamp: 'lr 1/13/2012 23:17'! removeAll 1 to: array size do: [ :index | array at: index put: nil ]. size := 0! ! !CTHashTable methodsFor: 'removing' stamp: 'lr 5/13/2012 18:19'! removeKey: aKey | previous index node | previous := nil. node := array at: (index := self indexFor: (comparator hashOf: aKey)). [ node isNil ] whileFalse: [ (comparator equals: aKey to: node key) ifTrue: [ previous isNil ifTrue: [ array at: index put: node next ] ifFalse: [ previous next: node next ]. size := size - 1. ^ node ]. previous := node. node := node next ]. ^ nil! ! !CTHashTable methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:08'! size ^ size! ! Object subclass: #CTIterable instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! !CTIterable commentStamp: 'lr 2/25/2013 08:24' prior: 0! Abstract container class common to all iterable containers.! CTIterable subclass: #CTContainer instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! !CTContainer commentStamp: 'lr 2/25/2013 08:24' prior: 0! Abstract container class common to all iterable containers.! CTContainer subclass: #CTCollection instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! !CTCollection commentStamp: 'lr 4/25/2012 14:48' prior: 0! Abstract collection class common to all containers that contain simple elements.! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 19:24'! with: anObject1 ^ (self new: 1) add: anObject1; yourself! ! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 19:24'! with: anObject1 with: anObject2 ^ (self new: 2) add: anObject1; add: anObject2; yourself! ! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 19:24'! with: anObject1 with: anObject2 with: anObject3 ^ (self new: 3) add: anObject1; add: anObject2; add: anObject3; yourself! ! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 19:24'! with: anObject1 with: anObject2 with: anObject3 with: anObject4 ^ (self new: 4) add: anObject1; add: anObject2; add: anObject3; add: anObject4; yourself! ! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 1/10/2012 22:21'! withAll: aCollection ^ (self new: aCollection size) addAll: aCollection; yourself! ! !CTCollection methodsFor: 'adding' stamp: 'lr 8/7/2011 11:03'! add: anObject "Ensures that the receiver contains anObject." self subclassResponsibility! ! !CTCollection methodsFor: 'adding' stamp: 'lr 1/1/2012 17:43'! addAll: aCollection "Ensures that the receiver contains all elements of aCollection." aCollection iterator addTo: self! ! !CTCollection methodsFor: 'testing' stamp: 'lr 1/28/2012 16:40'! includes: anObject "Tests if anObject is contained in the receiver." ^ self iterator includes: anObject! ! !CTCollection methodsFor: 'testing' stamp: 'lr 1/28/2012 16:39'! includesAll: aCollection "Tests all objects of aCollection are included in the receiver." ^ aCollection iterator allSatisfy: [ :each | self includes: each ]! ! !CTCollection methodsFor: 'printing' stamp: 'lr 2/18/2012 08:30'! printElementsOn: aStream | iterator | iterator := self iterator. (iterator limit: CTSettings elementsToPrint) do: [ :each | aStream cr; tab; print: each ]. iterator hasNext ifTrue: [ aStream cr; tab; nextPutAll: '...' ]! ! !CTCollection methodsFor: 'removing' stamp: 'lr 12/28/2011 16:02'! remove: anObject "Removes anObject from the receiver, throw an error if not found." ^ self remove: anObject ifAbsent: [ self elementNotFound: anObject ]! ! !CTCollection methodsFor: 'removing' stamp: 'lr 8/7/2011 11:04'! remove: anObject ifAbsent: aBlock "Removes anObject from the receiver, evaluate aBlock if anObject is not present." self subclassResponsibility! ! CTCollection subclass: #CTList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! !CTList commentStamp: 'lr 4/25/2012 14:48' prior: 0! Abstract list common to all list implementations.! CTList subclass: #CTArrayList instanceVariableNames: 'array firstIndex lastIndex' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTArrayList commentStamp: 'lr 4/20/2012 21:40' prior: 0! An array-based list implementation that can grow efficiently at beginning and end.! !CTArrayList methodsFor: 'adding' stamp: 'lr 4/21/2012 09:52'! add: anObject at: anInteger | target | target := firstIndex + anInteger - 1. (target between: firstIndex and: lastIndex + 1) ifFalse: [ ^ self indexOutOfBounds: anInteger ]. self size // 2 < anInteger ifTrue: [ lastIndex = array size ifTrue: [ self growAtLast ]. lastIndex to: target by: -1 do: [ :index | array at: index + 1 put: (array at: index) ]. lastIndex := lastIndex + 1 ] ifFalse: [ firstIndex = 1 ifTrue: [ self growAtFirst ]. firstIndex := firstIndex - 1. target := firstIndex + anInteger - 1. firstIndex to: target - 1 by: 1 do: [ :index | array at: index put: (array at: index + 1) ] ]. ^ array at: target put: anObject! ! !CTArrayList methodsFor: 'adding' stamp: 'lr 1/1/2012 01:17'! addFirst: anObject firstIndex = 1 ifTrue: [ self growAtFirst ]. firstIndex := firstIndex - 1. array at: firstIndex put: anObject. ^ anObject! ! !CTArrayList methodsFor: 'adding' stamp: 'lr 1/1/2012 01:13'! addLast: anObject lastIndex = array size ifTrue: [ self growAtLast ]. lastIndex := lastIndex + 1. array at: lastIndex put: anObject. ^ anObject! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 12/31/2011 11:21'! at: anInteger ifAbsent: aBlock | index | index := firstIndex + anInteger - 1. (index between: firstIndex and: lastIndex) ifFalse: [ ^ aBlock value ]. ^ array at: index! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 12/31/2011 11:22'! at: anInteger put: anObject | index | index := firstIndex + anInteger - 1. (index between: firstIndex and: lastIndex) ifFalse: [ ^ self indexOutOfBounds: anInteger ]. ^ array at: index put: anObject! ! !CTArrayList methodsFor: 'private' stamp: 'lr 8/7/2011 11:42'! growAtFirst | newArray newFirstIndex newLastIndex | newArray := Array new: array size * 3 // 2 + 1. newFirstIndex := newArray size - array size + firstIndex. newLastIndex := newFirstIndex + lastIndex - firstIndex. newArray replaceFrom: newFirstIndex to: newLastIndex with: array startingAt: firstIndex. array := newArray. firstIndex := newFirstIndex. lastIndex := newLastIndex! ! !CTArrayList methodsFor: 'private' stamp: 'lr 8/7/2011 11:42'! growAtLast | newArray | newArray := Array new: array size * 3 // 2 + 1. newArray replaceFrom: firstIndex to: lastIndex with: array startingAt: firstIndex. array := newArray! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 2/6/2012 20:32'! immutable ^ CTImmutableList withAll: (array copyFrom: firstIndex to: lastIndex)! ! !CTArrayList methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:19'! initialize: anInteger array := Array new: anInteger. firstIndex := 1. lastIndex := 0! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 4/21/2012 21:12'! iterator ^ CTListIterator on: array start: firstIndex stop: lastIndex! ! !CTArrayList methodsFor: 'copying' stamp: 'lr 1/11/2012 20:57'! postCopy super postCopy. array := array copy! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 12/30/2011 10:41'! removeAll firstIndex to: lastIndex do: [ :index | array at: index put: nil ]. firstIndex := 1. lastIndex := 0! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 1/1/2012 01:02'! removeAt: anInteger ifAbsent: aBlock | target object | target := firstIndex + anInteger - 1. (target between: firstIndex and: lastIndex) ifFalse: [ ^ aBlock value ]. object := array at: target. firstIndex + lastIndex // 2 < target ifTrue: [ target to: lastIndex - 1 by: 1 do: [ :index | array at: index put: (array at: index + 1) ]. array at: lastIndex put: nil. lastIndex := lastIndex - 1 ] ifFalse: [ target to: firstIndex + 1 by: -1 do: [ :index | array at: index put: (array at: index - 1) ]. array at: firstIndex put: nil. firstIndex := firstIndex + 1 ]. ^ object! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 1/20/2012 22:13'! removeFirst | element | lastIndex < firstIndex ifTrue: [ ^ self noSuchElement ]. element := array at: firstIndex. array at: firstIndex put: nil. firstIndex := firstIndex + 1. ^ element! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 1/20/2012 22:13'! removeLast | element | lastIndex < firstIndex ifTrue: [ ^ self noSuchElement ]. element := array at: lastIndex. array at: lastIndex put: nil. lastIndex := lastIndex - 1. ^ element! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 12/28/2011 19:36'! size ^ lastIndex - firstIndex + 1! ! !CTArrayList methodsFor: 'sorting' stamp: 'lr 2/11/2012 23:16'! sort: aComparator aComparator sort: array from: firstIndex to: lastIndex! ! CTList subclass: #CTDelegateList instanceVariableNames: 'delegate' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTDelegateList commentStamp: 'lr 4/25/2012 14:41' prior: 0! A list that delegates to another list.! !CTDelegateList class methodsFor: 'instance creation' stamp: 'lr 4/5/2012 10:59'! on: aList ^ self basicNew initializeOn: aList! ! !CTDelegateList methodsFor: 'adding' stamp: 'lr 4/21/2012 14:17'! add: anObject at: anInteger ^ delegate add: anObject at: anInteger! ! !CTDelegateList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! at: anInteger ifAbsent: aBlock ^ delegate at: anInteger ifAbsent: aBlock! ! !CTDelegateList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! at: anInteger put: anObject ^ delegate at: anInteger put: anObject! ! !CTDelegateList methodsFor: 'initialization' stamp: 'lr 4/21/2012 14:17'! initializeOn: aList delegate := aList! ! !CTDelegateList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! iterator ^ delegate iterator! ! !CTDelegateList methodsFor: 'copying' stamp: 'lr 4/21/2012 14:17'! postCopy super postCopy. delegate := delegate copy! ! !CTDelegateList methodsFor: 'removing' stamp: 'lr 4/21/2012 14:17'! removeAll delegate removeAll! ! !CTDelegateList methodsFor: 'removing' stamp: 'lr 4/21/2012 14:17'! removeAt: anInteger ifAbsent: aBlock ^ delegate removeAt: anInteger ifAbsent: aBlock! ! !CTDelegateList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! size ^ delegate size! ! CTDelegateList subclass: #CTReversedList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTReversedList commentStamp: 'lr 4/25/2012 14:41' prior: 0! A reversed view onto another list.! !CTReversedList methodsFor: 'adding' stamp: 'lr 4/21/2012 23:30'! add: anObject at: anInteger ^ delegate add: anObject at: delegate size - anInteger + 2! ! !CTReversedList methodsFor: 'adding' stamp: 'lr 4/21/2012 14:17'! addFirst: anObject ^ delegate addLast: anObject! ! !CTReversedList methodsFor: 'adding' stamp: 'lr 4/21/2012 14:17'! addLast: anObject ^ delegate addFirst: anObject! ! !CTReversedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! at: anInteger ifAbsent: aBlock ^ delegate at: delegate size - anInteger + 1 ifAbsent: aBlock! ! !CTReversedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 23:18'! at: anInteger put: anObject ^ delegate at: delegate size - anInteger + 1 put: anObject! ! !CTReversedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! first ^ delegate last! ! !CTReversedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 23:11'! iterator ^ CTListIterator on: self! ! !CTReversedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! last ^ delegate first! ! !CTReversedList methodsFor: 'removing' stamp: 'lr 4/21/2012 14:17'! removeAt: anInteger ifAbsent: aBlock ^ delegate removeAt: delegate size - anInteger + 1 ifAbsent: aBlock! ! !CTReversedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! reversed ^ delegate! ! CTDelegateList subclass: #CTSubList instanceVariableNames: 'firstIndex lastIndex' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTSubList commentStamp: 'lr 5/13/2012 18:21' prior: 0! A modifiable view onto another list.! !CTSubList class methodsFor: 'instance creation' stamp: 'lr 2/11/2012 11:41'! on: anArray start: aStartInteger stop: aStopInteger ^ self basicNew initializeOn: anArray start: aStartInteger stop: aStopInteger! ! !CTSubList methodsFor: 'adding' stamp: 'lr 4/21/2012 14:17'! add: anObject at: anInteger (anInteger between: 1 and: lastIndex - firstIndex + 2) ifFalse: [ ^ self indexOutOfBounds: anInteger ]. lastIndex := lastIndex + 1. ^ delegate add: anObject at: firstIndex + anInteger - 1! ! !CTSubList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! at: anInteger ifAbsent: aBlock ^ (anInteger between: 1 and: lastIndex - firstIndex + 1) ifTrue: [ delegate at: firstIndex + anInteger - 1 ifAbsent: aBlock ] ifFalse: [ aBlock value ]! ! !CTSubList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! at: anInteger put: anObject ^ (anInteger between: 1 and: lastIndex - firstIndex + 1) ifTrue: [ delegate at: firstIndex + anInteger - 1 put: anObject ] ifFalse: [ self indexOutOfBounds: anInteger ]! ! !CTSubList methodsFor: 'initialization' stamp: 'lr 4/5/2012 10:50'! initializeOn: aList start: aStartInteger stop: aStopInteger self initializeOn: (aList validateBoundsFrom: aStartInteger to: aStopInteger). firstIndex := aStartInteger. lastIndex := aStopInteger! ! !CTSubList methodsFor: 'accessing' stamp: 'lr 4/21/2012 21:12'! iterator ^ CTListIterator on: delegate start: firstIndex stop: lastIndex! ! !CTSubList methodsFor: 'removing' stamp: 'lr 4/21/2012 14:17'! removeAll firstIndex to: lastIndex do: [ :index | delegate removeAt: firstIndex ]. lastIndex := firstIndex - 1! ! !CTSubList methodsFor: 'removing' stamp: 'lr 4/21/2012 14:16'! removeAt: anInteger ifAbsent: aBlock (anInteger between: 1 and: lastIndex - firstIndex + 1) ifFalse: [ ^ aBlock value ]. lastIndex := lastIndex - 1. ^ delegate removeAt: firstIndex + anInteger - 1 ifAbsent: aBlock! ! !CTSubList methodsFor: 'accessing' stamp: 'lr 2/11/2012 12:01'! size ^ lastIndex - firstIndex + 1! ! !CTSubList methodsFor: 'sorting' stamp: 'lr 4/21/2012 14:17'! sort: aComparator aComparator sort: delegate from: firstIndex to: lastIndex! ! CTDelegateList subclass: #CTUnmodifiableList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTUnmodifiableList commentStamp: 'lr 4/25/2012 14:27' prior: 0! A read-only view onto another list.! !CTUnmodifiableList methodsFor: 'adding' stamp: 'lr 2/6/2012 07:13'! add: anObject at: anInteger self unsupportedOperation! ! !CTUnmodifiableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 07:13'! at: anInteger put: anObject self unsupportedOperation! ! !CTUnmodifiableList methodsFor: 'copying' stamp: 'lr 2/8/2012 19:36'! copy ^ self! ! !CTUnmodifiableList methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! immutable ^ delegate immutable! ! !CTUnmodifiableList methodsFor: 'removing' stamp: 'lr 2/6/2012 07:13'! removeAll self unsupportedOperation! ! !CTUnmodifiableList methodsFor: 'removing' stamp: 'lr 2/6/2012 07:13'! removeAt: anInteger ifAbsent: aBlock self unsupportedOperation! ! !CTUnmodifiableList methodsFor: 'sorting' stamp: 'lr 4/5/2012 11:18'! sort: aComparator self unsupportedOperation! ! !CTUnmodifiableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 20:43'! unmodifiable ^ self! ! CTList subclass: #CTImmutableList instanceVariableNames: 'array' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTImmutableList commentStamp: 'lr 4/25/2012 14:29' prior: 0! An immutable list backed internally by an array.! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:51'! new: anInteger ^ self withAll: #()! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:30'! with: anObject1 ^ self withAll: (Array with: anObject1)! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:30'! with: anObject1 with: anObject2 ^ self withAll: (Array with: anObject1 with: anObject2)! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:29'! with: anObject1 with: anObject2 with: anObject3 ^ self withAll: (Array with: anObject1 with: anObject2 with: anObject3)! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:29'! with: anObject1 with: anObject2 with: anObject3 with: anObject4 ^ self withAll: (Array with: anObject1 with: anObject2 with: anObject3 with: anObject4)! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:29'! withAll: anArray ^ self basicNew initializeWithAll: anArray! ! !CTImmutableList methodsFor: 'adding' stamp: 'lr 2/6/2012 06:58'! add: anObject at: anInteger self unsupportedOperation! ! !CTImmutableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 06:58'! at: anInteger ifAbsent: aBlock ^ array at: anInteger ifAbsent: aBlock! ! !CTImmutableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 06:58'! at: anInteger put: anObject self unsupportedOperation! ! !CTImmutableList methodsFor: 'copying' stamp: 'lr 2/8/2012 19:35'! copy ^ self! ! !CTImmutableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 20:42'! immutable ^ self! ! !CTImmutableList methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:19'! initializeWithAll: anArray array := anArray! ! !CTImmutableList methodsFor: 'accessing' stamp: 'lr 4/21/2012 21:12'! iterator ^ CTListIterator on: array! ! !CTImmutableList methodsFor: 'removing' stamp: 'lr 2/6/2012 06:59'! removeAll self unsupportedOperation! ! !CTImmutableList methodsFor: 'removing' stamp: 'lr 2/6/2012 06:59'! removeAt: anInteger ifAbsent: aBlock self unsupportedOperation! ! !CTImmutableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 06:52'! size ^ array size! ! !CTImmutableList methodsFor: 'sorting' stamp: 'lr 4/5/2012 12:01'! sort: aComparator self unsupportedOperation! ! !CTImmutableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 20:42'! unmodifiable ^ self! ! CTList subclass: #CTLinkedList instanceVariableNames: 'size root' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTLinkedList commentStamp: 'lr 5/13/2012 18:11' prior: 0! A list built from linked nodes providing constant insertion at beginning and end.! !CTLinkedList methodsFor: 'adding' stamp: 'lr 1/13/2012 11:29'! add: anObject at: anInteger | node | 1 = anInteger ifTrue: [ ^ self addFirst: anObject ]. size + 1 = anInteger ifTrue: [ ^ self addLast: anObject ]. node := (self nodeAt: anInteger) ifNil: [ ^ self indexOutOfBounds: anInteger ]. root add: (self newNode: anObject) before: node. size := size + 1. ^ anObject! ! !CTLinkedList methodsFor: 'adding' stamp: 'lr 1/13/2012 11:29'! addFirst: anObject root add: (self newNode: anObject) after: root. size := size + 1. ^ anObject! ! !CTLinkedList methodsFor: 'adding' stamp: 'lr 1/13/2012 12:57'! addLast: anObject root add: (self newNode: anObject) before: root. size := size + 1. ^ anObject! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 1/1/2012 17:13'! at: anInteger ifAbsent: aBlock | node | node := (self nodeAt: anInteger) ifNil: [ ^ aBlock value ]. ^ node object! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 1/1/2012 17:12'! at: anInteger put: anObject | node | node := (self nodeAt: anInteger) ifNil: [ ^ self indexOutOfBounds: anInteger ]. node object: anObject. ^ anObject! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 1/13/2012 11:27'! first ^ self isEmpty ifTrue: [ self noSuchElement ] ifFalse: [ root after object ]! ! !CTLinkedList methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:20'! initialize: anInteger root := CTLinkedListRoot new. size := 0! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 4/21/2012 22:09'! iterator ^ self nodeIterator collect: [ :each | each object ]! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 1/13/2012 11:27'! last ^ self isEmpty ifTrue: [ self noSuchElement ] ifFalse: [ root before object ]! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 1/1/2012 17:18'! newNode: anObject ^ self nodeClass on: anObject! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 1/1/2012 18:08'! nodeAt: anInteger | node | (anInteger between: 1 and: size) ifFalse: [ ^ nil ]. node := root. anInteger < (size // 2) ifTrue: [ 1 to: anInteger do: [ :index | node := node after ] ] ifFalse: [ 1 to: size - anInteger + 1 do: [ :index | node := node before ] ]. ^ node! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 11/6/2011 17:07'! nodeClass ^ CTLinkedListNode! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 4/21/2012 22:08'! nodeIterator ^ root iterator! ! !CTLinkedList methodsFor: 'copying' stamp: 'lr 1/13/2012 11:14'! postCopy super postCopy. root := root copy! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 4/21/2012 09:20'! remove: anObject ifAbsent: aBlock | node | node := root iterator detect: [ :each | each object = anObject ] ifNone: [ ^ aBlock value ]. root remove: node. size := size - 1. ^ node object! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 1/13/2012 11:09'! removeAll root removeAll. size := 0! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 1/13/2012 11:36'! removeAt: anInteger ifAbsent: aBlock | node | (node := self nodeAt: anInteger) isNil ifTrue: [ ^ aBlock value ]. root remove: node. size := size - 1. ^ node object! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 1/20/2012 22:14'! removeFirst | node | size = 0 ifTrue: [ ^ self noSuchElement ]. root remove: (node := root after). size := size - 1. ^ node object! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 1/20/2012 22:14'! removeLast | node | size = 0 ifTrue: [ ^ self noSuchElement ]. root remove: (node := root before). size := size - 1. ^ node object! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:29'! size ^ size! ! !CTLinkedList methodsFor: 'sorting' stamp: 'lr 2/11/2012 23:16'! sort: aComparator | node nodes | node := root. nodes := Array new: size. 1 to: nodes size do: [ :index | root remove: (nodes at: index put: (node := node after)) ]. (aComparator transform: #object) sort: nodes. 1 to: nodes size do: [ :index | root add: (nodes at: index) before: root ]! ! !CTList methodsFor: 'adding' stamp: 'lr 1/10/2012 22:34'! add: anObject "Appends anObject to the receiver." ^ self addLast: anObject! ! !CTList methodsFor: 'adding' stamp: 'lr 11/6/2011 09:34'! add: anObject at: anInteger "Adds anObject at the position anInteger." self subclassResponsibility! ! !CTList methodsFor: 'adding' stamp: 'lr 1/20/2012 20:52'! addFirst: anObject "Adds anObject at the beginning of the receiver." ^ self add: anObject at: 1! ! !CTList methodsFor: 'adding' stamp: 'lr 1/20/2012 20:52'! addLast: anObject "Adds anObject at the end of the receiver." ^ self add: anObject at: self size + 1! ! !CTList methodsFor: 'accessing' stamp: 'lr 8/7/2011 16:14'! at: anInteger "Returns the element at index anInteger, or throws an exception." ^ self at: anInteger ifAbsent: [ self indexOutOfBounds: anInteger ]! ! !CTList methodsFor: 'accessing' stamp: 'lr 1/1/2012 18:05'! at: anInteger ifAbsent: aBlock "Returns the element at anInteger, otherwise answer the result of evaluating aBlock." self subclassResponsibility! ! !CTList methodsFor: 'accessing' stamp: 'lr 8/7/2011 15:57'! at: anInteger put: anObject "Replaces the element at anInteger with anObject." self subclassResponsibility! ! !CTList methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:55'! first "Answers the first element of the collection." ^ self at: 1 ifAbsent: [ self noSuchElement ]! ! !CTList methodsFor: 'accessing' stamp: 'lr 4/21/2012 09:49'! from: aStartInteger to: aStopInteger "Answer a mutable sub-list view of the receiver from aStartInteger to aStopInteger." ^ CTSubList on: self start: aStartInteger stop: aStopInteger! ! !CTList methodsFor: 'accessing' stamp: 'lr 4/21/2012 09:20'! immutable ^ (self iterator addTo: (CTArrayList new: self size)) immutable! ! !CTList methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:55'! last "Answers the last element of the collection." ^ self at: self size ifAbsent: [ self noSuchElement ]! ! !CTList methodsFor: 'removing' stamp: 'lr 1/21/2012 19:33'! remove: anObject ifAbsent: aBlock ^ self removeAt: (self iterator indexOf: anObject ifAbsent: [ ^ aBlock value ]) ifAbsent: aBlock! ! !CTList methodsFor: 'removing' stamp: 'lr 12/30/2011 10:42'! removeAt: anInteger "Removes the element at index anInteger, throws an error if it does not exist." ^ self removeAt: anInteger ifAbsent: [ self indexOutOfBounds: anInteger ]! ! !CTList methodsFor: 'removing' stamp: 'lr 12/30/2011 10:42'! removeAt: anInteger ifAbsent: aBlock "Removes the element at index anInteger, evaluates aBlock if it does not exist." ^ self subclassResponsibility! ! !CTList methodsFor: 'removing' stamp: 'lr 1/20/2012 22:11'! removeFirst "Removes the first element of the receiver." ^ self removeAt: 1 ifAbsent: [ self noSuchElement ]! ! !CTList methodsFor: 'removing' stamp: 'lr 1/20/2012 22:11'! removeLast "Removes the last element of the receiver." ^ self removeAt: self size ifAbsent: [ self noSuchElement ]! ! !CTList methodsFor: 'accessing' stamp: 'lr 4/21/2012 09:49'! reversed "Answer a mutable reversed view onto the receiver." ^ CTReversedList on: self! ! !CTList methodsFor: 'sorting' stamp: 'lr 2/11/2012 15:23'! sort "Sorts the collection by default order." self sort: CTNaturalComparator new! ! !CTList methodsFor: 'sorting' stamp: 'lr 4/5/2012 11:03'! sort: aComparator "Sorts the collection by aComparator." aComparator sort: self! ! !CTList methodsFor: 'accessing' stamp: 'lr 2/6/2012 07:14'! unmodifiable ^ CTUnmodifiableList on: self! ! !CTList methodsFor: 'private' stamp: 'lr 2/11/2012 15:20'! validateBoundsFrom: aStartInteger to: aStopInteger (self isEmpty and: [ aStartInteger = 1 and: [ aStopInteger = 0 ] ]) ifTrue: [ ^ self ]. (aStartInteger between: 1 and: self size) ifFalse: [ ^ self indexOutOfBounds: aStartInteger ]. aStartInteger - 1 = aStopInteger ifTrue: [ ^ self ]. (aStopInteger between: 1 and: self size) ifFalse: [ ^ self indexOutOfBounds: aStopInteger ]! ! CTList subclass: #CTVectorList instanceVariableNames: 'array size' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTVectorList commentStamp: 'lr 4/20/2012 21:41' prior: 0! An array-based list implementation that can grow efficiently at the end.! !CTVectorList methodsFor: 'adding' stamp: 'lr 1/21/2012 19:30'! add: anObject at: anInteger (anInteger between: 1 and: size + 1) ifFalse: [ ^ self indexOutOfBounds: anInteger ]. size = array size ifTrue: [ self grow ]. size to: anInteger by: -1 do: [ :index | array at: index + 1 put: (array at: index) ]. size := size + 1. array at: anInteger put: anObject. ^ anObject! ! !CTVectorList methodsFor: 'adding' stamp: 'lr 1/21/2012 19:30'! addLast: anObject array size = size ifTrue: [ self grow ]. ^ array at: (size := size + 1) put: anObject! ! !CTVectorList methodsFor: 'accessing' stamp: 'lr 1/21/2012 19:19'! at: anInteger ifAbsent: aBlock ^ (anInteger between: 1 and: size) ifTrue: [ array at: anInteger ] ifFalse: [ aBlock value ]! ! !CTVectorList methodsFor: 'accessing' stamp: 'lr 1/21/2012 19:20'! at: anInteger put: anObject ^ (anInteger between: 1 and: size) ifTrue: [ array at: anInteger put: anObject ] ifFalse: [ self indexOutOfBounds: anInteger ]! ! !CTVectorList methodsFor: 'private' stamp: 'lr 1/21/2012 19:27'! grow | newArray | newArray := Array new: array size * 3 // 2 + 1. newArray replaceFrom: 1 to: size with: array startingAt: 1. array := newArray! ! !CTVectorList methodsFor: 'accessing' stamp: 'lr 2/6/2012 20:32'! immutable ^ CTImmutableList withAll: (array copyFrom: 1 to: size)! ! !CTVectorList methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:20'! initialize: anInteger array := Array new: anInteger. size := 0! ! !CTVectorList methodsFor: 'accessing' stamp: 'lr 4/21/2012 21:12'! iterator ^ CTListIterator on: array start: 1 stop: size! ! !CTVectorList methodsFor: 'copying' stamp: 'lr 1/21/2012 19:15'! postCopy super postCopy. array := array copy! ! !CTVectorList methodsFor: 'removing' stamp: 'lr 1/21/2012 19:21'! removeAll 1 to: size do: [ :index | array at: index put: nil ]. size := 0! ! !CTVectorList methodsFor: 'removing' stamp: 'lr 1/21/2012 19:32'! removeAt: anInteger ifAbsent: aBlock | object | (anInteger between: 1 and: size) ifFalse: [ ^ aBlock value ]. object := array at: anInteger. array replaceFrom: anInteger to: size - 1 with: array startingAt: anInteger + 1. array at: size put: nil. size := size - 1. ^ object! ! !CTVectorList methodsFor: 'removing' stamp: 'lr 1/21/2012 19:25'! removeLast | object | size = 0 ifTrue: [ ^ self noSuchElement ]. object := array at: size. array at: size put: nil. size := size - 1. ^ object! ! !CTVectorList methodsFor: 'accessing' stamp: 'lr 1/21/2012 19:20'! size ^ size! ! !CTVectorList methodsFor: 'sorting' stamp: 'lr 2/11/2012 23:16'! sort: aComparator aComparator sort: array from: 1 to: size! ! CTCollection subclass: #CTPriorityQueue instanceVariableNames: 'array size comparator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Misc'! !CTPriorityQueue commentStamp: 'lr 4/25/2012 14:47' prior: 0! A list that can efficiently provide its smallest element.! !CTPriorityQueue class methodsFor: 'instance creation' stamp: 'lr 1/26/2012 18:53'! new: anInteger ^ self new: anInteger comparator: CTNaturalComparator new! ! !CTPriorityQueue class methodsFor: 'instance creation' stamp: 'lr 1/26/2012 10:38'! new: anInteger comparator: aComparator ^ self basicNew initialize: anInteger comparator: aComparator! ! !CTPriorityQueue methodsFor: 'adding' stamp: 'lr 1/20/2012 22:42'! add: anObject array size = size ifTrue: [ self grow ]. array at: (size := size + 1) put: anObject. self swim: size. ^ anObject! ! !CTPriorityQueue methodsFor: 'private' stamp: 'lr 1/20/2012 22:21'! grow | newArray | newArray := Array new: array size * 3 // 2 + 1. newArray replaceFrom: 1 to: size with: array startingAt: 1. array := newArray! ! !CTPriorityQueue methodsFor: 'accessing' stamp: 'lr 4/1/2012 12:20'! immutable self unsupportedOperation! ! !CTPriorityQueue methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:20'! initialize: anInteger comparator: aComparator array := Array new: anInteger. comparator := aComparator. size := 0! ! !CTPriorityQueue methodsFor: 'accessing' stamp: 'lr 4/21/2012 21:12'! iterator "Answer an iterator of the elements of the receiver in random order." ^ CTListIterator on: array start: 1 stop: size! ! !CTPriorityQueue methodsFor: 'copying' stamp: 'lr 1/26/2012 18:54'! postCopy super postCopy. array := array copy! ! !CTPriorityQueue methodsFor: 'removing' stamp: 'lr 1/26/2012 10:37'! remove: anObject ifAbsent: aBlock 1 to: size do: [ :index | (comparator equals: anObject to: (array at: index)) ifTrue: [ ^ self removeAt: index ] ]. ^ aBlock value! ! !CTPriorityQueue methodsFor: 'removing' stamp: 'lr 1/20/2012 23:18'! removeAll 1 to: size do: [ :index | array at: index put: nil ]. size := 0! ! !CTPriorityQueue methodsFor: 'private' stamp: 'lr 1/21/2012 09:24'! removeAt: anInteger | object | object := array at: anInteger. array at: anInteger put: (array at: size). array at: size put: nil. size := size - 1. anInteger > size ifFalse: [ self sink: anInteger ]. ^ object ! ! !CTPriorityQueue methodsFor: 'removing' stamp: 'lr 1/21/2012 09:19'! removeFirst ^ self removeAt: 1! ! !CTPriorityQueue methodsFor: 'private' stamp: 'lr 1/26/2012 10:37'! sink: anInteger | parentIndex parentValue childIndex childValue | parentIndex := anInteger. parentValue := array at: parentIndex. [ (childIndex := parentIndex + parentIndex) <= size ] whileTrue: [ (childIndex < size and: [ comparator less: (array at: childIndex + 1) than: (array at: childIndex) ]) ifTrue: [ childIndex := childIndex + 1]. (comparator less: (childValue := array at: childIndex) than: parentValue) ifFalse: [ ^ array at: parentIndex put: parentValue ]. array at: parentIndex put: childValue. parentIndex := childIndex ]. ^ array at: parentIndex put: parentValue! ! !CTPriorityQueue methodsFor: 'accessing' stamp: 'lr 1/20/2012 22:19'! size ^ size! ! !CTPriorityQueue methodsFor: 'private' stamp: 'lr 5/13/2012 18:19'! swim: anInteger | currentValue currentIndex parentValue parentIndex | currentValue := array at: (currentIndex := anInteger). [ currentIndex > 1 and: [ comparator less: currentValue than: (parentValue := array at: (parentIndex := currentIndex // 2)) ] ] whileTrue: [ array at: currentIndex put: parentValue. currentIndex := parentIndex ]. array at: currentIndex put: currentValue! ! !CTPriorityQueue methodsFor: 'accessing' stamp: 'lr 4/1/2012 12:20'! unmodifiable self unsupportedOperation! ! CTCollection subclass: #CTSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! !CTSet commentStamp: 'lr 4/25/2012 14:48' prior: 0! Abstract set common to all set implementations.! CTSet subclass: #CTDelegateSet instanceVariableNames: 'delegate' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTDelegateSet commentStamp: 'lr 4/25/2012 14:40' prior: 0! A set that delegates to another set.! !CTDelegateSet class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 14:18'! on: aSet ^ self basicNew initializeOn: aSet! ! !CTDelegateSet methodsFor: 'adding' stamp: 'lr 4/21/2012 14:17'! add: anObject ^ delegate add: anObject! ! !CTDelegateSet methodsFor: 'testing' stamp: 'lr 4/21/2012 14:21'! includes: anObject ^ delegate includes: anObject! ! !CTDelegateSet methodsFor: 'initialization' stamp: 'lr 4/21/2012 14:21'! initialize: anInteger comparator: aComparator self unsupportedOperation! ! !CTDelegateSet methodsFor: 'initialization' stamp: 'lr 4/21/2012 14:18'! initializeOn: aSet delegate := aSet! ! !CTDelegateSet methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! iterator ^ delegate iterator! ! !CTDelegateSet methodsFor: 'copying' stamp: 'lr 4/21/2012 14:17'! postCopy super postCopy. delegate := delegate copy! ! !CTDelegateSet methodsFor: 'removing' stamp: 'lr 4/21/2012 14:17'! remove: anObject ifAbsent: aBlock ^ delegate remove: anObject ifAbsent: aBlock! ! !CTDelegateSet methodsFor: 'removing' stamp: 'lr 4/21/2012 14:17'! removeAll ^ delegate removeAll! ! !CTDelegateSet methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! size ^ delegate size! ! CTDelegateSet subclass: #CTImmutableSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTImmutableSet commentStamp: 'lr 4/25/2012 14:39' prior: 0! An immutable set backed internally by a CTLinkedHashSet.! !CTImmutableSet class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:51'! new: anInteger ^ self withAll: #()! ! !CTImmutableSet class methodsFor: 'instance creation' stamp: 'lr 2/17/2012 23:46'! with: anObject1 ^ self withAll: (Array with: anObject1)! ! !CTImmutableSet class methodsFor: 'instance creation' stamp: 'lr 2/17/2012 23:46'! with: anObject1 with: anObject2 ^ self withAll: (Array with: anObject1 with: anObject2)! ! !CTImmutableSet class methodsFor: 'instance creation' stamp: 'lr 2/17/2012 23:46'! with: anObject1 with: anObject2 with: anObject3 ^ self withAll: (Array with: anObject1 with: anObject2 with: anObject3)! ! !CTImmutableSet class methodsFor: 'instance creation' stamp: 'lr 2/17/2012 23:46'! with: anObject1 with: anObject2 with: anObject3 with: anObject4 ^ self withAll: (Array with: anObject1 with: anObject2 with: anObject3 with: anObject4)! ! !CTImmutableSet class methodsFor: 'instance creation' stamp: 'lr 2/17/2012 23:46'! withAll: anArray ^ self basicNew initializeWithAll: anArray! ! !CTImmutableSet methodsFor: 'adding' stamp: 'lr 2/17/2012 23:48'! add: anObject self unsupportedOperation! ! !CTImmutableSet methodsFor: 'copying' stamp: 'lr 2/17/2012 23:49'! copy ^ self! ! !CTImmutableSet methodsFor: 'accessing' stamp: 'lr 2/17/2012 23:36'! immutable ^ self! ! !CTImmutableSet methodsFor: 'initialization' stamp: 'lr 4/21/2012 14:17'! initializeWithAll: aCollection delegate := CTLinkedHashSet withAll: aCollection! ! !CTImmutableSet methodsFor: 'removing' stamp: 'lr 2/17/2012 23:48'! remove: anObject ifAbsent: aBlock self unsupportedOperation! ! !CTImmutableSet methodsFor: 'removing' stamp: 'lr 2/17/2012 23:48'! removeAll self unsupportedOperation! ! !CTImmutableSet methodsFor: 'accessing' stamp: 'lr 2/17/2012 23:49'! unmodifiable ^ self! ! CTDelegateSet subclass: #CTUnmodifiableSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTUnmodifiableSet commentStamp: 'lr 4/25/2012 14:27' prior: 0! A read-only view onto another set.! !CTUnmodifiableSet methodsFor: 'adding' stamp: 'lr 2/17/2012 23:32'! add: anObject self unsupportedOperation! ! !CTUnmodifiableSet methodsFor: 'copying' stamp: 'lr 2/17/2012 23:32'! copy ^ self! ! !CTUnmodifiableSet methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:17'! immutable ^ delegate immutable! ! !CTUnmodifiableSet methodsFor: 'removing' stamp: 'lr 2/17/2012 23:32'! remove: anObject ifAbsent: aBlock self unsupportedOperation! ! !CTUnmodifiableSet methodsFor: 'removing' stamp: 'lr 2/17/2012 23:32'! removeAll self unsupportedOperation! ! !CTUnmodifiableSet methodsFor: 'accessing' stamp: 'lr 2/17/2012 23:33'! unmodifiable ^ self! ! CTSet subclass: #CTHashSet instanceVariableNames: 'table' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTHashSet commentStamp: 'lr 4/25/2012 14:42' prior: 0! A set that hashes its elements.! !CTHashSet methodsFor: 'adding' stamp: 'lr 1/13/2012 22:38'! add: anObject (table at: anObject) ifNil: [ table add: (self newNode: anObject) ]. ^ anObject! ! !CTHashSet methodsFor: 'testing' stamp: 'lr 1/14/2012 09:57'! includes: anObject ^ (table at: anObject) notNil! ! !CTHashSet methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:20'! initialize: anInteger comparator: aComparator table := self tableClass new: anInteger comparator: aComparator! ! !CTHashSet methodsFor: 'accessing' stamp: 'lr 1/12/2012 20:31'! iterator ^ table iterator collect: [ :each | each key ]! ! !CTHashSet methodsFor: 'private' stamp: 'lr 1/13/2012 22:37'! newNode: anObject ^ self nodeClass new key: anObject; yourself! ! !CTHashSet methodsFor: 'private' stamp: 'lr 1/13/2012 13:53'! nodeClass ^ CTHashSetNode! ! !CTHashSet methodsFor: 'copying' stamp: 'lr 1/13/2012 13:51'! postCopy table := table copy! ! !CTHashSet methodsFor: 'removing' stamp: 'lr 1/13/2012 23:54'! remove: anObject ifAbsent: aBlock ^ (table removeKey: anObject) ifNil: [ aBlock value ] ifNotNil: [ :node | node key ]! ! !CTHashSet methodsFor: 'removing' stamp: 'lr 1/12/2012 20:33'! removeAll table removeAll! ! !CTHashSet methodsFor: 'accessing' stamp: 'lr 1/12/2012 20:31'! size ^ table size! ! !CTHashSet methodsFor: 'private' stamp: 'lr 1/13/2012 22:42'! tableClass ^ CTHashTable! ! CTHashSet subclass: #CTLinkedHashSet instanceVariableNames: 'root' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTLinkedHashSet commentStamp: 'lr 4/25/2012 14:42' prior: 0! A set that hashes its elements and keep their addition order through a linked list.! !CTLinkedHashSet methodsFor: 'adding' stamp: 'lr 1/5/2013 15:43'! add: anObject (table at: anObject) ifNil: [ | node | node := self newNode: anObject. root add: node before: root. table add: node ]. ^ anObject! ! !CTLinkedHashSet methodsFor: 'initialization' stamp: 'lr 1/24/2012 19:37'! initialize: anInteger comparator: aComparator super initialize: anInteger comparator: aComparator. root := self listClass new! ! !CTLinkedHashSet methodsFor: 'accessing' stamp: 'lr 4/21/2012 09:18'! iterator ^ root iterator collect: [ :each | each key ]! ! !CTLinkedHashSet methodsFor: 'private' stamp: 'lr 1/13/2012 22:43'! listClass ^ CTLinkedListRoot! ! !CTLinkedHashSet methodsFor: 'private' stamp: 'lr 1/13/2012 22:35'! nodeClass ^ CTLinkedHashSetNode! ! !CTLinkedHashSet methodsFor: 'copying' stamp: 'lr 4/21/2012 09:20'! postCopy super postCopy. root := root copy. table := table copyEmpty. root iterator addTo: table! ! !CTLinkedHashSet methodsFor: 'removing' stamp: 'lr 1/13/2012 23:54'! remove: anObject ifAbsent: aBlock ^ (table removeKey: anObject) ifNil: [ aBlock value ] ifNotNil: [ :node | root remove: node. node key ]! ! !CTLinkedHashSet methodsFor: 'removing' stamp: 'lr 1/13/2012 13:25'! removeAll super removeAll. root removeAll! ! CTSet subclass: #CTKeysOfMap instanceVariableNames: 'map' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTKeysOfMap commentStamp: 'lr 5/13/2012 18:21' prior: 0! A modifiable view onto the keys of a map.! !CTKeysOfMap class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 19:19'! on: aMap ^ self basicNew initializeOn: aMap! ! !CTKeysOfMap methodsFor: 'adding' stamp: 'lr 4/21/2012 14:06'! add: anObject self unsupportedOperation! ! !CTKeysOfMap methodsFor: 'testing' stamp: 'lr 4/22/2012 00:19'! includes: anObject ^ map includesKey: anObject! ! !CTKeysOfMap methodsFor: 'initialization' stamp: 'lr 5/13/2012 18:13'! initialize: anInteger comparator: aComparator self unsupportedOperation! ! !CTKeysOfMap methodsFor: 'initialization' stamp: 'lr 4/21/2012 21:07'! initializeOn: aMap map := aMap! ! !CTKeysOfMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 22:09'! iterator ^ map nodeIterator collect: [ :each | each key ]! ! !CTKeysOfMap methodsFor: 'removing' stamp: 'lr 4/22/2012 00:13'! remove: anObject ifAbsent: aBlock ^ map removeKey: anObject ifAbsent: aBlock! ! !CTKeysOfMap methodsFor: 'removing' stamp: 'lr 4/21/2012 14:06'! removeAll ^ map removeAll! ! !CTKeysOfMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:06'! size ^ map size! ! !CTSet class methodsFor: 'accessing' stamp: 'lr 1/27/2012 14:19'! defaultComparator ^ CTNaturalComparator new! ! !CTSet class methodsFor: 'instance creation' stamp: 'lr 1/27/2012 14:20'! new: anInteger ^ self new: anInteger comparator: self defaultComparator! ! !CTSet class methodsFor: 'instance creation' stamp: 'lr 1/27/2012 14:20'! new: anInteger comparator: aComparator ^ self basicNew initialize: anInteger comparator: aComparator! ! !CTSet methodsFor: 'accessing' stamp: 'lr 2/17/2012 23:58'! immutable ^ CTImmutableSet withAll: self! ! !CTSet methodsFor: 'initialization' stamp: 'lr 4/23/2012 22:39'! initialize: anInteger comparator: aComparator self subclassResponsibility! ! !CTSet methodsFor: 'accessing' stamp: 'lr 2/17/2012 23:34'! unmodifiable ^ CTUnmodifiableSet on: self! ! CTSet subclass: #CTTreeSet instanceVariableNames: 'tree' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTTreeSet commentStamp: 'lr 4/25/2012 14:44' prior: 0! A set that stores its elements in their natural sorted order.! !CTTreeSet methodsFor: 'adding' stamp: 'lr 1/15/2012 15:34'! add: anObject tree add: (self newNode: anObject). ^ anObject! ! !CTTreeSet methodsFor: 'testing' stamp: 'lr 1/15/2012 14:46'! includes: anObject ^ (tree at: anObject) notNil! ! !CTTreeSet methodsFor: 'initialization' stamp: 'lr 2/18/2012 08:21'! initialize: anInteger comparator: aComparator tree := self treeClass comparator: aComparator! ! !CTTreeSet methodsFor: 'accessing' stamp: 'lr 4/21/2012 09:20'! iterator ^ tree iterator collect: [ :each | each key ]! ! !CTTreeSet methodsFor: 'private' stamp: 'lr 1/15/2012 14:13'! newNode: anObject ^ self nodeClass new key: anObject; yourself! ! !CTTreeSet methodsFor: 'private' stamp: 'lr 3/30/2012 17:51'! nodeClass ^ CTRedBlackTreeNode! ! !CTTreeSet methodsFor: 'copying' stamp: 'lr 1/25/2012 22:55'! postCopy super postCopy. tree := tree copy! ! !CTTreeSet methodsFor: 'removing' stamp: 'lr 1/24/2012 20:05'! remove: anObject ifAbsent: aBlock ^ (tree removeKey: anObject) ifNil: [ aBlock value ] ifNotNil: [ :node | node key ]! ! !CTTreeSet methodsFor: 'removing' stamp: 'lr 1/24/2012 20:05'! removeAll tree removeAll! ! !CTTreeSet methodsFor: 'accessing' stamp: 'lr 1/15/2012 15:28'! size ^ tree size! ! !CTTreeSet methodsFor: 'private' stamp: 'lr 3/30/2012 17:50'! treeClass ^ CTRedBlackTree! ! CTCollection subclass: #CTValuesOfMap instanceVariableNames: 'map' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTValuesOfMap commentStamp: 'lr 5/13/2012 18:21' prior: 0! A modifiable view onto the values of a map.! !CTValuesOfMap class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 19:19'! on: aMap ^ self basicNew initializeOn: aMap! ! !CTValuesOfMap methodsFor: 'adding' stamp: 'lr 4/21/2012 14:08'! add: anObject self unsupportedOperation! ! !CTValuesOfMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:12'! immutable ^ map immutable values! ! !CTValuesOfMap methodsFor: 'initialization' stamp: 'lr 4/21/2012 21:07'! initializeOn: aMap map := aMap! ! !CTValuesOfMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 22:09'! iterator ^ map nodeIterator collect: [ :each | each object ]! ! !CTValuesOfMap methodsFor: 'removing' stamp: 'lr 4/21/2012 14:11'! remove: anObject ifAbsent: aBlock map iterator do: [ :key :value | anObject = value ifTrue: [ ^ map removeKey: key ] ]. ^ aBlock value! ! !CTValuesOfMap methodsFor: 'removing' stamp: 'lr 4/21/2012 14:08'! removeAll map removeAll! ! !CTValuesOfMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:08'! size ^ map size! ! !CTValuesOfMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 14:13'! unmodifiable ^ map unmodifiable values! ! !CTContainer class methodsFor: 'accessing' stamp: 'lr 2/19/2012 11:18'! defaultCapacity ^ CTSettings defaultCapacity! ! !CTContainer class methodsFor: 'instance creation' stamp: 'lr 2/19/2012 11:18'! new ^ self new: self defaultCapacity! ! !CTContainer class methodsFor: 'instance creation' stamp: 'lr 2/19/2012 11:30'! new: anInteger ^ self basicNew initialize: anInteger ! ! !CTContainer methodsFor: 'private' stamp: 'lr 4/21/2012 09:42'! elementNotFound: anObject "Signals an error that anObject was not found in the container." ^ CTElementNotFoundError new element: anObject; signal! ! !CTContainer methodsFor: 'accessing' stamp: 'lr 4/25/2012 14:28'! immutable "Answer an immutable view of the container." self subclassResponsibility! ! !CTContainer methodsFor: 'private' stamp: 'lr 4/21/2012 10:11'! indexOutOfBounds: anInteger "Signals an error that anInteger exceeds the bounds of the container." ^ CTIndexOutOfBoundsError new index: anInteger; signal! ! !CTContainer methodsFor: 'initialization' stamp: 'lr 2/19/2012 11:30'! initialize: anInteger self unsupportedOperation! ! !CTContainer methodsFor: 'private' stamp: 'lr 4/21/2012 09:43'! keyNotFound: anObject "Signals an error that anObject is not a valid key of the container." ^ CTKeyNotFoundError new key: anObject; signal! ! !CTContainer methodsFor: 'private' stamp: 'lr 4/21/2012 09:43'! noSuchElement "Signals an error that the container does not contain the requested element." ^ CTNoSuchElementError signal! ! !CTContainer methodsFor: 'printing' stamp: 'lr 3/30/2012 11:21'! printElementsOn: aStream self subclassResponsibility! ! !CTContainer methodsFor: 'printing' stamp: 'lr 2/19/2012 11:17'! printOn: aStream super printOn: aStream. self printElementsOn: aStream! ! !CTContainer methodsFor: 'removing' stamp: 'lr 4/21/2012 09:41'! removeAll "Remove all the elements from the container." self subclassResponsibility! ! !CTContainer methodsFor: 'accessing' stamp: 'lr 4/25/2012 14:28'! unmodifiable "Answer a read-only view of the container." self subclassResponsibility! ! !CTContainer methodsFor: 'private' stamp: 'lr 4/21/2012 09:43'! unsupportedOperation "Signals an error that the container does not support the requested operation." ^ CTUnsupportedOperationError signal! ! CTContainer subclass: #CTMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! !CTMap commentStamp: 'lr 4/25/2012 14:49' prior: 0! Abstract map common to all map implementations.! CTMap subclass: #CTDelegateMap instanceVariableNames: 'delegate' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTDelegateMap commentStamp: 'lr 4/25/2012 14:26' prior: 0! A map that delegates to another map.! !CTDelegateMap class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 19:25'! on: aMap ^ self basicNew initializeOn: aMap! ! !CTDelegateMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 19:21'! at: aKey ifAbsent: aBlock ^ delegate at: aKey ifAbsent: aBlock! ! !CTDelegateMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 19:21'! at: aKey put: aValue ^ delegate at: aKey put: aValue! ! !CTDelegateMap methodsFor: 'testing' stamp: 'lr 4/21/2012 19:22'! includesKey: aKey ^ delegate includesKey: aKey! ! !CTDelegateMap methodsFor: 'initialization' stamp: 'lr 4/21/2012 19:24'! initialize: anInteger comparator: aComparator self unsupportedOperation! ! !CTDelegateMap methodsFor: 'initialization' stamp: 'lr 4/21/2012 19:24'! initializeOn: aSet delegate := aSet! ! !CTDelegateMap methodsFor: 'private' stamp: 'lr 4/21/2012 19:22'! nodeIterator ^ delegate nodeIterator! ! !CTDelegateMap methodsFor: 'copying' stamp: 'lr 4/21/2012 19:24'! postCopy super postCopy. delegate := delegate copy! ! !CTDelegateMap methodsFor: 'removing' stamp: 'lr 4/21/2012 19:21'! removeAll delegate removeAll! ! !CTDelegateMap methodsFor: 'removing' stamp: 'lr 4/21/2012 19:22'! removeKey: aKey ifAbsent: aBlock ^ delegate removeKey: aKey ifAbsent: aBlock! ! !CTDelegateMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 19:21'! size ^ delegate size! ! CTDelegateMap subclass: #CTImmutableMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTImmutableMap commentStamp: 'lr 4/25/2012 14:40' prior: 0! An immutable set backed internally by a CTLinkedHashMap.! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:37'! key: aKey1 value: aValue1 ^ self withAll: (CTLinkedHashMap key: aKey1 value: aValue1)! ! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:37'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 ^ self withAll: (CTLinkedHashMap key: aKey1 value: aValue1 key: aKey2 value: aValue2)! ! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:37'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 ^ self withAll: (CTLinkedHashMap key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3)! ! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:37'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 key: aKey4 value: aValue4 ^ self withAll: (CTLinkedHashMap key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 key: aKey4 value: aValue4)! ! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 4/1/2012 16:36'! keys: aKeysCollection values: aValuesCollection ^ self withAll: (CTLinkedHashMap keys: aKeysCollection values: aValuesCollection)! ! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 23:17'! new: anInteger comparator: aComparator ^ self withAll: (CTLinkedHashMap new: 0)! ! !CTImmutableMap class methodsFor: 'instance creation' stamp: 'lr 2/18/2012 22:15'! withAll: aMap ^ self basicNew initializeWithAll: aMap! ! !CTImmutableMap methodsFor: 'accessing' stamp: 'lr 2/18/2012 09:14'! at: aKey put: aValue self unsupportedOperation! ! !CTImmutableMap methodsFor: 'copying' stamp: 'lr 2/18/2012 09:10'! copy ^ self! ! !CTImmutableMap methodsFor: 'accessing' stamp: 'lr 2/18/2012 09:10'! immutable ^ self! ! !CTImmutableMap methodsFor: 'initialization' stamp: 'lr 4/21/2012 19:20'! initializeWithAll: aMap delegate := CTLinkedHashMap withAll: aMap! ! !CTImmutableMap methodsFor: 'removing' stamp: 'lr 2/18/2012 09:15'! removeAll self unsupportedOperation! ! !CTImmutableMap methodsFor: 'removing' stamp: 'lr 2/18/2012 09:15'! removeKey: aKey ifAbsent: aBlock self unsupportedOperation! ! !CTImmutableMap methodsFor: 'accessing' stamp: 'lr 2/18/2012 09:10'! unmodifiable ^ self! ! CTDelegateMap subclass: #CTUnmodifiableMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTUnmodifiableMap commentStamp: 'lr 4/25/2012 14:27' prior: 0! A read-only view onto another map.! !CTUnmodifiableMap methodsFor: 'accessing' stamp: 'lr 2/18/2012 09:16'! at: aKey put: aValue self unsupportedOperation! ! !CTUnmodifiableMap methodsFor: 'copying' stamp: 'lr 2/18/2012 09:10'! copy ^ self! ! !CTUnmodifiableMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 19:20'! immutable ^ delegate immutable! ! !CTUnmodifiableMap methodsFor: 'removing' stamp: 'lr 2/18/2012 09:16'! removeAll self unsupportedOperation! ! !CTUnmodifiableMap methodsFor: 'removing' stamp: 'lr 2/18/2012 09:16'! removeKey: aKey ifAbsent: aBlock self unsupportedOperation! ! !CTUnmodifiableMap methodsFor: 'accessing' stamp: 'lr 2/18/2012 09:10'! unmodifiable ^ self! ! CTMap subclass: #CTHashMap instanceVariableNames: 'table' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTHashMap commentStamp: 'lr 4/25/2012 14:43' prior: 0! A map that hashes its elements by their key.! !CTHashMap methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:13'! at: aKey ifAbsent: aBlock ^ (table at: aKey) ifNil: [ aBlock value ] ifNotNil: [ :node | node object ] ! ! !CTHashMap methodsFor: 'accessing' stamp: 'lr 1/14/2012 10:31'! at: aKey put: anObject (table at: aKey) ifNil: [ table add: (self newNode: aKey with: anObject) ] ifNotNil: [ :node | node object: anObject ]. ^ anObject! ! !CTHashMap methodsFor: 'testing' stamp: 'lr 1/14/2012 12:11'! includesKey: aKey ^ (table at: aKey) notNil! ! !CTHashMap methodsFor: 'initialization' stamp: 'lr 2/19/2012 11:21'! initialize: anInteger comparator: aComparator table := self tableClass new: anInteger comparator: aComparator! ! !CTHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 10:13'! newNode: aKey with: anObject ^ self nodeClass new key: aKey; object: anObject; yourself! ! !CTHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 10:12'! nodeClass ^ CTHashMapNode! ! !CTHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 12:00'! nodeIterator ^ table iterator! ! !CTHashMap methodsFor: 'copying' stamp: 'lr 1/13/2012 13:14'! postCopy super postCopy. table := table copy! ! !CTHashMap methodsFor: 'removing' stamp: 'lr 1/13/2012 13:14'! removeAll table removeAll! ! !CTHashMap methodsFor: 'removing' stamp: 'lr 1/14/2012 11:42'! removeKey: aKey ifAbsent: aBlock ^ (table removeKey: aKey) ifNil: [ aBlock value ] ifNotNil: [ :node | node object ]! ! !CTHashMap methodsFor: 'accessing' stamp: 'lr 1/13/2012 13:10'! size ^ table size! ! !CTHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 10:11'! tableClass ^ CTHashTable! ! CTHashMap subclass: #CTLinkedHashMap instanceVariableNames: 'root' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTLinkedHashMap commentStamp: 'lr 4/25/2012 14:43' prior: 0! A map that hashes its elements by their key and keeps their addition order through a linked list.! !CTLinkedHashMap methodsFor: 'accessing' stamp: 'lr 1/5/2013 15:46'! at: aKey put: anObject (table at: aKey) ifNil: [ | node | node := self newNode: aKey with: anObject. root add: node before: root. table add: node ] ifNotNil: [ :node | node object: anObject ]. ^ anObject! ! !CTLinkedHashMap methodsFor: 'initialization' stamp: 'lr 1/27/2012 14:16'! initialize: anInteger comparator: aComparator super initialize: anInteger comparator: aComparator. root := self listClass new! ! !CTLinkedHashMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 09:30'! iterator ^ CTMapIterator on: root iterator! ! !CTLinkedHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 10:15'! listClass ^ CTLinkedListRoot! ! !CTLinkedHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 10:13'! nodeClass ^ CTLinkedHashMapNode! ! !CTLinkedHashMap methodsFor: 'private' stamp: 'lr 4/21/2012 21:07'! nodeIterator ^ root iterator! ! !CTLinkedHashMap methodsFor: 'copying' stamp: 'lr 4/21/2012 09:20'! postCopy super postCopy. root := root copy. table := table copyEmpty. root iterator addTo: table! ! !CTLinkedHashMap methodsFor: 'removing' stamp: 'lr 1/14/2012 10:18'! removeAll super removeAll. root removeAll! ! !CTLinkedHashMap methodsFor: 'removing' stamp: 'lr 1/14/2012 10:18'! removeKey: aKey ifAbsent: aBlock ^ (table removeKey: aKey) ifNil: [ aBlock value ] ifNotNil: [ :node | root remove: node. node object ]! ! !CTMap class methodsFor: 'accessing' stamp: 'lr 1/27/2012 14:18'! defaultComparator ^ CTNaturalComparator new! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 4/1/2012 16:33'! key: aKey1 value: aValue1 "Creates a new map from a key-value pair." ^ (self new: 1) at: aKey1 put: aValue1; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 4/1/2012 16:34'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 "Creates a new map from two key-value pairs." ^ (self new: 2) at: aKey1 put: aValue1; at: aKey2 put: aValue2; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 4/1/2012 16:34'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 "Creates a new map from three key-value pairs." ^ (self new: 3) at: aKey1 put: aValue1; at: aKey2 put: aValue2; at: aKey3 put: aValue3; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 4/1/2012 16:34'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 key: aKey4 value: aValue4 "Creates a new map from four key-value pairs." ^ (self new: 4) at: aKey1 put: aValue1; at: aKey2 put: aValue2; at: aKey3 put: aValue3; at: aKey4 put: aValue4; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 4/1/2012 16:38'! keys: aKeysCollection values: aValuesCollection "Creates a new map from a collection of keys and a collection of values." | map keys values | map := self new: aKeysCollection size. keys := aKeysCollection iterator. values := aValuesCollection iterator. [ keys hasNext ] whileTrue: [ map at: keys next put: values nextOrNil ]. ^ map! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 2/19/2012 11:18'! new: anInteger ^ self new: anInteger comparator: self defaultComparator! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 2/19/2012 11:18'! new: anInteger comparator: aComparator ^ self basicNew initialize: anInteger comparator: aComparator! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/14/2012 11:23'! withAll: aMap ^ aMap iterator inject: (self new: aMap size) into: [ :result :key :value | result at: key put: value; yourself ]! ! !CTMap methodsFor: 'accessing' stamp: 'lr 1/1/2012 17:19'! at: aKey ^ self at: aKey ifAbsent: [ self keyNotFound: aKey ]! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:19'! at: aKey ifAbsent: aBlock self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 4/3/2012 20:06'! at: aKey ifAbsentPut: aBlock ^ self at: aKey ifAbsent: [ self at: aKey put: aBlock value ]! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:21'! at: aKey ifPresent: aBlock ^ aBlock value: (self at: aKey ifAbsent: [ ^ nil ])! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:22'! at: aKey put: aValue self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 2/18/2012 09:13'! immutable "Answer an immutable copy of the receiver. The copy is immutable and changes in receiver are not reflected." ^ CTImmutableMap withAll: self! ! !CTMap methodsFor: 'testing' stamp: 'lr 2/19/2012 10:58'! includesAllKeys: aContainer "Tests if all objects of aContainer are keys in the receiver." ^ aContainer iterator allSatisfy: [ :each | self includesKey: each ]! ! !CTMap methodsFor: 'testing' stamp: 'lr 1/14/2012 12:11'! includesKey: aKey self subclassResponsibility! ! !CTMap methodsFor: 'initialization' stamp: 'lr 2/19/2012 11:20'! initialize: anInteger comparator: aComparator self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 1/14/2012 12:02'! iterator "Answer a default iterator over the key and values in this collection." ^ CTMapIterator on: self nodeIterator! ! !CTMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 13:51'! keys "Answer a view on the keys of this map." ^ CTKeysOfMap on: self! ! !CTMap methodsFor: 'private' stamp: 'lr 1/14/2012 12:00'! nodeIterator "Answer a node iterator over the nodes of this map." self subclassResponsibility! ! !CTMap methodsFor: 'printing' stamp: 'lr 2/18/2012 08:30'! printElementsOn: aStream | iterator | iterator := self iterator. (iterator limit: CTSettings elementsToPrint) do: [ :key :value | aStream cr; tab; print: key; nextPutAll: ': '; print: value ]. iterator hasNext ifTrue: [ aStream cr; tab; nextPutAll: '...' ]! ! !CTMap methodsFor: 'removing' stamp: 'lr 1/1/2012 17:21'! removeKey: aKey ^ self removeKey: aKey ifAbsent: [ self keyNotFound: aKey ]! ! !CTMap methodsFor: 'removing' stamp: 'lr 1/1/2012 17:21'! removeKey: aKey ifAbsent: aBlock self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 3/30/2012 11:27'! unmodifiable "Answer an unmodifiable view of the receiver. The copy itself is immutable but changes in the receiver are reflected in the view." ^ CTUnmodifiableMap on: self! ! !CTMap methodsFor: 'accessing' stamp: 'lr 4/21/2012 13:51'! values "Answer an view on the values of this map." ^ CTValuesOfMap on: self! ! CTMap subclass: #CTTreeMap instanceVariableNames: 'tree' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTTreeMap commentStamp: 'lr 4/25/2012 14:44' prior: 0! A set that stores its elements in the natural sorted order of their keys.! !CTTreeMap methodsFor: 'accessing' stamp: 'lr 1/25/2012 08:07'! at: aKey ifAbsent: aBlock ^ (tree at: aKey) ifNil: [ aBlock value ] ifNotNil: [ :node | node object ]! ! !CTTreeMap methodsFor: 'accessing' stamp: 'lr 1/25/2012 08:07'! at: aKey put: aValue (tree add: (self newNode: aKey)) object: aValue. ^ aValue! ! !CTTreeMap methodsFor: 'testing' stamp: 'lr 1/25/2012 08:10'! includesKey: aKey ^ (tree at: aKey) notNil! ! !CTTreeMap methodsFor: 'initialization' stamp: 'lr 2/19/2012 11:21'! initialize: anInteger comparator: aComparator tree := self treeClass comparator: aComparator! ! !CTTreeMap methodsFor: 'private' stamp: 'lr 1/24/2012 20:53'! newNode: anObject ^ self nodeClass new key: anObject; yourself! ! !CTTreeMap methodsFor: 'private' stamp: 'lr 1/24/2012 20:53'! nodeClass ^ CTTreeMapNode! ! !CTTreeMap methodsFor: 'private' stamp: 'lr 4/21/2012 20:59'! nodeIterator ^ tree iterator! ! !CTTreeMap methodsFor: 'copying' stamp: 'lr 1/25/2012 22:54'! postCopy super postCopy. tree := tree copy! ! !CTTreeMap methodsFor: 'removing' stamp: 'lr 1/25/2012 08:09'! removeAll tree removeAll! ! !CTTreeMap methodsFor: 'removing' stamp: 'lr 1/25/2012 08:09'! removeKey: aKey ifAbsent: aBlock ^ (tree removeKey: aKey) ifNil: [ aBlock value ] ifNotNil: [ :node | node object ]! ! !CTTreeMap methodsFor: 'accessing' stamp: 'lr 1/24/2012 20:53'! size ^ tree size! ! !CTTreeMap methodsFor: 'private' stamp: 'lr 3/30/2012 17:51'! treeClass ^ CTRedBlackTree! ! !CTIterable class methodsFor: 'accessing' stamp: 'lr 2/25/2013 08:24'! browserIcon ^ #collection! ! !CTIterable methodsFor: 'testing' stamp: 'lr 2/25/2013 08:25'! isEmpty "Answer if the receiver contains no elements." ^ self size = 0! ! !CTIterable methodsFor: 'accessing' stamp: 'lr 2/25/2013 08:24'! iterator "Answer a default iterator over the elements in this container." self subclassResponsibility! ! !CTIterable methodsFor: 'testing' stamp: 'lr 2/25/2013 08:25'! notEmpty "Answer true the receiver contains any elements." ^ self size > 0! ! !CTIterable methodsFor: 'accessing' stamp: 'lr 2/25/2013 08:26'! size "Answer the number of elements in this container." | tally iterator | tally := 0. iterator := self iterator. [ iterator hasNext ] whileTrue: [ iterator next. tally := tally + 1 ]. ^ tally! ! Object subclass: #CTIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTIterator commentStamp: 'lr 4/21/2012 11:53' prior: 0! Abstract iterator class that implements all necessary behavior to iterate over different kinds of collections in different ways. Iterators are one-time consumable, that is that most operations exhaust (or partially exhaust) them so that they cannot meaningfully used anymore. It is cheap however to create a new iterator whenever one is needed.! CTIterator subclass: #CTDelegateIterator instanceVariableNames: 'delegate' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTDelegateIterator commentStamp: 'lr 4/3/2012 19:18' prior: 0! An iterator that delegates to another iterator.! !CTDelegateIterator class methodsFor: 'instance creation' stamp: 'lr 1/1/2012 18:06'! on: anIterator ^ self basicNew initializeOn: anIterator! ! !CTDelegateIterator methodsFor: 'private' stamp: 'lr 4/21/2012 11:53'! apply: aBlock with: anObject ^ delegate apply: aBlock with: anObject! ! !CTDelegateIterator methodsFor: 'private' stamp: 'lr 4/21/2012 11:53'! apply: aBlock with: anObject with: anotherObject ^ delegate apply: aBlock with: anObject with: anotherObject! ! !CTDelegateIterator methodsFor: 'testing' stamp: 'lr 4/21/2012 11:53'! hasNext ^ delegate hasNext! ! !CTDelegateIterator methodsFor: 'initialization' stamp: 'lr 4/21/2012 11:53'! initializeOn: anIterator delegate := anIterator! ! !CTDelegateIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 11:53'! next ^ delegate next! ! CTDelegateIterator subclass: #CTFlatteningIterator instanceVariableNames: 'current block' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTFlatteningIterator commentStamp: 'lr 12/29/2012 15:41' prior: 0! An iterator that lazily flattens its elements.! !CTFlatteningIterator class methodsFor: 'instance creation' stamp: 'lr 12/29/2012 15:38'! on: anIterator block: aBlock ^ self basicNew initializeOn: anIterator block: aBlock! ! !CTFlatteningIterator methodsFor: 'testing' stamp: 'lr 12/29/2012 17:15'! hasNext | hasNext | [ (hasNext := current hasNext) or: [ delegate hasNext not ] ] whileFalse: [ current := (self apply: block with: delegate next) iterator ]. ^ hasNext! ! !CTFlatteningIterator methodsFor: 'initialization' stamp: 'lr 12/29/2012 17:18'! initializeOn: anIterator block: aBlock self initializeOn: anIterator. block := aBlock. current := CTEmptyIterator new! ! !CTFlatteningIterator methodsFor: 'accessing' stamp: 'lr 12/29/2012 17:15'! next [ current hasNext or: [ delegate hasNext not ] ] whileFalse: [ current := (self apply: block with: delegate next) iterator ]. ^ current next! ! CTDelegateIterator subclass: #CTIndexingIterator instanceVariableNames: 'index' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTIndexingIterator commentStamp: 'lr 4/21/2012 12:05' prior: 0! An iterator that indexes each element.! !CTIndexingIterator methodsFor: 'private' stamp: 'lr 4/21/2012 12:23'! apply: aBlock with: anObject ^ aBlock value: index value: anObject! ! !CTIndexingIterator methodsFor: 'private' stamp: 'lr 4/21/2012 12:23'! apply: aBlock with: anObject with: anotherObject ^ aBlock value: anObject value: index value: anotherObject! ! !CTIndexingIterator methodsFor: 'initialization' stamp: 'lr 4/21/2012 12:09'! initializeOn: anIterator super initializeOn: anIterator. index := 0! ! !CTIndexingIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 12:03'! next | element | element := super next. index := index + 1. ^ element! ! !CTIndexingIterator methodsFor: 'iterators' stamp: 'lr 4/21/2012 20:55'! withIndex ^ self! ! CTDelegateIterator subclass: #CTLimitingIterator instanceVariableNames: 'limit' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTLimitingIterator commentStamp: '' prior: 0! An iterator that limits its consumable elements to a fixed number.! !CTLimitingIterator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 14:47'! on: anIterator limit: anInteger ^ self basicNew initializeOn: anIterator limit: anInteger! ! !CTLimitingIterator methodsFor: 'testing' stamp: 'lr 4/21/2012 11:53'! hasNext ^ 0 < limit and: [ delegate hasNext ]! ! !CTLimitingIterator methodsFor: 'initialization' stamp: 'lr 2/12/2012 14:47'! initializeOn: anIterator limit: anInteger self initializeOn: anIterator. limit := anInteger! ! !CTLimitingIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 11:53'! next self hasNext ifFalse: [ ^ self noSuchElementError ]. limit := limit - 1. ^ delegate next! ! CTDelegateIterator subclass: #CTMapIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTMapIterator methodsFor: 'private' stamp: 'lr 4/21/2012 20:57'! apply: aBlock with: aNode ^ aBlock value: aNode key value: aNode object! ! !CTMapIterator methodsFor: 'private' stamp: 'lr 4/21/2012 20:57'! apply: aBlock with: anObject with: aNode ^ aBlock value: anObject value: aNode key value: aNode object! ! CTDelegateIterator subclass: #CTMutatingIterator instanceVariableNames: 'block' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTMutatingIterator commentStamp: 'lr 4/3/2012 19:18' prior: 0! An iterator that lazily mutates its elements.! !CTMutatingIterator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 14:48'! on: anIterator block: aBlock ^ self basicNew initializeOn: anIterator block: aBlock! ! !CTMutatingIterator methodsFor: 'initialization' stamp: 'lr 2/12/2012 14:48'! initializeOn: anIterator block: aBlock self initializeOn: anIterator. block := aBlock! ! !CTMutatingIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 11:53'! next ^ self apply: block with: delegate next! ! CTDelegateIterator subclass: #CTPartitionIterator instanceVariableNames: 'size' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTPartitionIterator commentStamp: 'lr 4/21/2012 11:54' prior: 0! An iterator that lazily splits its iterator into lists of a specified size.! !CTPartitionIterator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 14:48'! on: anIterator size: anInteger ^ self basicNew initializeOn: anIterator size: anInteger! ! !CTPartitionIterator methodsFor: 'initialization' stamp: 'lr 2/12/2012 14:58'! initializeOn: anIterator size: anInteger self initializeOn: anIterator. size := anInteger! ! !CTPartitionIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 11:53'! next | list | list := CTVectorList new: size. [ list addLast: delegate next. list size < size and: [ delegate hasNext ] ] whileTrue. ^ list! ! CTDelegateIterator subclass: #CTPeekingIterator instanceVariableNames: 'defined current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTPeekingIterator commentStamp: 'lr 4/21/2012 11:54' prior: 0! An iterator that can peek onto the next element of its delegate.! CTPeekingIterator subclass: #CTFilteringIterator instanceVariableNames: 'predicate' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTFilteringIterator commentStamp: 'lr 4/21/2012 11:55' prior: 0! An iterator that lazily filters its elements using a provided predicate.! !CTFilteringIterator class methodsFor: 'instance creation' stamp: 'lr 2/12/2012 14:46'! on: anIterator predicate: aBlock ^ self basicNew initializeOn: anIterator predicate: aBlock! ! !CTFilteringIterator methodsFor: 'testing' stamp: 'lr 4/21/2012 11:53'! hasNext defined ifTrue: [ ^ true ]. [ delegate hasNext ifFalse: [ ^ false ]. self apply: predicate with: (current := delegate next) ] whileFalse. ^ defined := true! ! !CTFilteringIterator methodsFor: 'initialization' stamp: 'lr 4/4/2012 17:14'! initializeOn: anIterator predicate: aBlock self initializeOn: anIterator. predicate := aBlock! ! !CTPeekingIterator methodsFor: 'testing' stamp: 'lr 4/21/2012 11:53'! hasNext defined ifTrue: [ ^ true ]. delegate hasNext ifFalse: [ ^ false ]. current := delegate next. ^ defined := true! ! !CTPeekingIterator methodsFor: 'initialization' stamp: 'lr 4/4/2012 17:14'! initializeOn: anIterator super initializeOn: anIterator. defined := false! ! !CTPeekingIterator methodsFor: 'accessing' stamp: 'lr 4/4/2012 17:14'! next self hasNext ifFalse: [ ^ self noSuchElementError ]. defined := false. ^ current! ! !CTPeekingIterator methodsFor: 'accessing' stamp: 'lr 4/4/2012 17:16'! peek self hasNext ifFalse: [ ^ self noSuchElementError ]. ^ current! ! !CTPeekingIterator methodsFor: 'iterators' stamp: 'lr 4/4/2012 17:40'! peeking ^ self! ! CTPeekingIterator subclass: #CTUniqueIterator instanceVariableNames: 'seen' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTUniqueIterator commentStamp: 'lr 1/5/2013 15:17' prior: 0! An iterator that lazily filters out duplicated elements.! !CTUniqueIterator class methodsFor: 'instance creation' stamp: 'lr 1/5/2013 15:21'! on: anIterator comparator: aComparator ^ self basicNew initializeOn: anIterator comparator: aComparator! ! !CTUniqueIterator methodsFor: 'testing' stamp: 'lr 1/5/2013 15:20'! hasNext defined ifTrue: [ ^ true ]. [ delegate hasNext ifFalse: [ ^ false ]. seen includes: (current := delegate next) ] whileTrue. seen add: current. ^ defined := true! ! !CTUniqueIterator methodsFor: 'initialization' stamp: 'lr 1/5/2013 15:21'! initializeOn: anIterator comparator: aComparator self initializeOn: anIterator. seen := CTHashSet new: CTHashSet defaultCapacity comparator: aComparator! ! CTIterator subclass: #CTDispatchingIterator instanceVariableNames: 'iterators' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTDispatchingIterator commentStamp: 'lr 4/3/2012 19:20' prior: 0! An iterator that dispatches to other iterators.! CTDispatchingIterator subclass: #CTChainingIterator instanceVariableNames: 'iterator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTChainingIterator commentStamp: 'lr 4/5/2012 12:08' prior: 0! An iterator that chains iterators together.! !CTChainingIterator methodsFor: 'iterators' stamp: 'lr 4/22/2012 00:49'! , anIterable iterators addLast: anIterable iterator! ! !CTChainingIterator methodsFor: 'testing' stamp: 'lr 4/5/2012 12:17'! hasNext | hasNext | [ (hasNext := iterator hasNext) or: [ iterators isEmpty ] ] whileFalse: [ iterator := iterators removeFirst ]. ^ hasNext! ! !CTChainingIterator methodsFor: 'initialization' stamp: 'lr 4/5/2012 12:10'! initializeOn: aContainer super initializeOn: (aContainer as: CTArrayList). iterator := CTEmptyIterator new! ! !CTChainingIterator methodsFor: 'accessing' stamp: 'lr 4/5/2012 12:17'! next [ iterator hasNext or: [ iterators isEmpty ] ] whileFalse: [ iterator := iterators removeFirst ]. ^ iterator next! ! !CTDispatchingIterator class methodsFor: 'instance creation' stamp: 'lr 4/5/2012 12:21'! on: aContainer ^ self basicNew initializeOn: aContainer! ! !CTDispatchingIterator methodsFor: 'initialization' stamp: 'lr 4/5/2012 12:21'! initializeOn: aContainer iterators := aContainer! ! CTDispatchingIterator subclass: #CTMergingIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTMergingIterator commentStamp: 'lr 4/5/2012 12:17' prior: 0! An iterator that merges two or more iterators based on a comparator.! !CTMergingIterator class methodsFor: 'instance creation' stamp: 'lr 4/26/2012 22:11'! on: aContainer ^ self on: aContainer comparator: CTNaturalComparator new! ! !CTMergingIterator class methodsFor: 'instance creation' stamp: 'lr 4/26/2012 22:11'! on: aContainer comparator: aComparator ^ self basicNew initializeOn: aContainer comparator: aComparator! ! !CTMergingIterator methodsFor: 'iterators' stamp: 'lr 4/26/2012 22:11'! <> anIterable | iterator | iterator := anIterable iterator. iterator hasNext ifTrue: [ iterators add: iterator peeking ]! ! !CTMergingIterator methodsFor: 'testing' stamp: 'lr 4/26/2012 22:11'! hasNext ^ iterators notEmpty! ! !CTMergingIterator methodsFor: 'initialization' stamp: 'lr 4/26/2012 22:11'! initializeOn: aContainer comparator: aComparator self initializeOn: (CTPriorityQueue new: aContainer size comparator: (aComparator transform: #peek)). aContainer iterator do: [ :iterator | self <> iterator ]! ! !CTMergingIterator methodsFor: 'accessing' stamp: 'lr 4/26/2012 22:11'! next | iterator element | self hasNext ifFalse: [ ^ self noSuchElementError ]. iterator := iterators removeFirst. element := iterator next. iterator hasNext ifTrue: [ iterators add: iterator ]. ^ element! ! CTDispatchingIterator subclass: #CTZippingIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTZippingIterator commentStamp: 'lr 4/4/2012 17:08' prior: 0! An iterator that consumes the elements of two or more iterators in parallel.! !CTZippingIterator methodsFor: 'private' stamp: 'lr 4/3/2012 19:41'! apply: aBlock with: anObject ^ aBlock valueWithArguments: anObject! ! !CTZippingIterator methodsFor: 'private' stamp: 'lr 4/3/2012 19:45'! apply: aBlock with: anObject with: anotherObject ^ aBlock valueWithArguments: ((Array new: 1 + anotherObject size) at: 1 put: anObject; replaceFrom: 2 to: anotherObject size + 1 with: anotherObject; yourself)! ! !CTZippingIterator methodsFor: 'testing' stamp: 'lr 4/3/2012 19:47'! hasNext 1 to: iterators size do: [ :index | (iterators at: index) hasNext ifFalse: [ ^ false ] ]. ^ true! ! !CTZippingIterator methodsFor: 'accessing' stamp: 'lr 4/3/2012 19:50'! next | result | result := Array new: iterators size. 1 to: iterators size do: [ :index | result at: index put: (iterators at: index) next ]. ^ result! ! !CTZippingIterator methodsFor: 'iterators' stamp: 'lr 4/22/2012 00:49'! | anIterable ^ self class on: (iterators copyWith: anIterable iterator)! ! CTIterator subclass: #CTEmptyIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! CTEmptyIterator class instanceVariableNames: 'instance'! !CTEmptyIterator commentStamp: '' prior: 0! An empty iterator that has no elements.! CTEmptyIterator class instanceVariableNames: 'instance'! !CTEmptyIterator class methodsFor: 'class initialization' stamp: 'lr 4/21/2012 23:49'! initialize instance := self basicNew! ! !CTEmptyIterator class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 10:09'! new ^ instance! ! !CTEmptyIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 19:01'! hasNext ^ false! ! !CTEmptyIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 19:14'! next ^ self noSuchElementError! ! CTIterator subclass: #CTHashTableIterator instanceVariableNames: 'array index node' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTHashTableIterator class methodsFor: 'instance creation' stamp: 'lr 1/12/2012 19:30'! on: anArray ^ self basicNew initializeOn: anArray! ! !CTHashTableIterator methodsFor: 'testing' stamp: 'lr 1/12/2012 19:33'! hasNext ^ node notNil! ! !CTHashTableIterator methodsFor: 'initialization' stamp: 'lr 1/28/2012 16:47'! initializeOn: anArray node := anArray at: (index := (array := anArray) size). [ node isNil and: [ index > 1 ] ] whileTrue: [ node := array at: (index := index - 1) ]! ! !CTHashTableIterator methodsFor: 'accessing' stamp: 'lr 4/22/2012 13:08'! next | result | node isNil ifTrue: [ ^ self noSuchElementError ]. node := (result := node) next. [ node isNil and: [ index > 1 ] ] whileTrue: [ node := array at: (index := index - 1) ]. ^ result! ! !CTIterator class methodsFor: 'accessing' stamp: 'lr 4/1/2012 17:03'! browserIcon ^ #stream! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 4/22/2012 00:48'! , anIterable "Answer a chained iterator that continues with the argument if the receiver is exhausted." ^ CTChainingIterator on: (Array with: self with: anIterable iterator) iterator! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 4/26/2012 22:11'! <> anIterable "Answer an iterator that merges the receiver and anIterable." ^ CTMergingIterator on: (Array with: self with: anIterable iterator)! ! !CTIterator methodsFor: 'collections' stamp: 'lr 1/1/2012 00:17'! addTo: aCollection "Add the elements of the receiving iterator to aCollection, answer aCollection." [ self hasNext ] whileTrue: [ aCollection add: self next ]. ^ aCollection! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/15/2012 17:09'! allSatisfy: aBlock "Tests whether all of the elements of the receiver satisfy aBlock. Answer true if all do, false otherwise." [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifFalse: [ ^ false ] ]. ^ true! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/15/2012 17:09'! anySatisfy: aBlock "Tests whether any of the elements of the receiver satisfy aBlock. Answer true if any does, false otherwise." [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifTrue: [ ^ true ] ]. ^ false! ! !CTIterator methodsFor: 'private' stamp: 'lr 1/9/2012 21:03'! apply: aBlock with: anObject ^ aBlock value: anObject! ! !CTIterator methodsFor: 'private' stamp: 'lr 1/9/2012 21:05'! apply: aBlock with: anObject with: anotherObject ^ aBlock value: anObject value: anotherObject! ! !CTIterator methodsFor: 'converting' stamp: 'lr 1/27/2012 14:10'! as: aCollectionClass "Converts the remainder of this iterator into aCollectionClass." ^ self addTo: aCollectionClass new! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 2/12/2012 15:30'! at: anInteger "Returns the element at index anInteger, or throws an exception." ^ self at: anInteger ifAbsent: [ self indexOutOfBounds: anInteger ] ! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 2/12/2012 15:37'! at: anInteger ifAbsent: aBlock "Returns the element at index anInteger, or evaluate aBlock." (0 < anInteger and: [ self hasNext ]) ifFalse: [ ^ aBlock value ]. 1 to: anInteger - 1 do: [ :index | self next. self hasNext ifFalse: [ ^ aBlock value ] ]. ^ self next! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 1/1/2012 00:33'! collect: aBlock "Answer an iterator that transforms all the elements of the receiving iterator with aBlock." ^ CTMutatingIterator on: self block: aBlock! ! !CTIterator methodsFor: 'copying' stamp: 'lr 4/21/2012 11:08'! copy CTUnsupportedOperationError signal! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/9/2012 21:04'! count: aBlock "Counts the elements of the receiver that satisfy aBlock." | tally | tally := 0. [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifTrue: [ tally := tally + 1 ] ]. ^ tally! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/29/2011 08:10'! detect: aBlock "Answer the first element for which aBlock returns true, otherwise throw CTNoSuchElementError." ^ self detect: aBlock ifNone: [ self noSuchElementError ]! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/9/2012 21:04'! detect: aBlock ifNone: anAbsentBlock "Answer the first element for which aBlock returns true, otherwise answer the result of evaluating anAbsentBlock." [ self hasNext ] whileTrue: [ | current | (self apply: aBlock with: (current := self next)) ifTrue: [ ^ current ] ]. ^ anAbsentBlock value! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/9/2012 21:03'! do: aBlock "Evaluate aBlock with each of the elements of the receiver." [ self hasNext ] whileTrue: [ self apply: aBlock with: self next ]! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/9/2012 21:04'! do: aBlock separatedBy: aSeparatorBlock "Evaluate aBlock with each of the elements of the receiver, and evaluate aSeparatorBlock in-between each of the elements." | beforeFirst | beforeFirst := true. [ self hasNext ] whileTrue: [ beforeFirst ifTrue: [ beforeFirst := false ] ifFalse: [ aSeparatorBlock value ]. self apply: aBlock with: self next ]! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/31/2011 16:31'! find: aBlock "Answer the index of the first element satisfying aBlock, otherwise return 0." ^ self find: aBlock ifAbsent: [ 0 ]! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/9/2012 21:04'! find: aBlock ifAbsent: anAbsentBlock "Answer the index of the first element satisfying aBlock, otherwise evaluate anAbsentBlock." | index | index := 1. [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifTrue: [ ^ index ]. index := index + 1 ]. ^ anAbsentBlock value! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 12/29/2012 14:43'! flatten: aBlock "Answer an iterator that flattens all the elements of the receiving iterator with aBlock." ^ CTFlatteningIterator on: self block: aBlock! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 4/21/2012 10:14'! groupBy: aBlock "Groups the elements of an iterable by aBlock." | map | map := CTLinkedHashMap new. [ self hasNext ] whileTrue: [ | key value | key := aBlock value: (value := self next). (map at: key ifAbsentPut: [ CTLinkedHashSet new ]) add: value ]. ^ map! ! !CTIterator methodsFor: 'testing' stamp: 'lr 12/29/2011 05:48'! hasNext "Answer whether there is a next element in the iterator." self subclassResponsibility ! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/1/2012 13:53'! includes: anObject "Tests whether the receiver contains anObject." [ self hasNext ] whileTrue: [ anObject = self next ifTrue: [ ^ true ] ]. ^ false! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/29/2011 23:38'! indexOf: anObject "Answer the index of the first occurence of anObject, otherwise return 0." ^ self indexOf: anObject ifAbsent: [ 0 ]! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/1/2012 13:53'! indexOf: anObject ifAbsent: anAbsentBlock "Answer the index of the first occurence of anObject, evaluate anAbsentBlock otherwise." | index | index := 1. [ self hasNext ] whileTrue: [ anObject = self next ifTrue: [ ^ index ]. index := index + 1 ]. ^ anAbsentBlock value! ! !CTIterator methodsFor: 'private' stamp: 'lr 5/13/2012 18:17'! indexOutOfBounds: anInteger "Signals an error that anInteger exceeds the bounds of the container." ^ CTIndexOutOfBoundsError new index: anInteger; signal! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/9/2012 21:05'! inject: anObject into: aBlock "Accumulate a running value associated with evaluating aBlock with the current value of anObject and the receivers elements as block arguments." | nextValue | nextValue := anObject. [ self hasNext ] whileTrue: [ nextValue := self apply: aBlock with: nextValue with: self next ]. ^ nextValue! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 4/21/2012 11:59'! iterator "Answer an iterator of the receiver." ^ self! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 2/12/2012 15:29'! last "Answer the last element of the receiver." | current | [ current := self next. self hasNext ] whileTrue. ^ current! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 1/1/2012 00:48'! limit: anInteger "Answer an iterator that consumes at most anInteger elements of the receiving iterator." ^ CTLimitingIterator on: self limit: anInteger! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 1/1/2012 00:29'! next "Answer the next element of this iterator, or raise CTNoSuchElementError if the receiver is exhausted." self subclassResponsibility! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 4/1/2012 16:38'! nextOr: anObject "Answer the next element of this iterator, or anObject if the receiver is exhausted." ^ self hasNext ifTrue: [ self next ] ifFalse: [ anObject ]! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 4/1/2012 16:35'! nextOrNil "Answer the next element of this iterator, or nil if the receiver is exhausted." ^ self nextOr: nil! ! !CTIterator methodsFor: 'private' stamp: 'lr 8/3/2011 19:14'! noSuchElementError ^ CTNoSuchElementError signal! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/15/2012 17:09'! noneSatisfy: aBlock "Tests whether none of the elements of the receiver satisfy aBlock. Answer true if none does, false otherwise.." [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifTrue: [ ^ false ] ]. ^ true! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 2/12/2012 14:57'! partition: anInteger "Answer an iterator that partitions the receiver into lists of anInteger elements." ^ CTPartitionIterator on: self size: anInteger! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 4/4/2012 17:26'! peeking "Answer an iterator that allows to peek the next element." ^ CTPeekingIterator on: self! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 4/22/2012 13:04'! reduce: aBlock "Reduce the elements of the receiver into aBlock. The argument aBlock must take two or more arguments. Fails if the receiver contains less elements than the block expects." | arguments | aBlock argumentCount < 2 ifTrue: [ ^ CTIllegalArgumentError signal: 'aBlock expected to expect at least 2 arguments' ]. arguments := Array new: aBlock argumentCount. arguments at: 1 put: self next. [ self hasNext ] whileTrue: [ 2 to: arguments size do: [ :index | arguments at: index put: self next ]. arguments at: 1 put: (aBlock valueWithArguments: arguments) ]. ^ arguments at: 1! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 1/20/2012 17:27'! reject: aBlockPredicate "Answer an iterator that contains all the elements of the receiving iterator that do not satisfy aBlockPredicate." ^ CTFilteringIterator on: self predicate: [ :each | (aBlockPredicate value: each) not ]! ! !CTIterator methodsFor: 'collections' stamp: 'lr 4/23/2012 21:38'! removeFrom: aCollection "Remove the elements of the receiving iterator from aCollection, answer aCollection." [ self hasNext ] whileTrue: [ aCollection remove: self next ifAbsent: [ nil ] ]. ^ aCollection! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 1/20/2012 17:27'! select: aBlockPredicate "Answer an iterator that contains all the elements of the receiving iterator that do satisfy aBlockPredicate." ^ CTFilteringIterator on: self predicate: aBlockPredicate! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 1/1/2012 13:55'! size "Answer the number of remaining elements in the receiving iterator." | tally | tally := 0. [ self hasNext ] whileTrue: [ tally := tally + 1. self next ]. ^ tally! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 1/5/2013 15:23'! unique "Answer an iterator that filters out repeated elements using the natural comparator." ^ self unique: CTNaturalComparator new! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 1/5/2013 15:23'! unique: aComparator "Answer an iterator that filters out repeated elements." ^ CTUniqueIterator on: self comparator: aComparator! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 4/21/2012 20:55'! withIndex "Answer an iterator that knows the current element index." ^ CTIndexingIterator on: self! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 4/22/2012 00:49'! | anIterable "Combines the receiving iterator into an iterator of the receiver and the argument." ^ CTZippingIterator on: (Array with: self with: anIterable iterator)! ! CTIterator subclass: #CTLinkedListIterator instanceVariableNames: 'root current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTLinkedListIterator class methodsFor: 'instance creation' stamp: 'lr 1/13/2012 10:33'! on: aNode ^ self basicNew initializeOn: aNode! ! !CTLinkedListIterator methodsFor: 'testing' stamp: 'lr 4/21/2012 12:00'! hasNext ^ current after ~~ root! ! !CTLinkedListIterator methodsFor: 'initialization' stamp: 'lr 4/21/2012 12:03'! initializeOn: aNode root := current := aNode! ! !CTLinkedListIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 12:03'! next ^ current after == root ifTrue: [ self noSuchElementError ] ifFalse: [ current := current after ]! ! CTIterator subclass: #CTListIterator instanceVariableNames: 'list start stop position' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTListIterator commentStamp: 'lr 4/21/2012 21:13' prior: 0! An iterator over for arrays, lists and other collections with indexed access.! !CTListIterator class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 21:12'! on: aList ^ self on: aList start: 1 stop: aList size! ! !CTListIterator class methodsFor: 'instance creation' stamp: 'lr 4/21/2012 21:12'! on: aList start: aStartIndex stop: aStopIndex ^ self basicNew initializeOn: aList start: aStartIndex stop: aStopIndex ! ! !CTListIterator methodsFor: 'testing' stamp: 'lr 4/21/2012 11:47'! hasNext ^ position < stop! ! !CTListIterator methodsFor: 'initialization' stamp: 'lr 5/13/2012 18:22'! initializeOn: aList start: aStartInteger stop: aStopInteger list := aList. start := aStartInteger. stop := aStopInteger. position := aStartInteger - 1! ! !CTListIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 21:13'! next ^ self hasNext ifFalse: [ self noSuchElementError ] ifTrue: [ list at: (position := position + 1) ]! ! CTIterator subclass: #CTPluggableIterator instanceVariableNames: 'next hasNext' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTPluggableIterator commentStamp: 'lr 2/13/2012 07:11' prior: 0! A pluggable iterator is implemented with blocks, this is useful if the inner state of a collection should be visible and for testing.! !CTPluggableIterator class methodsFor: 'instance creation' stamp: 'lr 4/26/2012 22:23'! next: nextBlock ^ self next: nextBlock hasNext: [ true ]! ! !CTPluggableIterator class methodsFor: 'instance creation' stamp: 'lr 2/13/2012 07:13'! next: nextBlock hasNext: hasNextBlock ^ self basicNew initializeNext: nextBlock hasNext: hasNextBlock! ! !CTPluggableIterator methodsFor: 'testing' stamp: 'lr 2/13/2012 07:11'! hasNext ^ hasNext value! ! !CTPluggableIterator methodsFor: 'initialization' stamp: 'lr 2/13/2012 07:13'! initializeNext: nextBlock hasNext: hasNextBlock next := nextBlock. hasNext := hasNextBlock! ! !CTPluggableIterator methodsFor: 'accessing' stamp: 'lr 2/13/2012 07:12'! next ^ next value! ! CTIterator subclass: #CTRedBlackTreeIterator instanceVariableNames: 'parents current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTRedBlackTreeIterator class methodsFor: 'instance creation' stamp: 'lr 1/25/2012 22:39'! on: aNode ^ self basicNew initializeOn: aNode! ! !CTRedBlackTreeIterator methodsFor: 'testing' stamp: 'lr 3/31/2012 09:12'! hasNext ^ current notNil or: [ parents size > 0 ]! ! !CTRedBlackTreeIterator methodsFor: 'initialization' stamp: 'lr 3/31/2012 09:12'! initializeOn: aRoot parents := CTVectorList new. current := aRoot ! ! !CTRedBlackTreeIterator methodsFor: 'accessing' stamp: 'lr 4/21/2012 19:47'! next | node | node := current. [ node isNil ] whileFalse: [ parents addLast: node. node := node left ]. parents isEmpty ifTrue: [ ^ self noSuchElementError ]. node := parents removeLast. current := node right. ^ node! ! Object subclass: #CTLinkedListNode instanceVariableNames: 'object before after' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTLinkedListNode class methodsFor: 'instance creation' stamp: 'lr 11/6/2011 17:27'! on: anObject ^ self basicNew object: anObject! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 1/1/2012 18:06'! after ^ after! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 1/1/2012 18:07'! after: aNode after := aNode! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 1/1/2012 18:06'! before ^ before! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 1/1/2012 18:06'! before: aNode before := aNode! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:26'! object ^ object! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:26'! object: anObject object := anObject! ! Object subclass: #CTLinkedListRoot instanceVariableNames: 'before after' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTLinkedListRoot class methodsFor: 'instance creation' stamp: 'lr 1/13/2012 10:54'! new ^ self basicNew initialize! ! !CTLinkedListRoot methodsFor: 'adding' stamp: 'lr 1/13/2012 12:55'! add: aNode after: anotherNode aNode after: anotherNode after. aNode before: anotherNode. anotherNode after before: aNode. anotherNode after: aNode! ! !CTLinkedListRoot methodsFor: 'adding' stamp: 'lr 1/13/2012 13:00'! add: aNode before: anotherNode aNode after: anotherNode. aNode before: anotherNode before. anotherNode before after: aNode. anotherNode before: aNode! ! !CTLinkedListRoot methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:14'! after ^ after! ! !CTLinkedListRoot methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:15'! after: aNode after := aNode! ! !CTLinkedListRoot methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:14'! before ^ before! ! !CTLinkedListRoot methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:14'! before: aNode before := aNode! ! !CTLinkedListRoot methodsFor: 'copying' stamp: 'lr 4/21/2012 09:20'! copy | copy iterator | copy := super copy initialize. iterator := self iterator. [ iterator hasNext ] whileTrue: [ copy add: iterator next copy before: copy ]. ^ copy! ! !CTLinkedListRoot methodsFor: 'initialization' stamp: 'lr 1/13/2012 10:53'! initialize before := after := self! ! !CTLinkedListRoot methodsFor: 'converting' stamp: 'lr 4/21/2012 12:00'! iterator ^ CTLinkedListIterator on: self! ! !CTLinkedListRoot methodsFor: 'removing' stamp: 'lr 1/13/2012 11:32'! remove: aNode aNode before after: aNode after. aNode after before: aNode before! ! !CTLinkedListRoot methodsFor: 'removing' stamp: 'lr 1/13/2012 10:19'! removeAll before := after := self! ! Object subclass: #CTRedBlackTree instanceVariableNames: 'size comparator root' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTRedBlackTree class methodsFor: 'instance creation' stamp: 'lr 3/30/2012 17:53'! comparator: aComparator ^ self basicNew initializeComparator: aComparator! ! !CTRedBlackTree methodsFor: 'modifying' stamp: 'lr 3/30/2012 22:22'! add: aNode root := self add: aNode into: root. root red: false. ^ aNode! ! !CTRedBlackTree methodsFor: 'private' stamp: 'lr 5/13/2012 18:17'! add: aNode into: aParentNode | node | node := aParentNode ifNil: [ size := size + 1. ^ aNode red: true ]. (comparator equals: aNode key to: node key) ifTrue: [ node := aNode left: node left; right: node right; red: node red; yourself ] ifFalse: [ (comparator less: aNode key than: node key) ifTrue: [ node left: (self add: aNode into: node left) ] ifFalse: [ node right: (self add: aNode into: node right) ] ]. ^ self fixUp: node! ! !CTRedBlackTree methodsFor: 'accessing' stamp: 'lr 3/30/2012 13:19'! at: aKey | current | current := root. [ current notNil ] whileTrue: [ (comparator equals: aKey to: current key) ifTrue: [ ^ current ]. current := (comparator less: aKey than: current key) ifTrue: [ current left ] ifFalse: [ current right ] ]. ^ nil! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/31/2012 15:34'! colorFlip: aNode aNode red: aNode red not. aNode left red: aNode left red not. aNode right red: aNode right red not! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/31/2012 15:37'! fixUp: aNode | node | node := aNode. (self isRed: node right) ifTrue: [ node := self rotateLeft: node ]. ((self isRed: node left) and: [ self isRed: node left left ]) ifTrue: [ node := self rotateRight: node ]. ((self isRed: node left) and: [ self isRed: node right ]) ifTrue: [ self colorFlip: node ]. ^ node! ! !CTRedBlackTree methodsFor: 'initialization' stamp: 'lr 3/30/2012 17:53'! initializeComparator: aComparator size := 0. comparator := aComparator! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/30/2012 18:07'! isRed: aNode ^ aNode notNil and: [ aNode red ]! ! !CTRedBlackTree methodsFor: 'converting' stamp: 'lr 4/22/2012 00:45'! iterator ^ CTRedBlackTreeIterator on: root! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/31/2012 15:34'! moveLeft: aNode | node | self colorFlip: (node := aNode). (self isRed: node right left) ifTrue: [ node right: (self rotateRight: node right). node := self rotateLeft: node. self colorFlip: node ]. ^ node! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/31/2012 15:34'! moveRight: aNode | node | self colorFlip: (node := aNode). (self isRed: node left left) ifTrue: [ node := self rotateRight: node. self colorFlip: node ]. ^ node! ! !CTRedBlackTree methodsFor: 'copying' stamp: 'lr 4/21/2012 09:20'! postCopy | iterator | iterator := self iterator. self removeAll. [ iterator hasNext ] whileTrue: [ self add: iterator next copy ]! ! !CTRedBlackTree methodsFor: 'private' stamp: 'lr 4/1/2012 10:49'! remove: aNode from: aParentNode | node | node := aParentNode. (comparator less: aNode key than: node key) ifTrue: [ ((self isRed: node left) or: [ self isRed: node left left ]) ifFalse: [ node := self moveLeft: node ]. node left: (self remove: aNode from: node left) ] ifFalse: [ (self isRed: node left) ifTrue: [ node := self rotateRight: node ]. ((comparator equals: aNode key to: node key) and: [ node right isNil ]) ifTrue: [ size := size - 1. ^ nil ]. ((self isRed: node right) or: [ self isRed: node right left ]) ifFalse: [ node := self moveRight: node ]. (comparator equals: aNode key to: node key) ifFalse: [ node right: (self remove: aNode from: node right) ] ifTrue: [ | minimum | minimum := node right. [ minimum left isNil ] whileFalse: [ minimum := minimum left ]. node copyState: minimum. node right: (self removeMinimum: node right) ] ]. ^ self fixUp: node ! ! !CTRedBlackTree methodsFor: 'modifying' stamp: 'lr 3/30/2012 13:26'! removeAll root := nil. size := 0! ! !CTRedBlackTree methodsFor: 'modifying' stamp: 'lr 3/31/2012 15:57'! removeKey: aKey | node | node := (self at: aKey) ifNil: [ ^ nil ]. root := self remove: node from: root. root ifNotNil: [ root red: false ]. ^ node! ! !CTRedBlackTree methodsFor: 'private' stamp: 'lr 4/1/2012 10:35'! removeMinimum: aNode | node | (node := aNode) left ifNil: [ size := size - 1. ^ nil ]. ((self isRed: node left) or: [ self isRed: node left left ]) ifFalse: [ node := self moveLeft: node ]. node left: (self removeMinimum: node left). ^ self fixUp: node! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/31/2012 15:34'! rotateLeft: aNode | node | node := aNode right. aNode right: node left. node left: aNode. node red: aNode red. aNode red: true. ^ node! ! !CTRedBlackTree methodsFor: 'private-balance' stamp: 'lr 3/30/2012 13:41'! rotateRight: aNode | node | node := aNode left. aNode left: node right. node right: aNode. node red: aNode red. aNode red: true. ^ node! ! !CTRedBlackTree methodsFor: 'accessing' stamp: 'lr 3/30/2012 13:19'! size ^ size! ! Object subclass: #CTRedBlackTreeNode instanceVariableNames: 'key red left right' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTRedBlackTreeNode methodsFor: 'copying' stamp: 'lr 4/1/2012 10:49'! copyState: aNode key := aNode key! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! key ^ key! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! key: anObject key := anObject! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! left ^ left! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! left: aNode left := aNode! ! !CTRedBlackTreeNode methodsFor: 'copying' stamp: 'lr 3/31/2012 11:07'! postCopy super postCopy. red := left := right := nil! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! red ^ red! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! red: aBoolean red := aBoolean! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! right ^ right! ! !CTRedBlackTreeNode methodsFor: 'accessing' stamp: 'lr 3/30/2012 17:43'! right: aNode right := aNode! ! CTRedBlackTreeNode subclass: #CTTreeMapNode instanceVariableNames: 'object' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTTreeMapNode methodsFor: 'copying' stamp: 'lr 4/1/2012 10:49'! copyState: aNode super copyState: aNode. object := aNode object! ! !CTTreeMapNode methodsFor: 'accessing' stamp: 'lr 1/24/2012 21:00'! object ^ object! ! !CTTreeMapNode methodsFor: 'accessing' stamp: 'lr 1/24/2012 21:00'! object: anObject object := anObject! ! Object subclass: #CTSettings instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core'! CTSettings class instanceVariableNames: 'defaultCapacity elementsToPrint'! !CTSettings commentStamp: 'lr 5/13/2012 18:05' prior: 0! Common settings of the container framework (see class side).! CTSettings class instanceVariableNames: 'defaultCapacity elementsToPrint'! !CTSettings class methodsFor: 'accessing' stamp: 'lr 2/18/2012 08:31'! defaultCapacity ^ defaultCapacity! ! !CTSettings class methodsFor: 'accessing' stamp: 'lr 2/18/2012 08:32'! defaultCapacity: anInteger defaultCapacity := anInteger! ! !CTSettings class methodsFor: 'accessing' stamp: 'lr 2/18/2012 08:32'! elementsToPrint ^ elementsToPrint! ! !CTSettings class methodsFor: 'accessing' stamp: 'lr 2/18/2012 08:32'! elementsToPrint: anInteger elementsToPrint := anInteger! ! !CTSettings class methodsFor: 'class initialization' stamp: 'lr 4/1/2012 17:03'! initialize self elementsToPrint: 7. self defaultCapacity: 10! ! !CTSettings class methodsFor: 'settings' stamp: 'lr 4/1/2012 16:08'! settingsOn: aBuilder (aBuilder group: #containers) label: 'Containers' translated; description: 'Settings related to the container library'; with: [ (aBuilder setting: #elementsToPrint) target: self; label: 'Elements to print in print string'; description: 'The number of elements to print in inspectors and other tools when looking at containers.'. (aBuilder setting: #defaultCapacity) target: self; label: 'Default capacity of collections'; description: 'The number of slots to allocate by default that the container can hold without growing.' ]! ! !CTSettings methodsFor: 'accessing' stamp: 'lr 4/24/2012 19:05'! license ^ 'Copyright (c) 2012 Lukas Renggli, renggli@gmail.com Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: - The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. - The Software or portions thereof shall not be changed, repackaged or integrated with other systems if this prevents the unmodified Software from working. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.'! ! CTNaturalComparator initialize! CTIdentityComparator initialize! CTEmptyIterator initialize! CTSettings initialize!