Team proposal: Morphic Splitters

Steven Swerling sswerling at yahoo.com
Wed Feb 23 19:47:11 UTC 2005


> 1.  One simple first step would be to strip an image down to just the basic tools, run the iterative part of major shrink, and then see what is left of Morphic.
> 
> 2.  I would like to do the same (perhaps they have already done it) for Pavel and Steven's "Small-3.7" and QuiteSmall images.  This is excellent work, very much in the spirit of this project.  I hope they will sign on, at least in an advisory capacity.

Oops, I should make a couple comments on what major shrink tools I ran 
in QuiteSmall, it might save you some time if you do item #2 above.

(This is a bit long)

On QuiteSmall, I ran a modified version of #removeAllUnsentMessages. The 
modification exludes any methods for stripping if those methods existed 
in a class that I regarded as "sacrosanct" (judged subjectively). They 
were any classes in:

'System-*', 'Kernel-*', 'Graphics-*', 'Compiler-*', 'Collections-*', 
'MCInstal*', 'Network*', 'SAR*', 'ST80*', 'SUnit*', 'PackageInfo*',
'Morphic-Support'.

Then, piecemeal, I added to those classes for exclusion the following:

PluggableListMorph, ScrollPane, PluggableTextMorph, TextMorph, 
PluggableListItemWrapper, SystemWindow, ParagraphEditor, 
TextMorphEditor, NewParagraph.

I should have included a few more classes to that, but got in the habit 
of just filing them in after the strip:

ChangeSet, StandardFileMenu and StandardFileMenuResult, VersionsBrowser.

After running #removeAllUnsentMessages, I then filed back in a 
hodge-podge of stuff. It's too crufty to go into details, but loosely 
that includes snippets of code from Cursor, HaloMorph, some Morph access 
message categories, some PasteUpMorph methods, Preferences.

Sorry that's a bit messy, but it will give you some idea of how much 
further the stock #majorShrink type tricks will take you on QuiteSmall.

I was able to get more stuff out of QuiteSmall but never distributed 
them, since I felt it necessary to make them reloadable, but I didn't 
find the time to get reloads working:
1. Removing nonessential system tools (judged subjectively), I lopped 
another 100K from the image.
2. Stripping Networking-* got me another 100K or so. Hard to imagine 
many apps wouldn't want this functionality, though.
3. Stripping SUnit-* got me about 45K.

Although "Behavior obsoleteSubclasses" yields an empty collection, 
"Smalltalk obsoleteBehaviors" returns a 12 item Array. I didn't have the 
chops to track those down.

I wanted to strip out ObjectWithDocumentation, but some ChangeSet 
classes are subclasses of this. It would be nice to make the coupling 
between change set and ObjectWDocs a bit more pluggable for deployment 
images.

There are still some more classes from MVC that could be stripped, but I 
didn't get around to it.

For reference, below is the version of removeAllUnsentMessages that I 
ran, and below that is the final crunching scripts that I ran (mostly 
taken from majorShrink)

==== Here is the version of removeAllUnsentMessages I used, for 
reference ====
'From Squeak3.7 of ''4 September 2004'' [latest update: #5989] on 18 
February 2005 at 7:17 pm'!

!SystemDictionary methodsFor: 'shrinking' stamp: 'sps 2/16/2005 20:54'!
removeAllUnSentMessagesSpareKernel

	"
Smalltalk removeAllUnSentMessagesSpareKernel
"
	"Remove all implementations of unsent messages."
	| sels n catsToExclude catMatches classesToSave selsToSave |

	catsToExclude _ {
		'System-*'. 'Kernel-*'. 'Graphics-*'. 'Compiler-*'. 'Collections-*'.
		'MCInstal*'. 'Network*'. 'SAR*'. 'ST80*'. 'SUnit*'. 'PackageInfo*'.
		'Morphic-Support'.
	}.
	
	classesToSave _ OrderedCollection new.
	catsToExclude do: [ :catPrefix |
		catMatches _ (SystemOrganization categoriesMatching: catPrefix).
		catMatches do: [ :category |
			classesToSave addAll: (SystemOrganization superclassOrder: category)
		]
	].

	classesToSave
		add: PluggableListMorph;
		add: ScrollPane;
		add: PluggableTextMorph;
		add: TextMorph;
		add: PluggableListItemWrapper;
		add: SystemWindow;
		add: ParagraphEditor;
		add: TextMorphEditor ;
		add: NewParagraph;
		yourself.
		
	selsToSave _ OrderedCollection new.
	classesToSave do: [ :cls |
		selsToSave addAll: cls methodDict keys.
		selsToSave addAll: cls class methodDict keys.
	].
"	classesToSave explore.
	catsToExclude explore."
	sels _ self systemNavigation allUnSentMessages.
	selsToSave do: [ :s | sels remove: s ifAbsent:[] ].
	
	"The following should be preserved for doIts, etc"
	"needed even after #majorShrink is pulled"
	#(#rehashWithoutBecome #compactSymbolTable #rebuildAllProjects 
#browseAllSelect:  #lastRemoval #scrollBarValue: vScrollBarValue: 
#scrollBarMenuButtonPressed: #withSelectionFrom: #to: #removeClassNamed: 
#dragon: #hilberts: #mandala: #web #test3 #factorial #tinyBenchmarks 
#benchFib #newDepth: #restoreAfter: #forgetDoIts #zapAllMethods 
#obsoleteClasses #removeAllUnSentMessages #abandonSources 
#removeUnreferencedKeys #reclaimDependents #zapOrganization 
#condenseChanges #browseObsoleteReferences 
#subclass:instanceVariableNames:classVariableNames:poolDictionaries:category: 
#methodsFor:stamp: #methodsFor:stamp:prior: #instanceVariableNames: 
#startTimerInterruptWatcher #unusedClasses )
		do: [:sel | sels
				remove: sel
				ifAbsent: []].
	"The following may be sent by perform: in dispatchOnChar..."
	(ParagraphEditor classPool at: #CmdActions) asSet
		do: [:sel | sels
				remove: sel
				ifAbsent: []].
	(ParagraphEditor classPool at: #ShiftCmdActions) asSet
		do: [:sel | sels
				remove: sel
				ifAbsent: []].
	sels size = 0
		ifTrue: [^ 0].
	n _ 0.
	

	self systemNavigation
		allBehaviorsDo: [:x | n _ n + 1].
	'Removing ' , sels size printString , ' messages . . .'
		displayProgressAt: Sensor cursorPoint
		from: 0
		to: n
		during: [:bar |
			n _ 0.
			self systemNavigation
				allBehaviorsDo: [:class |
					bar value: (n _ n + 1).
					sels
						do: [:sel | class basicRemoveSelector: sel]]].
	^ sels size
! !

==== Here is the "final crunch" that I ran after doing all my main 
shrinking. Most of it is lifted from majorShrink ====

	
[Smalltalk removeAllUnSentMessagesSpareKernel  > 0]whileTrue:[].

"(NOTE: After the step above, I filed in a bunch of miscellaneous stuff 
to shore up the image and make sure the scripts below work)"

"Remove Dead Selectors"
killed _ OrderedCollection new.
Smalltalk allClasses do: [ :theClass |
(Array with: theClass with: theClass class) do: [ :cls |
	org _ cls organization.
	sels _ cls selectors.
	org categories do: [ :cat |
		(org listAtCategoryNamed: cat) do: [ :sel |
			(sels includes: sel) ifFalse:[
				org removeElement: sel.
				killed add: (cat->sel).]]].
]].

"Remove Empty Method Categories"
killed _ OrderedCollection new.
Smalltalk allClasses do: [ :theClass |
(Array with: theClass with: theClass class) do: [ :cls |
	org _ cls organization.
	org categories do: [ :cat |
		((org listAtCategoryNamed: cat) isEmpty & (cat ~~ #'no messages')) ifTrue:
			[killed add: cls->cat.
			cls removeCategory: cat]].
]].


	Project rebuildAllProjects.
	ListParagraph initialize.
	PopUpMenu initialize.
	ChangeSet  noChanges.
	ChangeSorter classPool at: #AllChangeSets
		put: (OrderedCollection with: ChangeSet current).
		
	SystemDictionary removeSelector: #majorShrink.
	SystemOrganization removeEmptyCategories.
	
	"Goes too far: Smalltalk allClassesDo: [:c | c zapOrganization]."
	
	Smalltalk garbageCollect.

	'Rehashing method dictionaries . . .'
		displayProgressAt: Sensor cursorPoint
		from: 0 to: MethodDictionary instanceCount
		during: [:bar |
			oldDicts _ MethodDictionary allInstances.
			newDicts _ Array new: oldDicts size.
			oldDicts withIndexDo: [:d :index |
				bar value: index.
				newDicts at: index put: d rehashWithoutBecome.
			].
			oldDicts elementsExchangeIdentityWith: newDicts.
		].
	oldDicts _ newDicts _ nil.
	Project rebuildAllProjects.
	ChangeSet current initialize.
	Clipboard initialize.
	Clipboard allInstances do: [ :i | i initialize ].	
		
	"seems to take more than one try to gc all the weak refs in SymbolTable"

	3 timesRepeat: [
		Smalltalk garbageCollect.
		Symbol compactSymbolTable.
	].





More information about the Squeak-dev mailing list