Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Smalltalk makeSqueaklandRelease
Last updated at 7:20 pm UTC on 5 November 2006
The call

Smalltalk makeSqueaklandRelease

does some cleanup and discards certain subsystems.

See also Smalltalk majorShrink and Smalltalk majorShrink.

makeSqueaklandRelease
"Smalltalk makeSqueaklandRelease"
"NOTE: This method assumes that
ALL WINDOWS HAVE BEEN CLOSED (most importantly all project windows) ALL GLOBAL FLAPS HAVE BEEN DESTROYED (not just disabled)
This method may needs to be run twice - upon the first run you will probably receive an error message saying 'still have obsolete behaviors'. Close the notifier and try again. If there are still obsolete behaviors then go looking for them.
Last update: ar 8/18/2001 01:14 for Squeak 3.1"
| ss |
(self confirm: self version , '
Is this the correct version designation?
If not, choose no, and fix it.') ifFalse: [^ self].
"Delete all projects"
Project allSubInstancesDo:[:p|
(p == Project current) ifFalse:[Project deletingProject: p].
].
"Fix up for some historical problem"
Smalltalk allObjectsDo:[:o|
o isMorph ifTrue:[o removeProperty: #undoGrabCommand].
].
"Hm ... how did this come in?!"
Smalltalk keys do:[:x|
(x class == String and:[(Smalltalk at: x) isBehavior]) ifTrue:[Smalltalk removeKey: x].
].
"Remove stuff from References"
References keys do:[:k| References removeKey: k].
"Reset command history"
CommandHistory resetAllHistory.
"Clean out Undeclared"
Undeclared removeUnreferencedKeys.
"Reset scripting system"
StandardScriptingSystem initialize.
"Reset preferences"
Preferences
chooseInitialSettings;
installBrightWindowColors.
"Do a nice fat GC"
Smalltalk garbageCollect.
"Dependents mean that we're holding onto stuff"
(Object classPool at: #DependentsFields) size > 1
ifTrue: [self error:'Still have dependents'].
"Set a few default preferences"
#(
(honorDesktopCmdKeys false)
(warnIfNoChangesFile false)
(warnIfNoSourcesFile false)
(showDirectionForSketches true)
(menuColorFromWorld false)
(unlimitedPaintArea true)
(useGlobalFlaps false)
(mvcProjectsAllowed false)
(projectViewsInWindows false)
(automaticKeyGeneration true)
(securityChecksEnabled true)
(showSecurityStatus false)
(startInUntrustedDirectory true)
(warnAboutInsecureContent false)
(promptForUpdateServer false)
(fastDragWindowForMorphic false)
) do:[:spec|
Preferences setPreference: spec first toValue: (spec last == #true).
].
"Initialize Browser (e.g., reset recent classes etc)"
Browser initialize.
"Check for Undeclared"
Undeclared isEmpty
ifFalse: [self error:'Please clean out Undeclared'].
"Remove graphics we don't want"
ScriptingSystem deletePrivateGraphics.
"Remove a few text styles"
#(Helvetica Palatino Courier) do:
[:n | TextConstants removeKey: n ifAbsent: []].
"Dump all player uniclasses"
Smalltalk at: #Player ifPresent:[:player|
player allSubclassesDo:[:cls|
cls isSystemDefined ifFalse:[cls removeFromSystem]]].
"Dump all Wonderland uniclasses"
Smalltalk at: #WonderlandActor ifPresent:[:wnldActor|
wnldActor allSubclassesDo:[:cls|
cls isSystemDefined ifFalse:[cls removeFromSystem]]].
"Attempt to get rid of them"
Smalltalk garbageCollect.
"Now remove larger parts"
Smalltalk
discardFFI;
discard3D;
discardSUnit;
discardSpeech;
discardVMConstruction;
discardPWS;
discardIRC.
"Dump change sets"
ChangeSorter removeChangeSetsNamedSuchThat:
[:cs| cs name ~= Smalltalk changes name].
"Clear current change set"
Smalltalk changes clear.
Smalltalk changes name: 'Unnamed1'.
Smalltalk garbageCollect.
"Reinitialize DataStream; it may hold on to some zapped entitities"
DataStream initialize.
"Remove refs to old ControlManager"
ScheduledControllers _ nil.
"Flush obsolete subclasses"
Behavior flushObsoleteSubclasses.
Smalltalk garbageCollect.
Smalltalk obsoleteBehaviors isEmpty
ifFalse:[self error:'Still have obsolete behaviors'].

"Clear all server entries"
ServerDirectory serverNames do: [:each | ServerDirectory removeServerNamed: each].
SystemVersion current resetHighestUpdate.

ss _ Set allSubInstances.
'Rehashing all sets' displayProgressAt: Sensor cursorPoint from: 1 to: ss size during:[:bar|
1 to: ss size do:[:i|
bar value: i.
(ss at: i) rehash.
].
].

Smalltalk obsoleteClasses isEmpty ifFalse: [self halt].
self halt: 'Ready to condense changes or sources'.
SystemDictionary removeSelector: #makeSqueaklandRelease.