SystemOrganization addCategory: #'Container-Core-Abstract'! SystemOrganization addCategory: #'Container-Core-Exceptions'! SystemOrganization addCategory: #'Container-Core-Comparators'! SystemOrganization addCategory: #'Container-Core-Iterators'! SystemOrganization addCategory: #'Container-Core-Lists'! SystemOrganization addCategory: #'Container-Core-Sets'! SystemOrganization addCategory: #'Container-Core-Maps'! SystemOrganization addCategory: #'Container-Core-Misc'! SystemOrganization addCategory: #'Container-Core-Finger'! SystemOrganization addCategory: #'Container-Core-Private'! !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! ! Error subclass: #CTElementNotFoundError instanceVariableNames: 'element' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-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: #CTIndexOutOfBoundsError instanceVariableNames: 'index' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-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: #CTKeyNotFoundError instanceVariableNames: 'key' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !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'! Error subclass: #CTUnsupportedOperationError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Exceptions'! !CTUnsupportedOperationError class methodsFor: 'exceptioninstantiator' stamp: 'pmm 2/5/2012 20:53'! selector: aSelector receiver: anObject self signal: (anObject class name) asString, ' >> #', aSelector asString! ! Object subclass: #CTCollection instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Abstract'! !CTCollection class methodsFor: 'accessing' stamp: 'lr 1/1/2012 10:12'! browserIcon ^ #collection! ! !CTCollection class methodsFor: 'accessing' stamp: 'lr 1/24/2012 20:47'! defaultCapacity ^ 10! ! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 1/24/2012 20:47'! new ^ self new: self defaultCapacity! ! !CTCollection class methodsFor: 'instance creation' stamp: 'lr 1/12/2012 20:29'! new: anInteger ^ self basicNew initialize: anInteger! ! !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: 'private' stamp: 'lr 12/28/2011 16:02'! elementNotFound: anObject ^ CTElementNotFoundError new element: anObject; signal! ! !CTCollection methodsFor: 'copying' stamp: 'lr 2/6/2012 07:12'! immutable "Answer an immutable copy of the receiver. The copy is immutable and changes in receiver are not reflected." self subclassResponsibility! ! !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: 'private' stamp: 'lr 12/28/2011 16:03'! indexOutOfBounds: anInteger ^ CTIndexOutOfBoundsError new index: anInteger; signal! ! !CTCollection methodsFor: 'initialization' stamp: 'lr 1/12/2012 20:30'! initialize: anInteger self initialize! ! !CTCollection methodsFor: 'testing' stamp: 'lr 1/15/2012 17:22'! isEmpty "Answer whether the receiver contains any elements." ^ self size == 0! ! !CTCollection methodsFor: 'iterators' 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 1/15/2012 17:20'! 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 1/15/2012 17:20'! printOn: aStream super printOn: 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 methodsFor: 'copying' stamp: 'lr 2/6/2012 07:12'! unmodifiable "Answer an unmodifyable view of the reciever. The copy itself is immutable but changes in the receiver are reflected in the view." self subclassResponsibility! ! !CTCollection methodsFor: 'private' stamp: 'lr 2/6/2012 06:58'! unsupportedOperation ^ CTUnsupportedOperationError signal! ! CTCollection subclass: #CTList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Abstract'! CTList subclass: #CTArrayList instanceVariableNames: 'array firstIndex lastIndex' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTArrayList methodsFor: 'adding' stamp: 'lr 1/20/2012 20:34'! 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. ^ 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: 'iterators' stamp: 'lr 1/13/2012 11:01'! backwardIterator ^ CTBackwardIndexedIterator on: array start: firstIndex stop: lastIndex offset: firstIndex - 1! ! !CTArrayList methodsFor: 'iterators' stamp: 'lr 1/13/2012 10:57'! forwardIterator ^ CTForwardIndexedIterator on: array start: firstIndex stop: lastIndex offset: firstIndex - 1! ! !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: 'copying' stamp: 'lr 2/6/2012 20:32'! immutable ^ CTImmutableList withAll: (array copyFrom: firstIndex to: lastIndex)! ! !CTArrayList methodsFor: 'initialization' stamp: 'lr 2/6/2012 20:34'! initialize: anInteger super initialize: anInteger. array := Array new: anInteger. firstIndex := 1. lastIndex := 0! ! !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 1/22/2012 16:43'! sort: anOrder from: aStartIndex to: aStopIndex anOrder sort: array from: firstIndex + aStartIndex - 1 to: firstIndex + aStopIndex - 1! ! CTList subclass: #CTEmptyList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! CTEmptyList class instanceVariableNames: 'default'! CTEmptyList class instanceVariableNames: 'default'! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:57'! new ^ default ifNil: [ default := self basicNew ]! ! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 20:54'! new: anInteger ^ self unsupportedOperation: #new:! ! !CTEmptyList class methodsFor: 'private' stamp: 'pmm 2/5/2012 20:54'! unsupportedOperation: aSelector CTUnsupportedOperationError selector: aSelector receiver: self! ! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:06'! with: anObject1 ^ self unsupportedOperation: #with:! ! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:06'! with: anObject1 with: anObject2 ^ self unsupportedOperation: #with:with:! ! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:06'! with: anObject1 with: anObject2 with: anObject3 ^ self unsupportedOperation: #with:with:with:! ! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:06'! with: anObject1 with: anObject2 with: anObject3 with: anObject4 ^ self unsupportedOperation: #with:with:with:with:! ! !CTEmptyList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:07'! withAll: aCollection ^ aCollection isEmpty ifTrue: [ self new ] ifFalse: [ self unsupportedOperation: #withAll: ]! ! !CTEmptyList methodsFor: 'adding' stamp: 'pmm 2/5/2012 20:32'! add: anObject self unsupportedOperation: #add:! ! !CTEmptyList methodsFor: 'adding' stamp: 'pmm 2/6/2012 20:36'! add: anObject at: anInteger anInteger == 1 ifTrue: [ self unsupportedOperation: #add:at: ] ifFalse: [ self indexOutOfBounds: anInteger ]! ! !CTEmptyList methodsFor: 'adding' stamp: 'pmm 2/5/2012 20:37'! addAll: aCollection aCollection isEmpty ifFalse: [ self unsupportedOperation: #addAll: ]. ^ aCollection! ! !CTEmptyList methodsFor: 'adding' stamp: 'pmm 2/5/2012 20:42'! addFirst: anObject self unsupportedOperation: #addFirst:! ! !CTEmptyList methodsFor: 'adding' stamp: 'pmm 2/5/2012 20:43'! addLast: anObject self unsupportedOperation: #addLast:! ! !CTEmptyList methodsFor: 'accessing' stamp: 'pmm 2/5/2012 20:45'! at: anInteger self indexOutOfBounds: anInteger! ! !CTEmptyList methodsFor: 'accessing' stamp: 'pmm 2/5/2012 20:40'! at: anInteger ifAbsent: aBlock ^ aBlock value! ! !CTEmptyList methodsFor: 'accessing' stamp: 'pmm 2/6/2012 20:31'! at: anInteger put: anObject self indexOutOfBounds: anInteger! ! !CTEmptyList methodsFor: 'iterators' stamp: 'pmm 2/5/2012 21:56'! backwardIterator ^ self iterator! ! !CTEmptyList methodsFor: 'copying' stamp: 'pmm 2/5/2012 21:32'! copy! ! !CTEmptyList methodsFor: 'accessing' stamp: 'pmm 2/5/2012 20:44'! first self noSuchElement! ! !CTEmptyList methodsFor: 'iterators' stamp: 'pmm 2/5/2012 21:56'! forwardIterator ^ self iterator! ! !CTEmptyList methodsFor: 'testing' stamp: 'pmm 2/5/2012 20:34'! includes: anObject ^ false! ! !CTEmptyList methodsFor: 'testing' stamp: 'pmm 2/5/2012 20:35'! includesAll: aCollection ^ aCollection isEmpty! ! !CTEmptyList methodsFor: 'testing' stamp: 'pmm 2/5/2012 20:42'! isEmpty ^ true! ! !CTEmptyList methodsFor: 'iterators' stamp: 'pmm 2/5/2012 21:09'! iterator ^ CTEmptyIterator new! ! !CTEmptyList methodsFor: 'accessing' stamp: 'pmm 2/5/2012 20:44'! last self noSuchElement! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:46'! remove: anObject self elementNotFound: anObject! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:37'! remove: anObject ifAbsent: aBlock ^ aBlock value! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:38'! removeAll ! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:46'! removeAt: anInteger self indexOutOfBounds: anInteger! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:43'! removeAt: anInteger ifAbsent: aBlock ^ aBlock value! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:44'! removeFirst self noSuchElement! ! !CTEmptyList methodsFor: 'removing' stamp: 'pmm 2/5/2012 20:44'! removeLast self noSuchElement! ! !CTEmptyList methodsFor: 'accessing' stamp: 'pmm 2/5/2012 20:30'! size ^ 0! ! !CTEmptyList methodsFor: 'sorting' stamp: 'pmm 2/5/2012 20:46'! sort! ! !CTEmptyList methodsFor: 'sorting' stamp: 'pmm 2/5/2012 20:47'! sort: anOrder! ! !CTEmptyList methodsFor: 'sorting' stamp: 'pmm 2/5/2012 20:47'! sort: anOrder from: aStartIndex to: aStopIndex! ! !CTEmptyList methodsFor: 'private' stamp: 'pmm 2/5/2012 20:54'! unsupportedOperation: aSelector CTUnsupportedOperationError selector: aSelector receiver: self! ! CTList subclass: #CTImmutableList instanceVariableNames: 'array' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTImmutableList class methodsFor: 'accessing' stamp: 'lr 2/6/2012 20:22'! defaultCapacity ^ 0! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:33'! new ^ self withAll: #()! ! !CTImmutableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 20:31'! new: anInteger ^ self withAll: (Array new: anInteger)! ! !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: 'iterators' stamp: 'lr 2/6/2012 20:27'! backwardIterator ^ CTBackwardIndexedIterator on: array! ! !CTImmutableList methodsFor: 'iterators' stamp: 'lr 2/6/2012 20:27'! forwardIterator ^ CTForwardIndexedIterator on: array! ! !CTImmutableList methodsFor: 'initialization' stamp: 'lr 2/6/2012 20:34'! initializeWithAll: anArray super initialize: anArray size. array := anArray! ! !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! ! CTList subclass: #CTLinkedList instanceVariableNames: 'size root' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !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: 'iterators' stamp: 'lr 1/13/2012 10:57'! backwardIterator ^ root backwardIterator collect: [ :each | each object ]! ! !CTLinkedList methodsFor: 'accessing' stamp: 'lr 1/13/2012 11:27'! first ^ self isEmpty ifTrue: [ self noSuchElement ] ifFalse: [ root after object ]! ! !CTLinkedList methodsFor: 'iterators' stamp: 'lr 1/13/2012 10:58'! forwardIterator ^ root forwardIterator collect: [ :each | each object ]! ! !CTLinkedList methodsFor: 'copying' stamp: 'lr 2/6/2012 07:16'! immutable ^ (self forwardIterator as: CTArrayList new) immutable! ! !CTLinkedList methodsFor: 'initialization' stamp: 'lr 1/13/2012 10:53'! initialize: anInteger super initialize: anInteger. root := CTLinkedListRoot new. size := 0! ! !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: 'copying' stamp: 'lr 1/13/2012 11:14'! postCopy super postCopy. root := root copy! ! !CTLinkedList methodsFor: 'removing' stamp: 'lr 1/13/2012 11:36'! remove: anObject ifAbsent: aBlock | node | node := root forwardIterator 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 1/23/2012 19:51'! sort: anOrder from: aStartIndex to: aStopIndex "This is kind of complicated, slow and ugly. Lists are not really good at this, but we can do it anyway: First we remove the nodes and copy them into an array, then we sort the array and fill it back into the list." | start stop nodes | start := (self nodeAt: aStartIndex) ifNil: [ self indexOutOfBounds: aStartIndex ]. start := start before. stop := (self nodeAt: aStopIndex) ifNil: [ self indexOutOfBounds: aStopIndex ]. stop := stop after. nodes := Array new: aStopIndex - aStartIndex + 1. 1 to: nodes size do: [ :index | root remove: (nodes at: index put: (start := start after)) ]. (anOrder transform: #object) sort: nodes. 1 to: nodes size do: [ :index | root add: (nodes at: index) before: stop ]! ! !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: 'iterators' stamp: 'lr 1/13/2012 10:56'! backwardIterator "Answer a reverse iterator over the elements of the receiving collection." 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: 'iterators' stamp: 'lr 1/13/2012 10:56'! forwardIterator "Answer a forward iterator over the elements of the receiving collection." self subclassResponsibility! ! !CTList methodsFor: 'iterators' stamp: 'lr 1/13/2012 10:56'! iterator ^ self forwardIterator! ! !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: 'sorting' stamp: 'lr 1/24/2012 19:15'! sort "Sorts the receiver collection by default order." self sort: CTNaturalComparator new! ! !CTList methodsFor: 'sorting' stamp: 'lr 1/22/2012 16:18'! sort: anOrder self sort: anOrder from: 1 to: self size! ! !CTList methodsFor: 'sorting' stamp: 'lr 1/22/2012 16:18'! sort: anOrder from: aStartIndex to: aStopIndex self error: self printString , ' does not support sorting'! ! !CTList methodsFor: 'copying' stamp: 'lr 2/6/2012 07:14'! unmodifiable ^ CTUnmodifiableList on: self! ! CTList subclass: #CTSingletonList instanceVariableNames: 'element' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:49'! new ^ self unsupportedOperation: #new! ! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:49'! new: anInteger ^ self unsupportedOperation: #new:! ! !CTSingletonList class methodsFor: 'private' stamp: 'pmm 2/5/2012 21:49'! unsupportedOperation: aSelector CTUnsupportedOperationError selector: aSelector receiver: self! ! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:48'! with: anObject1 ^ self basicNew initializeWith: anObject1! ! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:49'! with: anObject1 with: anObject2 ^ self unsupportedOperation: #with:with:! ! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:49'! with: anObject1 with: anObject2 with: anObject3 ^ self unsupportedOperation: #with:with:with:! ! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:50'! with: anObject1 with: anObject2 with: anObject3 with: anObject4 ^ self unsupportedOperation: #with:with:with:with:! ! !CTSingletonList class methodsFor: 'instance creation' stamp: 'pmm 2/6/2012 19:30'! withAll: aCollection ^ aCollection size = 1 ifTrue: [ self with: aCollection first ] ifFalse: [ self unsupportedOperation: #withAll: ]! ! !CTSingletonList methodsFor: 'adding' stamp: 'pmm 2/5/2012 21:42'! add: anObject self unsupportedOperation: #add:! ! !CTSingletonList methodsFor: 'adding' stamp: 'pmm 2/6/2012 20:20'! add: anObject at: anInteger anInteger == 1 ifTrue: [ self unsupportedOperation: #add: ] ifFalse: [ self indexOutOfBounds: anInteger ]! ! !CTSingletonList methodsFor: 'adding' stamp: 'pmm 2/5/2012 21:42'! addAll: aCollection aCollection isEmpty ifFalse: [ self unsupportedOperation: #addAll: ]. ^ aCollection! ! !CTSingletonList methodsFor: 'adding' stamp: 'pmm 2/5/2012 21:42'! addFirst: anObject self unsupportedOperation: #addFirst:! ! !CTSingletonList methodsFor: 'adding' stamp: 'pmm 2/5/2012 21:42'! addLast: anObject self unsupportedOperation: #addLast:! ! !CTSingletonList methodsFor: 'accessing' stamp: 'pmm 2/6/2012 19:35'! at: anInteger ifAbsent: aBlock ^ anInteger == 1 ifTrue: [ element ] ifFalse: [ aBlock value ]! ! !CTSingletonList methodsFor: 'accessing' stamp: 'pmm 2/6/2012 20:18'! at: anInteger put: anObject anInteger == 1 ifTrue: [ self unsupportedOperation: #at:put: ] ifFalse: [ self indexOutOfBounds: anInteger ]! ! !CTSingletonList methodsFor: 'iterators' stamp: 'pmm 2/5/2012 21:56'! backwardIterator ^ self iterator! ! !CTSingletonList methodsFor: 'copying' stamp: 'pmm 2/6/2012 19:53'! copy! ! !CTSingletonList methodsFor: 'accessing' stamp: 'pmm 2/6/2012 19:34'! first ^ element! ! !CTSingletonList methodsFor: 'iterators' stamp: 'pmm 2/5/2012 21:55'! forwardIterator ^ self iterator! ! !CTSingletonList methodsFor: 'testing' stamp: 'pmm 2/5/2012 21:47'! includes: anObject ^ anObject = element! ! !CTSingletonList methodsFor: 'initialization' stamp: 'pmm 2/5/2012 21:33'! initializeWith: anObject self initialize. element := anObject! ! !CTSingletonList methodsFor: 'testing' stamp: 'pmm 2/5/2012 21:47'! isEmpty ^ false! ! !CTSingletonList methodsFor: 'iterators' stamp: 'pmm 2/5/2012 21:55'! iterator ^ CTSingletonterator on: element! ! !CTSingletonList methodsFor: 'accessing' stamp: 'pmm 2/6/2012 19:34'! last ^ element! ! !CTSingletonList methodsFor: 'removing' stamp: 'pmm 2/5/2012 21:44'! remove: anObject element = anObject ifTrue: [ self unsupportedOperation: #remove: ] ifFalse: [ self elementNotFound: anObject ]! ! !CTSingletonList methodsFor: 'removing' stamp: 'pmm 2/5/2012 21:46'! removeAll self unsupportedOperation: #removeAll! ! !CTSingletonList methodsFor: 'removing' stamp: 'pmm 2/5/2012 21:45'! removeAt: anInteger ifAbsent: aBlock anInteger == 1 ifTrue: [ self unsupportedOperation: #remove:ifAbsent: ] ifFalse: [ self indexOutOfBounds: anInteger ]! ! !CTSingletonList methodsFor: 'removing' stamp: 'pmm 2/5/2012 21:46'! removeFirst self unsupportedOperation: #removeFirst! ! !CTSingletonList methodsFor: 'removing' stamp: 'pmm 2/5/2012 21:46'! removeLast self unsupportedOperation: #removeLast! ! !CTSingletonList methodsFor: 'accessing' stamp: 'pmm 2/5/2012 21:33'! size ^ 1! ! !CTSingletonList methodsFor: 'sorting' stamp: 'pmm 2/5/2012 21:47'! sort! ! !CTSingletonList methodsFor: 'sorting' stamp: 'pmm 2/5/2012 21:47'! sort: anOrder! ! !CTSingletonList methodsFor: 'sorting' stamp: 'pmm 2/5/2012 21:47'! sort: anOrder from: aStartIndex to: aStopIndex! ! !CTSingletonList methodsFor: 'private' stamp: 'pmm 2/5/2012 21:44'! unsupportedOperation: aSelector CTUnsupportedOperationError selector: aSelector receiver: self! ! CTList subclass: #CTUnmodifiableList instanceVariableNames: 'delegate' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !CTUnmodifiableList class methodsFor: 'instance creation' stamp: 'lr 2/6/2012 07:14'! on: aList ^ self basicNew initializeOn: aList! ! !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 ifAbsent: aBlock ^ delegate at: anInteger ifAbsent: aBlock! ! !CTUnmodifiableList methodsFor: 'accessing' stamp: 'lr 2/6/2012 07:13'! at: anInteger put: anObject self unsupportedOperation! ! !CTUnmodifiableList methodsFor: 'iterators' stamp: 'lr 2/6/2012 07:13'! backwardIterator ^ delegate backwardIterator! ! !CTUnmodifiableList methodsFor: 'iterators' stamp: 'lr 2/6/2012 07:13'! forwardIterator ^ delegate forwardIterator! ! !CTUnmodifiableList methodsFor: 'initialization' stamp: 'lr 2/6/2012 07:14'! initializeOn: aList self initialize: aList size. delegate := aList! ! !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: 'accessing' stamp: 'lr 2/6/2012 07:13'! size ^ delegate size! ! CTList subclass: #CTVectorList instanceVariableNames: 'array size' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Lists'! !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: 'iterators' stamp: 'lr 1/21/2012 19:21'! backwardIterator ^ CTBackwardIndexedIterator on: array start: 1 stop: size! ! !CTVectorList methodsFor: 'iterators' stamp: 'lr 1/21/2012 19:21'! forwardIterator ^ CTForwardIndexedIterator on: array start: 1 stop: size! ! !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: 'copying' stamp: 'lr 2/6/2012 20:32'! immutable ^ CTImmutableList withAll: (array copyFrom: 1 to: size)! ! !CTVectorList methodsFor: 'initialization' stamp: 'lr 1/21/2012 19:21'! initialize: anInteger super initialize: anInteger. array := Array new: anInteger. size := 0! ! !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 1/22/2012 16:21'! sort: anOrder from: aStartIndex to: aStopIndex anOrder sort: array from: aStartIndex to: aStopIndex! ! CTCollection subclass: #CTPriorityQueue instanceVariableNames: 'array size comparator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Misc'! !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: 'initialization' stamp: 'lr 1/26/2012 18:53'! initialize: anInteger comparator: aComparator self initialize: anInteger. array := Array new: anInteger. comparator := aComparator. size := 0! ! !CTPriorityQueue methodsFor: 'iterators' stamp: 'lr 1/21/2012 09:11'! iterator "Answer an iterator of the elements of the receiver in random order." ^ CTForwardIndexedIterator 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 1/26/2012 10:37'! 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! ! CTCollection subclass: #CTSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Abstract'! CTSet subclass: #CTHashSet instanceVariableNames: 'table' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !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 1/27/2012 21:56'! initialize: anInteger comparator: aComparator super initialize: anInteger comparator: aComparator. table := self tableClass new: anInteger comparator: aComparator! ! !CTHashSet methodsFor: 'iterators' 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 methodsFor: 'adding' stamp: 'lr 1/14/2012 10:15'! add: anObject (table at: anObject) ifNil: [ | node | node := self newNode: anObject. root add: node before: root. table add: node ] ifNotNil: [ :node | root remove: node; add: node before: root ]. ^ anObject! ! !CTLinkedHashSet methodsFor: 'iterators' stamp: 'lr 1/13/2012 22:45'! backwardIterator ^ root backwardIterator collect: [ :each | each key ]! ! !CTLinkedHashSet methodsFor: 'iterators' stamp: 'lr 1/13/2012 22:45'! forwardIterator ^ root forwardIterator collect: [ :each | each key ]! ! !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: 'iterators' stamp: 'lr 1/13/2012 22:44'! iterator ^ self forwardIterator! ! !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 1/27/2012 14:28'! postCopy super postCopy. root := root copy. table := table copyEmpty. root forwardIterator 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 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: 'initialization' stamp: 'lr 1/27/2012 21:56'! initialize: anInteger comparator: aComparator self initialize: anInteger! ! CTSet subclass: #CTTreeSet instanceVariableNames: 'tree' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTTreeSet methodsFor: 'adding' stamp: 'lr 1/15/2012 15:34'! add: anObject tree add: (self newNode: anObject). ^ anObject! ! !CTTreeSet methodsFor: 'iterators' stamp: 'lr 1/15/2012 15:19'! backwardIterator ^ tree backwardIterator collect: [ :each | each key ]! ! !CTTreeSet methodsFor: 'iterators' stamp: 'lr 1/15/2012 15:19'! forwardIterator ^ tree forwardIterator collect: [ :each | each key ]! ! !CTTreeSet methodsFor: 'testing' stamp: 'lr 1/15/2012 14:46'! includes: anObject ^ (tree at: anObject) notNil! ! !CTTreeSet methodsFor: 'initialization' stamp: 'lr 1/27/2012 21:56'! initialize: anInteger comparator: aComparator super initialize: anInteger comparator: aComparator. tree := self treeClass comparator: aComparator! ! !CTTreeSet methodsFor: 'iterators' stamp: 'lr 1/25/2012 07:43'! iterator ^ self forwardIterator! ! !CTTreeSet methodsFor: 'private' stamp: 'lr 1/15/2012 14:13'! newNode: anObject ^ self nodeClass new key: anObject; yourself! ! !CTTreeSet methodsFor: 'private' stamp: 'lr 1/27/2012 14:22'! nodeClass ^ CTSplayTreeNode! ! !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 1/24/2012 20:04'! treeClass ^ CTSplayTree! ! Object subclass: #CTComparator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Comparators'! !CTComparator commentStamp: 'lr 1/27/2012 14:29' prior: 0! Abstract stategy 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 1/27/2012 14:27'! , anOrder ^ self class on: (comparators copyWith: anOrder)! ! !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 1/24/2012 19:21'! 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 1/27/2012 14:30'! , anOrder "Combine the order of the receiver with the order of the argument." ^ CTCombinedComparator on: (Array with: self with: anOrder)! ! !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: 'private' stamp: 'lr 1/24/2012 19:30'! insertionSort: anArray from: startInteger to: stopInteger "In-place insertion sort algorithm, very efficient for small arrays." | key value inner | startInteger + 1 to: stopInteger do: [ :outer | 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 1/24/2012 19:30'! 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 1/24/2012 19:30'! quickSort: anArray from: startInteger to: stopInteger "Approximative in-place implementation of QuickSort, very efficient for large arrays." | 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 1/27/2012 14:30'! reverse "Reverses the order 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 1/23/2012 23: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 QuickSort that brings elements close to their final position, and then we fix up the final order with InsertionSort (as recommended by Robert Sedgewick)." self quickSort: anArray from: startInteger to: stopInteger. self insertionSort: anArray from: startInteger to: stopInteger! ! !CTComparator methodsFor: 'operators' stamp: 'lr 1/24/2012 19:14'! transform: aSymbol "Transform the object to 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 1/21/2012 10:49'! on: anOrder ^ self basicNew initializeOn: anOrder! ! !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 1/24/2012 19:13'! 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 1/22/2012 10:18'! on: anOrder selector: aSymbol ^ (self on: anOrder) setSelector: 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: '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: $)! ! !CTMutatingComparator methodsFor: 'initialization' stamp: 'lr 1/22/2012 10:18'! setSelector: aSelector selector := aSelector! ! 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 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: 'instance creation' stamp: 'lr 1/22/2012 09:21'! new ^ instance ifNil: [ instance := self basicNew ]! ! !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'! ! Object variableSubclass: #CTFingerArray instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTFingerArray class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 14:23'! new: anInteger ^ self basicNew: anInteger! ! !CTFingerArray class methodsFor: 'as yet unclassified' stamp: 'lr 2/5/2012 14:17'! with: aFirstObject ^ (self basicNew: 1) at: 1 put: aFirstObject; yourself! ! !CTFingerArray class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 14:23'! with: aFirstObject with: aSecondObject ^ (self basicNew: 2) at: 1 put: aFirstObject; at: 2 put: aSecondObject; yourself! ! !CTFingerArray class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 14:23'! with: aFirstObject with: aSecondObject with: aThirdObject ^ (self basicNew: 3) at: 1 put: aFirstObject; at: 2 put: aSecondObject; at: 3 put: aThirdObject; yourself! ! !CTFingerArray class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 14:23'! with: aFirstObject with: aSecondObject with: aThirdObject with: aFourthObject ^ (self basicNew: 4) at: 1 put: aFirstObject; at: 2 put: aSecondObject; at: 3 put: aThirdObject; at: 4 put: aFourthObject; yourself! ! !CTFingerArray class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 14:51'! withAll: anArray | result | result := self basicNew: anArray size. result replaceFrom: 1 to: result size with: anArray startingAt: 1. ^ result! ! !CTFingerArray methodsFor: 'adding' stamp: 'lr 2/5/2012 15:44'! , aFingerArray | array | array := self class new: self size + aFingerArray size. array replaceFrom: 1 to: self size with: self startingAt: 1. array replaceFrom: self size + 1 to: array size with: aFingerArray startingAt: 1. ^ array! ! !CTFingerArray methodsFor: 'adding' stamp: 'lr 2/5/2012 16:09'! addFirst: anObject ^ self addFirst: anObject as: self class! ! !CTFingerArray methodsFor: 'adding' stamp: 'lr 2/5/2012 16:09'! addFirst: anObject as: aClass | array | array := aClass new: self size + 1. array replaceFrom: 2 to: array size with: self startingAt: 1. array at: 1 put: anObject. ^ array! ! !CTFingerArray methodsFor: 'adding' stamp: 'lr 2/5/2012 16:09'! addLast: anObject ^ self addLast: anObject as: self class! ! !CTFingerArray methodsFor: 'adding' stamp: 'lr 2/5/2012 16:09'! addLast: anObject as: aClass | array | array := aClass new: self size + 1. array replaceFrom: 1 to: self size with: self startingAt: 1. array at: array size put: anObject. ^ array! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:53'! allButFirst ^ self allButFirst: 1 as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:53'! allButFirst: anInteger ^ self allButFirst: anInteger as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:55'! allButFirst: anInteger as: aClass | result | result := aClass basicNew: self size - anInteger. result replaceFrom: 1 to: result size with: self startingAt: anInteger + 1. ^ result! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:54'! allButLast ^ self allButLast: 1 as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:54'! allButLast: anInteger ^ self allButLast: anInteger as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:55'! allButLast: anInteger as: aClass | result | result := aClass basicNew: self size - anInteger. result replaceFrom: 1 to: result size with: self startingAt: 1. ^ result! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 14:07'! first ^ self at: 1! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:52'! first: anInteger ^ self first: anInteger as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:51'! first: anInteger as: aClass | result | result := aClass basicNew: anInteger. result replaceFrom: 1 to: anInteger with: self startingAt: 1. ^ result! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 17:41'! from: aStartInteger to: aStopInteger ^ self from: aStartInteger to: aStopInteger as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 16:06'! from: aStartInteger to: aStopInteger as: aClass | result | result := aClass basicNew: aStopInteger - aStartInteger + 1. result replaceFrom: 1 to: result size with: self startingAt: aStartInteger. ^ result! ! !CTFingerArray methodsFor: 'iterators' stamp: 'lr 2/5/2012 15:18'! iterator ^ CTForwardIndexedIterator on: self! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 14:08'! last ^ self at: self size! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:51'! last: anInteger ^ self last: anInteger as: self class! ! !CTFingerArray methodsFor: 'accessing' stamp: 'lr 2/5/2012 16:06'! last: anInteger as: aClass | result | result := aClass basicNew: anInteger. result replaceFrom: 1 to: anInteger with: self startingAt: self size - anInteger + 1. ^ result! ! !CTFingerArray methodsFor: 'printing' stamp: 'lr 2/5/2012 15:19'! printOn: aStream self iterator do: [ :each | aStream print: each ] separatedBy: [ aStream nextPut: $ ]! ! !CTFingerArray methodsFor: 'private' stamp: 'lr 2/5/2012 14:15'! replaceFrom: aStartInteger to: aStopInteger with: aFingerArray startingAt: aReplacementInteger | index offset | offset := aReplacementInteger - aStartInteger. index := aStartInteger - 1. [ (index := index + 1) <= aStopInteger ] whileTrue: [ self at: index put: (aFingerArray at: offset + index) ]! ! CTFingerArray variableSubclass: #CTFingerDigit instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! CTFingerArray variableSubclass: #CTFingerNode instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTFingerNode methodsFor: 'printing' stamp: 'lr 2/5/2012 14:44'! printOn: aStream aStream nextPut: $(. super printOn: aStream. aStream nextPut: $)! ! Object subclass: #CTFingerTree instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTFingerTree commentStamp: '' prior: 0! Ralf Hinze and Ross Paterson, Finger trees: a simple general-purpose data structure, Journal of Functional Programming/ 16:2 (2006) pp 197-217. http://www.soi.city.ac.uk/~ross/papers/FingerTree.pdf! CTFingerTree subclass: #CTDeepFingerTree instanceVariableNames: 'prefix tree suffix' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTDeepFingerTree class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 10:06'! prefix: aPrefixArray tree: aFingerTree suffix: aSuffixArray ^ self basicNew initializePrefix: aPrefixArray tree: aFingerTree suffix: aSuffixArray! ! !CTDeepFingerTree methodsFor: 'operators' stamp: 'lr 2/5/2012 18:18'! , aFingerTree ^ aFingerTree appendToDeep: self! ! !CTDeepFingerTree methodsFor: 'adding' stamp: 'lr 2/5/2012 16:08'! addFirst: anObject ^ prefix size = 4 ifTrue: [ CTDeepFingerTree prefix: (CTFingerDigit with: anObject with: prefix first) tree: (tree addFirst: (prefix allButFirst: 1 as: CTFingerNode)) suffix: suffix ] ifFalse: [ CTDeepFingerTree prefix: (prefix addFirst: anObject) tree: tree suffix: suffix ]! ! !CTDeepFingerTree methodsFor: 'adding' stamp: 'lr 2/5/2012 16:08'! addLast: anObject ^ suffix size = 4 ifTrue: [ CTDeepFingerTree prefix: prefix tree: (tree addLast: (suffix allButLast: 1 as: CTFingerNode)) suffix: (CTFingerDigit with: suffix last with: anObject) ] ifFalse: [ CTDeepFingerTree prefix: prefix tree: tree suffix: (suffix addLast: anObject) ]! ! !CTDeepFingerTree methodsFor: 'accessing' stamp: 'lr 2/5/2012 17:29'! allButFirst prefix size > 1 ifTrue: [ ^ CTDeepFingerTree prefix: prefix allButFirst tree: tree suffix: suffix ]. tree isEmpty ifFalse: [ ^ CTDeepFingerTree prefix: (CTFingerDigit withAll: tree first) tree: tree allButFirst suffix: suffix ]. suffix size > 1 ifTrue: [ ^ CTDeepFingerTree prefix: suffix allButLast tree: tree suffix: (suffix from: suffix size to: suffix size) ]. ^ CTSingleFingerTree object: suffix last! ! !CTDeepFingerTree methodsFor: 'accessing' stamp: 'lr 2/5/2012 15:24'! allButLast suffix size > 1 ifTrue: [ ^ CTDeepFingerTree prefix: prefix tree: tree suffix: suffix allButLast ]. tree isEmpty ifFalse: [ ^ CTDeepFingerTree prefix: prefix tree: tree allButLast suffix: (CTFingerDigit withAll: tree last) ]. prefix size > 1 ifTrue: [ ^ CTDeepFingerTree prefix: (prefix copyFrom: 1 to: 1) tree: tree suffix: prefix allButFirst ]. ^ CTSingleFingerTree object: prefix first! ! !CTDeepFingerTree methodsFor: 'private' stamp: 'lr 2/5/2012 18:19'! appendToDeep: aDeepFingerTree ^ CTDeepFingerTree prefix: aDeepFingerTree prefix tree: (aDeepFingerTree tree addFromArray: aDeepFingerTree suffix , prefix) , tree suffix: suffix! ! !CTDeepFingerTree methodsFor: 'accessing' stamp: 'lr 2/5/2012 10:08'! first ^ prefix first! ! !CTDeepFingerTree methodsFor: 'initialization' stamp: 'lr 2/5/2012 10:05'! initializePrefix: aPrefixArray tree: aFingerTree suffix: aSuffixArray prefix := aPrefixArray. tree := aFingerTree. suffix := aSuffixArray! ! !CTDeepFingerTree methodsFor: 'accessing' stamp: 'lr 2/5/2012 10:08'! last ^ suffix last! ! !CTDeepFingerTree methodsFor: 'private' stamp: 'lr 2/4/2012 18:50'! prefix ^ prefix! ! !CTDeepFingerTree methodsFor: 'printing' stamp: 'lr 2/5/2012 14:33'! printOn: aStream aStream nextPut: $<; print: prefix; nextPut: $ ; print: tree; nextPut: $ ; print: suffix; nextPut: $>! ! !CTDeepFingerTree methodsFor: 'private' stamp: 'lr 2/4/2012 18:50'! suffix ^ suffix! ! !CTDeepFingerTree methodsFor: 'private' stamp: 'lr 2/4/2012 18:50'! tree ^ tree! ! CTFingerTree subclass: #CTEmptyFingerTree instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTEmptyFingerTree methodsFor: 'operators' stamp: 'lr 2/2/2012 20:35'! , aFingerTree ^ aFingerTree! ! !CTEmptyFingerTree methodsFor: 'adding' stamp: 'lr 2/5/2012 10:04'! addFirst: anObject ^ CTSingleFingerTree object: anObject! ! !CTEmptyFingerTree methodsFor: 'adding' stamp: 'lr 2/5/2012 10:04'! addLast: anObject ^ CTSingleFingerTree object: anObject! ! !CTEmptyFingerTree methodsFor: 'accessing' stamp: 'lr 2/4/2012 16:01'! allButFirst ^ self noSuchElement! ! !CTEmptyFingerTree methodsFor: 'accessing' stamp: 'lr 2/4/2012 16:01'! allButLast ^ self noSuchElement! ! !CTEmptyFingerTree methodsFor: 'private' stamp: 'lr 2/5/2012 18:18'! appendToDeep: aDeepFingerTree ^ aDeepFingerTree! ! !CTEmptyFingerTree methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:46'! first ^ self noSuchElement! ! !CTEmptyFingerTree methodsFor: 'testing' stamp: 'lr 2/2/2012 22:49'! isEmpty ^ true! ! !CTEmptyFingerTree methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:46'! last ^ self noSuchElement! ! !CTEmptyFingerTree methodsFor: 'printing' stamp: 'lr 2/4/2012 14:37'! printOn: aStream aStream nextPutAll: '<>'! ! !CTFingerTree methodsFor: 'operators' stamp: 'lr 2/4/2012 18:32'! , aTree "Concatenates the receiver with the argument and answer the composed tree. In most cases this operation is really simple to implement, except if two deep trees are composed." self subclassResponsibility! ! !CTFingerTree methodsFor: 'adding' stamp: 'lr 2/4/2012 13:27'! addFirst: anObject "Add anObject to the beginning of the receiver, and answer the modified tree." self subclassResponsibility ! ! !CTFingerTree methodsFor: 'private' stamp: 'lr 2/5/2012 17:52'! addFromArray: aFingerArray ^ (aFingerArray size = 2 or: [ aFingerArray size = 3 ]) ifTrue: [ self addLast: (aFingerArray first: aFingerArray size as: CTFingerNode) ] ifFalse: [ aFingerArray size = 4 ifTrue: [ (self addLast: (aFingerArray first: 2 as: CTFingerNode)) addLast: (aFingerArray last: 2 as: CTFingerNode) ] ifFalse: [ (self addLast: (aFingerArray first: 3 as: CTFingerNode)) addFromArray: (aFingerArray allButFirst: 3 as: CTFingerNode) ] ]! ! !CTFingerTree methodsFor: 'adding' stamp: 'lr 2/4/2012 13:28'! addLast: anObject "Add anObject to the end of the receiver, and answer the modified tree." self subclassResponsibility ! ! !CTFingerTree methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:45'! allButFirst "Answer everything but the first element." self subclassResponsibility! ! !CTFingerTree methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:45'! allButLast "Answer everything but the last element." self subclassResponsibility! ! !CTFingerTree methodsFor: 'private' stamp: 'lr 2/5/2012 18:18'! appendToDeep: aDeepFingerTree self subclassResponsibility! ! !CTFingerTree methodsFor: 'iterators' stamp: 'lr 2/4/2012 13:29'! backwardIterator "Answer a reverse-order iterator over the tree." ^ CTBackwardFingerIterator on: self! ! !CTFingerTree methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:44'! first "Answer the first element." self subclassResponsibility! ! !CTFingerTree methodsFor: 'iterators' stamp: 'lr 2/4/2012 13:28'! forwardIterator "Answer an natural-order iterator over the tree." ^ CTForwardFingerIterator on: self! ! !CTFingerTree methodsFor: 'testing' stamp: 'lr 2/4/2012 13:29'! isEmpty "Answer true if the receiver is empty." ^ false! ! !CTFingerTree methodsFor: 'iterators' stamp: 'lr 2/5/2012 18:16'! iterator "Answer a default iterator over the tree." ^ self forwardIterator! ! !CTFingerTree methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:45'! last "Answer the last element." self subclassResponsibility! ! !CTFingerTree methodsFor: 'private' stamp: 'lr 2/2/2012 22:46'! noSuchElement ^ CTNoSuchElementError signal! ! CTFingerTree subclass: #CTSingleFingerTree instanceVariableNames: 'object' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTSingleFingerTree class methodsFor: 'instance creation' stamp: 'lr 2/5/2012 10:04'! object: anObject ^ self basicNew initializeObject: anObject! ! !CTSingleFingerTree methodsFor: 'operators' stamp: 'lr 2/4/2012 13:25'! , aTree ^ aTree addFirst: object! ! !CTSingleFingerTree methodsFor: 'adding' stamp: 'lr 2/5/2012 17:47'! addFirst: anObject ^ CTDeepFingerTree prefix: (CTFingerDigit with: anObject) tree: CTEmptyFingerTree new suffix: (CTFingerDigit with: object)! ! !CTSingleFingerTree methodsFor: 'adding' stamp: 'lr 2/5/2012 14:46'! addLast: anObject ^ CTDeepFingerTree prefix: (CTFingerDigit with: object) tree: CTEmptyFingerTree new suffix: (CTFingerDigit with: anObject)! ! !CTSingleFingerTree methodsFor: 'accessing' stamp: 'lr 2/5/2012 10:03'! allButFirst ^ CTEmptyFingerTree new! ! !CTSingleFingerTree methodsFor: 'accessing' stamp: 'lr 2/5/2012 10:03'! allButLast ^ CTEmptyFingerTree new! ! !CTSingleFingerTree methodsFor: 'private' stamp: 'lr 2/5/2012 18:18'! appendToDeep: aDeepFingerTree ^ aDeepFingerTree addLast: object! ! !CTSingleFingerTree methodsFor: 'accessing' stamp: 'lr 2/4/2012 13:25'! first ^ object! ! !CTSingleFingerTree methodsFor: 'initialization' stamp: 'lr 2/5/2012 10:04'! initializeObject: anObject object := anObject! ! !CTSingleFingerTree methodsFor: 'accessing' stamp: 'lr 2/4/2012 13:25'! last ^ object! ! !CTSingleFingerTree methodsFor: 'printing' stamp: 'lr 2/5/2012 14:33'! printOn: aStream aStream nextPut: $<; print: object; nextPut: $>! ! 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 1/24/2012 19:32'! 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: 2 * array size ]! ! !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 1/12/2012 19:49'! capacityFor: anInteger | capacity | capacity := 1. [ capacity < anInteger ] whileTrue: [ capacity := 2 * capacity ]. ^ capacity! ! !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: 'iterators' 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: 'lr 1/13/2012 23:50'! postCopy array := array copy. 1 to: array size do: [ :index | | node prev | 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 1/24/2012 19:33'! removeKey: aKey | index node previous | 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: #CTIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! CTIterator subclass: #CTBinaryTreeIterator instanceVariableNames: 'stack current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! CTBinaryTreeIterator subclass: #CTBackwardBinaryTreeIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTBackwardBinaryTreeIterator methodsFor: 'accessing' stamp: 'lr 1/25/2012 22:44'! next | node | node := current. [ node isNil ] whileFalse: [ stack addLast: node. node := node right ]. stack isEmpty ifTrue: [ ^ self noSuchElementError ]. node := stack removeLast. current := node left. ^ node! ! !CTBinaryTreeIterator class methodsFor: 'instance creation' stamp: 'lr 1/25/2012 22:39'! on: aNode ^ self basicNew initializeOn: aNode! ! !CTBinaryTreeIterator methodsFor: 'testing' stamp: 'lr 1/25/2012 22:49'! hasNext ^ current notNil or: [ stack size > 0 ]! ! !CTBinaryTreeIterator methodsFor: 'initialization' stamp: 'lr 1/25/2012 22:44'! initializeOn: aRoot stack := CTVectorList new. current := aRoot ! ! !CTBinaryTreeIterator methodsFor: 'copying' stamp: 'lr 1/27/2012 21:57'! postCopy super postCopy. stack := stack copy! ! CTBinaryTreeIterator subclass: #CTForwardBinaryTreeIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTForwardBinaryTreeIterator methodsFor: 'accessing' stamp: 'lr 1/25/2012 22:44'! next | node | node := current. [ node isNil ] whileFalse: [ stack addLast: node. node := node left ]. stack isEmpty ifTrue: [ ^ self noSuchElementError ]. node := stack removeLast. current := node right. ^ node! ! CTIterator subclass: #CTDelegateIterator instanceVariableNames: 'iterator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! CTDelegateIterator subclass: #CTChainingIterator instanceVariableNames: 'iterators' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTChainingIterator commentStamp: '' prior: 0! An iterator that chains iterators together.! !CTChainingIterator methodsFor: 'iterators' stamp: 'lr 2/4/2012 20:05'! , anIterator | result | result := CTArrayList with: iterator. iterators addTo: result. result addLast: anIterator. ^ CTChainingIterator on: result iterator! ! !CTChainingIterator methodsFor: 'testing' stamp: 'lr 2/4/2012 20:13'! hasNext | hasNext | [ (hasNext := iterator hasNext) or: [ iterators hasNext not ] ] whileFalse: [ iterator := iterators next ]. ^ hasNext! ! !CTChainingIterator methodsFor: 'initialization' stamp: 'lr 2/4/2012 20:07'! initializeOn: anIterator super initializeOn: CTEmptyIterator new. iterators := anIterator! ! !CTChainingIterator methodsFor: 'accessing' stamp: 'lr 2/4/2012 20:15'! next [ iterator hasNext or: [ iterators hasNext not ] ] whileFalse: [ iterator := iterators next ]. ^ iterator next! ! CTDelegateIterator subclass: #CTCyclingIterator instanceVariableNames: 'current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-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 1/1/2012 00:42'! initializeOn: anIterator super initializeOn: anIterator copy. current := anIterator! ! !CTCyclingIterator methodsFor: 'accessing' stamp: 'lr 1/1/2012 00:40'! next ^ self hasNext ifTrue: [ current next ] ifFalse: [ self noSuchElementError ]! ! !CTDelegateIterator class methodsFor: 'instance creation' stamp: 'lr 1/1/2012 18:06'! on: anIterator ^ self basicNew initializeOn: anIterator! ! !CTDelegateIterator methodsFor: 'private' stamp: 'lr 1/9/2012 21:08'! apply: aBlock with: anObject ^ iterator apply: aBlock with: anObject! ! !CTDelegateIterator methodsFor: 'private' stamp: 'lr 1/9/2012 21:09'! apply: aBlock with: anObject with: anotherObject ^ iterator apply: aBlock with: anObject with: anotherObject! ! !CTDelegateIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 18:22'! hasNext ^ iterator hasNext! ! !CTDelegateIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 17:58'! initializeOn: anIterator 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: #CTFilteringIterator instanceVariableNames: 'predicate defined current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTFilteringIterator commentStamp: '' prior: 0! An iterator that filters its elements using the given block predicate.! !CTFilteringIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 23:00'! on: anIterator predicate: aBlock ^ (self on: anIterator) setPredicate: aBlock! ! !CTFilteringIterator methodsFor: 'testing' stamp: 'lr 1/9/2012 21:19'! hasNext defined ifTrue: [ ^ true ]. [ iterator hasNext ifFalse: [ ^ false ]. self apply: predicate with: (current := iterator next) ] whileFalse. ^ defined := true! ! !CTFilteringIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 23:47'! next self hasNext ifFalse: [ ^ self noSuchElementError ]. defined := false. ^ current! ! !CTFilteringIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 23:44'! setPredicate: aValuable predicate := aValuable. defined := false! ! 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 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: #CTMapIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !CTMapIterator methodsFor: 'private' stamp: 'lr 1/14/2012 10:33'! apply: aBlock with: aNode ^ aBlock numArgs = 2 ifTrue: [ aBlock value: aNode key value: aNode object ] ifFalse: [ super apply: aBlock with: aNode object ]! ! !CTMapIterator methodsFor: 'private' stamp: 'lr 1/14/2012 10:32'! apply: aBlock with: anObject with: aNode ^ aBlock numArgs = 3 ifTrue: [ aBlock value: anObject value: aNode key value: aNode object ] ifFalse: [ super apply: aBlock with: anObject with: aNode object ]! ! CTDelegateIterator subclass: #CTMutatingIterator instanceVariableNames: 'block' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTMutatingIterator commentStamp: '' prior: 0! An iterator that lazily mutates the consumed elements.! !CTMutatingIterator class methodsFor: 'instance creation' stamp: 'lr 1/1/2012 00:33'! on: anIterator block: aBlock ^ (self on: anIterator) setBlock: aBlock! ! !CTMutatingIterator methodsFor: 'accessing' stamp: 'lr 1/9/2012 21:18'! next ^ self apply: block with: iterator next! ! !CTMutatingIterator methodsFor: 'initialization' stamp: 'lr 1/1/2012 00:34'! setBlock: aBlock block := aBlock! ! CTIterator subclass: #CTEmptyIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! CTEmptyIterator class instanceVariableNames: 'default'! !CTEmptyIterator commentStamp: '' prior: 0! An empty iterator that has no elements.! CTEmptyIterator class instanceVariableNames: 'default'! !CTEmptyIterator class methodsFor: 'instance creation' stamp: 'lr 1/27/2012 22:01'! new ^ default ifNil: [ default := self basicNew ]! ! !CTEmptyIterator methodsFor: 'converting' stamp: 'pmm 2/6/2012 20:27'! as: aCollectionClass ^ aCollectionClass new! ! !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: #CTFingerIterator instanceVariableNames: 'tree' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! CTFingerIterator subclass: #CTBackwardFingerIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTBackwardFingerIterator methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:58'! next | element | element := tree last. tree := tree allButLast. ^ element! ! !CTFingerIterator class methodsFor: 'instance creation' stamp: 'lr 2/2/2012 22:33'! on: aFingerTree ^ self basicNew initializeOn: aFingerTree! ! !CTFingerIterator methodsFor: 'testing' stamp: 'lr 2/2/2012 22:52'! hasNext ^ tree isEmpty not! ! !CTFingerIterator methodsFor: 'initialization' stamp: 'lr 2/2/2012 22:33'! initializeOn: aFingerTree tree := aFingerTree! ! CTFingerIterator subclass: #CTForwardFingerIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Finger'! !CTForwardFingerIterator methodsFor: 'accessing' stamp: 'lr 2/2/2012 22:58'! next | element | element := tree first. tree := tree allButFirst. ^ element! ! 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 1/28/2012 16:47'! next | result | node := (result := node) next. [ node isNil and: [ index > 1 ] ] whileTrue: [ node := array at: (index := index - 1) ]. ^ result! ! CTIterator subclass: #CTIndexedIterator instanceVariableNames: 'array start stop offset position' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTIndexedIterator commentStamp: '' prior: 0! Abstract iterator class for arrays and other collections supporting indexed access.! CTIndexedIterator subclass: #CTBackwardIndexedIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTBackwardIndexedIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 13:08'! hasNext ^ position > start! ! !CTBackwardIndexedIterator methodsFor: 'initialization' stamp: 'lr 1/10/2012 07:00'! initializeOn: anArray start: aStartInteger stop: aStopInteger offset: anOffsetInteger self initializeOn: anArray start: aStartInteger stop: aStopInteger offset: anOffsetInteger position: aStopInteger + 1! ! !CTBackwardIndexedIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:08'! next ^ self hasNext ifFalse: [ self noSuchElementError ] ifTrue: [ array at: (position := position - 1) ]! ! CTIndexedIterator subclass: #CTForwardIndexedIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTForwardIndexedIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 13:07'! hasNext ^ position < stop! ! !CTForwardIndexedIterator methodsFor: 'initialization' stamp: 'lr 1/10/2012 06:59'! initializeOn: anArray start: aStartInteger stop: aStopInteger offset: anOffsetInteger self initializeOn: anArray start: aStartInteger stop: aStopInteger offset: anOffsetInteger position: aStartInteger - 1! ! !CTForwardIndexedIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 13:08'! next ^ self hasNext ifFalse: [ self noSuchElementError ] ifTrue: [ array at: (position := position + 1) ]! ! !CTIndexedIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 14:47'! on: anArray ^ self on: anArray start: 1 stop: anArray size! ! !CTIndexedIterator class methodsFor: 'instance creation' stamp: 'lr 1/10/2012 07:00'! on: anArray start: aStartIndex stop: aStopIndex ^ self on: anArray start: aStartIndex stop: aStopIndex offset: 0! ! !CTIndexedIterator class methodsFor: 'instance creation' stamp: 'lr 1/10/2012 07:00'! on: anArray start: aStartIndex stop: aStopIndex offset: anOffsetInteger ^ self basicNew initializeOn: anArray start: aStartIndex stop: aStopIndex offset: anOffsetInteger! ! !CTIndexedIterator methodsFor: 'private' stamp: 'lr 1/10/2012 06:58'! apply: aBlock with: anObject ^ aBlock numArgs = 2 ifTrue: [ aBlock value: position - offset value: anObject ] ifFalse: [ super apply: aBlock with: anObject ]! ! !CTIndexedIterator methodsFor: 'private' stamp: 'lr 1/10/2012 07:15'! apply: aBlock with: anObject with: anotherObject ^ aBlock numArgs = 3 ifTrue: [ aBlock value: anObject value: position - offset value: anotherObject ] ifFalse: [ super apply: aBlock with: anObject with: anotherObject ]! ! !CTIndexedIterator methodsFor: 'initialization' stamp: 'lr 1/10/2012 06:59'! initializeOn: anArray start: aStartInteger stop: aStopInteger offset: anOffsetInteger self subclassResponsibility! ! !CTIndexedIterator methodsFor: 'initialization' stamp: 'lr 1/10/2012 06:59'! initializeOn: anArray start: aStartInteger stop: aStopInteger offset: anOffsetInteger position: aPositionInteger array := anArray. start := aStartInteger. stop := aStopInteger. offset := anOffsetInteger. position := aPositionInteger! ! !CTIterator class methodsFor: 'accessing' stamp: 'lr 1/1/2012 10:12'! browserIcon ^ #stream! ! !CTIterator methodsFor: 'iterators' stamp: 'lr 2/4/2012 20:05'! , anIterator ^ CTChainingIterator on: (Array with: self with: anIterator) 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: '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: '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: 'iterators' stamp: 'lr 1/1/2012 18:04'! cycle "Answer an iterator that cycles multiple times trough the receiver. If the receiver is an non-empty iterator then the resulting iterator is of an infinite size." ^ self hasNext ifTrue: [ CTCyclingIterator on: self ] ifFalse: [ CTEmptyIterator new ]! ! !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: '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: '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: 'testing' stamp: 'lr 12/29/2011 21:31'! isEmpty "Answer whether there is a next element in the iterator." ^ self hasNext not! ! !CTIterator methodsFor: 'accessing' stamp: 'lr 1/27/2012 21:59'! iterator "Answer an iterator of the receiver, that is a copy of the receiver." ^ self copy! ! !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: '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: 'enumerating' stamp: 'lr 1/21/2012 20:02'! 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 | 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 1/1/2012 00:18'! removeFrom: aCollection "Remove the elements of the receiving iterator from aCollection. answer aCollection." [ self hasNext ] whileTrue: [ aCollection remove: self next ]. ^ 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 subclass: #CTLinkedListIterator instanceVariableNames: 'root current' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! CTLinkedListIterator subclass: #CTBackwardLinkedListIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTBackwardLinkedListIterator methodsFor: 'testing' stamp: 'lr 1/13/2012 10:32'! hasNext ^ current before ~~ root! ! !CTBackwardLinkedListIterator methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:33'! next ^ current before == root ifTrue: [ self noSuchElementError ] ifFalse: [ current := current before ]! ! CTLinkedListIterator subclass: #CTForwardLinkedListIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTForwardLinkedListIterator methodsFor: 'testing' stamp: 'lr 1/13/2012 10:32'! hasNext ^ current after ~~ root! ! !CTForwardLinkedListIterator methodsFor: 'accessing' stamp: 'lr 1/13/2012 10:33'! next ^ current after == root ifTrue: [ self noSuchElementError ] ifFalse: [ current := current after ]! ! !CTLinkedListIterator class methodsFor: 'instance creation' stamp: 'lr 1/13/2012 10:33'! on: aNode ^ self basicNew initializeOn: aNode! ! !CTLinkedListIterator methodsFor: 'initialization' stamp: 'lr 1/13/2012 10:33'! initializeOn: aNode root := current := aNode! ! CTIterator subclass: #CTSingletonterator instanceVariableNames: 'element atEnd' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTSingletonterator commentStamp: '' prior: 0! An empty iterator that has no elements.! !CTSingletonterator class methodsFor: 'instance creation' stamp: 'pmm 2/5/2012 21:54'! on: anObject ^ self basicNew initializeWith: anObject! ! !CTSingletonterator methodsFor: 'converting' stamp: 'pmm 2/6/2012 19:57'! as: aCollectionClass "Converts the remainder of this iterator into aCollectionClass." ^ aCollectionClass with: element! ! !CTSingletonterator methodsFor: 'testing' stamp: 'pmm 2/5/2012 21:54'! hasNext ^ atEnd not! ! !CTSingletonterator methodsFor: 'initialization' stamp: 'pmm 2/5/2012 21:54'! initializeWith: anObject self initialize. element := anObject. atEnd := false! ! !CTSingletonterator methodsFor: 'accessing' stamp: 'pmm 2/5/2012 21:55'! next atEnd := true. ^ element! ! 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: 'iterators' stamp: 'lr 1/13/2012 10:58'! backwardIterator ^ CTBackwardLinkedListIterator on: self! ! !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 1/13/2012 13:22'! copy | copy iterator | copy := super copy initialize. iterator := self forwardIterator. [ iterator hasNext ] whileTrue: [ copy add: iterator next copy before: copy ]. ^ copy! ! !CTLinkedListRoot methodsFor: 'iterators' stamp: 'lr 1/13/2012 10:34'! forwardIterator ^ CTForwardLinkedListIterator on: self! ! !CTLinkedListRoot methodsFor: 'initialization' stamp: 'lr 1/13/2012 10:53'! initialize before := after := 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: #CTMap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Abstract'! CTMap subclass: #CTHashMap instanceVariableNames: 'table' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !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 1/27/2012 14:16'! initialize: anInteger comparator: aComparator super 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 methodsFor: 'accessing' stamp: 'lr 1/14/2012 11:37'! 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. root remove: node; add: node before: root ]. ^ anObject! ! !CTLinkedHashMap methodsFor: 'iterators' stamp: 'lr 1/27/2012 14:05'! backwardIterator ^ CTMapIterator on: self backwardNodeIterator! ! !CTLinkedHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 12:01'! backwardNodeIterator ^ root backwardIterator! ! !CTLinkedHashMap methodsFor: 'iterators' stamp: 'lr 1/27/2012 14:05'! forwardIterator ^ CTMapIterator on: self forwardNodeIterator! ! !CTLinkedHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 12:01'! forwardNodeIterator ^ root forwardIterator! ! !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: '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 1/14/2012 12:00'! nodeIterator ^ self forwardNodeIterator! ! !CTLinkedHashMap methodsFor: 'copying' stamp: 'lr 1/27/2012 14:28'! postCopy super postCopy. root := root copy. table := table copyEmpty. root forwardIterator 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/1/2012 10:12'! browserIcon ^ #collection! ! !CTMap class methodsFor: 'accessing' stamp: 'lr 1/24/2012 20:47'! defaultCapacity ^ 10! ! !CTMap class methodsFor: 'accessing' stamp: 'lr 1/27/2012 14:18'! defaultComparator ^ CTNaturalComparator new! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/15/2012 17:24'! key: aKey1 value: aValue1 ^ (self new: 1) at: aKey1 put: aValue1; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/15/2012 17:25'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 ^ (self new: 2) at: aKey1 put: aValue1; at: aKey2 put: aValue2; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/15/2012 17:25'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 ^ (self new: 3) at: aKey1 put: aValue1; at: aKey2 put: aValue2; at: aKey3 put: aValue3; yourself! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/15/2012 17:25'! key: aKey1 value: aValue1 key: aKey2 value: aValue2 key: aKey3 value: aValue3 key: aKey4 value: aValue4 ^ (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 1/24/2012 20:48'! new ^ self new: self defaultCapacity! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/27/2012 14:17'! new: anInteger ^ self new: anInteger comparator: self defaultComparator! ! !CTMap class methodsFor: 'instance creation' stamp: 'lr 1/27/2012 14:17'! 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 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: 'testing' stamp: 'lr 1/14/2012 12:11'! includesKey: aKey self subclassResponsibility! ! !CTMap methodsFor: 'initialization' stamp: 'lr 1/27/2012 14:20'! initialize: anInteger comparator: aComparator self initialize! ! !CTMap methodsFor: 'testing' stamp: 'lr 1/15/2012 17:22'! isEmpty "Answer whether the receiver contains any elements." ^ self size == 0! ! !CTMap methodsFor: 'iterators' 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: 'private' stamp: 'lr 1/1/2012 17:21'! keyNotFound: anObject ^ CTKeyNotFoundError new key: anObject; signal! ! !CTMap methodsFor: 'iterators' stamp: 'lr 1/14/2012 12:02'! keys "Answer an iterator over the keys of this map." ^ self nodeIterator collect: [ :node | node key ]! ! !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 1/15/2012 17:21'! printElementsOn: aStream | iterator | iterator := self iterator. (iterator limit: 5) do: [ :key :value | aStream cr; tab; print: key; nextPutAll: ': '; print: value ]. iterator hasNext ifTrue: [ aStream cr; tab; nextPutAll: '...' ]! ! !CTMap methodsFor: 'printing' stamp: 'lr 1/15/2012 17:20'! printOn: aStream super printOn: aStream. self printElementsOn: aStream! ! !CTMap methodsFor: 'removing' stamp: 'lr 1/1/2012 17:21'! removeAll self subclassResponsibility! ! !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 1/15/2012 17:22'! size "Returns the number of elements in this collection." self subclassResponsibility! ! !CTMap methodsFor: 'iterators' stamp: 'lr 1/14/2012 12:02'! values "Answer an iterator over the values of this map." ^ self nodeIterator collect: [ :node | node object ]! ! CTMap subclass: #CTTreeMap instanceVariableNames: 'tree' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !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: 'iterators' stamp: 'lr 1/27/2012 14:05'! backwardIterator ^ CTMapIterator on: self backwardNodeIterator! ! !CTTreeMap methodsFor: 'private' stamp: 'lr 1/27/2012 14:03'! backwardNodeIterator ^ tree backwardIterator! ! !CTTreeMap methodsFor: 'iterators' stamp: 'lr 1/27/2012 14:05'! forwardIterator ^ CTMapIterator on: self forwardNodeIterator! ! !CTTreeMap methodsFor: 'private' stamp: 'lr 1/27/2012 14:03'! forwardNodeIterator ^ tree forwardIterator! ! !CTTreeMap methodsFor: 'testing' stamp: 'lr 1/25/2012 08:10'! includesKey: aKey ^ (tree at: aKey) notNil! ! !CTTreeMap methodsFor: 'initialization' stamp: 'lr 1/27/2012 14:16'! initialize: anInteger comparator: aComparator super 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 1/27/2012 14:02'! nodeIterator ^ self forwardNodeIterator! ! !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 1/24/2012 20:53'! treeClass ^ CTSplayTree! ! Object subclass: #CTSplayTree instanceVariableNames: 'root size comparator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTSplayTree class methodsFor: 'instance creation' stamp: 'lr 1/24/2012 19:59'! comparator: aComparator ^ self basicNew initializeComparator: aComparator! ! !CTSplayTree methodsFor: 'modifying' stamp: 'lr 1/25/2012 08:08'! add: aNode root isNil ifTrue: [ aNode left: nil; right: nil ] ifFalse: [ root := self splay: aNode key. (comparator equals: aNode key to: root key) ifTrue: [ ^ root ]. (comparator less: aNode key than: root key) ifTrue: [ aNode left: root left; right: root. root left: nil ] ifFalse: [ aNode right: root right; left: root. root right: nil ] ]. size := size + 1. root := aNode. ^ aNode! ! !CTSplayTree methodsFor: 'accessing' stamp: 'lr 1/28/2012 16:26'! at: aKey root ifNil: [ ^ nil ]. root := self splay: aKey. ^ (comparator equals: aKey to: root key) ifTrue: [ root ]! ! !CTSplayTree methodsFor: 'iterators' stamp: 'lr 1/25/2012 22:38'! backwardIterator ^ CTBackwardBinaryTreeIterator on: root! ! !CTSplayTree methodsFor: 'iterators' stamp: 'lr 1/25/2012 22:39'! forwardIterator ^ CTForwardBinaryTreeIterator on: root! ! !CTSplayTree methodsFor: 'initialization' stamp: 'lr 1/24/2012 20:56'! initializeComparator: aComparator size := 0. comparator := aComparator! ! !CTSplayTree methodsFor: 'copying' stamp: 'lr 1/25/2012 22:59'! postCopy | iterator | iterator := self forwardIterator. self removeAll. [ iterator hasNext ] whileTrue: [ self add: iterator next copy ]! ! !CTSplayTree methodsFor: 'modifying' stamp: 'lr 1/24/2012 20:56'! removeAll root := nil. size := 0! ! !CTSplayTree methodsFor: 'modifying' stamp: 'lr 1/28/2012 16:31'! removeKey: aKey | node | root isNil ifTrue: [ ^ nil ]. root := node := self splay: aKey. (comparator equals: aKey to: root key) ifFalse: [ ^ nil ]. root left isNil ifTrue: [ root := root right ] ifFalse: [ | temp | temp := root right. root := root left. root := self splay: aKey. root right: temp ]. size := size - 1. ^ node left: nil; right: nil; yourself! ! !CTSplayTree methodsFor: 'private' stamp: 'lr 1/21/2012 23:49'! rotateLeft: aNode | current | current := aNode left. aNode left: current right. ^ current right: aNode! ! !CTSplayTree methodsFor: 'private' stamp: 'lr 1/21/2012 23:49'! rotateRight: aNode | current | current := aNode right. aNode right: current left. ^ current left: aNode! ! !CTSplayTree methodsFor: 'accessing' stamp: 'lr 1/24/2012 20:55'! size ^ size! ! !CTSplayTree methodsFor: 'private' stamp: 'lr 1/24/2012 20:58'! splay: aKey | current left right header | current := root. left := right := header := CTSplayTreeNode new. [ current isNil or: [ comparator equals: aKey to: current key ] ] whileFalse: [ (comparator less: aKey than: current key) ifTrue: [ (current left notNil and: [ comparator less: aKey than: current left key ]) ifTrue: [ current := self rotateLeft: current ]. current left isNil ifTrue: [ ^ self splay: current left: left right: right header: header ]. right left: current. right := current. current := current left ] ifFalse: [ (current right notNil and: [ comparator less: current right key than: aKey ]) ifTrue: [ current := self rotateRight: current ]. current right isNil ifTrue: [ ^ self splay: current left: left right: right header: header ]. left right: current. left := current. current := current right ] ]. ^ self splay: current left: left right: right header: header! ! !CTSplayTree methodsFor: 'private' stamp: 'lr 1/28/2012 16:33'! splay: aNode left: leftNode right: rightNode header: headerNode leftNode right: aNode left. rightNode left: aNode right. ^ aNode left: headerNode right; right: headerNode left; yourself! ! Object subclass: #CTSplayTreeNode instanceVariableNames: 'left right key' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/27/2012 14:22'! key ^ key! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/27/2012 14:22'! key: anObject key := anObject! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/24/2012 20:57'! left ^ left! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/24/2012 21:00'! left: aNode left := aNode! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/24/2012 20:57'! right ^ right! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/24/2012 21:00'! right: aNode right := aNode! ! CTSplayTreeNode subclass: #CTTreeMapNode instanceVariableNames: 'object' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Maps'! !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! ! !SequenceableCollection methodsFor: '*container-core-iterators' stamp: 'lr 1/13/2012 11:01'! backwardIterator "Answer a reverse iterator over the elements of the receiving collection." ^ CTBackwardIndexedIterator on: self! ! !SequenceableCollection methodsFor: '*container-core-iterators' stamp: 'lr 1/13/2012 11:01'! forwardIterator "Answer a reverse iterator over the elements of the receiving collection." ^ CTForwardIndexedIterator on: self! ! !SequenceableCollection methodsFor: '*container-core-iterators' stamp: 'lr 1/13/2012 11:00'! iterator "Answer a default iterator over the elements in this collection." ^ self forwardIterator! !