Login

Squeak Smalltalk Image Maintenance

Something I've learned since I've become a Smalltalker, is that to live in an image, one must learn to maintain the image.

I used to keep a fresh image handy and whenever things got out of whack, I'd just start over in a new image. I did this out of ignorance; I wasn't aware of how to keep one image from collecting cruft. I'd end up with a ton of obsolete classes that I didn't have a clue how to get rid of, or even understand how they came to be.

This happened a lot when I'd load or unload Monticello packages I'd created, usually due to hidden dependencies between packages. Eventually I learned to package my code better, and found a patch for Monticello that made dependencies actually work the way I expected them to.

I also learned about a great little tool called the PointerFinder from someone on Squeak-Dev, with which I could find all references to an object allowing me to hunt down and clean up bad refs, ridding myself of all those obsolete classes that would accumulate over time. This also taught me how those references came to be, and why they couldn't be cleaned up automatically. This one tool finally allowed me to live in one image and just keep it clean, I rarely if ever need to start from a fresh image any more.

Ultimately, I developed my own version of #garbageCollect that I tossed into a utility class to help me maintain my image. Whenever I find some new maintenance tip to help keep my image clean and organized, I just toss it in here. The last few lines are the most interesting, either everything goes well and the image is saved, or obsolete classes are found and a PointerFinder is launched on each one forcing me to clean up those bad references right away.

Here's what I've collected so far...

garbageCollect
    | tasks |
    tasks := OrderedCollection new
                add: [MCFileBasedRepository flushAllCaches];
                add: [WARegistry clearAllHandlers];
                add: [SMSqueakMap default clearCaches];
                add: [Smalltalk removeEmptyMessageCategories];
                add: [Workspace
                        allSubInstancesDo: [:each | each setBindings: Dictionary new]];
                add: [Undeclared removeUnreferencedKeys];
                add: [Categorizer sortAllCategories];
                add: [ODBCConnection cleanAll];
                add: [Symbol compactSymbolTable];
                add: [ReleaseBuilderDeveloper new fixObsoleteReferences];
                add: [Smalltalk garbageCollectMost];
                 yourself.
    Utilities
        informUserDuring: [:bar | tasks
                do: [:block | 
                    bar value: block printString.
                    [block value]
                        on: Error
                        do: [:error | Transcript show: error;
                                 cr]]].
    SystemNavigation default obsoleteClasses isEmpty
        ifTrue: [SmalltalkImage current saveSession]
        ifFalse: [SystemNavigation default obsoleteClasses
                do: [:each | [PointerFinder on: each]
                        on: Error
                        do: [:error | Transcript show: error; cr]]]

Hopefully the code speaks for itself, and you can remove anything that doesn't apply to your image. If you have any new tips that I'm unaware of, I'd love to hear about them. I'm always looking for a new trick!

I have this wired up to a hot key via KeyBinder, and simply run it once in a while to ensure everything stays nice and clean, and the image organized and small.

Comments (automatically disabled after 1 year)

Göran Krampe] 6379 days ago

Hi!

I notice you use "SMSqueakMap default clearCaches". This "nils out" the contents in the map itself - but I am hard pressed to see how that would remove any "dangling" objects since the map is totally self contained AFAIK.

But I can be wrong. :)

Ramon Leon 6379 days ago

I'm not sure where I picked that one up, maybe I was just hoping it'd reduce memory use within the image for deployment purposes. I just like clean caches!

Brian Brown 6379 days ago

Hey Ramon, are you going to publish your Utility class somewhere? :-)

Ramon Leon 6379 days ago

Isn't that what I'm doing... one post at a time. ;) Besides... you have my base image, snoop around.

timbomb 6379 days ago

Hey Ramon, I just wanted to thank you for taking the time to blog about Smalltalk and Seaside from the point of view of a working programmer. It's great to see that you're making it work, but posts like this where you're obviously doing real stuff, not just experimenting are tremendously valuable - not just as HOWTOs for other Seaside folk, but also to reinforce the credibility of the environment.

Summary: you rock :)

Tim

Ramon Leon 6379 days ago

Thanks, I appreciate the kind words.

[...] Squeak Smalltalk Image Maintainence | OnSmalltalk: A Squeak, Smalltalk, Seaside, Web Development Blog Ramon’s tips for maintaining a Smalltalk image over time. (tags: smalltalk programming monticello) [...]

Michael Davies 6288 days ago

Hi Ramon, I just found this useful bit of code while googling for an issue with obsolete classes. Thanks for publishing this. (Thanks also for your comments on my blog yesterday).

Cheers, Michael

Ramon Leon 6288 days ago

Any time.

nitin bhatia 6265 days ago

goood

Warren Wilkinson 6156 days ago

Thank you so much for this! I'd spent hours looking around for ways to clean up my squeak image and wasn't getting anywhere chasing down pointers trying to find why my image was retaining several thousand database entries in memory after Seaside was terminated.

Running this once brought my image down from 99 Megs to 26 Megs. (And the previous night my image was up to 360 Megs forcing me to revert to a previously saved image).

Ramon Leon 6156 days ago

You're welcome.

about me|good books|popular posts|atom|rss