SystemOrganization addCategory: #'Container-Core-Abstract'! SystemOrganization addCategory: #'Container-Core-Exceptions'! SystemOrganization addCategory: #'Container-Core-Orders'! 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-Private'! !Symbol methodsFor: '*container-core-order' stamp: 'lr 1/22/2012 11:52'! asOrder ^ self asOrder: CTNaturalOrder new! ! !Symbol methodsFor: '*container-core-order' stamp: 'lr 1/22/2012 10:17'! asOrder: anOrder ^ anOrder 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'! !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! ! Object subclass: #CTAvlBalancedTree instanceVariableNames: 'root order' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTAvlBalancedTree methodsFor: 'modifying' stamp: 'lr 1/15/2012 14:53'! add: aNode root := self add: aNode to: root! ! !CTAvlBalancedTree methodsFor: 'modifying' stamp: 'lr 1/22/2012 09:03'! add: newNode to: aNode aNode isNil ifTrue: [ ^ newNode height: 0 ]. (order less: newNode key than: aNode key) ifTrue: [ aNode left: (self add: newNode to: aNode left) ] ifFalse: [ aNode right: (self add: newNode to: aNode right) ]. ^ self balance: aNode! ! !CTAvlBalancedTree methodsFor: 'accessing' stamp: 'lr 1/22/2012 09:02'! at: aKey | node | node := root. [ node isNil or: [ order equals: aKey to: node key ] ] whileFalse: [ node := (order less: aKey than: node key) ifTrue: [ node left ] ifFalse: [ node right ] ]. ^ node! ! !CTAvlBalancedTree methodsFor: 'iterators' stamp: 'lr 1/15/2012 15:19'! backwardIterator ^ root isNil ifTrue: [ CTEmptyIterator new ] ifFalse: [ CTBackwardBalancedTreeIterator on: root ]! ! !CTAvlBalancedTree methodsFor: 'balancing' stamp: 'lr 1/15/2012 15:31'! balance: aNode | delta height | delta := self deltaOf: aNode. delta < -1 ifTrue: [ (self deltaOf: aNode right) > 0 ifTrue: [ aNode right: (self rotateRight: aNode right) ]. ^ self rotateLeft: aNode ]. delta > 1 ifTrue: [ (self deltaOf: aNode left) < 0 ifTrue: [ aNode left: (self rotateLeft: aNode left) ]. ^ self rotateRight: aNode ]. height := 0. (aNode left notNil and: [ aNode left height > height ]) ifTrue: [ height := aNode left height ]. (aNode right notNil and: [ aNode right height > height ]) ifTrue: [ height := aNode right height ]. aNode height: height + 1. ^ aNode! ! !CTAvlBalancedTree methodsFor: 'balancing' stamp: 'lr 1/15/2012 14:42'! deltaOf: aNode ^ (aNode left ifNil: [ 0 ] ifNotNil: [ :node | node height ]) - (aNode right ifNil: [ 0 ] ifNotNil: [ :node | node height ])! ! !CTAvlBalancedTree methodsFor: 'accessing' stamp: 'lr 1/15/2012 15:16'! first "Answer the first node in the tree." | node | root isNil ifTrue: [ ^ nil ]. node := root. [ node left isNil ] whileFalse: [ node := node left ]. ^ node! ! !CTAvlBalancedTree methodsFor: 'iterators' stamp: 'lr 1/15/2012 15:18'! forwardIterator ^ root isNil ifTrue: [ CTEmptyIterator new ] ifFalse: [ CTForwardBalancedTreeIterator on: root ]! ! !CTAvlBalancedTree methodsFor: 'accessing' stamp: 'lr 1/15/2012 15:17'! last "Answer the last node in the tree." | node | root isNil ifTrue: [ ^ nil ]. node := root. [ node right isNil ] whileFalse: [ node := node right ]. ^ node! ! !CTAvlBalancedTree methodsFor: 'balancing' stamp: 'lr 1/21/2012 21:35'! move: aLeftNode right: aRightNode aLeftNode isNil ifTrue: [ ^ aRightNode ]. aLeftNode right: (self move: aLeftNode right right: aRightNode). ^ self balance: aLeftNode! ! !CTAvlBalancedTree methodsFor: 'modifying' stamp: 'lr 1/15/2012 14:54'! remove: aNode root := self remove: aNode from: root! ! !CTAvlBalancedTree methodsFor: 'modifying' stamp: 'lr 1/22/2012 09:03'! remove: oldNode from: aNode aNode isNil ifTrue: [ ^ nil ]. aNode == oldNode ifTrue: [ | temp | temp := self move: aNode left right: aNode right. aNode left: nil; right: nil. ^ temp ]. (order less: oldNode key than: aNode key) ifTrue: [ aNode left: (self remove: oldNode from: aNode left) ] ifFalse: [ aNode right: (self remove: oldNode from: aNode right) ]. ^ self balance: aNode! ! !CTAvlBalancedTree methodsFor: 'modifying' stamp: 'lr 1/15/2012 15:01'! removeAll root := nil! ! !CTAvlBalancedTree methodsFor: 'balancing' stamp: 'lr 1/15/2012 14:41'! rotateLeft: aNode | temp | temp := aNode right. aNode right: temp left. temp left: (self balance: aNode). ^ self balance: temp! ! !CTAvlBalancedTree methodsFor: 'balancing' stamp: 'lr 1/15/2012 14:42'! rotateRight: aNode | temp | temp := aNode left. aNode left: temp right. temp right: (self balance: aNode). ^ self balance: temp! ! 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: 'instance-creation' stamp: 'lr 1/13/2012 23:48'! new ^ self new: 10! ! !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: '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 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: 'initialization' stamp: 'lr 1/12/2012 20:47'! 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: #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: '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/22/2012 16:17'! sort "Sorts the receiver collection by default order." self sort: CTNaturalOrder 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 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: '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 order' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Misc'! !CTPriorityQueue class methodsFor: 'instance creation' stamp: 'lr 1/20/2012 22:53'! new ^ self new: 10! ! !CTPriorityQueue class methodsFor: 'instance creation' stamp: 'lr 1/22/2012 11:52'! new: anInteger ^ self new: anInteger order: CTNaturalOrder new! ! !CTPriorityQueue class methodsFor: 'instance creation' stamp: 'lr 1/20/2012 22:54'! new: anInteger order: anOrder ^ self basicNew initialize: anInteger order: anOrder! ! !CTPriorityQueue class methodsFor: 'instance creation' stamp: 'lr 1/20/2012 22:54'! order: anOrder ^ self new: 10 order: anOrder! ! !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/20/2012 22:52'! initialize: anInteger order: anOrder array := Array new: anInteger. size := 0. order := anOrder! ! !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: 'removing' stamp: 'lr 1/21/2012 09:19'! remove: anObject ifAbsent: aBlock 1 to: size do: [ :index | (order 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/21/2012 14:37'! sink: anInteger | parentIndex parentValue childIndex childValue | parentIndex := anInteger. parentValue := array at: parentIndex. [ (childIndex := parentIndex + parentIndex) <= size ] whileTrue: [ (childIndex < size and: [ order less: (array at: childIndex + 1) than: (array at: childIndex) ]) ifTrue: [ childIndex := childIndex + 1]. (order 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/20/2012 22:50'! swim: anInteger | currentValue currentIndex parentValue parentIndex | currentValue := array at: (currentIndex := anInteger). [ currentIndex > 1 and: [ order 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/13/2012 22:42'! initialize: anInteger table := self tableClass new: anInteger! ! !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/13/2012 22:43'! initialize: anInteger super initialize: anInteger. 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/13/2012 23:53'! postCopy root := root copy. table := self tableClass new: self size. 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 methodsFor: 'testing' stamp: 'lr 1/14/2012 09:55'! includes: anObject "Tests if anObject is contained in the receiver." self subclassResponsibility! ! !CTSet methodsFor: 'testing' stamp: 'lr 1/14/2012 09:56'! includesAll: aCollection "Tests all objects of aCollection are included in the receiver." ^ aCollection iterator allSatisfy: [ :each | self includes: each ]! ! 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/15/2012 14:45'! initialize: anInteger super initialize: anInteger. tree := self treeClass new. size := 0! ! !CTTreeSet methodsFor: 'iterators' stamp: 'lr 1/15/2012 15:19'! 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/15/2012 14:45'! nodeClass ^ CTTreeSetNode! ! !CTTreeSet methodsFor: 'removing' stamp: 'lr 1/15/2012 15:02'! remove: anObject ifAbsent: aBlock ^ (tree at: anObject) ifNil: [ aBlock value ] ifNotNil: [ :node | tree remove: node. node key ]! ! !CTTreeSet methodsFor: 'removing' stamp: 'lr 1/15/2012 15:01'! removeAll tree removeAll. size := 0! ! !CTTreeSet methodsFor: 'accessing' stamp: 'lr 1/15/2012 15:28'! size ^ tree size! ! !CTTreeSet methodsFor: 'private' stamp: 'lr 1/21/2012 21:31'! treeClass ^ CTAvlBalancedTree! ! 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' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTHashTable class methodsFor: 'instance creation' stamp: 'lr 1/14/2012 13:42'! new ^ self new: 10! ! !CTHashTable class methodsFor: 'instance creation' stamp: 'lr 1/12/2012 19:49'! new: anInteger ^ self basicNew initialize: anInteger! ! !CTHashTable methodsFor: 'adding' stamp: 'lr 1/13/2012 23:47'! add: aNode | index | index := self indexFor: (self hashFor: 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/14/2012 11:36'! at: aKey | node | node := array at: (self indexFor: (self hashFor: aKey)). [ node isNil or: [ self compare: node key with: aKey ] ] 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: 'configuration' stamp: 'lr 1/12/2012 19:55'! compare: aKey with: anotherKey ^ aKey = anotherKey! ! !CTHashTable methodsFor: 'private' stamp: 'lr 1/13/2012 23:49'! 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: (self hashFor: (node key)). node next: (array at: index). array at: index put: node. node := nextNode ] ]! ! !CTHashTable methodsFor: 'configuration' stamp: 'lr 1/12/2012 19:55'! hashFor: aKey ^ aKey hash! ! !CTHashTable methodsFor: 'private' stamp: 'lr 1/13/2012 23:17'! indexFor: anInteger ^ (anInteger \\ array size) + 1! ! !CTHashTable methodsFor: 'initialization' stamp: 'lr 1/13/2012 23:17'! initialize: anInteger | capacity | capacity := self capacityFor: (anInteger / self loadFactor) truncated. threshold := (self loadFactor * capacity) truncated. array := Array new: capacity. size := 0! ! !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: '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/13/2012 23:17'! removeKey: aKey | index node previous | node := array at: (index := self indexFor: (self hashFor: aKey)). [ node isNil ] whileFalse: [ (self compare: aKey with: 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: #CTBalancedTreeIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! CTBalancedTreeIterator subclass: #CTBackwardBalancedTreeIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! CTBalancedTreeIterator subclass: #CTForwardBalancedTreeIterator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! CTIterator subclass: #CTDelegateIterator instanceVariableNames: 'iterator' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! 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 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 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 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 class instanceVariableNames: 'default'! !CTEmptyIterator class methodsFor: 'initialization' stamp: 'lr 1/10/2012 23:38'! initialize default := self basicNew initialize! ! !CTEmptyIterator class methodsFor: 'instance creation' stamp: 'lr 1/10/2012 23:39'! new "For efficience reasons and because the empty iterator has no state, always return the same instance." ^ default! ! !CTEmptyIterator methodsFor: 'testing' stamp: 'lr 8/3/2011 19:01'! hasNext ^ false! ! !CTEmptyIterator methodsFor: 'accessing' stamp: 'lr 8/3/2011 19:14'! next ^ self noSuchElementError! ! CTIterator subclass: #CTHashTableIterator instanceVariableNames: 'array index node' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTHashTableIterator class methodsFor: 'instance creation' stamp: 'lr 1/12/2012 19:30'! on: anArray ^ self basicNew initializeOn: anArray! ! !CTHashTableIterator methodsFor: 'testing' stamp: 'lr 1/12/2012 19:33'! hasNext ^ node notNil! ! !CTHashTableIterator methodsFor: 'initialization' stamp: 'lr 1/12/2012 19:59'! initializeOn: anArray array := anArray. index := anArray size. node := anArray at: index. [ node isNil and: [ index > 1 ] ] whileTrue: [ node := array at: (index := index - 1) ]! ! !CTHashTableIterator methodsFor: 'accessing' stamp: 'lr 1/12/2012 20:02'! next | result | result := node. node := 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: 'lr 12/31/2011 14:30' prior: 0! Abstract iterator class for arrays and other collections supporting indexed access. Instance Variables: array start stop position ! 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: '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: '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/15/2012 17:07'! conform: aBlock "Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise." [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifFalse: [ ^ false ] ]. ^ true! ! !CTIterator methodsFor: 'enumerating' stamp: 'lr 1/15/2012 17:07'! contains: aBlock "Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise." [ self hasNext ] whileTrue: [ (self apply: aBlock with: self next) ifTrue: [ ^ true ] ]. ^ false! ! !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/1/2012 17:32'! iterator "Answer a default iterator of the receiver." ^ self! ! !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: #CTPluggableIterator instanceVariableNames: 'hasNextBlock nextBlock' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTPluggableIterator class methodsFor: 'instance creation' stamp: 'lr 12/31/2011 12:54'! hasNext: aHasNextBlock next: aNextBlock ^ self basicNew initializeHasNext: aHasNextBlock next: aNextBlock! ! !CTPluggableIterator methodsFor: 'testing' stamp: 'lr 12/31/2011 12:55'! hasNext ^ hasNextBlock value! ! !CTPluggableIterator methodsFor: 'initialization' stamp: 'lr 12/31/2011 12:55'! initializeHasNext: aHasNextBlock next: aNextBlock hasNextBlock := aHasNextBlock. nextBlock := aNextBlock! ! !CTPluggableIterator methodsFor: 'accessing' stamp: 'lr 12/31/2011 12:55'! next ^ nextBlock value! ! CTIterator subclass: #CTRangeIterator instanceVariableNames: 'start stop step index size' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Iterators'! !CTRangeIterator class methodsFor: 'instance creation' stamp: 'lr 12/28/2011 21:07'! from: aStartValue to: aStopValue ^ self from: aStartValue to: aStopValue step: 1! ! !CTRangeIterator class methodsFor: 'instance creation' stamp: 'lr 12/28/2011 21:08'! from: aStartValue to: aStopValue step: aStepValue ^ self basicNew initializeFrom: aStartValue to: aStopValue step: aStepValue! ! !CTRangeIterator methodsFor: 'testing' stamp: 'lr 1/14/2012 13:51'! hasNext ^ index < size! ! !CTRangeIterator methodsFor: 'initialization' stamp: 'lr 1/14/2012 13:50'! initializeFrom: aStartValue to: aStopValue step: aStepValue self initialize. start := aStartValue. stop := aStopValue. step := aStepValue. size := step < 0 ifTrue: [ start < stop ifTrue: [ 0 ] ifFalse: [ (stop - start) // step + 1 ] ] ifFalse: [ stop < start ifTrue: [ 0 ] ifFalse: [ (stop - start) // step + 1 ] ]. index := 0! ! !CTRangeIterator methodsFor: 'accessing' stamp: 'lr 1/14/2012 13:51'! next ^ index < size ifTrue: [ start + ((index := index + 1) * step) ] ifFalse: [ self noSuchElementError ]! ! 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/14/2012 10:11'! initialize: anInteger super initialize: anInteger. table := self tableClass new: anInteger! ! !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: 'initialization' 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: 'private' stamp: 'lr 1/14/2012 12:01'! backwardNodeIterator ^ root backwardIterator! ! !CTLinkedHashMap methodsFor: 'private' stamp: 'lr 1/14/2012 12:01'! forwardNodeIterator ^ root forwardIterator! ! !CTLinkedHashMap methodsFor: 'initialization' stamp: 'lr 1/14/2012 10:15'! initialize: anInteger super initialize: anInteger. 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/14/2012 10:16'! postCopy root := root copy. table := self tableClass new: self size. 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: '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/14/2012 11:21'! new ^ self new: 10! ! !CTMap class methodsFor: 'instance-creation' stamp: 'lr 1/14/2012 11:21'! new: anInteger ^ self basicNew initialize: anInteger! ! !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/15/2012 17:22'! initialize: anInteger 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'! Object subclass: #CTOrder instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! !CTOrder commentStamp: '' prior: 0! Abstract strategy to encapulsate the behavior to define order and equality among objects.! CTOrder subclass: #CTCombinedOrder instanceVariableNames: 'orders' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! !CTCombinedOrder commentStamp: '' prior: 0! Cobines one or more orders together, that is if an element is equal according to the first orther consider the next order, etc.! !CTCombinedOrder class methodsFor: 'instance creation' stamp: 'lr 1/22/2012 09:25'! on: anArray ^ self basicNew initializeOn: anArray! ! !CTCombinedOrder methodsFor: 'operators' stamp: 'lr 1/22/2012 09:24'! , anOrder ^ CTCombinedOrder on: (orders copyWith: anOrder)! ! !CTCombinedOrder methodsFor: 'comparing' stamp: 'lr 1/22/2012 16:05'! equals: leftObject to: rightObject 1 to: orders size do: [ :index | ((orders at: index) equals: leftObject to: rightObject) ifFalse: [ ^ false ] ]. ^ true! ! !CTCombinedOrder methodsFor: 'initialization' stamp: 'lr 1/22/2012 16:06'! initializeOn: aCollection orders := aCollection asArray! ! !CTCombinedOrder methodsFor: 'comparing' stamp: 'lr 1/22/2012 16:04'! less: leftObject than: rightObject | order | 1 to: orders size do: [ :index | ((order := orders at: index) equals: leftObject to: rightObject) ifFalse: [ ^ order less: leftObject than: rightObject ] ]. ^ false! ! !CTCombinedOrder methodsFor: 'printing' stamp: 'lr 1/22/2012 09:44'! printOn: aStream aStream nextPut: $(. orders do: [ :each | aStream print: each ] separatedBy: [ aStream nextPutAll: ' , ' ]. aStream nextPut: $)! ! CTOrder subclass: #CTDelegateOrder instanceVariableNames: 'order' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! !CTDelegateOrder commentStamp: '' prior: 0! Abstract wrapper around another order strategy.! !CTDelegateOrder class methodsFor: 'instance creation' stamp: 'lr 1/21/2012 10:49'! on: anOrder ^ self basicNew initializeOn: anOrder! ! !CTDelegateOrder methodsFor: 'comparing' stamp: 'lr 1/21/2012 10:48'! equals: leftObject to: rightObject ^ order equals: leftObject to: rightObject! ! !CTDelegateOrder methodsFor: 'initialization' stamp: 'lr 1/21/2012 10:49'! initializeOn: anOrder order := anOrder! ! !CTDelegateOrder methodsFor: 'comparing' stamp: 'lr 1/21/2012 10:48'! less: leftObject than: rightObject ^ order less: leftObject than: rightObject! ! !CTDelegateOrder methodsFor: 'printing' stamp: 'lr 1/22/2012 10:20'! printOn: aStream aStream print: order! ! CTDelegateOrder subclass: #CTMutatingOrder instanceVariableNames: 'selector' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! !CTMutatingOrder commentStamp: '' prior: 0! Mutates the elements compared with the wrapped order with the given selector.! !CTMutatingOrder class methodsFor: 'instance creation' stamp: 'lr 1/22/2012 10:18'! on: anOrder selector: aSymbol ^ (self on: anOrder) setSelector: aSymbol! ! !CTMutatingOrder methodsFor: 'comparing' stamp: 'lr 1/22/2012 11:24'! equals: leftObject to: rightObject ^ order equals: (leftObject perform: selector) to: (rightObject perform: selector)! ! !CTMutatingOrder methodsFor: 'comparing' stamp: 'lr 1/22/2012 11:24'! less: leftObject than: rightObject ^ order less: (leftObject perform: selector) than: (rightObject perform: selector)! ! !CTMutatingOrder methodsFor: 'printing' stamp: 'lr 1/22/2012 10:20'! printOn: aStream aStream nextPut: $(. super printOn: aStream. aStream nextPutAll: ' transform: '; print: selector; nextPut: $)! ! !CTMutatingOrder methodsFor: 'initialization' stamp: 'lr 1/22/2012 10:18'! setSelector: aSelector selector := aSelector! ! CTDelegateOrder subclass: #CTReverseOrder instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! !CTReverseOrder commentStamp: '' prior: 0! Reverses the order of the wrapped order.! !CTReverseOrder methodsFor: 'comparing' stamp: 'lr 1/21/2012 10:48'! equals: leftObject to: rightObject ^ order equals: rightObject to: leftObject! ! !CTReverseOrder methodsFor: 'comparing' stamp: 'lr 1/21/2012 10:48'! less: leftObject than: rightObject ^ order less: rightObject than: leftObject! ! !CTReverseOrder methodsFor: 'utilities' stamp: 'lr 1/21/2012 10:48'! maximum: anIterable ^ order minimum: anIterable! ! !CTReverseOrder methodsFor: 'utilities' stamp: 'lr 1/21/2012 10:48'! minimum: anIterable ^ order maximum: anIterable! ! !CTReverseOrder methodsFor: 'prrinting' stamp: 'lr 1/22/2012 09:22'! printOn: aStream aStream print: order; nextPutAll: ' reverse'! ! !CTReverseOrder methodsFor: 'accessing' stamp: 'lr 1/21/2012 10:48'! reverse ^ order! ! CTOrder subclass: #CTNaturalOrder instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! CTNaturalOrder class instanceVariableNames: 'instance'! !CTNaturalOrder commentStamp: '' prior: 0! The natural order of Smalltalk objects, using #< and #= of the involved objects.! CTNaturalOrder class instanceVariableNames: 'instance'! CTNaturalOrder subclass: #CTIdentityOrder instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Orders'! !CTIdentityOrder commentStamp: '' prior: 0! The natural order of Smalltalk objects, using #< and #== (identity-equals) of the involved objects.! !CTIdentityOrder methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:57'! equals: leftObject to: rightObject ^ leftObject == rightObject! ! !CTNaturalOrder class methodsFor: 'instance creation' stamp: 'lr 1/22/2012 09:21'! new ^ instance ifNil: [ instance := self basicNew ]! ! !CTNaturalOrder methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:58'! equals: leftObject to: rightObject ^ leftObject = rightObject! ! !CTNaturalOrder methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:57'! less: leftObject than: rightObject ^ leftObject < rightObject! ! !CTNaturalOrder methodsFor: 'prrinting' stamp: 'lr 1/22/2012 09:22'! printOn: aStream aStream print: self class; nextPutAll: ' new'! ! !CTOrder methodsFor: 'operators' stamp: 'lr 1/22/2012 09:24'! , anOrder "Combine the receving order with the argument." ^ CTCombinedOrder on: (Array with: self with: anOrder)! ! !CTOrder methodsFor: 'comparing' stamp: 'lr 1/20/2012 17:57'! equals: leftObject to: rightObject "Retruns true if the left-object and the right-object are equal." self subclassResponsibility! ! !CTOrder 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! ! !CTOrder methodsFor: 'testing' stamp: 'lr 1/21/2012 10:53'! isStrict: anIterable "Answer true if the argument is striclty 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! ! !CTOrder 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! ! !CTOrder 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! ! !CTOrder 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! ! !CTOrder methodsFor: 'private-sorting' stamp: 'lr 1/22/2012 19:10'! partition: 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! ! !CTOrder methodsFor: 'operators' stamp: 'lr 1/22/2012 13:24'! reverse "Reverses the receving order." ^ CTReverseOrder on: self! ! !CTOrder methodsFor: 'sorting' stamp: 'lr 1/22/2012 17:57'! sort: anArray "Sorts anArray in-place using the receving ordering." self sort: anArray from: 1 to: anArray size! ! !CTOrder methodsFor: 'sorting' stamp: 'lr 1/23/2012 20:18'! sort: anArray from: startIndex to: stopIndex "Sorts anArray in-place using the receving ordering from startIndex to stopIndex." | pivot index | startIndex < stopIndex ifFalse: [ ^ self ]. startIndex + 1 = stopIndex ifTrue: [ (self less: (anArray at: stopIndex) than: (anArray at: startIndex)) ifTrue: [ anArray swap: startIndex with: stopIndex ]. ^ self ]. pivot := anArray at: (index := stopIndex + startIndex // 2). anArray at: index put: (anArray at: startIndex). anArray at: startIndex put: pivot. index := self partition: anArray from: startIndex to: stopIndex. self sort: anArray from: startIndex to: index - 1. self sort: anArray from: index + 1 to: stopIndex! ! !CTOrder methodsFor: 'operators' stamp: 'lr 1/22/2012 13:27'! transform: aSymbol "Transform the object to by performing aSymbol on the object." ^ CTMutatingOrder on: self selector: aSymbol! ! Object subclass: #CTRedBlackBalancedTree instanceVariableNames: 'root' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTRedBlackBalancedTree methodsFor: 'modifying' stamp: 'lr 1/19/2012 19:35'! add: aNode ifPresent: aBlock root := self add: aNode to: root ifPresent: aBlock. root black: true! ! !CTRedBlackBalancedTree methodsFor: 'modifying' stamp: 'lr 1/19/2012 19:40'! add: newNode to: treeNode ifPresent: aBlock newNode isNil ifTrue: [ ^ newNode black: false ]. newNode key = treeNode key ifTrue: [ ^ aBlock value: treeNode ]. newNode key < treeNode key ifTrue: [ treeNode left: (self add: newNode to: treeNode left ifPresent: aBlock) ] ifFalse: [ treeNode right: (self add: newNode to: treeNode right ifPresent: aBlock) ]. ^ self balance: treeNode! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:43'! balance: aNode | node | node := aNode. ((self isBlack: node right) or: [ (self isBlack: node left) not ]) ifFalse: [ node := self rotateLeft: node ]. ((self isBlack: node left) or: [ self isBlack: node left left ]) ifFalse: [ node := self rotateRight: node ]. ((self isBlack: node left) or: [ self isBlack: node right ]) ifFalse: [ self flipColors: node ]. ^ node! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:14'! flipColors: aNode aNode black: aNode black not. aNode left black: aNode left black not. aNode right black: aNode right black not! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:19'! isBlack: aNode ^ aNode isNil or: [ aNode black ]! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:22'! moveLeft: aNode self flipColors: aNode. (self isBlack: aNode right left) ifTrue: [ ^ aNode ]. aNode right: (self rotateRight: aNode right). ^ self rotateLeft: aNode! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:22'! moveRight: aNode self flipColors: aNode. (self isBlack: aNode left left) ifTrue: [ aNode ]. ^ self rotateRight: aNode right ! ! !CTRedBlackBalancedTree methodsFor: 'modifying' stamp: 'lr 1/19/2012 20:14'! removeKey: aKey from: aNode ifAbsent: aBlock | node | aNode isNil ifTrue: [ ^ aBlock value ]. node := aNode. aKey < aNode key ifTrue: [ ((self isBlack: aNode left) and: [ self isBlack: aNode left left ]) ifTrue: [ ] ]! ! !CTRedBlackBalancedTree methodsFor: 'modifying' stamp: 'lr 1/19/2012 19:46'! removeKey: aKey ifAbsent: aBlock ((self isBlack: root left) and: [ self isBlack: root right ]) ifTrue: [ root black: false ]. root := self removeKey: aKey from: root ifAbsent: aBlock. root isNil ifFalse: [ root black: true ]! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:14'! rotateLeft: aNode | node | node := aNode right. aNode right: node left. node left: aNode. node black: node left black. node left black: false. ^ node! ! !CTRedBlackBalancedTree methodsFor: 'rotating' stamp: 'lr 1/19/2012 19:15'! rotateRight: aNode | node | node := aNode left. aNode left: node right. node right: aNode. node black: node right black. node right black: false. ^ node! ! Object subclass: #CTSplayTree instanceVariableNames: 'root order' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTSplayTree class methodsFor: 'instance creation' stamp: 'lr 1/22/2012 11:52'! new ^ self order: CTNaturalOrder new! ! !CTSplayTree class methodsFor: 'instance creation' stamp: 'lr 1/22/2012 09:09'! order: anOrder ^ self basicNew initializeOrder: anOrder! ! !CTSplayTree methodsFor: 'modifying' stamp: 'lr 1/22/2012 00:02'! add: aNode ifPresent: aBlock root isNil ifTrue: [ aNode left: nil; right: nil ] ifFalse: [ root := self splay: aNode key. (order equals: aNode key to: root key) ifTrue: [ ^ aBlock value: root ]. (order 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 ] ]. root := aNode! ! !CTSplayTree methodsFor: 'accessing' stamp: 'lr 1/22/2012 00:03'! at: aKey root isNil ifTrue: [ ^ nil ]. root := self splay: aKey. (order equals: aKey to: root key) ifTrue: [ ^ root ]. ^ nil! ! !CTSplayTree methodsFor: 'initialization' stamp: 'lr 1/22/2012 09:08'! initializeOrder: anOrder order := anOrder! ! !CTSplayTree methodsFor: 'modifying' stamp: 'lr 1/22/2012 09:04'! removeAll root := nil! ! !CTSplayTree methodsFor: 'modifying' stamp: 'lr 1/22/2012 09:10'! removeKey: aKey | node | root isNil ifTrue: [ ^ nil ]. root := node := self splay: aKey. (order equals: aKey to: root key) ifFalse: [ ^ nil ]. root left isNil ifTrue: [ root := node right ] ifFalse: [ root := self splay: node left key. root right: node right ]. ^ node left: nil; right: nil! ! !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: 'private' stamp: 'lr 1/21/2012 23:58'! splay: aKey | current left right header | current := root. left := right := header := CTSplayTreeNode new. [ current isNil or: [ order equals: aKey to: current key ] ] whileFalse: [ (order less: aKey than: current key) ifTrue: [ (current left notNil and: [ order 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: [ order 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/22/2012 00:03'! splay: aNode left: leftNode right: rightNode header: headerNode leftNode right: aNode left. rightNode left: aNode right. ^ aNode left: headerNode right; right: headerNode left! ! Object subclass: #CTSplayTreeNode instanceVariableNames: 'key left right' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Private'! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/21/2012 22:58'! key ^ key! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/21/2012 22:58'! key: anObject key := anObject! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/21/2012 22:58'! left ^ left! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/21/2012 22:58'! left: anObject left := anObject! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/21/2012 22:58'! right ^ right! ! !CTSplayTreeNode methodsFor: 'accessing' stamp: 'lr 1/21/2012 22:58'! right: anObject right := anObject! ! Object subclass: #CTTreeSetNode instanceVariableNames: 'key left right height' classVariableNames: '' poolDictionaries: '' category: 'Container-Core-Sets'! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! height ^ height! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! height: anInteger height := anInteger! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! key ^ key! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! key: anObject key := anObject! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! left ^ left! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! left: aNode left := aNode! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! right ^ right! ! !CTTreeSetNode methodsFor: 'accessing' stamp: 'lr 1/15/2012 14:44'! right: aNode right := aNode! ! CTEmptyIterator initialize!