[squeak-dev] The Trunk: Collections-topa.726.mcz

Chris Muller asqueaker at gmail.com
Tue Dec 6 18:11:08 UTC 2016


More specifically, will existing instances work or is there some
conversion needed?

On Tue, Dec 6, 2016 at 12:10 PM, Chris Muller <asqueaker at gmail.com> wrote:
> Is this backward compatible?
>
> On Tue, Dec 6, 2016 at 7:31 AM,  <commits at source.squeak.org> wrote:
>> Tobias Pape uploaded a new version of Collections to project The Trunk:
>> http://source.squeak.org/trunk/Collections-topa.726.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Collections-topa.726
>> Author: topa
>> Time: 6 December 2016, 2:31:08.021296 pm
>> UUID: 8409fe6a-d5ea-4d4e-ac78-243182dd1fd7
>> Ancestors: Collections-topa.725
>>
>> Adopt improved (ie, actually working) Linked List from our relatives.
>>
>> =============== Diff against Collections-topa.725 ===============
>>
>> Item was added:
>> + ----- Method: Link>>asLink (in category 'converting') -----
>> + asLink
>> +
>> +       ^ self!
>>
>> Item was changed:
>>   ----- Method: Link>>nextLink (in category 'accessing') -----
>>   nextLink
>> -       "Answer the link to which the receiver points."
>>
>> +       ^ nextLink!
>> -       ^nextLink!
>>
>> Item was changed:
>>   ----- Method: Link>>nextLink: (in category 'accessing') -----
>>   nextLink: aLink
>>         "Store the argument, aLink, as the link to which the receiver refers.
>>         Answer aLink."
>>
>> +       ^ nextLink := aLink!
>> -       ^nextLink := aLink!
>>
>> Item was changed:
>>   SequenceableCollection subclass: #LinkedList
>>         instanceVariableNames: 'firstLink lastLink'
>>         classVariableNames: ''
>>         poolDictionaries: ''
>>         category: 'Collections-Sequenceable'!
>>
>> + !LinkedList commentStamp: 'topa 12/6/2016 14:17' prior: 0!
>> + I represent a collection of links, which are containers for other objects. Using the message sequence addFirst:/removeLast causes the receiver to behave as a stack; using addLast:/removeFirst causes the receiver to behave as a queue.
>> +
>> + If you attempt to add any object into a LinkedList that is not a Link, it will automatically be wrapped by a ValueLink. A LinkedList therefore behaves very much like any collection, except that certain calls such as atIndex: are linear rather than constant time.!
>> - !LinkedList commentStamp: '<historical>' prior: 0!
>> - I represent a collection of links, which are containers for other objects. Using the message sequence addFirst:/removeLast causes the receiver to behave as a stack; using addLast:/removeFirst causes the receiver to behave as a queue.!
>>
>> Item was added:
>> + ----- Method: LinkedList class>>new: (in category 'instance creation') -----
>> + new: anInt
>> +       "LinkedList don't need capacity"
>> +       ^self new!
>>
>> Item was added:
>> + ----- Method: LinkedList class>>new:streamContents: (in category 'stream creation') -----
>> + new: size streamContents: aBlock
>> +       ^ self withAll: (super new: size streamContents: aBlock)!
>>
>> Item was added:
>> + ----- Method: LinkedList class>>newFrom: (in category 'instance creation') -----
>> + newFrom: aCollection
>> +       "Answer an instance with same elements as aCollection."
>> +       ^self new
>> +               addAll: aCollection;
>> +               yourself!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>add: (in category 'adding') -----
>> + add: aLinkOrObject
>> - add: aLink
>>         "Add aLink to the end of the receiver's list. Answer aLink."
>>
>> +       ^self addLast: aLinkOrObject!
>> -       ^self addLast: aLink!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>add:after: (in category 'adding') -----
>> + add: link after: otherLinkOrObject
>> - add: link after: otherLink
>> -
>>         "Add otherLink  after link in the list. Answer aLink."
>>
>> +       | otherLink |
>> +       otherLink := self linkAt: (self indexOf: otherLinkOrObject).
>> +       ^ self add: link afterLink: otherLink!
>> -       | savedLink |
>> -       lastLink == otherLink ifTrue: [^ self addLast: link].
>> -       savedLink := otherLink nextLink.
>> -       otherLink nextLink: link.
>> -       link nextLink:  savedLink.
>> -       ^link.!
>>
>> Item was added:
>> + ----- Method: LinkedList>>add:afterLink: (in category 'adding') -----
>> + add: aLinkOrObject afterLink: otherLink
>> +
>> +       "Add otherLink  after link in the list. Answer aLink."
>> +
>> +       | savedLink aLink |
>> +       lastLink == otherLink ifTrue: [^ self addLast: aLinkOrObject].
>> +       savedLink := otherLink nextLink.
>> +       aLink := aLinkOrObject asLink.
>> +       otherLink nextLink: aLink.
>> +       aLink nextLink:  savedLink.
>> +       ^aLink.!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>add:before: (in category 'adding') -----
>> + add: link before: otherLinkOrObject
>> +       "Add otherLink  after link in the list. Answer aLink."
>> - add: link before: otherLink
>>
>> +       | otherLink |
>> +       otherLink := self linkAt: (self indexOf: otherLinkOrObject).
>> +       ^ self add: link beforeLink: otherLink!
>> -       | aLink |
>> -       firstLink == otherLink ifTrue: [^ self addFirst: link].
>> -       aLink := firstLink.
>> -       [aLink == nil] whileFalse: [
>> -               aLink nextLink == otherLink ifTrue: [
>> -                       link nextLink: aLink nextLink.
>> -                       aLink nextLink: link.
>> -                       ^ link
>> -               ].
>> -                aLink := aLink nextLink.
>> -       ].
>> -       ^ self errorNotFound: otherLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>add:beforeLink: (in category 'adding') -----
>> + add: aLinkOrObject beforeLink: otherLink
>> +
>> +       | currentLink|
>> +
>> +       firstLink == otherLink ifTrue: [^ self addFirst: aLinkOrObject].
>> +
>> +       currentLink := firstLink.
>> +       [currentLink == nil] whileFalse: [
>> +               currentLink nextLink == otherLink ifTrue: [
>> +                       | aLink |
>> +                       aLink := aLinkOrObject asLink.
>> +                       aLink nextLink: currentLink nextLink.
>> +                       currentLink nextLink: aLink.
>> +                       ^ aLink
>> +               ].
>> +                currentLink := currentLink nextLink.
>> +       ].
>> +       ^ self errorNotFound: otherLink!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>addFirst: (in category 'adding') -----
>> + addFirst: aLinkOrObject
>> - addFirst: aLink
>>         "Add aLink to the beginning of the receiver's list. Answer aLink."
>> +       |aLink|
>> +       aLink := aLinkOrObject asLink.
>> -
>>         self isEmpty ifTrue: [lastLink := aLink].
>>         aLink nextLink: firstLink.
>>         firstLink := aLink.
>>         ^aLink!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>addLast: (in category 'adding') -----
>> + addLast: aLinkOrObject
>> - addLast: aLink
>>         "Add aLink to the end of the receiver's list. Answer aLink."
>> +       |aLink|
>> +       aLink := aLinkOrObject asLink.
>> -
>>         self isEmpty
>>                 ifTrue: [firstLink := aLink]
>>                 ifFalse: [lastLink nextLink: aLink].
>>         lastLink := aLink.
>>         ^aLink!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>at: (in category 'accessing') -----
>>   at: index
>>
>> +       ^(self linkAt: index) value!
>> -       | i |
>> -       i := 0.
>> -       self do: [:link |
>> -               (i := i + 1) = index ifTrue: [^ link]].
>> -       ^ self errorSubscriptBounds: index!
>>
>> Item was added:
>> + ----- Method: LinkedList>>at:put: (in category 'accessing') -----
>> + at: index put: anObject
>> +
>> +       ^self at: index putLink: (self linkOf: anObject ifAbsent: [anObject asLink])!
>>
>> Item was added:
>> + ----- Method: LinkedList>>at:putLink: (in category 'accessing') -----
>> + at: index putLink: aLink
>> +       | previousLink nextLink |
>> +       "Please don't put a link which is already in the list, or you will create an infinite loop"
>> +       (self validIndex: index) ifFalse: [^ self errorOutOfBounds].
>> +
>> +       index = 1 ifTrue: [
>> +               aLink nextLink: self firstLink nextLink.
>> +               firstLink := aLink.
>> +               aLink nextLink ifNil: [lastLink := aLink].
>> +               ^ aLink].
>> +
>> +       previousLink := self linkAt: index - 1.
>> +       nextLink := previousLink nextLink nextLink.
>> +
>> +       nextLink
>> +               ifNil: [aLink nextLink: self lastLink]
>> +               ifNotNil: [:link |aLink nextLink: link].
>> +
>> +       previousLink nextLink: aLink.
>> +
>> +       nextLink ifNil: [
>> +               lastLink := aLink.
>> +               aLink nextLink: nil].
>> +
>> +       ^ aLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>collect: (in category 'enumerating') -----
>> + collect: aBlock
>> +       "Evaluate aBlock with each of the receiver's elements as the argument.
>> +       Collect the resulting values into a collection like the receiver. Answer
>> +       the new collection."
>> +
>> +       | aLink newCollection |
>> +       newCollection := self class new.
>> +       aLink := firstLink.
>> +       [aLink == nil] whileFalse:
>> +               [newCollection add: (aBlock value: aLink value).
>> +                aLink := aLink nextLink].
>> +       ^ newCollection!
>>
>> Item was added:
>> + ----- Method: LinkedList>>collect:thenSelect: (in category 'enumerating') -----
>> + collect: collectBlock thenSelect: selectBlock
>> +       "Optimized version of SequenceableCollection>>#collect:#thenSelect:"
>> +
>> +       | newCollection newElement |
>> +       newCollection := self class new.
>> +       self
>> +               do: [ :each |
>> +                       newElement := collectBlock value: each.
>> +                       (selectBlock value: newElement)
>> +                               ifTrue: [ newCollection add: newElement ] ].
>> +       ^ newCollection!
>>
>> Item was added:
>> + ----- Method: LinkedList>>copyWith: (in category 'copying') -----
>> + copyWith: newElement
>> +       ^self copy add: newElement; yourself!
>>
>> Item was added:
>> + ----- Method: LinkedList>>copyWithout: (in category 'copying') -----
>> + copyWithout: oldElement
>> +       |newInst|
>> +       newInst := self class new.
>> +       self do: [:each | each = oldElement ifFalse: [newInst add: each]].
>> +       ^newInst!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>do: (in category 'enumerating') -----
>>   do: aBlock
>>
>>         | aLink |
>>         aLink := firstLink.
>>         [aLink == nil] whileFalse:
>> +               [aBlock value: aLink value.
>> -               [aBlock value: aLink.
>>                  aLink := aLink nextLink]!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>first (in category 'accessing') -----
>>   first
>>         "Answer the first link. Create an error notification if the receiver is
>>         empty."
>>
>> +       ^ self firstLink value!
>> -       self emptyCheck.
>> -       ^firstLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>firstLink (in category 'accessing') -----
>> + firstLink
>> +       "Answer the first link. Create an error notification if the receiver is
>> +       empty."
>> +
>> +       self emptyCheck.
>> +       ^firstLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>indexOf:startingAt:ifAbsent: (in category 'private') -----
>> + indexOf: anElement startingAt: start ifAbsent: exceptionBlock
>> +       "Answer the index of the first occurence of anElement after start
>> +       within the receiver. If the receiver does not contain anElement,
>> +       answer the      result of evaluating the argument, exceptionBlock."
>> +
>> +       |currentLink index|
>> +       currentLink := self linkAt: start ifAbsent: [nil].
>> +       index := start.
>> +       [currentLink isNil ]
>> +               whileFalse: [currentLink value = anElement value ifTrue: [^index].
>> +                                       currentLink := currentLink nextLink.
>> +                                       index := index +1].
>> +       ^exceptionBlock value!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>isEmpty (in category 'testing') -----
>>   isEmpty
>>
>> +       ^ firstLink isNil!
>> -       ^firstLink == nil!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>last (in category 'accessing') -----
>>   last
>>         "Answer the last link. Create an error notification if the receiver is
>>         empty."
>>
>> +
>> +       ^self lastLink value!
>> -       self emptyCheck.
>> -       ^lastLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>lastLink (in category 'accessing') -----
>> + lastLink
>> +       "Answer the last link. Create an error notification if the receiver is
>> +       empty."
>> +
>> +       self emptyCheck.
>> +       ^lastLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>linkAt: (in category 'private') -----
>> + linkAt: index
>> +
>> +       ^self linkAt: index ifAbsent: [ self errorSubscriptBounds: index]!
>>
>> Item was added:
>> + ----- Method: LinkedList>>linkAt:ifAbsent: (in category 'private') -----
>> + linkAt: index ifAbsent: errorBlock
>> +
>> +       | i |
>> +       i := 0.
>> +       self linksDo: [:link | (i := i + 1) = index ifTrue: [^ link]].
>> +       ^ errorBlock value!
>>
>> Item was added:
>> + ----- Method: LinkedList>>linkOf: (in category 'private') -----
>> + linkOf: anObject
>> +
>> +       ^ self
>> +               linkOf: anObject
>> +               ifAbsent: [self error: 'No such element']!
>>
>> Item was added:
>> + ----- Method: LinkedList>>linkOf:ifAbsent: (in category 'private') -----
>> + linkOf: anObject ifAbsent: errorBlock
>> +
>> +       self    linksDo: [:link | link value = anObject value ifTrue: [^ link]].
>> +       ^ errorBlock value!
>>
>> Item was added:
>> + ----- Method: LinkedList>>linksDo: (in category 'enumerating') -----
>> + linksDo: aBlock
>> +
>> +       | aLink |
>> +       aLink := firstLink.
>> +       [aLink == nil] whileFalse:
>> +               [aBlock value: aLink.
>> +                aLink := aLink nextLink]!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>postCopy (in category 'copying') -----
>>   postCopy
>>         | aLink |
>>         super postCopy.
>> +       firstLink ifNotNil: [
>> -       firstLink isNil ifFalse: [
>>                 aLink := firstLink := firstLink copy.
>>                 [aLink nextLink isNil] whileFalse: [aLink nextLink: (aLink := aLink nextLink copy)].
>>                 lastLink := aLink].!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>remove:ifAbsent: (in category 'removing') -----
>> + remove: aLinkOrObject ifAbsent: aBlock
>> +       "Remove aLink from the receiver. If it is not there, answer the result of evaluating aBlock."
>> +
>> +       | link |
>> +       link := self linkOf: aLinkOrObject ifAbsent: [^aBlock value].
>> +       self removeLink: link ifAbsent: [^aBlock value].
>> +       ^aLinkOrObject!
>> - remove: aLink ifAbsent: aBlock
>> -       "Remove aLink from the receiver. If it is not there, answer the result of
>> -       evaluating aBlock."
>> -
>> -       | tempLink |
>> -       aLink == firstLink
>> -               ifTrue: [firstLink := aLink nextLink.
>> -                               aLink == lastLink
>> -                                       ifTrue: [lastLink := nil]]
>> -               ifFalse: [tempLink := firstLink.
>> -                               [tempLink == nil ifTrue: [^aBlock value].
>> -                                tempLink nextLink == aLink]
>> -                                       whileFalse: [tempLink := tempLink nextLink].
>> -                               tempLink nextLink: aLink nextLink.
>> -                               aLink == lastLink
>> -                                       ifTrue: [lastLink := tempLink]].
>> -       aLink nextLink: nil.
>> -       ^aLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>removeAllSuchThat: (in category 'removing') -----
>> + removeAllSuchThat: aBlock
>> +       "Evaluate aBlock for each element and remove all that elements from
>> +       the receiver for that aBlock evaluates to true.  For LinkedLists, it's safe to use do:."
>> +
>> +       self do: [:each | (aBlock value: each) ifTrue: [self remove: each]]!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>removeFirst (in category 'removing') -----
>>   removeFirst
>>         "Remove the first element and answer it. If the receiver is empty, create
>>         an error notification."
>>
>>         | oldLink |
>>         self emptyCheck.
>>         oldLink := firstLink.
>>         firstLink == lastLink
>>                 ifTrue: [firstLink := nil. lastLink := nil]
>>                 ifFalse: [firstLink := oldLink nextLink].
>>         oldLink nextLink: nil.
>> +       ^oldLink value!
>> -       ^oldLink!
>>
>> Item was changed:
>>   ----- Method: LinkedList>>removeLast (in category 'removing') -----
>>   removeLast
>>         "Remove the receiver's last element and answer it. If the receiver is
>>         empty, create an error notification."
>>
>>         | oldLink aLink |
>>         self emptyCheck.
>>         oldLink := lastLink.
>>         firstLink == lastLink
>>                 ifTrue: [firstLink := nil. lastLink := nil]
>>                 ifFalse: [aLink := firstLink.
>>                                 [aLink nextLink == oldLink] whileFalse:
>>                                         [aLink := aLink nextLink].
>>                                  aLink nextLink: nil.
>>                                  lastLink := aLink].
>>         oldLink nextLink: nil.
>> +       ^oldLink value!
>> -       ^oldLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>removeLink: (in category 'removing') -----
>> + removeLink: aLink
>> +       ^self removeLink: aLink ifAbsent: [self error: 'no such method!!']!
>>
>> Item was added:
>> + ----- Method: LinkedList>>removeLink:ifAbsent: (in category 'removing') -----
>> + removeLink: aLink ifAbsent: aBlock
>> +       "Remove aLink from the receiver. If it is not there, answer the result of
>> +       evaluating aBlock."
>> +
>> +       | tempLink |
>> +       aLink == firstLink
>> +               ifTrue: [firstLink := aLink nextLink.
>> +                               aLink == lastLink
>> +                                       ifTrue: [lastLink := nil]]
>> +               ifFalse: [tempLink := firstLink.
>> +                               [tempLink == nil ifTrue: [^aBlock value].
>> +                                tempLink nextLink == aLink]
>> +                                       whileFalse: [tempLink := tempLink nextLink].
>> +                               tempLink nextLink: aLink nextLink.
>> +                               aLink == lastLink
>> +                                       ifTrue: [lastLink := tempLink]].
>> +       "Not nilling the link enables us to delete while iterating"
>> +       "aLink nextLink: nil."
>> +       ^aLink!
>>
>> Item was added:
>> + ----- Method: LinkedList>>select: (in category 'enumerating') -----
>> + select: aBlock
>> +       "Reimplemennt #select: for speedup on linked lists.
>> +       The super implemention accesses the linkes by index, thus causing an O(n^2)"
>> +
>> +       | newCollection |
>> +       newCollection := self class new.
>> +       self do: [:each | (aBlock value: each) ifTrue: [newCollection add: each]].
>> +       ^newCollection!
>>
>> Item was added:
>> + ----- Method: LinkedList>>select:thenCollect: (in category 'enumerating') -----
>> + select: selectBlock thenCollect: collectBlock
>> +       "Optimized version of SequenceableCollection>>#select:thenCollect:"
>> +
>> +       | newCollection |
>> +       newCollection := self class new.
>> +       self    do: [ :each | (selectBlock value: each) ifTrue: [newCollection add: (collectBlock value: each)]].
>> +       ^ newCollection!
>>
>> Item was added:
>> + ----- Method: LinkedList>>swap:with: (in category 'accessing') -----
>> + swap: ix1 with: ix2
>> +       "Reimplemented, super would create an infinite loop"
>> +       | minIx maxIx link1Prev link2Prev link1 link2 link1Next link2Next newLink2Next |
>> +       ((self validIndex: ix1) and: [self validIndex: ix2])    ifFalse: [^ self errorOutOfBounds].
>> +
>> +       "Get edge case out of the way"
>> +       ix1 = ix2 ifTrue: [^ self ].
>> +
>> +       "Sort indexes to make boundary-checks easier"
>> +       minIx := ix1 min: ix2.
>> +       maxIx := ix2 max: ix1.
>> +
>> +       link1Prev := (minIx = 1) ifFalse: [self linkAt: minIx -1].
>> +       link1 := link1Prev ifNotNil: [ link1Prev nextLink]
>> +                               ifNil: [self linkAt: minIx].
>> +       link1Next := link1 nextLink.
>> +       link2Prev := self linkAt: maxIx -1.
>> +       link2 := link2Prev nextLink.
>> +       link2Next := link2 nextLink.
>> +
>> +       "Link at start being swapped"
>> +       link1 = firstLink ifTrue: [firstLink := link2.] ifFalse: [link1Prev nextLink: link2].
>> +       "Link at end being swapped"
>> +       link2 = lastLink ifTrue: [lastLink := link1] ifFalse: [].
>> +       "Links  being swapped adjacent"
>> +       newLink2Next := (link1 nextLink = link2) ifTrue: [link1] ifFalse: [link2Prev nextLink: link1.
>> +               link1Next].
>> +       link1 nextLink: link2Next.
>> +       link2 nextLink: newLink2Next.
>> +       !
>>
>> Item was added:
>> + ----- Method: LinkedList>>validIndex: (in category 'private') -----
>> + validIndex: index
>> +
>> +        ^ index > 0 and: [index <= self size]!
>>
>> Item was added:
>> + ----- Method: Object>>asLink (in category '*collections') -----
>> + asLink
>> +
>> +       ^ ValueLink value: self!
>>
>> Item was added:
>> + Link subclass: #ValueLink
>> +       instanceVariableNames: 'value'
>> +       classVariableNames: ''
>> +       poolDictionaries: ''
>> +       category: 'Collections-Support'!
>> +
>> + !ValueLink commentStamp: 'HenrikSperreJohansen 10/18/2009 15:57' prior: 0!
>> + A ValueLink is a Link containing a Value.
>> + Adding an object to a LinkedList which is not a Link will create a ValueLink containing that object.
>> +
>> +
>> + value - The object this link points to.!
>>
>> Item was added:
>> + ----- Method: ValueLink class>>value: (in category 'instance creation') -----
>> + value: aValue
>> +
>> +       ^self new value: aValue!
>>
>> Item was added:
>> + ----- Method: ValueLink>>= (in category 'comparing') -----
>> + = anotherObject
>> +
>> +       ^self species == anotherObject species
>> +       and: [self value = anotherObject value
>> +       and: [self nextLink == anotherObject nextLink]]!
>>
>> Item was added:
>> + ----- Method: ValueLink>>hash (in category 'comparing') -----
>> + hash
>> +
>> +       ^self value hash bitXor: self nextLink identityHash
>> + !
>>
>> Item was added:
>> + ----- Method: ValueLink>>printOn: (in category 'printing') -----
>> + printOn: aStream
>> +
>> +       super printOn: aStream.
>> +       aStream nextPut: $(.
>> +       value printOn: aStream.
>> +       aStream nextPut: $)
>> + !
>>
>> Item was added:
>> + ----- Method: ValueLink>>value (in category 'accessing') -----
>> + value
>> +
>> +       ^ value!
>>
>> Item was added:
>> + ----- Method: ValueLink>>value: (in category 'accessing') -----
>> + value: anObject
>> +
>> +       value := anObject.!
>>
>>


More information about the Squeak-dev mailing list