Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Smalltalk majorShrink (archive)
Last updated at 12:48 am UTC on 17 January 2006
This page contains archived material from the page Smalltalk majorShrink. It may be used as a ressource for creating a comprehensiv entry on Smalltalk majorShrink.
[21-FEB-03] hjh

Notes and emails about 'Smalltalk majorShrink'





ChangeSorter


ChangeSorter removeChangeSetsNamedSuchThat:
[:aName | aName first isDigit]


frees a considerable amount of space. It removes all ChangeSets beginning with a digit. These are the ones which are built up during the code update. If you have Projects with names which begin with a digit they are eliminated as well.


Dan Ingalls's comment on the mailing list on 20 Aug 2001

ChangeSet allInstancesDo: [:cs | cs zapHistory].

removes only the old versions of the methods but leaves the ChangeSets in place.

Smalltalk printSpaceAnalysis
generates a file STspace.text.

Methods of the Smalltalk object (an instance of SystemDictionary which discard code:

SystemDictionary selectors asSortedCollection do: [:s | (s asString beginsWith: 'discard') ifTrue: [Transcript show: s printString; cr]].

gives

#discard3D
#discardDiscards
#discardFFI
#discardFlash
#discardIRC
#discardMIDI
#discardMVC
#discardMorphic
#discardNetworking
#discardOddsAndEnds
#discardPWS
#discardPluggableWebServer
#discardSUnit
#discardSoundAndSpeech
#discardSoundSynthesis
#discardSpeech
#discardTrueType
#discardVMConstruction
#discardWonderland


Jon Hylands posted on October 8, 2002 a changeset to the mailing list that worked on version 3.2 and resulted in a 1.6 megabyte MVC-only image.

John W. Sarkela - 10-FEB-2003 (from the mailing list)

An important sanity check when shrinking images is the following:

1. Remove the part of major shrink that drops the source.
2. Attempt to recompile all the methods from source.

In my experience, this will reveal places in the code that reference
globals that have been removed from the system or which cannot
be defined or initialized in the shrunken image.

If you can recompile all the methods without error, then go ahead
and drop the source, do a full gc.

The following rather simple script reduces a pristine 16MB alpha image by about 50% while leaving most of the functionality in place (well, depending on your preferences).

It deletes
MVC Wonderland
Example projects: 
PluggableWebServer.
VMConstruction


The following was tested with a 4599 image (January 2002) which had 16008 kB in the beginning.

hide global flaps and delete the example projects manually.

"delete example projects manually"

"make sure the current project is the topmost project"
Project current setParent: Project current.

"remove changes files"
ChangeSorter removeChangeSetsNamedSuchThat:
[:aName | aName first isDigit].
/tt

"new image size 10749kB"

tt
Smalltalk at: #Wonderland ifPresent:[:cls| cls removeActorPrototypesFromSystem].
Player freeUnreferencedSubclasses.
MorphicModel removeUninstantiatedModels.
Utilities classPool at: #ScrapsBook put: nil.
Utilities zapUpdateDownloader.
ProjectHistory currentHistory initialize.
Project rebuildAllProjects.
/tt

"9663kb"
ttSmalltalk discardVMConstruction./tt
"8047kb"
tt
SystemOrganization removeSystemCategory: 'Morphic-Experimental'.
"7951kB"


SystemOrganization removeSystemCategory: 'Morphic-Games'.
"7845kB"

Smalltalk discardMVC.

"7589kB"


Smalltalk discardWonderland.
"7275kB"

Smalltalk discardPluggableWebServer.
/tt

Size of image: 7328kB

tt
SystemOrganization categories do: [ :cat | (cat beginsWith: 'Speech')
ifTrue: [ SystemOrganization removeSystemCategory: cat]].
/tt


The following code is the text of the method #majorShrink included in a #4599 image. You can use this as an example (which does not work anymore) to come up with your own version which suits your specific needs.
tt
bmajorShrink/b
"Undertake a major shrinkage of the image.
This method throws out lots of the system that is not needed for, eg, operation in a hand-held PC. majorShrink produces a 999k image in Squeak 2.8
Smalltalk majorShrink; abandonSources; lastRemoval"

| oldDicts newDicts |
Smalltalk isMorphic ifTrue: [^ self error: 'You can only run majorShrink in MVC'].
Project current isTopProject ifFalse: [^ self error: 'You can only run majorShrink in the top project'].
(Smalltalk confirm: 'All sub-projects will be deleted from this image.
You should already have made a backup copy,
or you must save with a different name after shrinking.
Shall we proceed to discard most of the content in this image?')
ifFalse: [^ self inform: 'No changes have been made.'].

"Remove all projects but the current one. - saves 522k"
ProjectView allInstancesDo: [:pv | pv controller closeAndUnscheduleNoTerminate].
Project current setParent: Project current.
MorphWorldView allInstancesDo: [:pv | pv topView controller closeAndUnscheduleNoTerminate].
Smalltalk at: #Wonderland ifPresent:[:cls| cls removeActorPrototypesFromSystem].
Player freeUnreferencedSubclasses.
MorphicModel removeUninstantiatedModels.
Utilities classPool at: #ScrapsBook put: nil.
Utilities zapUpdateDownloader.
ProjectHistory currentHistory initialize.
Project rebuildAllProjects.

Smalltalk discardVMConstruction. "755k"
Smalltalk discardSoundSynthesis. "544k"
Smalltalk discardOddsAndEnds. "227k"
Smalltalk discardNetworking. "234k"
Smalltalk discard3D. "407k"
Smalltalk discardFFI. "33k"
Smalltalk discardMorphic. "1372k"
Symbol rehash. "40k"
"Above by itself saves about 4,238k"

"Remove references to a few classes to be deleted, so that they won't leave obsolete versions around."
FileList removeSelector: #fileIntoNewChangeSet.
ChangeSet class compile: 'defaultName
^ ''Changes'' ' classified: 'initialization'.
ScreenController removeSelector: #openChangeManager.
ScreenController removeSelector: #exitProject.
ScreenController removeSelector: #openProject.
ScreenController removeSelector: #viewImageImports.

"Now delete various other classes.."
SystemOrganization removeSystemCategory: 'Graphics-Files'.
SystemOrganization removeSystemCategory: 'System-Object Storage'.
Smalltalk removeClassNamed: #ProjectController.
Smalltalk removeClassNamed: #ProjectView.
"Smalltalk removeClassNamed: #Project."
Smalltalk removeClassNamed: #Environment.
Smalltalk removeClassNamed: #Component1.

Smalltalk removeClassNamed: #FormSetFont.
Smalltalk removeClassNamed: #FontSet.
Smalltalk removeClassNamed: #InstructionPrinter.
Smalltalk removeClassNamed: #ChangeSorter.
Smalltalk removeClassNamed: #DualChangeSorter.
Smalltalk removeClassNamed: #EmphasizedMenu.
Smalltalk removeClassNamed: #MessageTally.

StringHolder class removeSelector: #originalWorkspaceContents.
CompiledMethod removeSelector: #symbolic.

RemoteString removeSelector: #makeNewTextAttVersion.
Utilities class removeSelector: #absorbUpdatesFromServer.
Smalltalk removeClassNamed: #PenPointRecorder.
Smalltalk removeClassNamed: #Path.
Smalltalk removeClassNamed: #Base64MimeConverter.
"Smalltalk removeClassNamed: #EToySystem. Dont bother - its very small and used for timestamps etc"
Smalltalk removeClassNamed: #RWBinaryOrTextStream.
Smalltalk removeClassNamed: #AttributedTextStream.
Smalltalk removeClassNamed: #WordNet.
Smalltalk removeClassNamed: #SelectorBrowser.

TextStyle allSubInstancesDo:
[:ts | ts newFontArray: (ts fontArray copyFrom: 1 to: (2 min: ts fontArray size))].
ListParagraph initialize.
PopUpMenu initialize.
StandardSystemView initialize.

Smalltalk noChanges.
ChangeSorter classPool at: #AllChangeSets
put: (OrderedCollection with: Smalltalk changes).
SystemDictionary removeSelector: #majorShrink.

[Smalltalk removeAllUnSentMessages 0]
whileTrue:
[Smalltalk unusedClasses do: [:c | (Smalltalk at: c) removeFromSystem]].
SystemOrganization removeEmptyCategories.
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.
Smalltalk changes initialize.

"seems to take more than one try to gc all the weak refs in SymbolTable"

3 timesRepeat: [
Smalltalk garbageCollect.
Symbol compactSymbolTable.
].
/tt
iNeeds update. The steps listed below don't work anymore right now as Squeak starts up with aMorphicas it's topmostProject.
There is a fair amount of support in Squeak for eliminating unnecessary code. Look in SystemDictionarymajorShrink and related methods.

Dan Ingalls

Running #majorShrink discards most non-fundamental subsystems within Squeak, including Morphic, so it must be run from within MVC. For those who have not used #majorShrink before, do the following:


(A SystemDictionarymajorShrink operation should reduce the size of the image to under 1 megabyte.)

There are also various methods for doing partial shrinks; look at all of the discardFoo methods inSystemDictionary.

From: JArchibald@aol.com
Date: Thu, 21 Jun 2001 09:56:45 EDT
Subject: Re: majorShrink

>6/21/01 3:44:21 AM EDT, fuxoft@terminal.cz =>
I tried "Smalltalk majorShrink" just for the hell of it and received "You
can only run majorShrink in the top project" error. >>

Hi Frantisek,

You probably tried to evaluate the #majorShrink that is in the distributed
image. The majorShrink that you need is in the fileIn at:


ftp://st.cs.uiuc.edu/pub/Smalltalk/Squeak/3.0/platform-independent/MajorShrink

For3.0.cs.gz

which is where Dan put it when 3.0 was released.

File this in and you're ready to go. You do need to be in an MVC project to
evaluate this appropriately. To get to one, select from the background menu,
'open...>MVC project' and then click on the mini-window that appears. Then
evaluate "Smalltalk majorShrink; abandonSources; lastRemoval."

This does not appear to execute correctly in the latest 3.1 for unstable test
pilots. I'll have to fix that.

Cheers,
Jerry.


From: Kevin Fisher
Subject: Re: [Rant] Shrinking problems and rampant interdependencies
Date: Mon, 23 Jul 2001 21:11:46 -0400

On Mon, Jul 23, 2001 at 04:57:23PM -0700, Tim Rowledge wrote:
> I'm trying to shrink an image. I need make an image with morphic but
> relatively little else outside the typical core stuff.

I feel your pain. :)


>
> In other words, a fairly typical sort of setup that many of us might
> want to use for a demo package; indeed very like the setup we used for
> the exobox code. It's not too hard to hack the majorShrink code to leave
> in morphic, add some code to dump odd parts of unwanted Morphic etc, but
> there are so many places where rampant interdependencies screw you.


Well, check out http://www.reasonability.net/ipaq... I have a changeset
up there that I use to shrink Squeak to fit on my iPaq. It throws away
a lot, but keeps a functional core. I make no guarantees, but it works
for me...heck, I can't even guarantee that I've kept/tossed the right
things, but the image resulting works just fine (so far!).

The results definitely vary depending on the image you run it on...if you
use this changeset on the 3.0 image you can get a very small Morphic
image (around 4.8M). However, the 3.1 image with the latest changesets is
about twice that size, with the same shrinker changeset.

(Note, the above sizes are also source-abandoned).

I've been unable to figure out just what is making the 3.1 image so
much bigger!

> Just as a for example, why does StandardScriptingSystem hold all the
icon Forms used in the debugger? You can't dump that class if you want a
working image. Foo!

I swear there are even more than back in 2.8. I'm annoyed.

tim


Check out the Projects that are resident in the image. Even after shrinkage
a number of the demo projects will still be around...I usually manually
delete them with "Project deletingProject:". Strangely, the "Building with
Squeak" project always returns to the Project list after I've shrunken
my image!

Also, I think something may be funky with the "Help-space left" command

in TheWorldMenu...whenever I select it, it ALWAYS reports that there is
"one undo record left in the system." Not sure if this is normal, or if
if this means there is something hanging around in memory that just refuses
to get GC'd.

From: Kevin Fisher kgf@golden.net>
Subject: Re: [Rant] Shrinking problems and rampant interdependencies
Date: Tue, 24 Jul 2001 08:09:48 -0400

On Mon, Jul 23, 2001 at 06:42:10PM -0700, Andreas Raab wrote:
[snip]
> This doesn't sound right. The Squeakland plugin image (which is 3.1 based)
> is about 5.5MB and it includes everything but FFI, 3D, Speech, and VM
> construction stuff.
>
> BTW, a common reason for large images are change sets - dumping all the
> updates can bring you a long step forward.

How do I dump the updates? My shrinkForIpaq method is essentially
a copy of majorShrink with some key changes (ie dump MVC, keep anything
that breaks Morphic if removed). If majorShrink abandons the updates
then it's probable that my shrinkForIpaq does as well.

I usually do a "Smalltalk shrinkForIpaq" followed by
"Smalltalk abandonSources; condenseChanges".

>
> > Also, I think something may be funky with the "Help->space
> > left" command in TheWorldMenu...whenever I select it, it ALWAYS
> > reports that there is "one undo record left in the system."
> > Not sure if this is normal, or if if this means there is something
> > hanging around in memory that just refuses to get GC'd.
>
> The latter. The following will do the trick:
>
> Smalltalk allObjectsDo:[:o|
> o isMorph ifTrue:[o removeProperty: #undoGrabCommand]].
>
> [This is due to a period between updates in which the undo command was not
> properly nuked]
>
> Cheers,
> - Andreas
>


Ah...thanks for that. It wasn't causing me any problems, but it was kind
of annoying. :)

Date: Thu, 26 Apr 2001 01:03:25 -0400 (EDT)
From: Bijan Parsia
Subject: Re: Smalltalk & Squeak featured on Slashdot

On Thu, 26 Apr 2001, Richard A. O'Keefe wrote:
[snip]
> Looking back through an old OOPSLA proceedings, I stumbled across a
> paper about Squeak. The image back then was about 1MB. Now it is about 9MB.

A shrinked image (with MVC and IDE) can prolly still come in under
1MB. With Morphic and a few other yummies you should be able to stay under
2.5 or so.

> It would be interesting to know roughly where the space is going.
> - IDE
> - Morphic
> - Scamper
> - Celeste
> - Balloon3D
> - Alice
> - Sound
> - Speech
> - ...
>
> Scamper is cute, but it feels even slower than HotJava (which is saying
> something) and I can't print from it, so
for me: 
it is bloat.

Hmm. I'm surprised at that. Scamper (for many things) is pretty nippy for
me. Two things which seem to get boggy are 1) downloading (and when this
gets bad, it's all bad ;)) and 2) scrolling really large pages (a know
problem with text morphs).

>Celeste is cool, but I continue to use /usr/bin/mailx as my mailer
precisely because it _can't_ do fancy things, and I had trouble hooking
it into UNIX mail anyway, so _for me_ it is bloat.

Well, it's "not used" :) Part of the problem with this is there are
"parts" of Celeste and Scamper, such as the URL classes or MailMessage,
that are things one most likely would like to have around. I.e., once you
get past the bits of these things that are really extentions of the core
system, what's left isn't (always) that huge.

But, of course, if you don't need them, you don't need them.
[snip]

But here's a tip to help figure some of this out. SystemDictionary has a
few useful space analysis tools in the miscellaneous protocol,
especially #spaceTally. From it's comment:

"Answer a collection of tuples representing the memory space (in
bytes) consumed by the code and instances of each class in the system. The
tuples have the form:
class code size instance count space for instances
(If you run this, be prepared for it to take a little while ;)

I ran this little do it on the result:

self detect:[:i | i first name = #Scamper]

and it gave me:

#(Scamper 9631 0 0)

Which, of course, doesn't cover much of the scamper classes. So I ran
this:

categories
categories := #(#'Network-Url' #'Network-Web Browser'
#'Network-HTML Formatter' #'Network-HTML Forms'
#'Network-HTML Parser Entities'
#'Network-HTML Parser' #'Network-HTML Tokenizer').
categories := self select: [:i | categories includes: i first category].
categories inject: 0 into: [:total :i | total + i second + i fourth]

And got:
71026

Changing the assignment:
categories := #(#'Network-Mail Reader').
yields:
55085

These are _not_ the big sources of image growth :)

A slight modification:

categories
categories := self select: [:i | i first category
beginsWith: 'Balloon3D'].
categories inject: 0 into: [:total :i | total + i second + i fourth]

Yields:
435885

Now, testing for beginsWith: 'Morphic' gets us:

3379693

Bloat at last!!!

But gee, to echo your point, Morphic is alot of stuff. There's a PDA, a
bunch of games, a EPS outputter, a set of interface widgets (a lot of
which are in use in my system, since I'm running in morphic and have a
gazillion windows open, etc.).

Not to shabby for an experimental, unoptimized system.

(This is out of 13.6 MB image, which, obviously, has seen some use and has
a fair number of extras loaded.)

(Assuming I haven't blown the calcuation any :))

This is _not_ to say that I won't be happy when Squeak gets a Smalltalk/X
like "load on demand" facility. Indeed, I'll be all the happier!

(FWIW, classes are generally cheap in Smalltalk. Just having more classes
isn't going to swell your system a lot. Ok ok, CompiledMethod leads the
space filling with an instances space size of 2228576, but that's with


> Is _any_ Smalltalk dialect used for such
applications [i.e., shell scripts and cgis–ed]? I suppose
> GNU Smalltalk or Budd's Little Smalltalk might be usable.

SmallScript is certainly targeted to those applications (among
others). Quick start up and dynamic loading are big features (it doesn't
store an image, but always reconstitutes one from files).

> Squeak is
> - a multimedia library
> - a compiler and development environment
> amongst other things.
[snip]

And, really, at it's heart, a place to inhabit.

(And _no_ you don't want to see my house :))

> I'm not sure that I _have_ a position on the "is Squeak bloated" question.
> I can see value in having a smaller image; but everywhere I look I see
> systems that are _less_ useful to me taking _more_ memory.

Indeed! And worse, less _interesting_. All I can _ever_ do with Acrobat is crash my machine view and sometimes print a subset of
pdfs I encounter. I, personally, get some entertainment from browsing
around the system and playing around with morph toys.

However, I've advocated that just as we have a "tiny" image around, it
wouldn't hurt to have a few "midsized" images around. Perhaps as a first step toward discovering some natural "break lines" in the system.

Cheers,
Bijan Parsia.

From: "Andreas Raab"
Subject: RE: [Rant] Shrinking problems and rampant interdependencies
Date: Tue, 24 Jul 2001 12:35:09 -0700

Kevin,

> How do I dump the updates?

Here's my (annotated) shrink script - have a look at it and see what might
benefit yours. Note that this one is written under the assumption that:
a) All windows have been closed
b) All global flaps were DESTROYED (not just hidden)

"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].
].
"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 initialize.
"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'].
"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.
"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.
Smalltalk garbageCollect.
"Remove refs to old ControlManager"
ScheduledControllers _ nil.
"Flush obsolete subclasses"
Behavior flushObsoleteSubclasses.
Smalltalk garbageCollect.
Smalltalk obsoleteBehaviors isEmpty
ifFalse:[self error:'Still have obsolete behaviors'].

At this point, your image should be at about 5.5 MB. The last test is
actually the most important one. If there's any stuff in the image that
shouldn't be in there it almost always shows up as some sort of obsolete
behavior. Tracking those is important.

Cheers,
- Andreas

From: Scott Wallace
Subject: RE: [Rant] Shrinking problems and rampant interdependencies
Date: Thu, 26 Jul 2001 18:23:05 -0700

At 5:28 PM -0700 7/26/01, Tim Rowledge wrote:
>
>...I also spent some time trying to peel StandardScriptingSystem away from
>some of the myriad places it sticks to, but eventually got beaten by its
>partner in crime 'Presenter' which is also everywhere I didn't want it
>to be. I gave up eventually, but I'm sure it must be possible given
>enough aspirin.


Tim,

Notice that there is actually only _one_ reference to
StandardScriptingSystem in the entire image, and that that lone
reference is in SystemDictionary method #makeExternalRelease, which
has no senders in the image and which is only called once or twice a
year, only manually, and only by Dan Ingalls. So in fact there is
virtually _nothing_ nailing StandardScriptingSystem down.

Instead, there is a global, #ScriptingSystem, which needs to be
present and which points to an instance of _something_, which need
not be a StandardScriptingSystem instance.

To solve your problem with very little effort, it should quite easily
work to define a MiniScriptingSystem class, a simple subclass of
Object, which will field all the message-sends directed to
  1. ScriptingSystem in your trimmed-down image.

Probably, the only message ever sent to ScriptingSystem by any
objects remaining in your stripped-down system is #formAtKey:. Maybe
also #fontForButtons and maybe something else, but in any case the
set of messages your MiniScriptingSystem will need to handle will be
very small.

Once you've defined your tiny MiniScriptingSystem class (which will
serve primarily, or only, to hold on to and provide access to a
dictionary of Forms,) all you need do is issue:

Smalltalk at: #ScriptingSystem put: MiniScriptingSystem new

and the next time you apply the shrinking procedure,
StandardScriptingSystem should be unreferenced (be sure
SystemDictionary.makeInternalRelease is gone or doctored!) and hence
should get stripped.

– Scott

From: Tim Rowledge
Subject: RE: [Rant] Shrinking problems and rampant interdependencies
Date: Sat, 28 Jul 2001 14:12:54 -0700

In message
Scott Wallace wrote:

> To solve your problem with very little effort, it should quite easily
> work to define a MiniScriptingSystem class, a simple subclass of
> Object, which will field all the message-sends directed to
> #ScriptingSystem in your trimmed-down image.
Actually I decided to (ab)use Morph for this purpose, since it seemed to
me that storing the icons for halos etc has very little to do with any
scripting system.
>
> Probably, the only message ever sent to ScriptingSystem by any
> objects remaining in your stripped-down system is #formAtKey:.
...and it seems like some helpString related bits here and there.

Like I said, even though I managed to remove the need for
StandardScriptingSystem I just couldn't build up the energy to decide
what (if anything) to do about Presenter. Some comments claim it is
optional, other code makes it look crucial... feh, never mind.

tim
Tim Rowledge, tim@sumeru.stanford.edu, http://sumeru.stanford.edu/tim
Strange OpCodes: ESR: Emulate Slide Rule