Skip to content

Commit

Permalink
When we remove a class from the system we do not need to flush all th…
Browse files Browse the repository at this point in the history
…e SystemDictionary caches.

This will speed up a little the removal of big packages from the system.
  • Loading branch information
jecisc committed Aug 6, 2019
1 parent 70ac7e7 commit d5b65c4
Showing 1 changed file with 14 additions and 10 deletions.
24 changes: 14 additions & 10 deletions src/System-Support/SystemDictionary.class.st
Expand Up @@ -206,21 +206,20 @@ SystemDictionary >> fillCaches [

{ #category : #'class and trait names' }
SystemDictionary >> flushClassNameCache [
"Smalltalk flushClassNameCache"
"Force recomputation of the cached list of class names and non-class names."

<script: 'Smalltalk flushClassNameCache'>
cachedClassNames := cachedNonClassNames := cachedBehaviors := nil
]

{ #category : #'classes and traits' }
SystemDictionary >> forgetClass: aClass logged: aBool [
SystemDictionary >> forgetClass: aClass logged: aBool [
"Delete the class, aClass, from the system.
Note that this doesn't do everything required to dispose of a class - to do that use Class>>removeFromSystem."

self organization removeElement: aClass name.
SessionManager default unregisterClassNamed: aClass name.
self removeKey: aClass name ifAbsent: [].
self flushClassNameCache
self removeKey: aClass name ifAbsent: [ ]
]

{ #category : #testing }
Expand Down Expand Up @@ -325,14 +324,19 @@ SystemDictionary >> removeClassNamed: aName [
self at: aName asSymbol ifPresent: [:oldClass | oldClass removeFromSystem]
]

{ #category : #removing }
SystemDictionary >> removeFromCaches: aClassName [
"In case we remove a key from the system dictionary, we do not need to flush all the caches. We can just remove it from the class name and non class name caches."

cachedClassNames ifNotNil: [ :cache | cache remove: aClassName ifAbsent: [ ] ].
cachedNonClassNames ifNotNil: [ :cache | cache remove: aClassName ifAbsent: [ ] ].
cachedBehaviors := nil
]

{ #category : #'dictionary access' }
SystemDictionary >> removeKey: key ifAbsent: aBlock [
"Remove key (and its associated value) from the receiver. If key is not in
the receiver, answer the result of evaluating aBlock. Otherwise, answer
the value externally named by key."

self flushClassNameCache.
^super removeKey: key ifAbsent: aBlock
self removeFromCaches: key.
^ super removeKey: key ifAbsent: aBlock
]

{ #category : #renaming }
Expand Down

0 comments on commit d5b65c4

Please sign in to comment.