Skip to content

Commit

Permalink
Further cleanings.
Browse files Browse the repository at this point in the history
```Smalltalk
coll1 := OrderedCollection new.
coll2 := OrderedCollection new.

1000 timesRepeat: [ coll1 add: 3000 atRandom.coll2 add: 3000 atRandom ].

"Before"
[ coll1 intersection: coll2 ] bench.  "'3468.413 per second'"

"After"
[ coll1 intersection: coll2 ] bench.  "'4011.395 per second'"

coll3 := #(1 2 3 4 5) asOrderedCollection.
coll4 :=#(4 5 6 7 8) asOrderedCollection.

"Before"
[ coll3 intersection: coll4 ] bench. "'731581.767 per second'"

"After"
[ coll3 intersection: coll4 ] bench. "'772582.850 per second'"
```
  • Loading branch information
jecisc committed Jul 18, 2019
1 parent deae92a commit 46c5d29
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 9 deletions.
6 changes: 1 addition & 5 deletions src/Collections-Abstract/Collection.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -907,11 +907,7 @@ Collection >> intersection: aCollection [

"(#() intersection: #(1 2 3 4)) >>> #()"

| set outputSet |
set := self asSet.
outputSet := Set new.
aCollection do: [ :each | (set includes: each) ifTrue: [ outputSet add: each ] ].
^ self species withAll: outputSet asArray
^ self species withAll: (self asSet intersection: aCollection) asArray
]

{ #category : #testing }
Expand Down
9 changes: 5 additions & 4 deletions src/Collections-Unordered/Set.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -152,15 +152,16 @@ Set >> includes: anObject [
Set >> intersection: aCollection [
"Answer the set theoretic intersection of two collections.
Optimized version for Sets where no intermediate Set is necessary"

"(#(1 2 3 4) asSet intersection: #(3 4 5) asSet) >>> #(3 4) asSet"

"(#(1 2 3 4) asSet intersection: #() asSet) >>> Set new"

"( #() asSet intersection: #(1 2 3 4) asSet) >>> Set new"

| outputSet |
outputSet := self class new.
aCollection do: [ :each|
((self includes: each) and: [(outputSet includes: each) not])
ifTrue: [ outputSet add: each]].
aCollection do: [ :each | (self includes: each) ifTrue: [ outputSet add: each ] ].
^ outputSet
]

Expand Down

0 comments on commit 46c5d29

Please sign in to comment.