SystemOrganization addCategory: #'Container-Abstract'! SystemOrganization addCategory: #'Container-Exceptions'! SystemOrganization addCategory: #'Container-Iterators'! SystemOrganization addCategory: #'Container-Lists'! SystemOrganization addCategory: #'Container-Sets'! SystemOrganization addCategory: #'Container-Maps'! SystemOrganization addCategory: #'Container-Tests'! Error subclass: #CTElementNotFoundError instanceVariableNames: 'element' classVariableNames: '' poolDictionaries: '' category: 'Container-Exceptions'! !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: #CTImmutableCollectionError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Exceptions'! Error subclass: #CTIndexOutOfBoundsError instanceVariableNames: 'index' classVariableNames: '' poolDictionaries: '' category: 'Container-Exceptions'! !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: #CTNoSuchElementError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Exceptions'! TestCase subclass: #CTCollectionTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Tests'! !CTCollectionTest class methodsFor: 'testing' stamp: 'lr 8/7/2011 19:59'! isAbstract ^ self name = #CTCollectionTest! ! !CTCollectionTest class methodsFor: 'accessing' stamp: 'lr 12/31/2011 12:42'! packageNamesUnderTest ^ #('Container')! ! !CTCollectionTest methodsFor: 'accessing' stamp: 'lr 11/5/2011 18:42'! collectionClass ^ CTCollection! ! !CTCollectionTest methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:17'! emptyCollection ^ self collectionClass new! ! !CTCollectionTest methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:18'! oneElementCollection ^ self collectionClass with: 1! ! !CTCollectionTest methodsFor: 'tests-iterators' stamp: 'lr 12/31/2011 17:12'! testEmptyIterator | iterator | iterator := self emptyCollection iterator. self deny: iterator hasNext; assert: iterator isEmpty. self should: [ iterator next ] raise: CTNoSuchElementError! ! !CTCollectionTest methodsFor: 'tests-testing' stamp: 'lr 8/7/2011 19:19'! testIsEmpty self assert: self emptyCollection isEmpty. self deny: self oneElementCollection isEmpty. self deny: self twoElementCollection isEmpty! ! !CTCollectionTest methodsFor: 'tests-iterators' stamp: 'lr 12/31/2011 12:48'! testSimpleIterator | iterator | iterator := self oneElementCollection iterator. self assert: iterator hasNext. self assert: iterator next notNil. self deny: iterator hasNext. self should: [ iterator next ] raise: CTNoSuchElementError! ! !CTCollectionTest methodsFor: 'tests-accessing' stamp: 'lr 8/7/2011 19:19'! testSize self assert: self emptyCollection size = 0. self assert: self oneElementCollection size = 1. self assert: self twoElementCollection size = 2! ! !CTCollectionTest methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:25'! twoElementCollection ^ self collectionClass with: 1 with: 2! ! CTCollectionTest subclass: #CTListTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Tests'! CTListTest subclass: #CTArrayListTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Tests'! !CTArrayListTest methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:21'! collectionClass ^ CTArrayList! ! CTListTest subclass: #CTLinkedListTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Tests'! !CTLinkedListTest methodsFor: 'accessing' stamp: 'lr 8/7/2011 19:21'! collectionClass ^ CTLinkedList! ! !CTListTest class methodsFor: 'testing' stamp: 'lr 8/7/2011 19:59'! isAbstract ^ self name = #CTListTest! ! !CTListTest methodsFor: 'accessing' stamp: 'lr 11/5/2011 18:42'! collectionClass ^ CTList! ! !CTListTest methodsFor: 'tests-iterators' stamp: 'lr 12/31/2011 14:39'! testEmptyReverseIterator | reverseIterator | reverseIterator := self emptyCollection reverseIterator. self deny: reverseIterator hasNext. self should: [ reverseIterator next ] raise: CTNoSuchElementError! ! !CTListTest methodsFor: 'tests-accessing' stamp: 'lr 8/7/2011 20:08'! testFirst self should: [ self emptyCollection first ] raise: CTNoSuchElementError. self assert: self oneElementCollection first = 1. self assert: self twoElementCollection first = 1! ! !CTListTest methodsFor: 'tests-accessing' stamp: 'lr 8/7/2011 19:54'! testLast self should: [ self emptyCollection last ] raise: CTNoSuchElementError. self assert: self oneElementCollection last = 1. self assert: self twoElementCollection last = 2! ! !CTListTest methodsFor: 'tests-iterators' stamp: 'lr 12/31/2011 14:40'! testSimpleReverseIterator | iterator reverseIterator | iterator := self oneElementCollection iterator. reverseIterator := self oneElementCollection reverseIterator. self assert: reverseIterator hasNext. self assert: reverseIterator next = iterator next. self deny: reverseIterator hasNext. self should: [ reverseIterator next ] raise: CTNoSuchElementError! ! TestCase subclass: #CTIteratorTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Tests'! !CTIteratorTest methodsFor: 'utilities' stamp: 'lr 12/31/2011 15:01'! assertIterator: anIteratorOne equals: anIteratorTwo [ anIteratorOne hasNext and: [ anIteratorTwo hasNext ] ] whileTrue: [ self assert: anIteratorOne next = anIteratorTwo next ]. self assertIteratorAtEnd: anIteratorOne; assertIteratorAtEnd: anIteratorTwo! ! !CTIteratorTest methodsFor: 'utilities' stamp: 'lr 12/31/2011 15:01'! assertIteratorAtEnd: anIterator self deny: anIterator hasNext! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 15:14'! testAllSatisfy self assert: (#() iterator allSatisfy: [ :each | each > 2 ]). self assert: (#() reverseIterator allSatisfy: [ :each | each > 2 ]). self deny: (#(1) iterator allSatisfy: [ :each | each > 2 ]). self deny: (#(1) reverseIterator allSatisfy: [ :each | each > 2 ]). self assert: (#(3) iterator allSatisfy: [ :each | each > 2 ]). self assert: (#(3) reverseIterator allSatisfy: [ :each | each > 2 ]). self deny: (#(2 3 4) iterator allSatisfy: [ :each | each > 2 ]). self deny: (#(2 3 4) reverseIterator allSatisfy: [ :each | each > 2 ]). self assert: (#(3 4 5) iterator allSatisfy: [ :each | each > 2 ]). self assert: (#(3 4 5) reverseIterator allSatisfy: [ :each | each > 2 ])! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 15:20'! testAnySatisfy self deny: (#() iterator anySatisfy: [ :each | each > 2 ]). self deny: (#() reverseIterator anySatisfy: [ :each | each > 2 ]). self assert: (#(3) iterator anySatisfy: [ :each | each > 2 ]). self assert: (#(3) reverseIterator anySatisfy: [ :each | each > 2 ]). self deny: (#(1) iterator anySatisfy: [ :each | each > 2 ]). self deny: (#(1) reverseIterator anySatisfy: [ :each | each > 2 ]). self assert: (#(1 2 3) iterator anySatisfy: [ :each | each > 2 ]). self assert: (#(1 2 3) reverseIterator anySatisfy: [ :each | each > 2 ]). self deny: (#(0 1 2) iterator anySatisfy: [ :each | each > 2 ]). self deny: (#(0 1 2) reverseIterator anySatisfy: [ :each | each > 2 ])! ! !CTIteratorTest methodsFor: 'tests-array' stamp: 'lr 12/31/2011 15:06'! testArrayIterator self assertIterator: #() iterator equals: #() reverseIterator. self assertIterator: #(1) iterator equals: #(1) reverseIterator. self assertIterator: #(1 2) iterator equals: #(2 1) reverseIterator. self assertIterator: #(1 2 3) iterator equals: #(3 2 1) reverseIterator. self assertIterator: #(1 2 3 4) iterator equals: #(4 3 2 1) reverseIterator. self assertIterator: #(1 2 3 4 5) iterator equals: #(5 4 3 2 1) reverseIterator! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 15:21'! testCount self assert: (#() iterator count: [ :each | each > 2 ]) = 0. self assert: (#() reverseIterator count: [ :each | each > 2 ]) = 0. self assert: (#(1) iterator count: [ :each | each > 2 ]) = 0. self assert: (#(1) reverseIterator count: [ :each | each > 2 ]) = 0. self assert: (#(1 2) iterator count: [ :each | each > 2 ]) = 0. self assert: (#(1 2) reverseIterator count: [ :each | each > 2 ]) = 0. self assert: (#(1 2 3) iterator count: [ :each | each > 2 ]) = 1. self assert: (#(1 2 3) reverseIterator count: [ :each | each > 2 ]) = 1. self assert: (#(1 2 3 4) iterator count: [ :each | each > 2 ]) = 2. self assert: (#(1 2 3 4) reverseIterator count: [ :each | each > 2 ]) = 2! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:16'! testDetect self should: [ #() iterator detect: [ :each | each > 2 ] ] raise: CTNoSuchElementError. self should: [ #() reverseIterator detect: [ :each | each > 2 ] ] raise: CTNoSuchElementError. self should: [ #(1) iterator detect: [ :each | each > 2 ] ] raise: CTNoSuchElementError. self should: [ #(1) reverseIterator detect: [ :each | each > 2 ] ] raise: CTNoSuchElementError. self assert: (#(3) iterator detect: [ :each | each > 2 ]) = 3. self assert: (#(3) reverseIterator detect: [ :each | each > 2 ]) = 3. self assert: (#(2 3 4) iterator detect: [ :each | each > 2 ]) = 3. self assert: (#(2 3 4) reverseIterator detect: [ :each | each > 2 ]) = 4. self assert: (#(3 4 5) iterator detect: [ :each | each > 2 ]) = 3. self assert: (#(3 4 5) reverseIterator detect: [ :each | each > 2 ]) = 5! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:20'! testDetectIfNone self assert: (#() iterator detect: [ :each | each > 2 ] ifNone: [ true ]). self assert: (#() reverseIterator detect: [ :each | each > 2 ] ifNone: [ true ]). self assert: (#(1) iterator detect: [ :each | each > 2 ] ifNone: [ true ]). self assert: (#(1) reverseIterator detect: [ :each | each > 2 ] ifNone: [ true ]). self assert: (#(3) iterator detect: [ :each | each > 2 ] ifNone: [ true ]) = 3. self assert: (#(3) reverseIterator detect: [ :each | each > 2 ] ifNone: [ true ]) = 3. self assert: (#(2 3 4) iterator detect: [ :each | each > 2 ] ifNone: [ true ]) = 3. self assert: (#(2 3 4) reverseIterator detect: [ :each | each > 2 ] ifNone: [ true ]) = 4. self assert: (#(3 4 5) iterator detect: [ :each | each > 2 ] ifNone: [ true ]) = 3. self assert: (#(3 4 5) reverseIterator detect: [ :each | each > 2 ] ifNone: [ true ]) = 5! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:27'! testDo | iterator | #() iterator do: [ :each | self assert: false ]. iterator := #(1 2 3 4) iterator. #(1 2 3 4) iterator do: [ :each | self assert: each = iterator next ]. self assertIteratorAtEnd: iterator! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:28'! testDoSeparatedBy | iterator | #() iterator do: [ :each | self assert: false ] separatedBy: [ self assert: false ]. iterator := #(1 nil 2 nil 3 nil 4) iterator. #(1 2 3 4) iterator do: [ :each | self assert: each = iterator next ] separatedBy: [ self assert: iterator next isNil ]. self assertIteratorAtEnd: iterator! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:31'! testFind self assert: (#() iterator find: [ :each | each > 2 ]) = 0. self assert: (#() reverseIterator find: [ :each | each > 2 ]) = 0. self assert: (#(1) iterator find: [ :each | each > 2 ]) = 0. self assert: (#(1) reverseIterator find: [ :each | each > 2 ]) = 0. self assert: (#(3) iterator find: [ :each | each > 2 ]) = 1. self assert: (#(3) reverseIterator find: [ :each | each > 2 ]) = 1. self assert: (#(2 3 4) iterator find: [ :each | each > 2 ]) = 2. self assert: (#(2 3 4) reverseIterator find: [ :each | each > 2 ]) = 1. self assert: (#(3 4 5) iterator find: [ :each | each > 2 ]) = 1. self assert: (#(3 4 5) reverseIterator find: [ :each | each > 2 ]) = 1! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:33'! testFindIfAbsent self assert: (#() iterator find: [ :each | each > 2 ] ifAbsent: [ true ]). self assert: (#() reverseIterator find: [ :each | each > 2 ] ifAbsent: [ true ]). self assert: (#(1) iterator find: [ :each | each > 2 ] ifAbsent: [ true ]). self assert: (#(1) reverseIterator find: [ :each | each > 2 ] ifAbsent: [ true ]). self assert: (#(3) iterator find: [ :each | each > 2 ] ifAbsent: [ true ]) = 1. self assert: (#(3) reverseIterator find: [ :each | each > 2 ] ifAbsent: [ true ]) = 1. self assert: (#(2 3 4) iterator find: [ :each | each > 2 ] ifAbsent: [ true ]) = 2. self assert: (#(2 3 4) reverseIterator find: [ :each | each > 2 ] ifAbsent: [ true ]) = 1. self assert: (#(3 4 5) iterator find: [ :each | each > 2 ] ifAbsent: [ true ]) = 1. self assert: (#(3 4 5) reverseIterator find: [ :each | each > 2 ] ifAbsent: [ true ]) = 1! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:51'! testIncludes self deny: (#() iterator includes: 2). self deny: (#() reverseIterator includes: 2). self deny: (#(1) iterator includes: 2). self deny: (#(1) reverseIterator includes: 2). self deny: (#(3) iterator includes: 2). self deny: (#(3) reverseIterator includes: 2). self deny: (#(3 4 5) iterator includes: 2). self deny: (#(3 4 5) reverseIterator includes: 2). self assert: (#(2 3 4) iterator includes: 2). self assert: (#(2 3 4) reverseIterator includes: 2)! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:56'! testIndexOf self assert: (#() iterator indexOf: 2) = 0. self assert: (#() reverseIterator indexOf: 2) = 0. self assert: (#(1) iterator indexOf: 2) = 0. self assert: (#(1) reverseIterator indexOf: 2) = 0. self assert: (#(2) iterator indexOf: 2) = 1. self assert: (#(2) reverseIterator indexOf: 2) = 1. self assert: (#(3 4 5) iterator indexOf: 2) = 0. self assert: (#(3 4 5) reverseIterator indexOf: 2) = 0. self assert: (#(2 3 4) iterator indexOf: 2) = 1. self assert: (#(2 3 4) reverseIterator indexOf: 2) = 3! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 16:58'! testIndexOfIfAbsent self assert: (#() iterator indexOf: 2 ifAbsent: [ true ]). self assert: (#() reverseIterator indexOf: 2 ifAbsent: [ true ]). self assert: (#(1) iterator indexOf: 2 ifAbsent: [ true ]). self assert: (#(1) reverseIterator indexOf: 2 ifAbsent: [ true ]). self assert: (#(2) iterator indexOf: 2 ifAbsent: [ true ]) = 1. self assert: (#(2) reverseIterator indexOf: 2 ifAbsent: [ true ]) = 1. self assert: (#(3 4 5) iterator indexOf: 2 ifAbsent: [ true ]). self assert: (#(3 4 5) reverseIterator indexOf: 2 ifAbsent: [ true ]). self assert: (#(2 3 4) iterator indexOf: 2 ifAbsent: [ true ]) = 1. self assert: (#(2 3 4) reverseIterator indexOf: 2 ifAbsent: [ true ]) = 3! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 17:11'! testInjectInto self assert: (#() iterator inject: 1 into: [ :a :b | a - b ]) = 1. self assert: (#() reverseIterator inject: 1 into: [ :a :b | a - b ]) = 1. self assert: (#(2) iterator inject: 1 into: [ :a :b | a - b ]) = -1. self assert: (#(2) reverseIterator inject: 1 into: [ :a :b | a - b ]) = -1. self assert: (#(3 4) iterator inject: 1 into: [ :a :b | a - b ]) = -6. self assert: (#(3 4) reverseIterator inject: 1 into: [ :a :b | a - b ]) = -6. self assert: (#(4 5 6) iterator inject: 1 into: [ :a :b | a - b ]) = -14. self assert: (#(4 5 6) reverseIterator inject: 1 into: [ :a :b | a - b ]) = -14. self assert: (#(5 6 7 8) iterator inject: 1 into: [ :a :b | a - b ]) = -25. self assert: (#(5 6 7 8) reverseIterator inject: 1 into: [ :a :b | a - b ]) = -25! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 17:00'! testNoneSatisfy self assert: (#() iterator noneSatisfy: [ :each | each > 2 ]). self assert: (#() reverseIterator noneSatisfy: [ :each | each > 2 ]). self deny: (#(3) iterator noneSatisfy: [ :each | each > 2 ]). self deny: (#(3) reverseIterator noneSatisfy: [ :each | each > 2 ]). self assert: (#(1) iterator noneSatisfy: [ :each | each > 2 ]). self assert: (#(1) reverseIterator noneSatisfy: [ :each | each > 2 ]). self deny: (#(1 2 3) iterator noneSatisfy: [ :each | each > 2 ]). self deny: (#(1 2 3) reverseIterator noneSatisfy: [ :each | each > 2 ]). self assert: (#(0 1 2) iterator noneSatisfy: [ :each | each > 2 ]). self assert: (#(0 1 2) reverseIterator noneSatisfy: [ :each | each > 2 ])! ! !CTIteratorTest methodsFor: 'tests-enumerating' stamp: 'lr 12/31/2011 17:08'! testReduce self should: [ #() iterator reduce: [ :a :b | a - b ] ] raise: CTNoSuchElementError. self should: [ #() reverseIterator reduce: [ :a :b | a - b ] ] raise: CTNoSuchElementError. self assert: (#(2) iterator reduce: [ :a :b | a - b ]) = 2. self assert: (#(2) reverseIterator reduce: [ :a :b | a - b ]) = 2. self assert: (#(3 4) iterator reduce: [ :a :b | a - b ]) = -1. self assert: (#(3 4) reverseIterator reduce: [ :a :b | a - b ]) = 1. self assert: (#(4 5 6) iterator reduce: [ :a :b | a - b ]) = -7. self assert: (#(4 5 6) reverseIterator reduce: [ :a :b | a - b ]) = -3. self assert: (#(5 6 7 8) iterator reduce: [ :a :b | a - b ]) = -16. self assert: (#(5 6 7 8) reverseIterator reduce: [ :a :b | a - b ]) = -10! ! !SequenceableCollection methodsFor: '*container-iterators' stamp: 'lr 12/31/2011 14:47'! iterator "Answer a default iterator over the elements in this collection." ^ CTForwardArrayIterator on: self! ! !SequenceableCollection methodsFor: '*container-iterators' stamp: 'lr 12/31/2011 14:47'! reverseIterator "Answer a reverse iterator over the elements in this collection." ^ CTReverseArrayIterator on: self! ! Object subclass: #CTCollection instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Abstract'! !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 methodsFor: 'adding' stamp: 'lr 8/7/2011 11:03'! add: anObject "Ensures that the receiver contains anObject." self subclassResponsibility! ! !CTCollection methodsFor: 'adding' stamp: 'lr 8/7/2011 11:03'! addAll: aCollection "Ensures that the receiver contains all elements of aCollection." aCollection iterator do: [ :each | self add: each ]! ! !CTCollection methodsFor: 'private' stamp: 'lr 12/28/2011 16:02'! elementNotFound: anObject ^ CTElementNotFoundError new element: anObject; signal! ! !CTCollection methodsFor: 'private' stamp: 'lr 12/28/2011 16:34'! immutableCollection ^ CTImmutableCollectionError signal! ! !CTCollection methodsFor: 'testing' stamp: 'lr 8/7/2011 11:05'! includes: anObject "Returns true if the receiver contains anObject." self iterator do: [ :each | anObject = each ifTrue: [ ^ true ] ]. ^ false! ! !CTCollection methodsFor: 'private' stamp: 'lr 12/28/2011 16:03'! indexOutOfBounds: anInteger ^ CTIndexOutOfBoundsError new index: anInteger; signal! ! !CTCollection methodsFor: 'testing' stamp: 'lr 6/7/2011 19:15'! isEmpty "Answer whether the receiver contains any elements." ^ self size = 0! ! !CTCollection methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:15'! iterator "Answer a default iterator over the elements in this collection." self subclassResponsibility! ! !CTCollection methodsFor: 'private' stamp: 'lr 8/7/2011 19:55'! noSuchElement ^ CTNoSuchElementError signal! ! !CTCollection methodsFor: 'printing' stamp: 'lr 12/30/2011 10:44'! printElementsOn: aStream | iterator | iterator := self iterator. (iterator limit: 5) do: [ :each | aStream cr; tab; print: each ]. iterator hasNext ifTrue: [ aStream cr; tab; nextPutAll: '...' ]! ! !CTCollection methodsFor: 'printing' stamp: 'lr 12/28/2011 19:43'! printInformationOn: aStream aStream nextPut: $[; print: self size; nextPut: $]! ! !CTCollection methodsFor: 'printing' stamp: 'lr 12/28/2011 19:43'! printOn: aStream super printOn: aStream. self printInformationOn: aStream. self printElementsOn: aStream! ! !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 methodsFor: 'removing' stamp: 'lr 12/30/2011 10:41'! removeAll "Removes all the elements from the receiver." self subclassResponsibility! ! !CTCollection methodsFor: 'accessing' stamp: 'lr 6/7/2011 19:15'! size "Returns the number of elements in this collection." self subclassResponsibility! ! CTCollection subclass: #CTList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Abstract'! CTList subclass: #CTArrayList instanceVariableNames: 'array firstIndex lastIndex' classVariableNames: '' poolDictionaries: '' category: 'Container-Lists'! !CTArrayList class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 19:10'! new ^ self new: 10! ! !CTArrayList class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 19:10'! new: anInteger ^ self basicNew initialize: anInteger! ! !CTArrayList methodsFor: 'adding' stamp: 'lr 11/6/2011 17:12'! add: anObject at: anInteger | target | anInteger = 1 ifTrue: [ ^ self addFirst: anObject ]. anInteger + 1 = self size ifTrue: [ ^ self addLast: anObject ]. target := anInteger + firstIndex - 1. (target between: firstIndex and: lastIndex) ifFalse: [ ^ self indexOutOfBounds: anInteger ]. array size // 2 < target 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. target := anInteger + firstIndex - 1 ]. firstIndex to: target - 1 by: 1 do: [ :index | array at: index put: (array at: index + 1) ]. firstIndex := firstIndex - 1 ]. array at: target put: anObject. ^ anObject ! ! !CTArrayList methodsFor: 'adding' stamp: 'lr 8/7/2011 11:38'! addFirst: anObject firstIndex = 1 ifTrue: [ self growAtFirst ]. firstIndex := firstIndex - 1. array at: firstIndex put: anObject! ! !CTArrayList methodsFor: 'adding' stamp: 'lr 8/7/2011 11:38'! addLast: anObject lastIndex = array size ifTrue: [ self growAtLast ]. lastIndex := lastIndex + 1. array at: lastIndex put: 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: 'initialization' stamp: 'lr 8/7/2011 19:09'! initialize: anInteger self initialize. array := Array new: anInteger. firstIndex := 1. lastIndex := 0! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:17'! iterator ^ CTForwardArrayIterator on: array start: firstIndex stop: lastIndex! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 12/31/2011 11:33'! remove: anObject ifAbsent: aBlock ^ self removeAt: (self iterator find: anObject ifAbsent: [ ^ aBlock value ]) ifAbsent: aBlock! ! !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 11/6/2011 17:02'! removeAt: anInteger ifAbsent: aBlock | target object | target := firstIndex + anInteger - 1. (target between: firstIndex and: lastIndex) ifFalse: [ ^ self indexOutOfBounds: anInteger ]. object := array at: target. array size // 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 - 1 put: (array at: index) ]. array at: firstIndex put: nil. firstIndex := firstIndex + 1 ]. ^ object! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 11/6/2011 16:54'! removeFirst | element | self isEmpty ifFalse: [ ^ self noSuchElement ]. element := array at: firstIndex. array at: firstIndex put: nil. firstIndex := firstIndex + 1. ^ element! ! !CTArrayList methodsFor: 'removing' stamp: 'lr 11/6/2011 16:55'! removeLast | element | self isEmpty ifFalse: [ ^ self noSuchElement ]. element := array at: lastIndex. array at: lastIndex put: nil. lastIndex := lastIndex - 1. ^ element! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:17'! reverseIterator ^ CTReverseArrayIterator on: array start: firstIndex stop: lastIndex! ! !CTArrayList methodsFor: 'accessing' stamp: 'lr 12/28/2011 19:36'! size ^ lastIndex - firstIndex + 1! ! CTList subclass: #CTLinkedList instanceVariableNames: 'size root' classVariableNames: '' poolDictionaries: '' category: 'Container-Lists'! !CTLinkedList class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 20:04'! new ^ self basicNew initialize! ! !CTLinkedList class methodsFor: 'instance creation' stamp: 'lr 8/7/2011 20:04'! new: anInteger ^ self new! ! !CTLinkedList methodsFor: 'adding' stamp: 'lr 11/6/2011 17:24'! add: anObject at: anInteger | node | anInteger = 1 ifTrue: [ ^ self addFirst: anObject ]. anInteger = (self size + 1) ifTrue: [ ^ self addLast: anObject ]. node := self nodeAt: anInteger. node isNil ifTrue: [ self indexOutOfBounds: anInteger ]. self nodeAdd: (self nodeOn: anObject) before: node. ^ anObject! ! !CTLinkedList methodsFor: 'adding' stamp: 'lr 12/31/2011 11:57'! addFirst: anObject self nodeAdd: (self nodeOn: anObject) before: root next. ^ anObject! ! !CTLinkedList methodsFor: 'adding' stamp: 'lr 11/6/2011 17:24'! addLast: anObject self nodeAdd: (self nodeOn: anObject) before: root. ^ anObject! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:28'! at: anInteger ifAbsent: aBlock | node | node := self nodeAt: anInteger. ^ node isNil ifTrue: [ aBlock value ] ifFalse: [ node object ]! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:29'! at: anInteger put: anObject | node | node := self entryAt: anInteger. node isNil ifTrue: [ ^ self indexOutOfBounds: anInteger ]. node object: anObject. ^ anObject! ! !CTLinkedList methodsFor: 'initialization' stamp: 'lr 12/31/2011 11:29'! initialize super initialize. root := self nodeClass new. root next: root; prev: root. size := 0! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:54'! iterator ^ self isEmpty ifTrue: [ CTEmptyIterator new ] ifFalse: [ CTForwardLinkedListIterator start: root next stop: root prev ]! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 11/6/2011 17:36'! nodeAdd: aNode before: anotherNode aNode prev: anotherNode prev. aNode next: anotherNode. aNode prev next: aNode. aNode next prev: aNode. size := size + 1! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 11/6/2011 17:36'! nodeAt: anInteger | node | (anInteger between: 1 and: size) ifFalse: [ ^ nil ]. node := root. anInteger < (size // 2) ifTrue: [ 1 to: anInteger do: [ :index | node := node next ] ] ifFalse: [ 1 to: size - anInteger + 1 do: [ :index | node := node prev ] ]. ^ node! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 11/6/2011 17:07'! nodeClass ^ CTLinkedListNode! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 11/6/2011 17:22'! nodeOn: anObject ^ self nodeClass on: anObject! ! !CTLinkedList methodsFor: 'private' stamp: 'lr 12/28/2011 19:28'! nodeRemove: aNode aNode before after: aNode after. aNode after before: aNode before. aNode before: nil. aNode after: nil. size := size - 1! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 12/28/2011 16:28'! remove: anObject ifAbsent: aBlock "Removes anObject from the receiver, evaluate aBlock if anObject is not present." self shouldBeImplemented! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 12/31/2011 11:30'! removeAll root next: root; prev: root. size := 0! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 11/6/2011 17:33'! removeAt: anInteger ifAbsent: aBlock | node | (node := self nodeAt: anInteger) isNil ifTrue: [ ^ self indexOutOfBounds: anInteger ]. self removeNode: node. ^ node object! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 12/31/2011 11:31'! removeFirst | node | self isEmpty ifTrue: [ ^ self noSuchElement ]. self nodeRemove: (node := root next). ^ node element! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 12/31/2011 11:30'! removeLast | node | self isEmpty ifTrue: [ ^ self noSuchElement ]. self nodeRemove: (node := root prev). ^ node element! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:55'! reverseIterator ^ self isEmpty ifTrue: [ CTEmptyIterator new ] ifFalse: [ CTReverseLinkedListIterator start: root next stop: root prev ]! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:29'! size ^ size! ! !CTList methodsFor: 'adding' stamp: 'lr 11/6/2011 09: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 11/6/2011 09:33'! addFirst: anObject "Adds anObject at the beginning of the receiver." self add: anObject at: 1! ! !CTList methodsFor: 'adding' stamp: 'lr 11/6/2011 09:34'! 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 8/7/2011 15:56'! at: anInteger ifAbsent: aBlock "Returns the element at anIndex, 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 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 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 11/6/2011 09:37'! removeFirst "Removes the first element of the receiver." ^ self removeAt: 1! ! !CTList methodsFor: 'removing' stamp: 'lr 11/6/2011 09:37'! removeLast "Removes the last element of the receiver." ^ self removeAt: self size! ! !CTList methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:19'! reverseIterator "Answer a reverse iterator over the range elements from aStartInteger to aStopInteger." self subclassResponsibility! ! CTCollection subclass: #CTSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Abstract'! CTSet subclass: #CTHashSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Sets'! CTHashSet subclass: #CTLinkedHashSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Sets'! CTSet subclass: #CTTreeSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Sets'! Object subclass: #CTHashEntry instanceVariableNames: 'key keyHash value next' classVariableNames: '' poolDictionaries: '' category: 'Container-Maps'! !CTHashEntry class methodsFor: 'instance creation' stamp: 'lr 6/7/2011 20:30'! key: aKey hash: aHash value: aValue next: anEntry ^ self basicNew initializeKey: aKey hash: aHash value: aValue next: anEntry! ! !CTHashEntry methodsFor: 'initialization' stamp: 'lr 7/13/2011 12:06'! initializeKey: aKey hash: anInteger value: aValue next: anEntry key := aKey. keyHash := anInteger. value := aValue. next := anEntry! ! !CTHashEntry methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:32'! key ^ key! ! !CTHashEntry methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:31'! keyHash ^ keyHash! ! !CTHashEntry methodsFor: 'accessing' stamp: 'lr 7/13/2011 12:06'! next ^ next! ! !CTHashEntry methodsFor: 'modifying' stamp: 'lr 6/7/2011 20:32'! replaceValue: aValue | oldValue | oldValue := value. value := aValue. ^ oldValue! ! !CTHashEntry methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:32'! value ^ value! ! CTHashEntry subclass: #CTLinkedHashEntry instanceVariableNames: 'before after' classVariableNames: '' poolDictionaries: '' category: 'Container-Maps'! Object subclass: #CTIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! CTIterator subclass: #CTArrayIterator instanceVariableNames: 'array start stop position' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTArrayIterator commentStamp: 'lr 12/31/2011 14:30' prior: 0! Abstract iterator class for arrays and other collections supporting indexed access. Instance Variables: array start stop position ! !CTArrayIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 14:47'! on: anArray ^ self on: anArray start: 1 stop: anArray size! ! !CTArrayIterator class methodsFor: 'instance creation' stamp: 'lr 12/29/2011 10:31'! on: anArray start: aStartIndex stop: aStopIndex ^ self basicNew initializeOn: anArray start: aStartIndex stop: aStopIndex! ! !CTArrayIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:07'! initializeOn: anArray start: aStartInteger stop: aStopInteger self subclassResponsibility! ! !CTArrayIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:07'! initializeOn: anArray start: aStartInteger stop: aStopInteger position: aPositionInteger array := anArray. start := aStartInteger. stop := aStopInteger. position := aPositionInteger! ! CTArrayIterator subclass: #CTForwardArrayIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTForwardArrayIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 13:07'! hasNext ^ position < stop! ! !CTForwardArrayIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:07'! initializeOn: anArray start: aStartInteger stop: aStopInteger self initializeOn: anArray start: aStartInteger stop: aStopInteger position: aStartInteger - 1! ! !CTForwardArrayIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:08'! next ^ self hasNext ifFalse: [ self noSuchElementError ] ifTrue: [ array at: (position := position + 1) ]! ! CTArrayIterator subclass: #CTReverseArrayIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTReverseArrayIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 13:08'! hasNext ^ position > start! ! !CTReverseArrayIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:09'! initializeOn: anArray start: aStartInteger stop: aStopInteger self initializeOn: anArray start: aStartInteger stop: aStopInteger position: aStopInteger + 1! ! !CTReverseArrayIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:08'! next ^ self hasNext ifFalse: [ self noSuchElementError ] ifTrue: [ array at: (position := position - 1) ]! ! CTIterator subclass: #CTChainingIterator instanceVariableNames: 'iterators current' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTChainingIterator class methodsFor: 'instance creation' stamp: 'lr 8/3/2011 19:55'! on: anIterator ^ self basicNew initializeOn: anIterator! ! !CTChainingIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 13:05'! withAll: anArray ^ self on: (CTArrayIterator on: anArray)! ! !CTChainingIterator methodsFor: 'testing' stamp: 'lr 12/29/2011 05:50'! hasNext | hasNext | [ (hasNext := current hasNext) not and: [ iterators hasNext ] ] whileTrue: [ current := iterators next ]. ^ hasNext ! ! !CTChainingIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 14:48'! initializeOn: anIterator iterators := anIterator iterator. current := CTEmptyIterator new! ! !CTChainingIterator methodsFor: 'accessing' stamp: 'lr 12/29/2011 05:51'! next ^ current next! ! CTIterator subclass: #CTDelegateIterator instanceVariableNames: 'iterator' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! CTDelegateIterator subclass: #CTBufferedIterator instanceVariableNames: 'element' classVariableNames: 'Sentinel' poolDictionaries: '' category: 'Container-Iterators'! !CTBufferedIterator class methodsFor: 'class initialization' stamp: 'lr 12/29/2011 10:29'! initialize Sentinel := Object new! ! !CTBufferedIterator methodsFor: 'iterators' stamp: 'lr 12/29/2011 10:25'! buffered ^ self! ! !CTBufferedIterator methodsFor: 'accessing' stamp: 'lr 12/29/2011 10:30'! current "Returns the currently buffered element, or throws a CTNoSuchElementError." ^ element == Sentinel ifTrue: [ element := self next ] ifFalse: [ element ]! ! !CTBufferedIterator methodsFor: 'initialization' stamp: 'lr 12/29/2011 10:28'! initialize super initialize. element := Sentinel! ! !CTBufferedIterator methodsFor: 'accessing' stamp: 'lr 12/29/2011 10:29'! next ^ element := super next! ! CTDelegateIterator subclass: #CTCyclingIterator instanceVariableNames: 'current' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTCyclingIterator commentStamp: 'lr 8/3/2011 18:08' prior: 0! An iterator that cycles infinitely over its elements.! !CTCyclingIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 18:17'! hasNext current hasNext ifFalse: [ current := iterator copy ]. ^ current hasNext! ! !CTCyclingIterator methodsFor: 'initialization' stamp: 'lr 8/3/2011 19:57'! initializeOn: anIterator super initializeOn: anIterator. current := anIterator copy! ! !CTCyclingIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 19:48'! next self hasNext ifFalse: [ ^ self noSuchElementError ]. ^ current next! ! !CTDelegateIterator class methodsFor: 'instance creation' stamp: 'lr 8/3/2011 19:21'! on: anInterator ^ self basicNew initializeOn: anInterator! ! !CTDelegateIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 18:22'! hasNext ^ iterator hasNext! ! !CTDelegateIterator methodsFor: 'initialization' stamp: 'lr 8/3/2011 19:21'! initializeOn: anIterator self initialize. iterator := anIterator! ! !CTDelegateIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 18:22'! next ^ iterator next! ! !CTDelegateIterator methodsFor: 'copying' stamp: 'lr 12/29/2011 10:36'! postCopy super postCopy. iterator := iterator copy! ! CTDelegateIterator subclass: #CTLimitingIterator instanceVariableNames: 'limit' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTLimitingIterator class methodsFor: 'instance creation' stamp: 'lr 12/28/2011 19:44'! on: anIterator limit: anInteger ^ (self on: anIterator) setLimit: anInteger! ! !CTLimitingIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 19:19'! hasNext ^ 0 < limit and: [ super hasNext ]! ! !CTLimitingIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 19:19'! next self hasNext ifFalse: [ ^ self noSuchElementError ]. limit := limit - 1. ^ super next! ! !CTLimitingIterator methodsFor: 'initialization' stamp: 'lr 8/3/2011 18:27'! setLimit: anInteger limit := anInteger! ! CTDelegateIterator subclass: #CTMutatingIterator instanceVariableNames: 'block' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTMutatingIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 18:21'! next ^ block value: iterator next! ! CTDelegateIterator subclass: #CTPeekingIterator instanceVariableNames: 'element' classVariableNames: 'Sentinel' poolDictionaries: '' category: 'Container-Iterators'! CTPeekingIterator subclass: #CTFilterIterator instanceVariableNames: 'predicate' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTFilterIterator class methodsFor: 'as yet unclassified' stamp: 'lr 8/3/2011 07:30'! initialize Sentinel := Object new! ! !CTFilterIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 19:44'! hasNext | next | [ element == Sentinel and: [ iterator hasNext ] ] whileTrue: [ next := iterator next. (predicate value: next) ifTrue: [ element := next ] ]. ^ element ~~ Sentinel! ! !CTFilterIterator methodsFor: 'initialization' stamp: 'lr 8/3/2011 19:41'! setPredicate: aValuable predicate := aValuable! ! !CTPeekingIterator class methodsFor: 'initialization' stamp: 'lr 8/3/2011 19:02'! initialize Sentinel := Object new! ! !CTPeekingIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 19:38'! hasNext (element == Sentinel and: [ iterator hasNext ]) ifTrue: [ element := iterator next ]. ^ element ~~ Sentinel! ! !CTPeekingIterator methodsFor: 'initialization' stamp: 'lr 8/3/2011 19:02'! initialize super initialize. element := Sentinel! ! !CTPeekingIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 19:40'! next | next | self hasNext ifFalse: [ ^ self noSuchElement ]. next := element. element := Sentinel. ^ next! ! !CTPeekingIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 19:40'! peek "Answer the next element without actually consuming it, or raise an CTNoSuchElementError." self hasNext ifFalse: [ ^ self noSuchElement ]. ^ element! ! CTIterator subclass: #CTEmptyIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !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 methodsFor: 'iterators' stamp: 'lr 12/31/2011 13:05'! , anIterator "Concatenates the receiving iterator with anIterator." ^ CTChainingIterator on: (CTArrayIterator on: (Array with: self with: anIterator))! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/29/2011 08:13'! allSatisfy: aBlock "Tests whether all of the elements of the receiver satisfy aBlock." self do: [ :each | (aBlock value: each) ifFalse: [ ^ false ] ]. ^ true! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/29/2011 21:27'! anySatisfy: aBlock "Tests whether any of the elements of the receiver satisfy aBlock." self do: [ :each | (aBlock value: each) ifTrue: [ ^ true ] ]. ^ false! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 12/29/2011 10:25'! buffered "Answer a buffered iterator of the receiver." ^ CTBufferedIterator on: self! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 12/28/2011 16:55'! collect: aBlock ^ CTMutatingIterator on: self! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/29/2011 08:15'! count: aBlock "Counts the elements of the receiver that satisfy aBlock." | tally | tally := 0. self do: [ :each | (aBlock value: each) 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 12/29/2011 08:13'! detect: aBlock ifNone: anAbsentBlock "Answer the first element for which aBlock returns true, otherwise answer the result of evaluating anAbsentBlock." self do: [ :each | (aBlock value: each) ifTrue: [ ^ each ] ]. ^ anAbsentBlock value! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/30/2011 21:31'! do: aBlock "Evaluate aBlock with each of the elements of the receiver." | index | index := 0. [ self hasNext ] whileTrue: [ aBlock cull: self next cull: (index := index + 1) ]! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/29/2011 08:26'! do: aBlock separatedBy: aSeparatorBlock "Evaluate aBlock with each of the elements of the receiver, and evaluate aSeparatorBlock inbetween each of the elements." | beforeFirst | beforeFirst := true. self do: [ :each | beforeFirst ifTrue: [ beforeFirst := false ] ifFalse: [ aSeparatorBlock value ]. aBlock value: each ]! ! !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 12/29/2011 23:38'! find: aBlock ifAbsent: anAbsentBlock "Answer the index of the first element satisfying aBlock, otherwise evaluate anAbsentBlock." | index | index := 1. self do: [ :each | (aBlock value: each) ifTrue: [ ^ index ]. index := index + 1 ]. ^ anAbsentBlock value! ! !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 12/29/2011 09:49'! includes: anObject "Tests whether the receiver contains anObject." self do: [ :each | anObject = each 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 12/29/2011 23:39'! indexOf: anObject ifAbsent: anAbsentBlock "Answer the index of the first occurence of anObject, evaluate anAbsentBlock otherwise." | index | index := 1. self do: [ :each | anObject = each ifTrue: [ ^ index ]. index := index + 1 ]. ^ anAbsentBlock value! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/31/2011 17:10'! inject: anObject into: aBlock "Accumulate a running value associated with evaluating aBlock with the current value of anObject and the receivers elemenets as block arguments." | nextValue | nextValue := anObject. self do: [ :each | nextValue := aBlock value: nextValue value: each ]. ^ nextValue! ! !CTIterator methodsFor: 'testing' stamp: 'lr 12/29/2011 21:31'! isEmpty "Answer whether there is a next element in the iterator." ^ self hasNext not! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 12/29/2011 10:01'! limit: anInteger "Answer an iterator that consumes at most anInteger elements." ^ CTLimitingIterator on: self limit: anInteger! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 12/29/2011 05:48'! next "Answer the next element in the iterator, or raise CTNoSuchElementError if no such element exists." self subclassResponsibility! ! !CTIterator methodsFor: 'private' stamp: 'lr 8/3/2011 19:14'! noSuchElementError ^ CTNoSuchElementError signal! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/30/2011 16:00'! noneSatisfy: aBlock "Tests whether none of the elements of the receiver satisfy aBlock." self do: [ :each | (aBlock value: each) ifTrue: [ ^ false ] ]. ^ true! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 12/30/2011 13:18'! reduce: aBlock "Reduce the elements of the receiver into aBlock. The argument aBlock must take two or more arguments." | 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 12/28/2011 16:56'! reject: aBlock ^ CTFilterIterator on: self block: [ :each | (aBlock value: each) not ]! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 12/28/2011 16:56'! select: aBlock ^ CTFilterIterator on: self block: aBlock! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 12/29/2011 23:28'! take: anInteger "Answer an iterator on the first n elements." | iterator | iterator := self limit: anInteger. [ iterator hasNext ] whileTrue: [ iterator next ]! ! CTIterator subclass: #CTLinkedListIterator instanceVariableNames: 'start stop current' classVariableNames: '' poolDictionaries: '' category: 'Container-Lists'! CTLinkedListIterator subclass: #CTForwardLinkedListIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Lists'! !CTForwardLinkedListIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 13:25'! hasNext ^ current ~~ stop! ! !CTForwardLinkedListIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:26'! initializeStart: aStartNode stop: aStopNode self initializeStart: aStartNode stop: aStopNode current: aStartNode prev! ! !CTForwardLinkedListIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:25'! next ^ self hasNext ifTrue: [ (current := current next) object ] ifFalse: [ self noSuchElementError ]! ! !CTLinkedListIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 11:06'! start: aStartNode stop: aStopNode ^ self basicNew initializeStart: aStartNode stop: aStopNode! ! !CTLinkedListIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:25'! initializeStart: aStartNode stop: aStopNode self subclassResponsibility! ! !CTLinkedListIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:25'! initializeStart: aStartNode stop: aStopNode current: aCurrentNode start := aStartNode. stop := aStopNode. current := aCurrentNode! ! CTLinkedListIterator subclass: #CTReverseLinkedListIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Lists'! !CTReverseLinkedListIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 13:27'! hasNext ^ current ~~ start! ! !CTReverseLinkedListIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 13:27'! initializeStart: aStartNode stop: aStopNode self initializeStart: aStartNode stop: aStopNode current: aStopNode next! ! !CTReverseLinkedListIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:26'! next ^ self hasNext ifTrue: [ (current := current prev) object ] ifFalse: [ self noSuchElementError ]! ! CTIterator subclass: #CTPluggableIterator instanceVariableNames: 'hasNextBlock nextBlock' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTPluggableIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 12:54'! hasNext: aHasNextBlock next: aNextBlock ^ self basicNew initializeHasNext: aHasNextBlock next: aNextBlock! ! !CTPluggableIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 12:55'! hasNext ^ hasNextBlock value! ! !CTPluggableIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 12:55'! initializeHasNext: aHasNextBlock next: aNextBlock hasNextBlock := aHasNextBlock. nextBlock := aNextBlock! ! !CTPluggableIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 12:55'! next ^ nextBlock value! ! CTIterator subclass: #CTRangeIterator instanceVariableNames: 'start stop step current' classVariableNames: '' poolDictionaries: '' category: 'Container-Iterators'! !CTRangeIterator class methodsFor: 'instance creation' stamp: 'lr 12/28/2011 21:07'! from: aStartValue to: aStopValue ^ self from: aStartValue to: aStopValue step: 1! ! !CTRangeIterator class methodsFor: 'instance creation' stamp: 'lr 12/28/2011 21:08'! from: aStartValue to: aStopValue step: aStepValue ^ self basicNew initializeFrom: aStartValue to: aStopValue step: aStepValue! ! !CTRangeIterator methodsFor: 'testing' stamp: 'lr 12/29/2011 21:36'! hasNext ^ step > 0 ifTrue: [ current < stop ] ifFalse: [ current > stop ]! ! !CTRangeIterator methodsFor: 'initialization' stamp: 'lr 12/29/2011 21:35'! initializeFrom: aStartValue to: aStopValue step: aStepValue self initialize. start := aStartValue. stop := aStopValue. step := aStepValue. current := aStartValue! ! !CTRangeIterator methodsFor: 'accessing' stamp: 'lr 12/29/2011 05:49'! next ^ current := current + step! ! Object subclass: #CTLinkedListNode instanceVariableNames: 'object next prev' classVariableNames: '' poolDictionaries: '' category: 'Container-Lists'! !CTLinkedListNode class methodsFor: 'instance creation' stamp: 'lr 11/6/2011 17:27'! on: anObject ^ self basicNew object: anObject! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:26'! next ^ next! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:26'! next: aNode next := 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! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:27'! prev ^ prev! ! !CTLinkedListNode methodsFor: 'accessing' stamp: 'lr 11/6/2011 17:27'! prev: aNode prev := aNode! ! Object subclass: #CTMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Abstract'! CTMap subclass: #CTHashMap instanceVariableNames: 'size modifications entries' classVariableNames: '' poolDictionaries: '' category: 'Container-Maps'! !CTHashMap class methodsFor: 'instance creation' stamp: 'lr 7/13/2011 12:18'! new ^ self new: 16! ! !CTHashMap class methodsFor: 'instance creation' stamp: 'lr 7/13/2011 12:18'! new: anInteger ^ self basicNew initialize: anInteger; yourself! ! !CTHashMap methodsFor: 'querying' stamp: 'lr 6/7/2011 20:18'! at: aKey ifAbsent: aBlock | hash entry | hash := self hashFor: aKey. entry := entries at: (self indexFor: hash). [ entry isNil ] whileFalse: [ (entry hash = hash and: [ self compare: aKey with: entry key ]) ifTrue: [ ^ entry value ]. entry := entry next ]. ^ aBlock value! ! !CTHashMap methodsFor: 'modifying' stamp: 'lr 7/13/2011 12:22'! at: aKey put: aValue | hash index entry | hash := self hashFor: aKey. index := self indexFor: hash. entry := entries at: index. [ entry isNil ] whileFalse: [ (entry hash = hash and: [ self compare: aKey with: entry key ]) ifTrue: [ entry setValue: aValue. ^ aValue ] ]. entries at: index put: (CTHashEntry key: aKey value: aValue hash: hash next: (entries at: index)). size := size + 1. ^ aValue! ! !CTHashMap methodsFor: 'private' stamp: 'lr 11/5/2011 19:15'! capacityFor: anInteger | capacity | capacity := 1. [ capacity < anInteger ] whileTrue: [ capacity := 2 * capacity ]. ^ capacity! ! !CTHashMap methodsFor: 'private' stamp: 'lr 6/7/2011 20:18'! compare: anObject with: anotherObject ^ anObject = anotherObject! ! !CTHashMap methodsFor: 'private' stamp: 'lr 11/5/2011 19:15'! hashFor: aKey ^ aKey hash! ! !CTHashMap methodsFor: 'private' stamp: 'lr 11/5/2011 19:15'! indexFor: anInteger ^ anInteger bitAnd: entries size - 1! ! !CTHashMap methodsFor: 'initialization' stamp: 'lr 7/13/2011 12:23'! initialize: anInteger size := modifications := 0. entries := Array new: (self capacityFor: anInteger)! ! !CTHashMap methodsFor: 'private' stamp: 'lr 7/13/2011 12:11'! loadFactor ^ 0.75! ! !CTHashMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:23'! size ^ size! ! CTHashMap subclass: #CTLinkedHashMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Maps'! !CTMap methodsFor: 'querying' stamp: 'lr 6/7/2011 20:19'! at: aKey ^ self at: aKey ifAbsent: [ self keyNotFound ]! ! !CTMap methodsFor: 'querying' stamp: 'lr 6/7/2011 20:19'! at: aKey ifAbsent: aBlock self subclassResponsibility! ! !CTMap methodsFor: 'querying' stamp: 'lr 6/7/2011 20:21'! at: aKey ifPresent: aBlock ^ aBlock value: (self at: aKey ifAbsent: [ ^ nil ])! ! !CTMap methodsFor: 'modifying' stamp: 'lr 6/7/2011 20:22'! at: aKey put: aValue self subclassResponsibility! ! !CTMap methodsFor: 'modifying' stamp: 'lr 7/13/2011 12:24'! clear self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:22'! entries ^ self subclassResponsibility! ! !CTMap methodsFor: 'testing' stamp: 'lr 6/7/2011 20:22'! includesKey: aKey ^ self keys includes: aKey! ! !CTMap methodsFor: 'testing' stamp: 'lr 6/7/2011 20:22'! includesValue: aValue ^ self values includes: aValue! ! !CTMap methodsFor: 'testing' stamp: 'lr 6/7/2011 20:23'! isEmpty ^ self size = 0! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:22'! keys ^ self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:23'! size self subclassResponsibility! ! !CTMap methodsFor: 'accessing' stamp: 'lr 6/7/2011 20:23'! values ^ self subclassResponsibility! ! CTMap subclass: #CTTreeMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Maps'! CTPeekingIterator initialize! CTFilterIterator initialize! CTBufferedIterator initialize!