The Trunk: Collections-topa.726.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
14 messages Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Collections-topa.726.mcz

commits-2
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.!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Chris Muller-3
Is this backward compatible?

On Tue, Dec 6, 2016 at 7:31 AM,  <[hidden email]> 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.!
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Chris Muller-3
More specifically, will existing instances work or is there some
conversion needed?

On Tue, Dec 6, 2016 at 12:10 PM, Chris Muller <[hidden email]> wrote:

> Is this backward compatible?
>
> On Tue, Dec 6, 2016 at 7:31 AM,  <[hidden email]> 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.!
>>
>>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Tobias Pape

On 06.12.2016, at 19:11, Chris Muller <[hidden email]> wrote:

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

As far as I can tell, no work needed.


>
> On Tue, Dec 6, 2016 at 12:10 PM, Chris Muller <[hidden email]> wrote:
>> Is this backward compatible?
>>
>> On Tue, Dec 6, 2016 at 7:31 AM,  <[hidden email]> 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.!
>>>
>>>
>


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Levente Uzonyi
Is there any use of these lists? I mean besides process scheduling.
I can't imagine a use-case where I would use a LinkedList instead of an
OrderedCollection (or another data structure).
I would also get rid of the current Stack implementation.

Levente

On Tue, 6 Dec 2016, Tobias Pape wrote:

>
> On 06.12.2016, at 19:11, Chris Muller <[hidden email]> wrote:
>
>> More specifically, will existing instances work or is there some
>> conversion needed?
>
> As far as I can tell, no work needed.
>
>
>>
>> On Tue, Dec 6, 2016 at 12:10 PM, Chris Muller <[hidden email]> wrote:
>>> Is this backward compatible?
>>>
>>> On Tue, Dec 6, 2016 at 7:31 AM,  <[hidden email]> 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.!
>>>>
>>>>
>>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Chris Muller-4
Not sure if you were joking; but..  :)  Magma includes an
implementation of Split-Ordered Lists (which make heavy use of
LinkedLists) to serve as the foundation of MagmaCollection.

http://cs.ucf.edu/~dcm/Teaching/COT4810-Spring2011/Literature/SplitOrderedLists.pdf

Its the use-case for having collections whose size exceeds available
RAM.  OrderedCollection is designed to operate on a fully-allocated
Array, which would be too large for memory.

LinkedList is a fundamental a data structure, this is reason enough it
should be included in Smalltalk and Squeak, IMO.


On Tue, Dec 6, 2016 at 1:08 PM, Levente Uzonyi <[hidden email]> wrote:

> Is there any use of these lists? I mean besides process scheduling.
> I can't imagine a use-case where I would use a LinkedList instead of an
> OrderedCollection (or another data structure).
> I would also get rid of the current Stack implementation.
>
> Levente
>
>
> On Tue, 6 Dec 2016, Tobias Pape wrote:
>
>>
>> On 06.12.2016, at 19:11, Chris Muller <[hidden email]> wrote:
>>
>>> More specifically, will existing instances work or is there some
>>> conversion needed?
>>
>>
>> As far as I can tell, no work needed.
>>
>>
>>>
>>> On Tue, Dec 6, 2016 at 12:10 PM, Chris Muller <[hidden email]>
>>> wrote:
>>>>
>>>> Is this backward compatible?
>>>>
>>>> On Tue, Dec 6, 2016 at 7:31 AM,  <[hidden email]> 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.!
>>>>>
>>>>>
>>>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

timrowledge
In reply to this post by Levente Uzonyi

> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>
> Is there any use of these lists? I mean besides process scheduling.
> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).

Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.


tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Useful Latin Phrases:- Sic faciunt omnes. = Everyone is doing it.



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Levente Uzonyi
On Tue, 6 Dec 2016, tim Rowledge wrote:

>
>> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>>
>> Is there any use of these lists? I mean besides process scheduling.
>> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).
>
> Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.

Using the current implementation, addition might be O(1) if you hold a
reference to the internal list node, but removal is O(n) unless you
maintain backwards pointers - aka make the list doubly-linked.

OrderedCollection is far superior in growing/shrinking (provided it's
done at one of its ends), both in term of run time and memory usage, since
it needs fewer objects.

Levente

>
>
> tim
> --
> tim Rowledge; [hidden email]; http://www.rowledge.org/tim
> Useful Latin Phrases:- Sic faciunt omnes. = Everyone is doing it.

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Tobias Pape

On 06.12.2016, at 21:23, Levente Uzonyi <[hidden email]> wrote:

> On Tue, 6 Dec 2016, tim Rowledge wrote:
>
>>
>>> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>>> Is there any use of these lists? I mean besides process scheduling.
>>> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).
>>
>> Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.
>
> Using the current implementation, addition might be O(1) if you hold a reference to the internal list node, but removal is O(n) unless you maintain backwards pointers - aka make the list doubly-linked.
>
> OrderedCollection is far superior in growing/shrinking (provided it's done at one of its ends), both in term of run time and memory usage, since it needs fewer objects.

Yes.

But sometimes you need a linked list.
It is not that the trunk _should_ use it but that Squeak programmers _can_ use it.
Let's not impose too much on the programmers. Linked lists are pretty standard :)


Best regards
        -Tobias

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Levente Uzonyi
In reply to this post by Chris Muller-4
On Tue, 6 Dec 2016, Chris Muller wrote:

> Not sure if you were joking; but..  :)  Magma includes an
> implementation of Split-Ordered Lists (which make heavy use of
> LinkedLists) to serve as the foundation of MagmaCollection.

No, I wasn't joking. I can hardly imagine a case where a singly linked
list (which is what LinkedList is) would turn out to be useful.

>
> http://cs.ucf.edu/~dcm/Teaching/COT4810-Spring2011/Literature/SplitOrderedLists.pdf
>
> Its the use-case for having collections whose size exceeds available
> RAM.  OrderedCollection is designed to operate on a fully-allocated
> Array, which would be too large for memory.

Let's face it, that's another collection, not a linked list. It uses
linked lists and other stuff internally.

>
> LinkedList is a fundamental a data structure, this is reason enough it
> should be included in Smalltalk and Squeak, IMO.

LinkedList is one of the least useful implementation of linked lists. It's
as minimal as possible, probably to make its access from the VM-side easier.

Levente

>
>
> On Tue, Dec 6, 2016 at 1:08 PM, Levente Uzonyi <[hidden email]> wrote:
>> Is there any use of these lists? I mean besides process scheduling.
>> I can't imagine a use-case where I would use a LinkedList instead of an
>> OrderedCollection (or another data structure).
>> I would also get rid of the current Stack implementation.
>>
>> Levente
>>
>>
>> On Tue, 6 Dec 2016, Tobias Pape wrote:
>>
>>>
>>> On 06.12.2016, at 19:11, Chris Muller <[hidden email]> wrote:
>>>
>>>> More specifically, will existing instances work or is there some
>>>> conversion needed?
>>>
>>>
>>> As far as I can tell, no work needed.
>>>
>>>
>>>>
>>>> On Tue, Dec 6, 2016 at 12:10 PM, Chris Muller <[hidden email]>
>>>> wrote:
>>>>>
>>>>> Is this backward compatible?
>>>>>
>>>>> On Tue, Dec 6, 2016 at 7:31 AM,  <[hidden email]> 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.!
>>>>>>
>>>>>>
>>>>
>>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Levente Uzonyi
In reply to this post by Tobias Pape
On Tue, 6 Dec 2016, Tobias Pape wrote:

>
> On 06.12.2016, at 21:23, Levente Uzonyi <[hidden email]> wrote:
>
>> On Tue, 6 Dec 2016, tim Rowledge wrote:
>>
>>>
>>>> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>>>> Is there any use of these lists? I mean besides process scheduling.
>>>> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).
>>>
>>> Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.
>>
>> Using the current implementation, addition might be O(1) if you hold a reference to the internal list node, but removal is O(n) unless you maintain backwards pointers - aka make the list doubly-linked.
>>
>> OrderedCollection is far superior in growing/shrinking (provided it's done at one of its ends), both in term of run time and memory usage, since it needs fewer objects.
>
> Yes.
>
> But sometimes you need a linked list.

Right. But whenever I do, I roll my own because
  - most of the time I need a doubly linked list (e.g. LRUCacheHeadNode and
LRUCacheNode)
  - I already have a class hierachy to match, so I can't subclass
LinkedList (see ODatedEntry in OCompletion, this is also a doubly linked
list)

> It is not that the trunk _should_ use it but that Squeak programmers _can_ use it.

There must be a reason why it's not being used in the Trunk. :)

Levente

> Let's not impose too much on the programmers. Linked lists are pretty standard :)
>
>
> Best regards
> -Tobias

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Tobias Pape

On 06.12.2016, at 22:25, Levente Uzonyi <[hidden email]> wrote:

> On Tue, 6 Dec 2016, Tobias Pape wrote:
>
>>
>> On 06.12.2016, at 21:23, Levente Uzonyi <[hidden email]> wrote:
>>
>>> On Tue, 6 Dec 2016, tim Rowledge wrote:
>>>>> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>>>>> Is there any use of these lists? I mean besides process scheduling.
>>>>> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).
>>>> Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.
>>> Using the current implementation, addition might be O(1) if you hold a reference to the internal list node, but removal is O(n) unless you maintain backwards pointers - aka make the list doubly-linked.
>>> OrderedCollection is far superior in growing/shrinking (provided it's done at one of its ends), both in term of run time and memory usage, since it needs fewer objects.
>>
>> Yes.
>>
>> But sometimes you need a linked list.
>
> Right. But whenever I do, I roll my own because
> - most of the time I need a doubly linked list (e.g. LRUCacheHeadNode and LRUCacheNode)
> - I already have a class hierachy to match, so I can't subclass LinkedList (see ODatedEntry in OCompletion, this is also a doubly linked list)
>
>> It is not that the trunk _should_ use it but that Squeak programmers _can_ use it.
>
> There must be a reason why it's not being used in the Trunk. :)

So is the XMLParser, the SerialPort, the SecureSocket, the POP3Client, the PNMReadWriter, the ScaleMorph, the AsyncFile ; Regex rarely, even the Abort exception is unused

I always thought as Squeak as an environment, as system I can program my application into.
If we say, bah we need no standard-library except for what is _used_ in trunk, this is moot :/

>
> Levente
>
>> Let's not impose too much on the programmers. Linked lists are pretty standard :)
>>
>>
>> Best regards
>> -Tobias


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Levente Uzonyi
On Tue, 6 Dec 2016, Tobias Pape wrote:

>
> On 06.12.2016, at 22:25, Levente Uzonyi <[hidden email]> wrote:
>
>> On Tue, 6 Dec 2016, Tobias Pape wrote:
>>
>>>
>>> On 06.12.2016, at 21:23, Levente Uzonyi <[hidden email]> wrote:
>>>
>>>> On Tue, 6 Dec 2016, tim Rowledge wrote:
>>>>>> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>>>>>> Is there any use of these lists? I mean besides process scheduling.
>>>>>> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).
>>>>> Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.
>>>> Using the current implementation, addition might be O(1) if you hold a reference to the internal list node, but removal is O(n) unless you maintain backwards pointers - aka make the list doubly-linked.
>>>> OrderedCollection is far superior in growing/shrinking (provided it's done at one of its ends), both in term of run time and memory usage, since it needs fewer objects.
>>>
>>> Yes.
>>>
>>> But sometimes you need a linked list.
>>
>> Right. But whenever I do, I roll my own because
>> - most of the time I need a doubly linked list (e.g. LRUCacheHeadNode and LRUCacheNode)
>> - I already have a class hierachy to match, so I can't subclass LinkedList (see ODatedEntry in OCompletion, this is also a doubly linked list)
>>
>>> It is not that the trunk _should_ use it but that Squeak programmers _can_ use it.
>>
>> There must be a reason why it's not being used in the Trunk. :)
>
> So is the XMLParser, the SerialPort, the SecureSocket, the POP3Client, the PNMReadWriter, the ScaleMorph, the AsyncFile ; Regex rarely, even the Abort exception is unused

Those are just tools, not data structures. You're comparing apples to
oranges.

>
> I always thought as Squeak as an environment, as system I can program my application into.
> If we say, bah we need no standard-library except for what is _used_ in trunk, this is moot :/

Who says that?

My point was that LinkedList in its current form is not generally useful.

Levente

>
>>
>> Levente
>>
>>> Let's not impose too much on the programmers. Linked lists are pretty standard :)
>>>
>>>
>>> Best regards
>>> -Tobias

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Collections-topa.726.mcz

Tobias Pape

On 06.12.2016, at 23:06, Levente Uzonyi <[hidden email]> wrote:

> On Tue, 6 Dec 2016, Tobias Pape wrote:
>
>>
>> On 06.12.2016, at 22:25, Levente Uzonyi <[hidden email]> wrote:
>>
>>> On Tue, 6 Dec 2016, Tobias Pape wrote:
>>>> On 06.12.2016, at 21:23, Levente Uzonyi <[hidden email]> wrote:
>>>>> On Tue, 6 Dec 2016, tim Rowledge wrote:
>>>>>>> On 06-12-2016, at 11:08 AM, Levente Uzonyi <[hidden email]> wrote:
>>>>>>> Is there any use of these lists? I mean besides process scheduling.
>>>>>>> I can't imagine a use-case where I would use a LinkedList instead of an OrderedCollection (or another data structure).
>>>>>> Anywhere that needs frequent adding and removing of items mid-list, or growing/shrinking. Saves constantly making a new array, copying gazillions of OOPs and possibly #become.
>>>>> Using the current implementation, addition might be O(1) if you hold a reference to the internal list node, but removal is O(n) unless you maintain backwards pointers - aka make the list doubly-linked.
>>>>> OrderedCollection is far superior in growing/shrinking (provided it's done at one of its ends), both in term of run time and memory usage, since it needs fewer objects.
>>>> Yes.
>>>> But sometimes you need a linked list.
>>> Right. But whenever I do, I roll my own because
>>> - most of the time I need a doubly linked list (e.g. LRUCacheHeadNode and LRUCacheNode)
>>> - I already have a class hierachy to match, so I can't subclass LinkedList (see ODatedEntry in OCompletion, this is also a doubly linked list)
>>>> It is not that the trunk _should_ use it but that Squeak programmers _can_ use it.
>>> There must be a reason why it's not being used in the Trunk. :)
>>
>> So is the XMLParser, the SerialPort, the SecureSocket, the POP3Client, the PNMReadWriter, the ScaleMorph, the AsyncFile ; Regex rarely, even the Abort exception is unused
>
> Those are just tools, not data structures. You're comparing apples to oranges.
>
>>
>> I always thought as Squeak as an environment, as system I can program my application into.
>> If we say, bah we need no standard-library except for what is _used_ in trunk, this is moot :/
>
> Who says that?
>
> My point was that LinkedList in its current form is not generally useful.

Maybe.
Before, it was even less. And scarcely tested.
Now it is usable and better tested.

Would you rather have it nuked?

>
> Levente
>
>>
>>> Levente
>>>> Let's not impose too much on the programmers. Linked lists are pretty standard :)
>>>> Best regards
>>>> -Tobias
>