[Morphic] About repositories and safe Unload/Loading of Nebraska

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Fri Nov 25 09:48:08 CET 2005


Cees De Groot puso en su mail :

> I'm stunned. Why? In fact, '*nebraska-support' should already be enough.
Well, I take your Nebraska-CdG.5.mcz as starting point.
Doing Dan thing and others , I found WorldState-*nebraska-Nebraska
support.st not in *Extensions.

And I should add a SelectallMethodsInCategorybeginsWith.1.cs because I don't
find a easy way to select ALL what begins with *nebraska.

I don't send to others thinking what sure exist a better way and I don't
found.

> I don't know... Can't we come up with something better to find out
> whether components are available or not? I mean, all this digging
> around in SystemOrganization (or Smalltalk, or...)

This should a question what Stef and people working on Kernel have a better
answer.
If you don't modify as I do, the image simple go nuts.
And how manage the loading again ?
You can't have in a single Monticello or in a .cs. (I try) .

So the take what I send as "fist try".

And thanks you, Juan and others , I learn about this tricky and dirty
business

-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #6704] on 10 November 2005 at 8:43:54 am'!
"Change Set:		SelectallMethodsInCategorybeginsWith
Date:			10 November 2005
Author:			Edgar J. De Cleene

I found useful selecing all methods with category beginning with choosen pattern>"!


!ClassDescription methodsFor: 'accessing method dictionary' stamp: 'edc 11/10/2005 08:35'!
allMethodsInCategorybeginsWith: aName 
	"Answer a list of all the method categories of the receiver and all its 
	superclasses"
	| aColl categorybeginsWith |
	aColl := OrderedCollection new.
	self withAllSuperclasses
		do: [:aClass | categorybeginsWith := aClass organization categories
										select: [:c | c beginsWith: aName]
										thenCollect: [:any | any].
							categorybeginsWith isEmptyOrNil
								ifFalse: [categorybeginsWith
										do: [:cat | aColl
				addAll: (aClass organization listAtCategoryNamed: cat)]]].
	^ aColl asSet asSortedArray! !


!SystemNavigation methodsFor: 'browse' stamp: 'edc 11/10/2005 07:00'!
allMethodsInCategorybeginsWith: category 
	| aCollection |
	aCollection _ SortedCollection new.
	Cursor wait showWhile:
		[self allBehaviorsDo:
			[:x | (x allMethodsInCategorybeginsWith: category) do:
				[:sel | aCollection add: x name , ' ' , sel]]].
	^aCollection.
	! !

-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #6704] on 24 November 2005 at 8:00:06 am'!

!ReleaseBuilder methodsFor: 'unloading' stamp: 'edc 11/24/2005 07:59'!
unloadNebraska
	"Safe unload of Nebraska from 3.9a 6703 image"
	"ReleaseBuilder new unloadNebraska"
	| toRemove selectorList actualClass |
	toRemove := SystemOrganization categoriesMatching: 'Nebraska*'.
	toRemove
		do: [:each | SystemOrganization removeSystemCategory: each].
	selectorList := SystemNavigation default allMethodsInCategorybeginsWith: '*nebraska'.
	selectorList
		do: [:each | 
			actualClass := Smalltalk
						atOrBelow: (each findTokens: ' ') first asSymbol
						ifAbsent: [].
			actualClass removeSelector: (each findTokens: ' ') last asSymbol].
	ReleaseBuilder new fixObsoleteReferences.
	SystemOrganization removeEmptyCategories.
	Smalltalk garbageCollect.! !


!WorldState methodsFor: 'update cycle' stamp: 'edc 11/15/2005 10:01'!
forceDamageToScreen: allDamage

	"here for the convenience of NebraskaWorldState"
	Display forceDamageToScreen: allDamage.
	
	(SystemOrganization categoriesMatching: 'Nebraska*') ifNotEmpty:[
	self remoteCanvasesDo: [ :each | 
		allDamage do: [:r | each forceToScreen: r].
		each displayIsFullyUpdated.]].! !


!WorldState reorganize!
('alarms' addAlarm:withArguments:for:at: adjustAlarmTimes: alarmSortBlock alarms removeAlarm:for: triggerAlarmsBefore:)
('canvas' assuredCanvas canvas canvas: doFullRepaint recordDamagedRect: resetDamageRecorder viewBox viewBox:)
('hands' activeHand addHand: hands handsDo: handsReverseDo: removeHand: selectHandsToDrawForDamage:)
('initialization' initialize stepListSize stepListSortBlock)
('object fileIn' convertAlarms convertStepList)
('objects from disk' convertToCurrentVersion:refStream:)
('stepping' adjustWakeupTimesIfNecessary adjustWakeupTimes: cleanseStepListForWorld: isStepping: isStepping:selector: listOfSteppingMorphs runLocalStepMethodsIn: runStepMethodsIn: startStepping:at:selector:arguments:stepTime: stopStepping: stopStepping:selector:)
('undo' commandHistory)
('undo support' clearCommandHistory)
('update cycle' checkIfUpdateNeeded displayWorldSafely: displayWorld:submorphs: doDeferredUpdatingFor: doOneCycleFor: doOneCycleNowFor: doOneSubCycleFor: drawWorld:submorphs:invalidAreasOn: forceDamageToScreen: handleFatalDrawingError: interCyclePause:)
('*MorphicExtras-hands' activeHand:)
('*nebraska-*nebraska-Nebraska support' addRemoteCanvas: assuredRemoteCanvas releaseRemoteServer remoteCanvasesDo: remoteServer remoteServer: removeRemoteCanvas:)
('*MorphicExtras-update cycle' displayWorldAsTwoTone:submorphs:color: doOneCycleInBackground startBackgroundProcess)
('*MorphicExtras-initialization' stepListSummary)
!



More information about the Morphic mailing list