[Cuis-dev] [RFC] Namespaces, changes to SystemDictionary, Object and a dictionary class for tracking environment implementations

Gerald Klix cuis.01 at klix.ch
Mon Oct 5 03:22:15 PDT 2020


Hi all, hi Juan,

here comes the announced monster change set.
I hope it "Carries it's own wait."

I added a EnvironmentImplementationDictionary class and changed all 
relevant methods in SystemDictionary to ask the single instance of 
EnvironmentImplementationDictionary if some
implementation can handle the request.

It is the simplest implementation I can think
of, that is consistent with your statement:
"Yes. I want Cuis to be a good place for doing any kinds of experiments. 
Adding hooks for optional pluggable behavior is a big part of that."

Please tell me if this is acceptable or
to big a change.


Best Regards,

Gerald
-------------- next part --------------
'From Cuis 5.0 [latest update: #4384] on 5 October 2020 at 11:56:57 am'!
"Change Set:		4387-SystemDictionary-refactorings-1-GeraldKlix-2020Oct02-21h11m
Date:			5 October 2020
Author:			Gerald Klix

Oddles of changes to Cuis' Core to accomodate multiple environment implemantations"!

Smalltalk renameClassNamed: #KlgEnvEnvironmentImplementations as: #EnvironmentImplementationsDictionary!
!classDefinition: #EnvironmentImplementationsDictionary category: #'System-Support'!
IdentityDictionary subclass: #EnvironmentImplementationsDictionary
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Support'!

!Object methodsFor: 'environment support' stamp: 'KLG 10/3/2020 06:11:48'!
installInEnvironmentAndReport
	"Install me in an environment and report the result.
	
 	This message is sent from SystemDictionary>>#at:put: and others.
	It enables objects that are perceived globaly visable by unaware tools,
	to avoid being put in Smalltalk. Instead this method should install the object
	in an environment or any other sort of namespace.
	
	Answer true if I was installed somewhere else. Answer false instead."

	^ false! !


!EnvironmentImplementationsDictionary methodsFor: 'class names' stamp: 'KLG 10/3/2020 08:13:27'!
classNamed: className 
	"className is either a class name or a class name followed by ' class'.
	Answer the class or metaclass it names.
	Answer nil if no class by that name.
	
	See SystemDictionary>>#classNamed:"

	self do: [ :manager |
		manager classNamed: className :: ifNotNil: [ :classFound | ^ classFound ] ].
	^ nil! !

!EnvironmentImplementationsDictionary methodsFor: 'class names' stamp: 'KLG 10/4/2020 17:05:32'!
fillClassNameCache: aClassSet andNonClassNameCache: aNonClassSet
	"Ask the implementation to fill the caches.
	
	See: SystemDictionary>>#fillCaches"

	self do: [ :manager |
		manager 
			fillClassNameCache: aClassSet
			andNonClassNameCache: aNonClassSet ]! !

!EnvironmentImplementationsDictionary methodsFor: 'class names' stamp: 'KLG 10/4/2020 17:06:12'!
hasClassNamed: aString
	"Answer whether there is a class of the given name, but don't intern aString if it's not alrady interned.  4/29/96 sw
	
	See SystemDictionary>>#hasClassNamed:
	"

	self do: [ :manager |
		manager hasClassNamed: aString :: ifTrue: [ ^ true ] ].
	^ false.! !

!EnvironmentImplementationsDictionary methodsFor: 'class names' stamp: 'KLG 10/4/2020 17:06:58'!
prepareToRenameClass: aClass as: newName 
	"Rename a class to a new name.
	
	Ask all environment implementations to handle that request.
	Implementations are up to themselves, when it comes
	to manage categories.
	
	See SystemDictionary>>#prepareToRenameClass:as: "

	self do: [ :manger |
		manger prepareToRenameClass: aClass as: newName :: ifTrue: [
			^ true ] ].
	^ false! !

!EnvironmentImplementationsDictionary methodsFor: 'class names' stamp: 'KLG 10/4/2020 17:08:19'!
removeClassNamed: aName
	"Invoked from fileouts:  if there is currently a class in the system named aName, then remove it.  If anything untoward happens, report it in the Transcript.  
	
	Ask the implementations to handle that case.
	
	See SystemDictionary>>#removeClassNamed:"
	
	self flag: #ProbablyOverkill.
	
	self do: [ :manager |
		manager removeClassNamed: aName :: ifTrue: [ ^ true ] ].
	^ false

! !

!EnvironmentImplementationsDictionary methodsFor: 'class names' stamp: 'KLG 10/4/2020 17:09:36'!
renameClassNamed: oldName as: newName
	"Invoked from fileouts:  if there is currently a class in the system named oldName, then rename it to newName.  If anything untoward happens, report it in the Transcript.  
	
	Ask the environment implementations to handle that case.
	
	See SystemDictionary>>#renameClassNamed:as:"

	self do: [ :manger |
		manger renameClassNamed: oldName as: newName :: ifTrue: [ ^ true ] ].
	^ false! !

!EnvironmentImplementationsDictionary methodsFor: 'housekeeping' stamp: 'KLG 10/5/2020 11:38:12'!
addObsoleteClassesTo: anOrderedCollection
	"Ask all implementations to add their obsolete classes to anOrderedColletion.
	
	See SystemDictionary>>#addObsoleteClasses"

	self do: [ :manager | manager addObsoleteClassesTo: anOrderedCollection ]! !

!EnvironmentImplementationsDictionary methodsFor: 'housekeeping' stamp: 'KLG 10/4/2020 17:10:55'!
cleanOutUndeclared
	"Clean undeclared stuff in every environment implementation.
	
	See See SystemDictionary>>#cleanOutUndeclared"
	
	self do: [ :manger | manger cleanOutUndeclared ]! !

!EnvironmentImplementationsDictionary methodsFor: 'retrieving' stamp: 'KLG 10/4/2020 17:12:25'!
addToPoolUsers: aDictionary
	"Add references to shared pools to aDictionary.
	
	See SystemDictionary>>#poolUsers"

	self do: [ :manager | manager addToPoolUsers: aDictionary]! !

!EnvironmentImplementationsDictionary methodsFor: 'retrieving' stamp: 'KLG 10/4/2020 17:11:29'!
allBehaviorsDo: aBlock 
	"Evaluate the argument, aBlock, for each kind of Behavior in the system 
	(that is, Object and its subclasses).
	
	See SystemDictionary>>#allBehaviorsDo:"

	self do: [ :manager | manager allBehaviorsDo: aBlock ]! !

!EnvironmentImplementationsDictionary methodsFor: 'shrinking' stamp: 'KLG 10/5/2020 11:49:59'!
removeSelector: descriptor
	"Safely remove a selector from a class (or metaclass). If the class
	or the method doesn't exist anymore, never mind and answer nil.
	This method should be used instead of 'Class removeSelector: #method'
	to omit global class references.
	
	Evaluate a aBlock if one of the implementations handle this request
	
	See: See SystemDictionary>>#removeSelector:."
	
	self do: [ :manger |
		manger removeSelector: descriptor :: ifNotNil: [  :affectedBehaviour |
			^ affectedBehaviour ] ].
	^ nil
! !


!SystemDictionary methodsFor: 'environment support' stamp: 'KLG 10/3/2020 07:22:36'!
environmentImplementations
	"Answer the environment implementations dictionary."

	^ self at: #EnvironmentImplementations ifAbsentPut: [
		EnvironmentImplementationsDictionary new ]! !


!EnvironmentImplementationsDictionary class methodsFor: 'class initialization' stamp: 'KLG 10/2/2020 21:16:31'!
initialize
	"Initialize me. That means: Create my sole instance."

	super initialize.
	Smalltalk at: #EnvironmentImplementations put: self new! !


!SystemDictionary methodsFor: 'class names' stamp: 'KLG 10/5/2020 11:27:53'!
classNamed: className 
	"className is either a class name or a class name followed by ' class'.
	Answer the class or metaclass it names.
	Answer nil if no class by that name."
	"
	Smalltalk classNamed: #Point
	Smalltalk classNamed: 'Point'
	Smalltalk classNamed: 'Point class'
	Smalltalk classNamed: 'BogusClassName'
	Smalltalk classNamed: 'BogusClassName class'

	Smalltalk classNamed: #Display
	Smalltalk classNamed: 'Display'
	Smalltalk classNamed: 'Display class'
	"

	self environmentImplementations classNamed: className :: ifNotNil: [ :classFound |
		^ classFound ].
	Smalltalk at: className asSymbol ifPresent: [ :found |
		^ found isBehavior ifTrue: [ found ]].

	(className withoutSuffix: ' class') ifNotNil: [ :baseName |
		Smalltalk at: baseName asSymbol ifPresent: [ :found |
			^ found isBehavior ifTrue: [ found class ]]].

	^ nil! !

!SystemDictionary methodsFor: 'class names' stamp: 'KLG 10/5/2020 11:31:24'!
fillCaches
	"Fill cachedClassNames and cachedNonClassNames. Return an array with the calculated values."

	| classNames nonClassNames |
	classNames _ IdentitySet new: self size.
	nonClassNames _ IdentitySet new.
	self environmentImplementations
		fillClassNameCache: classNames
		andNonClassNameCache: nonClassNames.
	self keysAndValuesDo: [ :key :value |
		value isInMemory ifTrue: [
			"The key == value name test below addresses two separate issues:
				1) Obsolete classes, where key = #Foo and value name = 'AnObsoleteFoo'
				2) Aliases, i.e., Smalltalk at: #OtherName put: aClass"
			(value class isMeta and: [ key == value name ])
				ifTrue: [ classNames add: key ]
				ifFalse: [ nonClassNames add: key ] ] ].
	classNames _ classNames asArray sort.
	nonClassNames _ nonClassNames asArray sort.
	cachedClassNames _ classNames.
	cachedNonClassNames _ nonClassNames.
	^{ classNames. nonClassNames }! !

!SystemDictionary methodsFor: 'class names' stamp: 'KLG 10/5/2020 11:33:09'!
hasClassNamed: aString
	"Answer whether there is a class of the given name, but don't intern aString if it's not alrady interned.  4/29/96 sw
	Smalltalk hasClassNamed: 'Morph'
	Smalltalk hasClassNamed: 'Display'
	Smalltalk hasClassNamed: 'xMorph'
	"

	self environmentImplementations hasClassNamed: aString :: ifTrue: [
		^ true ].
	Symbol hasInterned: aString ifTrue: [ :aSymbol |
		self at: aSymbol ifPresent: [ :global | ^global class isMeta ]].
	^ false! !

!SystemDictionary methodsFor: 'class names' stamp: 'KLG 10/5/2020 11:34:26'!
prepareToRenameClass: aClass as: newName 

	self environmentImplementations prepareToRenameClass: aClass as: newName :: ifTrue: [
		^ self ].
	^self prepareToRenameClass: aClass from: aClass name to: newName! !

!SystemDictionary methodsFor: 'class names' stamp: 'KLG 10/5/2020 11:35:40'!
removeClassNamed: aName
	"Invoked from fileouts:  if there is currently a class in the system named aName, then remove it.  If anything untoward happens, report it in the Transcript.  "

	| oldClass |
	self environmentImplementations removeClassNamed: aName :: ifTrue: [
		^ self ].
	oldClass _ self at: aName asSymbol ifAbsent: [
		Transcript newLine; show: 'Removal of class named ', aName, ' ignored because ', aName, ' does not exist.'.
		^ self].

	oldClass removeFromSystem! !

!SystemDictionary methodsFor: 'class names' stamp: 'KLG 10/5/2020 11:37:17'!
renameClassNamed: oldName as: newName
	"Invoked from fileouts:  if there is currently a class in the system named oldName, then rename it to newName.  If anything untoward happens, report it in the Transcript.  "

	| oldClass |
	self environmentImplementations renameClassNamed: oldName as: newName :: ifTrue: [
		^ self ].
	(oldClass _ self at: oldName asSymbol ifAbsent: nil)
		ifNil: [
			Transcript newLine; show: 'Class-rename for ', oldName, ' ignored because ', oldName, ' does not exist.'.
			^ self].

	oldClass rename: newName! !

!SystemDictionary methodsFor: 'dictionary access' stamp: 'KLG 10/3/2020 05:58:34'!
at: aKey put: anObject 
	"Override from Dictionary to check Undeclared and fix up
	references to undeclared variables."

	| association |
	"Let objects that belong to an environment, handle their installation."
	anObject installInEnvironmentAndReport ifTrue: [ ^ anObject ].
	(self includesKey: aKey) ifFalse: [
		self flushClassNameCache.

		"Update existing association if there is one."
		(Undeclared includesKey: aKey) ifTrue: [
			association _ self declare: aKey from: Undeclared.
			association value: anObject.
			^ anObject ]].

	"Update existing association if there is one."
	^super at: aKey put: anObject! !

!SystemDictionary methodsFor: 'housekeeping' stamp: 'KLG 10/5/2020 11:40:02'!
cleanOutUndeclared
	"Remove all unreferences classes."
	
	self environmentImplementations cleanOutUndeclared.
	Undeclared removeUnreferencedKeys! !

!SystemDictionary methodsFor: 'housekeeping' stamp: 'KLG 10/5/2020 11:38:50'!
obsoleteClasses   "Smalltalk obsoleteClasses inspect"
	"NOTE:  Also try inspecting comments below"
	| obs c |
	obs _ OrderedCollection new.  Smalltalk garbageCollect.
	self environmentImplementations addObsoleteClassesTo: obs.
	Metaclass allInstancesDo:
		[:m | c _ m soleInstance.
		(c notNil and: ['AnOb*' match: c name asString])
			ifTrue: [obs add: c]].
	^ obs asArray

"Likely in a ClassDict or Pool...
(Association allInstances select: [:a | (a value isKindOf: Class) and: ['AnOb*' match: a value name]]) asArray
"
"Obsolete class refs or super pointer in last lit of a method...
| n l found |
Smalltalk browseAllSelect:
	[:m | found _ false.
	1 to: m numLiterals do:
		[:i | (((l _ m literalAt: i) isMemberOf: Association)
				and: [(l value isKindOf: Behavior)
				and: ['AnOb*' match: l value name]])
			ifTrue: [found _ true]].
	found]
"! !

!SystemDictionary methodsFor: 'retrieving' stamp: 'KLG 10/5/2020 11:41:43'!
allBehaviorsDo: aBlock 
	"Evaluate the argument, aBlock, for each kind of Behavior in the system 
	(that is, Object and its subclasses).
	ar 7/15/1999: The code below will not enumerate any obsolete or anonymous
	behaviors for which the following should be executed:

		Smalltalk allObjectsDo:[:obj| obj isBehavior ifTrue:[aBlock value: obj]].

	but what follows is way faster than enumerating all objects."

	self environmentImplementations allBehaviorsDo: aBlock.
	Smalltalk do: [ :root |
		(root isBehavior and: [root superclass isNil]) ifTrue: [	"Grab ProtoObject and any other alike"
			root withAllSubclassesDo: [ :class |
				class isMeta ifFalse: [ "The metaclasses are rooted at Class; don't include them twice."
					aBlock
						value: class;
						value: class class ]]]]! !

!SystemDictionary methodsFor: 'retrieving' stamp: 'KLG 10/5/2020 11:41:03'!
poolUsers
	"Answer a dictionary of pool name -> classes that refer to it. Also includes any globally know dictionaries (such as Smalltalk, Undeclared etc) which although not strictly accurate is potentially useful information "
	"Smalltalk poolUsers"
	| poolUsers pool refs |
	poolUsers _ Dictionary new.
	self environmentImplementations addToPoolUsers: poolUsers.
	Smalltalk keys
		do: [ :k |
			 (((pool _ Smalltalk at: k) is: #Dictionary)
					or: [pool isKindOf: SharedPool class])
				ifTrue: [refs _ Smalltalk allClasses
								select: [:c | c sharedPools identityIncludes: pool]
								thenCollect: [:c | c name].
					refs _ refs asOrderedCollection.
					refs
						add: (Smalltalk
								allCallsOn: (Smalltalk associationAt: k)).
					poolUsers at: k put: refs]].
	^ poolUsers! !

!SystemDictionary methodsFor: 'shrinking' stamp: 'KLG 10/5/2020 11:50:12'!
removeSelector: descriptor
	"Safely remove a selector from a class (or metaclass). If the class
	or the method doesn't exist anymore, never mind and answer nil.
	This method should be used instead of 'Class removeSelector: #method'
	to omit global class references."

	| class sel |
	self environmentImplementations
		removeSelector: descriptor :: ifNotNil: [  :affectedBehaviour |
			^ affectedBehaviour ].
	class _ Smalltalk at: descriptor first ifAbsent: [^ nil].
	(descriptor size > 2 and: [descriptor second == #class])
		ifTrue:
			[class _ class class.
			sel _ descriptor third]
		ifFalse: [sel _ descriptor second].
	^ class removeSelector: sel! !

!methodRemoval: EnvironmentImplementationsDictionary #removeSelector:ifHandled: stamp: 'KLG 10/5/2020 11:50:27'!
EnvironmentImplementationsDictionary removeSelector: #removeSelector:ifHandled:!

!Object reorganize!
('Breakpoint' break)
('accessing' addInstanceVarNamed:withValue: at: at:put: basicAt: basicAt:put: basicSize customizeExplorerContents rawBasicAt: rawBasicAt:put: size yourself)
('as yet unclassified' revisar)
('associating' ->)
('binding' bindingOf:)
('casing' caseOf: caseOf:otherwise:)
('class membership' class isKindOf: isMemberOf: respondsTo:)
('comparing' = ~= hash literalEqual:)
('converting' adaptToFloat:andSend: adaptToFraction:andSend: adaptToInteger:andSend: as: asString complexContents copyAs: mustBeBoolean mustBeBooleanIn: withoutListWrapper)
('copying' copy copyForClipboard copyFrom: copySameFrom: postCopy shallowCopy veryDeepCopy)
('events-old protocol' addDependent: breakDependents changed changed: removeDependent: update:)
('error handling' assert: assert:description: caseError doesNotUnderstand: error: halt halt: handles: notYetImplemented notify: notify:at: primitiveFail primitiveFailed primitiveFailed: shouldBeImplemented shouldNotHappen shouldNotHappenBecause: shouldNotHappenBecauseErrorMessage shouldNotHappenErrorMessage shouldNotImplement subclassResponsibility)
('evaluating' value valueWithArguments: valueWithPossibleArgument:)
('events-accessing' actionForEvent: actionMap actionSequenceForEvent: actionsDo: hasActionForEvent: setActionSequence:forEvent: updateableActionMap)
('events-registering' when:evaluate: when:send:to: when:send:to:with: when:send:to:withArguments:)
('events-removing' releaseActionMap removeAction:forEvent: removeActionsForEvent: removeActionsSatisfying: removeActionsSatisfying:forEvent: removeActionsWithReceiver: removeActionsWithReceiver:forEvent:)
('events-triggering' triggerEvent: triggerEvent:with: triggerEvent:withArguments:)
('finalization' actAsExecutor executor finalizationRegistry finalize retryWithGC:until: toFinalizeSend:to:with:)
('inspecting' basicInspect copyToClipboard inspect inspectWithLabel: inspectorClass)
('macpal' flash)
('message handling' argumentName argumentNameSufix disableCode: executeMethod: perform: perform:with: perform:with:with: perform:with:with:with: perform:withArguments: perform:withArguments:inSuperclass: perform:withPossiblyWrongSizedArguments: with:executeMethod: with:with:executeMethod: with:with:with:executeMethod: with:with:with:with:executeMethod: withArgs:executeMethod:)
('object serialization' comeFullyUpOnReload: convertToCurrentVersion:refStream: objectForDataStream: readDataFrom:size: storeDataOn:)
('printing' displayStringOrText fullPrintString isLiteral longPrintOn: longPrintOn:limitedTo:indent: longPrintString longPrintStringLimitedTo: nominallyUnsent: print printAs:limitedTo: printOn: printString printStringLimitedTo: printText printTextLimitedTo: printWithClosureAnalysisOn: storeOn: storeString)
('system primitives' becomeForward: becomeForward:copyHash: className instVarAt: instVarAt:put: instVarAtPrim73: instVarAtPrim74:put: instVarNamed: instVarNamed:put: primitiveChangeClassTo: someObject)
('stepping' stepAt: wantsSteps)
('testing' is: isArray isBehavior isBlock isClosure isCollection isComplex isContext isFloat isFloatOrFloatComplex isFraction isInteger isInterval isMethodProperties isNumber isObject isPoint isPseudoContext isString isSymbol isVariableBinding name renameTo:)
('translation support' inline: success: var:declareC:)
('user interface' browseClassHierarchy confirm: confirm:orCancel: explore hasContentsInExplorer inform: request:do: request:initialAnswer: request:initialAnswer:do: request:initialAnswer:do:orCancel: request:initialAnswer:orCancel: request:initialAnswer:verifying:do: request:initialAnswer:verifying:do:orCancel:)
('private' deprecatedMethod errorDescriptionForSubcriptBounds: errorImproperStore errorNonIntegerIndex errorNotIndexable errorSubscriptBounds: primitiveError: setPinned: species storeAt:inTempFrame:)
('tracing' inboundPointers inboundPointersExcluding: outboundPointers outboundPointersDo:)
('morphic' activeHand runningWorld)
('user interface support' autoCompleterClassFor: editorClassFor: textStylerClassFor:)
('profiler support' profilerFriendlyCall:)
('pinning' isPinned pin unpin)
('debugging-haltOnce' clearHaltOnce haltOnce haltOnceEnabled setHaltOnce toggleHaltOnce)
('environment support' installInEnvironmentAndReport)
!


!EnvironmentImplementationsDictionary reorganize!
('accessing')
('class names' classNamed: fillClassNameCache:andNonClassNameCache: hasClassNamed: prepareToRenameClass:as: removeClassNamed: renameClassNamed:as:)
('housekeeping' addObsoleteClassesTo: cleanOutUndeclared)
('retrieving' addToPoolUsers: allBehaviorsDo:)
('shrinking' removeSelector:)
('ui')
('browsing')
('testing')
('classes and traits')
('environment support')
!

EnvironmentImplementationsDictionary initialize!

!SystemDictionary reorganize!
('accessing' classes description name organization summary)
('class names' classNamed: fillCaches flushClassNameCache forgetClass:logged: hasClassNamed: prepareToRenameClass:as: prepareToRenameClass:from:to: removeClassNamed: removeClassNamedIfInBaseSystem: renameAndUpdateReferences:as: renameClassNamed:as: renamedClass:from:)
('dictionary access' associationOrUndeclaredAt: at:put:)
('housekeeping' browseEqEqSentToSmallIntegerConstants browseObsoleteMethodReferences browseUndeclaredReferences cleanCompactObsoleteClasses cleanOutUndeclared condenseChanges condenseSources macroBenchmark1 macroBenchmark3 obsoleteBehaviors obsoleteClasses obsoleteMethodReferences recompileAllFrom: removeEmptyMessageCategories testDecompiler testFormatter testFormatter2 verifyChanges)
('image, changes name' alternativeSourcesName changeImageNameTo: currentChangesName currentSourcesName defaultChangesName defaultSourcesName defaultUserChangesName fullNameForChangesNamed: fullNameForImageNamed: imageName imageName: imagePath primImageName primVmPath vmPath)
('memory space' bytesLeft bytesLeft: bytesLeftString createStackOverflow garbageCollect garbageCollectMost growMemoryByAtLeast: installLowSpaceWatcher lowSpaceThreshold lowSpaceWatcher lowSpaceWatcherProcess okayToProceedEvenIfSpaceIsLow primBytesLeft primLowSpaceSemaphore: primSignalAtBytesLeft: primitiveGarbageCollect signalLowSpace stopLowSpaceWatcher useUpMemory useUpMemoryWithArrays useUpMemoryWithContexts useUpMemoryWithTinyObjects)
('code authors' allContributors contributionsOf: knownInitialsAndNames unknownContributors)
('miscellaneous' cogitClass exitToDebugger extraVMMemory extraVMMemory: getCurrentWorkingDirectory getSystemAttribute: getVMParameters handleUserInterrupt interpreterClass isDevelopmentEnvironmentPresent isHeadless listBuiltinModule: listBuiltinModules listLoadedModule: listLoadedModules logError:inContext:to: maxExternalSemaphores maxExternalSemaphores: osVersion platformName platformSubtype primGetCurrentWorkingDirectoryUnix primGetCurrentWorkingDirectoryWindows primVmFileName unloadModule: vmFileName vmOptionsDo: vmVersion voidCogVMState)
('object serialization' objectForDataStream: storeDataOn:)
('printing' printElementsOn: printOn:)
('profiling' clearProfile dumpProfile profile: startProfiling stopProfiling)
('retrieving' allBehaviorsDo: allCallsOn: allCallsOn:and: allClasses allClassesDo: allClassesImplementing: allGlobalRefs allGlobalRefsWithout: allImplementedMessages allImplementedMessagesWithout: allImplementorsOf: allImplementorsOf:localTo: allMethodsInCategory: allMethodsSourceStringMatching: allMethodsWithSourceString:matchCase: allMethodsWithString: allObjects allObjectsDo: allObjectsOrNil allPrimitiveMessages allPrimitiveMethodsInCategories: allReferencesToLiteral: allSelect: allSentMessages allSentMessagesWithout: allUnSentMessages allUnSentMessagesIn: allUnSentMessagesWithout: allUnimplementedCalls allUnusedClassesWithout: hierachySortedAllClassesDo: isThereAReferenceTo: isThereAnImplementorOf: isThereAnImplementorOf:exceptFor: numberOfImplementorsOf: numberOfSendersOf: pointersTo: pointersTo:except: poolUsers unimplemented)
('shrinking' abandonSources presumedSentMessages reduceCuis removeAllUnSentMessages removeSelector: removedUnusedClassesAndMethods reportClassAndMethodRemovalsFor: unusedClasses unusedClassesAndMethodsWithout:)
('snapshot and quit' add:toList:after: addToShutDownList: addToShutDownList:after: addToStartUpList: addToStartUpList:after: lastQuitLogPosition logSnapshot:andQuit: nopTag okayToDiscardUnsavedCode okayToSave printStuffToCleanOnImageSave processShutDownList: processStartUpList: quitNoSaveTag quitPrimitive quitPrimitive: quitTag removeFromShutDownList: removeFromStartUpList: saveAs saveAs:andQuit:clearAllClassState: saveAsNewVersion saveSession send:toClassesNamedIn:with: setGCParameters setPlatformPreferences snapshot:andQuit: snapshot:andQuit:clearAllClassState: snapshot:andQuit:embedded: snapshot:andQuit:embedded:clearAllClassState: snapshotEmbeddedPrimitive snapshotMessageFor:andQuit: snapshotPrimitive snapshotTag snapshotTagFor:andQuit: storeOn: tagHeader tagTail unbindExternalPrimitives)
('sources, change log' aboutThisSystem assureStartupStampLogged calcEndianness classRemoved:fromCategory: closeSourceFiles endianness evaluated:context: externalizeSources forceChangesToDisk internalizeChangeLog internalizeSources isBigEndian isLittleEndian lastUpdateString logChange: logChange:preamble: methodRemoved:selector:inProtocol:class: openSourceFiles openSourcesAndChanges systemInformationString timeStamp: version)
('special objects' clearExternalObjects compactClassesArray compactClassesArrayIncludes: externalObjects hasSpecialSelector:ifTrueSetByte: primitiveErrorTable recreateSpecialObjectsArray registerExternalObject: specialNargsAt: specialObjectsArray specialSelectorAt: specialSelectorSize specialSelectors unregisterExternalObject:)
('toDeprecate')
('ui' beep confirmRemovalOf:on: globals inspectGlobals primitiveBeep systemCategoryFromUserWithPrompt:)
('browsing' browseAllAccessesTo:from: browseAllCallsOn: browseAllCallsOn:and: browseAllCallsOn:localTo: browseAllCallsOnClass: browseAllImplementorsOf: browseAllImplementorsOf:localTo: browseAllImplementorsOfList: browseAllImplementorsOfList:title: browseAllMethodsInCategory: browseAllPrimitives browseAllReferencesToLiteral: browseAllSelect: browseAllSelect:name:autoSelect: browseAllStoresInto:from: browseAllUnSentMessages browseAllUnimplementedCalls browseClassCommentsWithString: browseClassesWithNamesContaining:caseSensitive: browseEqSmallConstant browseInstVarDefs: browseInstVarRefs: browseLikelyUnnededRedefinitions browseMessageList:name: browseMessageList:name:autoSelect: browseMessageList:ofSize:name:autoSelect: browseMethodsWithSourceString: browseMethodsWithString: browseMethodsWithString:matchCase: browseMyChanges browseObsoleteReferences browseViewReferencesFromNonViews showMenuOf:withFirstItem:ifChosenDo: showMenuOf:withFirstItem:ifChosenDo:withCaption:)
('private' allSymbolsIn:do: baseLabel)
('Closure measurements' browseMethodsWithClosuresThatAccessOuterTemps browseMethodsWithClosuresThatOnlyReadOuterTemps browseMethodsWithClosuresThatWriteOuterTemps browseMethodsWithClosuresThatWriteOuterTempsButCleanOtherwise browseMethodsWithEmptyClosures browseMethodsWithMoreThanOneClosure browseMethodsWithOnlyCleanClosures closuresInfoStringForClass:selector: eliotsClosureMeasurements eliotsClosureMeasurements2 eliotsClosureMeasurements2On: eliotsClosureMeasurementsOn:over:)
('removing' removeKey:ifAbsent:)
('system attributes' flagInterpretedMethods: isRunningCog isRunningCogit isSpur maxIdentityHash processHasThreadIdInstVar: processPreemptionYields processPreemptionYields:)
('query' hierarchySorted:do: methodsWithUnboundGlobals unusedBlocks)
('testing' hasBindingThatBeginsWith: isLiveSmalltalkImage isLiveTypingInstalled)
('classes and traits' classNames nonClassNames)
('image format' imageFormatVersion imageFormatVersionFromFile imageFormatVersionFromFileAsIs)
('AndreasProfiler-profiling' interruptChecksPerMSec longRunningPrimitive longRunningPrimitiveSemaphore: profilePrimitive profileSample profileSemaphore: profileStart:)
('startup' doStartUp: processCommandLineArgument:storeStartUpScriptArgsOn: processCommandLineArguments readCommandLineArguments setStartupStamp startUpArguments startUpScriptArguments)
('startup - restore lost changes' hasToRestoreChanges hasToRestoreChangesFrom: isQuitNoSaveRecord: isQuitRecord: isSnapshotQuitOrQuitNoSaveRecord: isSnapshotRecord: lostChangesDetectedCaption restoreLostChanges restoreLostChangesAutomatically restoreLostChangesAutomaticallyFrom: restoreLostChangesIfNecessary restoreLostChangesManually restoreLostChangesOptions restoringChangesHasErrorsCaption shouldShowFileInErrors withChangesFileDo:)
('image' wordSize)
('vm parameters' doMixedArithmetic doMixedArithmetic: vmParameterAt: vmParameterAt:put:)
('environment support' environmentImplementations)
!



More information about the Cuis-dev mailing list