Skip to content

Commit

Permalink
OrderedCollection had #compactInstances: add #compactAll and call it …
Browse files Browse the repository at this point in the history
…in cleanUp: just like HashedCollection

remove Behaviour >>compress (not called, can be called manually if needed (methodDict rehash_
#cleanUpForRelease
-- remove explicit call to #compactInstances, as this is now done with the #cleanup
-- add a final #rehash of all HashedCollections at the end
  • Loading branch information
MarcusDenker committed Mar 14, 2019
1 parent 3bff9d8 commit dabdf81
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 15 deletions.
10 changes: 5 additions & 5 deletions src/Collections-Abstract/HashedCollection.class.st
Expand Up @@ -35,14 +35,14 @@ HashedCollection class >> cleanUp: aggressive [

]

{ #category : #initialization }
{ #category : #cleanup }
HashedCollection class >> compactAll [
"HashedCollection rehashAll"
"HashedCollection compactAll"

self allSubclassesDo: #compactAllInstances
]

{ #category : #initialization }
{ #category : #cleanup }
HashedCollection class >> compactAllInstances [
"Do not use #allInstancesDo: because rehash may create new instances."

Expand Down Expand Up @@ -75,14 +75,14 @@ HashedCollection class >> newFrom: aCollection [
^self subclassResponsibility
]

{ #category : #initialization }
{ #category : #cleanup }
HashedCollection class >> rehashAll [
"HashedCollection rehashAll"

self allSubclassesDo: #rehashAllInstances
]

{ #category : #initialization }
{ #category : #cleanup }
HashedCollection class >> rehashAllInstances [
"Do not use #allInstancesDo: because rehash may create new instances."

Expand Down
16 changes: 15 additions & 1 deletion src/Collections-Sequenceable/OrderedCollection.class.st
Expand Up @@ -87,7 +87,21 @@ OrderedCollection class >> arrayType [
^ Array
]

{ #category : #initialization }
{ #category : #cleanup }
OrderedCollection class >> cleanUp: aggressive [
"Rehash all instances when cleaning aggressively"

aggressive ifTrue: [self compactAll].
]

{ #category : #cleanup }
OrderedCollection class >> compactAll [
"OrderedCollection compactAll"

self allSubclassesDo: #compactAllInstances
]

{ #category : #cleanup }
OrderedCollection class >> compactAllInstances [
self allInstances do: #compact
]
Expand Down
7 changes: 0 additions & 7 deletions src/Kernel/Behavior.class.st
Expand Up @@ -635,13 +635,6 @@ Behavior >> compiledMethodAt: selector ifPresent: anotherBlock ifAbsent: aBlock
^ self methodDict at: selector ifPresent: anotherBlock ifAbsent: aBlock
]

{ #category : #'accessing method dictionary' }
Behavior >> compress [
"Compact the method dictionary of the receiver."

self methodDict rehash
]

{ #category : #queries }
Behavior >> copiedFromSuperclass: method [
"Returns the methods that the receiver copied with its ancestors"
Expand Down
3 changes: 1 addition & 2 deletions src/Tool-ImageCleaner/ImageCleaner.class.st
Expand Up @@ -82,7 +82,6 @@ ImageCleaner >> cleanUpForRelease [

Author fullName: 'MrCleaner'.
self cleanUpMethods.
OrderedCollection compactAllInstances.
self class environment at: #MetacelloProjectRegistration ifPresent: [ :class | class resetRegistry ].
SystemNavigation new
allObjectsDo: [ :each |
Expand All @@ -100,7 +99,7 @@ ImageCleaner >> cleanUpForRelease [
cleanOutUndeclared;
fixObsoleteReferences;
cleanUp: true except: #() confirming: false.

HashedCollection rehashAll.
Author reset
]

Expand Down

0 comments on commit dabdf81

Please sign in to comment.