[squeak-dev] Re: The Trunk: System-ar.242.mcz

Juan Vuletich juan at jvuletich.org
Fri Feb 5 14:28:50 UTC 2010


Eliot Miranda wrote:
>
>
> On Wed, Feb 3, 2010 at 9:51 PM, Andreas Raab <andreas.raab at gmx.de 
> <mailto:andreas.raab at gmx.de>> wrote:
>
>     Eliot Miranda wrote:
>
>         Andreas,
>
>           one rationale for      ...
>                do: [| blockScope | ... blockScope := ...]
>              ...
>         over
>            | methodScope |
>            ...
>               do: [... methodScope := ...]
>         is that if ever one adds parallel do to the language the
>         former continues to work whereas the latter breaks.
>          Personally I find declaring things at method scope that are
>         truly block scope bad style and not forward looking.  Yes, the
>         auto declare facility is poor in this regard but it's fixable.
>
>
>     The change wasn't intentional, I was merging a whole bunch of
>     stuff from Juan and wasn't going to rewrite every method manually
>     to push the temps into the proper place. You'll have to accept
>     that when you merge external code you get some of that style along
>     with your own. Not much to do unless you fix the tools to do The
>     Right Thing by default.
>
>
> Ah!  Hush my mouth!!
>  
>
>
>     Cheers,
>      - Andreas
>

Yes, my mistake... Pre-closures code that was not checked yet.

BTW, I've been playing a bit with Eliot's measurements. The attach 
includes the result. It is done for Cuis, a bit of simple tweaking will 
be needed for Squeak.

Eliot, I think I found 2 bugs in your measurement code. One is in 
looking for copied values in the second scan. It should be done before 
the #interpretNextInstructionFor: call. This affects the count of clean 
closures. The other bug is that the second scan scans just for one 
closure. For methods with more than one closure (non-nested), we need to 
keep scanning, and the results are now not about closures, but about 
methods. Please look at my code to see how I did it. 
#eliotsClosureMeasurements is equivalent to yours, with a few comments 
on the bugs. #eliotsClosureMeasurements2 is my refactored and fixed 
version. There are several utility methods too, like 
#browseMethodsWithClosuresThatWriteOuterTemps .

With all this, Cuis 2.0 has 698 methods with closures that write to 
outer temps, including those in MessageTally. I'll review them all 
manually soon.

Cheers,
Juan Vuletich
-------------- next part --------------
'From Cuis 2.0 of 4 January 2010 [latest update: #393] on 5 February 2010 at 11:19:46 am'!
!classDefinition: #PlayingWithClosures category: #'Playing with Closures'!
Object subclass: #PlayingWithClosures
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Playing with Closures'!

!PlayingWithClosures commentStamp: 'jmv 12/28/2009 10:25' prior: 0!
Just some scripts for learning about Closures!


!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 12/28/2009 11:22'!
exp01Argument
	^ [ :a |
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 12/28/2009 11:11'!
exp01LocalTemp

	^ [ | a |
		a := 1.
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 12/28/2009 11:13'!
exp01RemoteTemp
	| a |
	a := 1.
	^ [
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 2/5/2010 10:59'!
exp01RemoteTempAssignedTwice
	| a |
	a := 1.
	^ [
		a := 2.
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 2/5/2010 10:49'!
exp01RemoteTempCanBeMovedInside
	| a |
	^ [
		a := 1.
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 2/5/2010 10:49'!
exp01RemoteTempCantBeMovedInside
	| a |
	a := 1.
	^ [
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 12/28/2009 11:14'!
exp01RemoteTempOptimized
	| a |
	a := 1.
	^1>0 ifTrue: [
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 12/28/2009 11:13'!
exp01RemoteTempOptimizedWithAssignment
	| a |
	^1>0 ifTrue: [
		a := 1.
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 12/28/2009 11:29'!
exp01RemoteTempWithAssignment
	| a |
	^ [ 
		a := 1.
		a+1 ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 2/5/2010 09:59'!
exp01SelfSend

	^ [ self printString, 'p' ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 2/5/2010 09:59'!
exp01SuperSend

	^ [ super exp01SuperSend, 'p' ]! !

!PlayingWithClosures class methodsFor: 'experiments' stamp: 'jmv 2/5/2010 10:46'!
exp01UpArrowReturn

	^ [ ^self ]! !


!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:43'!
browseMethodsWithClosuresThatAccessOuterTemps
	"
	Smalltalk browseMethodsWithClosuresThatAccessOuterTemps
	"

	self
		browseMessageList: (self allSelect: [ :m | 
			self eliotsClosureMeasurementsOn: m over: [ :closuresCount 
					:hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
				anyClosureHasCopied ].
			])
		name: 'Closures that read or write to outer temps'! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:43'!
browseMethodsWithClosuresThatOnlyReadOuterTemps
	"
	Smalltalk browseMethodsWithClosuresThatOnlyReadOuterTemps
	"

	self
		browseMessageList: (self allSelect: [ :m | 
			self eliotsClosureMeasurementsOn: m over: [ :closuresCount
					:hasIndirectTemps :anyClosureHasCopiedValues :anyClosureDoesUAR :anyClosureUsesSelf |
				anyClosureHasCopiedValues & hasIndirectTemps not].
			])
		name: 'Closures that read but not write to outer temps'! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:43'!
browseMethodsWithClosuresThatWriteOuterTemps
	"
	Smalltalk browseMethodsWithClosuresThatWriteOuterTemps
	"

	self
		browseMessageList: (self allSelect: [ :m | 
			self eliotsClosureMeasurementsOn: m over: [ :closuresCount 
					:hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
				hasIndirectTemps ].
			])
		name: ' Closures that write to outer temps'! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 11:04'!
browseMethodsWithClosuresThatWriteOuterTempsButCleanOtherwise
	"
	Smalltalk browseMethodsWithClosuresThatWriteOuterTempsButCleanOtherwise
	"

	self
		browseMessageList: (self allSelect: [ :m | 
			self eliotsClosureMeasurementsOn: m over: [ :closuresCount 
					:hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
				hasIndirectTemps and: [  anyClosureDoesUAR not and: [ anyClosureUsesSelf not ] ] ].
			])
		name: ' Closures that write to outer temps, but clean otherwise'! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:30'!
browseMethodsWithMoreThanOneClosure
	"
	Smalltalk browseMethodsWithMoreThanOneClosure
	"

	self
		browseMessageList: (self allSelect: [ :m | 
			self eliotsClosureMeasurementsOn: m over: [ :closuresCount 
					:hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
				closuresCount > 1 ].
			])
		name: 'Methods with more than one Closure'! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:31'!
browseMethodsWithOnlyCleanClosures
	"
	Smalltalk browseMethodsWithOnlyCleanClosures
	"
	self
		browseMessageList: (
			self allSelect: [ :m | 
				self eliotsClosureMeasurementsOn: m over: [ :closuresCount
						:hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
					closuresCount > 0 and: [
						(anyClosureHasCopied or: [ anyClosureDoesUAR or: [ anyClosureUsesSelf ]]) not ].
				]
			])
		name: 'Methods with only Clean Closures'! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 11:19'!
eliotsClosureMeasurements
	"
	Smalltalk eliotsClosureMeasurements
	From http://www.mirandabanda.org/cogblog/2008/11/14/mechanised-modifications-and-miscellaneous-measurements/
	by Eliot Miranda
	"
      | numMethods numMethodsWithClosure numMethodsWithIndirectTemps
         numClosures numClosuresWithCopiedValues numCopiedValuesForClosure
         numRemoteTemps numScopesWithRemoteTemps
         upArrowReturnsInClosure closureUsesSelfs upArrowReturnAndUsesSelfs numClean |

        numMethods := numMethodsWithClosure := numMethodsWithIndirectTemps :=
        numClosures := numClosuresWithCopiedValues := numCopiedValuesForClosure :=
        numRemoteTemps := numScopesWithRemoteTemps :=
        upArrowReturnsInClosure := closureUsesSelfs := upArrowReturnAndUsesSelfs := numClean := 0.
        self allSelect:
                 [:m| | s hasClosure hasIndirectTemps blkPc blkSz doesUAR usesSelf hasCopied sel|
			sel _ false.
                 hasClosure := hasIndirectTemps := false.
                 s := InstructionStream on: m.
                 s scanFor:
                          [:b|
                          b = 143 "closure creation" ifTrue:
                                   [hasClosure := true.
                                   numClosures := numClosures + 1.
                                   s followingByte >= 16 ifTrue:
                                            [numClosuresWithCopiedValues := numClosuresWithCopiedValues + 1.
                                             numCopiedValuesForClosure := numCopiedValuesForClosure + (s followingByte >> 4)]].
                          (b = 138 "indirect temp vector creation"
                           and: [s followingByte <= 127]) ifTrue:
                                   [hasIndirectTemps := true.
                                    numScopesWithRemoteTemps := numScopesWithRemoteTemps + 1.
                                    numRemoteTemps := numRemoteTemps + s followingByte].
                          false].
                 numMethods := numMethods + 1.
                 hasClosure ifTrue:
                          [numMethodsWithClosure := numMethodsWithClosure + 1.
                           s pc: m initialPC; scanFor: [:b| b = 143].

"jmv-This looks like the correct place to do this"
                           hasCopied := s followingByte >= 16.

                           blkSz := s interpretNextInstructionFor: BlockStartLocator new.
                           blkPc := s pc.
                           doesUAR := usesSelf := false.

"jmv-Doing this here looks like a bug. See the other comment"
                           hasCopied := s followingByte >= 16.

"jmv-Another bug. This only considers the first closure (and any nested closure in it), but not later ones"

                           s scanFor:
                                   [:b|
                                   s pc >= (blkPc + blkSz)
                                            ifTrue: [true]
                                            ifFalse:
                                                     [doesUAR := doesUAR or: [s willReturn and: [s willBlockReturn not]].
                                                      usesSelf := usesSelf or: [b = 112 "pushSelf"
                                                                                                  or: [b < 16 "pushInstVar"
                                                                                                  or: [(b = 128 and: [s followingByte <= 63]) "pushInstVar"
                                                                                                  or: [(b between: 96 and: 96 + 7) "storePopInstVar"
                                                                                                  or: [(b = 130 and: [s followingByte <= 63]) "storePopInstVar"
                                                                                                  or: [(b = 129 and: [s followingByte <= 63]) "storeInstVar"
                                                                                                  or: [b = 132 and: [s followingByte = 160]]]]]]]].
                                                     false]].
                           doesUAR ifTrue:
                                   [upArrowReturnsInClosure := upArrowReturnsInClosure + 1].
                           usesSelf ifTrue:
                                   [closureUsesSelfs := closureUsesSelfs + 1].
                           (doesUAR and: [usesSelf]) ifTrue:
                                   [upArrowReturnAndUsesSelfs := upArrowReturnAndUsesSelfs + 1].
                           (doesUAR or: [usesSelf or: [hasCopied]]) ifFalse:
                                   [numClean := numClean + 1]].
                 hasIndirectTemps ifTrue: [numMethodsWithIndirectTemps := numMethodsWithIndirectTemps + 1].
                 sel].
^        { {'Methods'. numMethods}. {'MethodsWithClosure'. numMethodsWithClosure}. {'MethodsWithIndirectTemps'. numMethodsWithIndirectTemps}.
         {'Closures'. numClosures}. {'CopiedValuesForClosures'. numCopiedValuesForClosure}. {'ClosuresWithCopiedValues'. numClosuresWithCopiedValues}.
         {'RemoteTemps'. numRemoteTemps}. {'ScopesWithRemoteTemps'. numScopesWithRemoteTemps}.
         {'MethodsWithUpArrowReturnsInClosures'. upArrowReturnsInClosure}. {'MethodsWithReferencesToSelfInClosures'. closureUsesSelfs}. {'Both'. upArrowReturnAndUsesSelfs}.
         {'MethodsWithOnlyCleanClosures'. numClean} }! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:44'!
eliotsClosureMeasurements2
	"
	Smalltalk eliotsClosureMeasurements2
	"
	| numMethods numMethodsWithClosure numMethodsWithIndirectTemps anyClosureDoesUARCount anyClosureUsesSelfCount bothCount onlyCleanBlocksCount anyClosureHasCopiedCount |

	numMethods := numMethodsWithClosure := numMethodsWithIndirectTemps :=
	anyClosureDoesUARCount := anyClosureUsesSelfCount := bothCount := onlyCleanBlocksCount := 0.
	anyClosureHasCopiedCount _ 0.
	self allSelect: [ :m | 
		self eliotsClosureMeasurementsOn: m over: [ :closuresCount :hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
			numMethods := numMethods + 1.
			closuresCount > 0 ifTrue: [ numMethodsWithClosure := numMethodsWithClosure + 1 ].
			hasIndirectTemps ifTrue: [ numMethodsWithIndirectTemps := numMethodsWithIndirectTemps + 1].
			anyClosureDoesUAR ifTrue: [ anyClosureDoesUARCount := anyClosureDoesUARCount + 1].
			anyClosureUsesSelf ifTrue: [ anyClosureUsesSelfCount := anyClosureUsesSelfCount + 1].
			(anyClosureDoesUAR and: [anyClosureUsesSelf]) ifTrue: [ bothCount := bothCount + 1].
			closuresCount > 0 ifTrue: [
				(anyClosureDoesUAR or: [anyClosureUsesSelf or: [anyClosureHasCopied]]) ifFalse: [
					onlyCleanBlocksCount := onlyCleanBlocksCount + 1]].
			anyClosureHasCopied ifTrue: [ anyClosureHasCopiedCount _ anyClosureHasCopiedCount + 1 ].
			false.
		]
	].
	^{
		{'Methods'. numMethods}. {'MethodsWithClosure'. numMethodsWithClosure}. 
		{'WithClosuresAccessingOuterTemps'. anyClosureHasCopiedCount}.
		{'WithClosuresWritingOuterTemps'. numMethodsWithIndirectTemps}.
		{'WithUpArrowReturnsInClosures'. anyClosureDoesUARCount}. 
		{'WithReferencesToSelfInClosures'. anyClosureUsesSelfCount}. 
		{'BothAbove'. bothCount}.
		{'WithOnlyCleanClosures'. onlyCleanBlocksCount}.
	}! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 11:00'!
eliotsClosureMeasurements2On: aMethod
	"
	A Couple of Clean Closures
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01Argument
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01LocalTemp
	
	Closures reading and writing to outer temps
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTemp
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTempWithAssignment

	Closure doing an up-arrow return
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01UpArrowReturn

	Closures sending messages to self & super
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01SelfSend
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01SuperSend

	A couple of non-closures, i.e. blocks that are optimized by the compiler and a closure is never created
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTempOptimized
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTempOptimizedWithAssignment
	
	A remote temp whose declaration can not be moved inside the block
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTempCantBeMovedInside
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTempAssignedTwice
	A remote temp whose declaration can be moved inside the block
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01RemoteTempCanBeMovedInside
	A not-so remote temp. The declaration was moved inside the block, making it a clean block
	Smalltalk eliotsClosureMeasurements2On: PlayingWithClosures class >> #exp01LocalTemp
	"
	| numMethods numMethodsWithClosure numMethodsWithIndirectTemps anyClosureDoesUARCount anyClosureUsesSelfCount bothCount onlyCleanBlocksCount anyClosureHasCopiedCount |

	numMethods := numMethodsWithClosure := numMethodsWithIndirectTemps :=
	anyClosureDoesUARCount := anyClosureUsesSelfCount := bothCount := onlyCleanBlocksCount := 0.
	anyClosureHasCopiedCount _ 0.
		self eliotsClosureMeasurementsOn: aMethod over: [ :closuresCount :hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
			numMethods := numMethods + 1.
			closuresCount > 0 ifTrue: [ numMethodsWithClosure := numMethodsWithClosure + 1 ].
			hasIndirectTemps ifTrue: [ numMethodsWithIndirectTemps := numMethodsWithIndirectTemps + 1].
			anyClosureDoesUAR ifTrue: [ anyClosureDoesUARCount := anyClosureDoesUARCount + 1].
			anyClosureUsesSelf ifTrue: [ anyClosureUsesSelfCount := anyClosureUsesSelfCount + 1].
			(anyClosureDoesUAR and: [anyClosureUsesSelf]) ifTrue: [ bothCount := bothCount + 1].
			closuresCount > 0 ifTrue: [
				(anyClosureDoesUAR or: [anyClosureUsesSelf or: [anyClosureHasCopied]]) ifFalse: [
					onlyCleanBlocksCount := onlyCleanBlocksCount + 1]].
			anyClosureHasCopied ifTrue: [ anyClosureHasCopiedCount _ anyClosureHasCopiedCount + 1 ].
			false.
		].
	^{
		{'Methods'. numMethods}. {'MethodsWithClosure'. numMethodsWithClosure}. 
		{'WithClosuresAccessingOuterTemps'. anyClosureHasCopiedCount}.
		{'WithClosuresWritingOuterTemps'. numMethodsWithIndirectTemps}.
		{'WithUpArrowReturnsInClosures'. anyClosureDoesUARCount}. 
		{'WithReferencesToSelfInClosures'. anyClosureUsesSelfCount}. 
		{'BothAbove'. bothCount}.
		{'WithOnlyCleanClosures'. onlyCleanBlocksCount}.
	}! !

!SystemDictionary methodsFor: 'Closure measurements' stamp: 'jmv 2/5/2010 10:29'!
eliotsClosureMeasurementsOn: m over: aFiveArgBlock
	"
	See senders.
	Or try something like:
		Smalltalk
			eliotsClosureMeasurementsOn: FileList >> #defaultContents
			over: [ :closuresCount :hasCopiedValuesForClosure :hasIndirectTemps :anyClosureHasCopied :anyClosureDoesUAR :anyClosureUsesSelf |
				(Array with: closuresCount with: hasCopiedValuesForClosure with: hasIndirectTemps with: anyClosureHasCopied with: anyClosureDoesUAR with: anyClosureUsesSelf)]

	From http://www.mirandabanda.org/cogblog/2008/11/14/mechanised-modifications-and-miscellaneous-measurements/
	by Eliot Miranda
	"
		| s nextScanStart thisClosureHasCopied closuresCount hasIndirectTemps blkPc blkSz anyClosureHasCopied anyClosureDoesUAR anyClosureUsesSelf analyzedClosures |
		closuresCount := 0.
		hasIndirectTemps := false.
		anyClosureHasCopied :=  anyClosureDoesUAR := anyClosureUsesSelf := false.
		s := InstructionStream on: m.
		s scanFor: [ :b |
			b = 16r8F "16r8F = 143 closure creation" ifTrue: [
				closuresCount := closuresCount + 1].
			(b = 16r8A "16r8A = 138indirect temp vector creation" and: [ s followingByte <= 127]) ifTrue: [
					hasIndirectTemps := true].
			false].
		nextScanStart := m initialPC.
		analyzedClosures := 0.
		[ analyzedClosures < closuresCount ] whileTrue: [
			s pc: nextScanStart; scanFor: [ :b | b = 16r8F ].	"16r8F = 143 Search for first closure"
			analyzedClosures := analyzedClosures + 1.
			thisClosureHasCopied := s followingByte >= 16r10.
			anyClosureHasCopied := anyClosureHasCopied | thisClosureHasCopied.
			blkSz := s interpretNextInstructionFor: BlockStartLocator new.		"Findout size of first closure"
			blkPc := s pc.
			s scanFor: [ :b |
				s pc >= (blkPc + blkSz)
					ifTrue: [
						nextScanStart := s pc.
						true]
					ifFalse: [
						b = 16r8F ifTrue: [			
							thisClosureHasCopied := s followingByte >= 16r10.
							anyClosureHasCopied := anyClosureHasCopied | thisClosureHasCopied.
							analyzedClosures := analyzedClosures + 1 ].
						anyClosureDoesUAR := anyClosureDoesUAR or: [s willReturn and: [s willBlockReturn not]].
						anyClosureUsesSelf := anyClosureUsesSelf or: [b = 16r70 "pushSelf"
											or: [b < 16r10 "pushInstVar"
											or: [(b = 16r80 and: [s followingByte <= 16r3F]) "pushInstVar"
											or: [(b between: 16r60 and: 16r60 + 7) "storePopInstVar"
											or: [(b = 16r82 and: [s followingByte <= 63]) "storePopInstVar"
											or: [(b = 16r81 and: [s followingByte <= 63]) "storeInstVar"
											or: [b = 16r84 and: [s followingByte = 160]]]]]]]].
						false]]].
		^aFiveArgBlock valueWithArguments: (Array
			with: closuresCount
			with: hasIndirectTemps
			with: anyClosureHasCopied
			with: anyClosureDoesUAR
			with: anyClosureUsesSelf)! !


!SystemDictionary reorganize!
('accessing' organization)
('class names' classNamed: classNames flushClassNameCache forgetClass:logged: hasClassNamed: removeClassNamed: renameAndUpdateReferences:as: renameClass:as: renameClassNamed:as:)
('dictionary access' associationAtOrAbove:ifAbsent: associationOrUndeclaredAt: at:put: atOrAbove:ifAbsent: atOrBelow:ifAbsent: environmentForCategory: includesKeyOrAbove: kernelCategories scopeFor:from:envtAndPathIfFound:)
('housekeeping' browseObsoleteMethodReferences browseUndeclaredReferences cleanOutUndeclared compressSources condenseChanges condenseSources forgetDoIts macroBenchmark1 macroBenchmark3 makeInternalRelease obsoleteBehaviors obsoleteClasses obsoleteMethodReferences reclaimDependents recompileAllFrom: removeAllLineFeeds removeEmptyMessageCategories removeTextCode testDecompiler testFormatter testFormatter2 verifyChanges)
('image, changes name' changeImageNameTo: changesName fullNameForChangesNamed: fullNameForImageNamed: imageName imageName: imagePath sourcesName vmPath)
('memory space' bytesLeft bytesLeft: bytesLeftString createStackOverflow garbageCollect garbageCollectMost installLowSpaceWatcher lowSpaceThreshold lowSpaceWatcher lowSpaceWatcherProcess okayToProceedEvenIfSpaceIsLow primBytesLeft primLowSpaceSemaphore: primSignalAtBytesLeft: primitiveGarbageCollect signalLowSpace useUpMemory useUpMemoryWithArrays useUpMemoryWithContexts useUpMemoryWithTinyObjects)
('code authors' agreedContributors allContributors contributionsOf: missingAuthorsWithMethods newContributors okContributors returnedSignatories)
('miscellaneous' exitToDebugger extraVMMemory extraVMMemory: getSystemAttribute: getVMParameters handleUserInterrupt hasMorphic listBuiltinModule: listBuiltinModules listLoadedModule: listLoadedModules logError:inContext:to: osVersion platformName platformSubtype setMacFileInfoOn: unloadModule: verifyMorphicAvailability vmParameterAt: vmParameterAt:put: vmVersion)
('objects from disk' objectForDataStream: storeDataOn:)
('printing' printElementsOn:)
('profiling' clearProfile dumpProfile profile: startProfiling stopProfiling)
('retrieving' allBehaviorsDo: allCallsOn: allCallsOn:and: allClasses allClassesDo: allClassesImplementing: allGlobalRefs allGlobalRefsWithout: allImplementedMessages allImplementedMessagesWithout: allImplementorsOf: allImplementorsOf:localTo: allMethodsInCategory: allMethodsWithSourceString:matchCase: allMethodsWithString: allObjectsDo: allObjectsSelect: allPrimitiveMessages allPrimitiveMethodsInCategories: allSelect: allSelectNoDoits: allSentMessages allSentMessagesWithout: allUnSentMessages allUnSentMessagesIn: allUnSentMessagesWithout: allUnimplementedCalls allUnusedClassesWithout: isThereAnImplementorOf: numberOfImplementorsOf: pointersTo: pointersTo:except: pointersToItem:of: poolUsers selectorsWithAnyImplementorsIn: unimplemented)
('shrinking' abandonSources abandonTempNames computeImageSegmentation discardNetworking discardOddsAndEnds fileOutAndRemove: fileOutAndRemove:retainingRoots: fileOutAndRemove:withOtherClasses:andOtherMessages: lastRemoval presumedSentMessages removeAllUnSentMessages removeSelector: removedUnusedClassesAndMethods reportClassAndMethodRemovalsFor: unusedClasses unusedClassesAndMethodsWithout: writeImageSegmentsFrom:withKernel:)
('snapshot and quit' add:toList:after: addToShutDownList: addToShutDownList:after: addToStartUpList: addToStartUpList:after: lastQuitLogPosition processShutDownList: processStartUpList: quitPrimitive readDocumentFile removeFromShutDownList: removeFromStartUpList: saveAs saveAsEmbeddedImage saveAsNewVersion saveChangesInFileNamed: saveImageInFileNamed: saveImageSegments saveSession send:toClassesNamedIn:with: setGCParameters setPlatformPreferences shutDown snapshot:andQuit: snapshotEmbeddedPrimitive snapshotPrimitive unbindExternalPrimitives)
('sources, change log' aboutThisSystem assureStartupStampLogged closeSourceFiles currentChangeSetString datedVersion endianness event: externalizeSources forceChangesToDisk internalizeChangeLog internalizeSources isBigEndian isLittleEndian lastUpdateString logChange: logChange:preamble: openSourceFiles recover: systemInformationString timeStamp: version writeRecentCharacters:toFileNamed: writeRecentToFile)
('special objects' clearExternalObjects compactClassesArray externalObjects hasSpecialSelector:ifTrueSetByte: recreateSpecialObjectsArray registerExternalObject: specialNargsAt: specialObjectsArray specialSelectorAt: specialSelectorSize specialSelectors unregisterExternalObject:)
('copying' veryDeepCopyWith:)
('deprecated' removeClassFromSystem:logged: swapBytesIn:from:to:)
('toDeprecate' getFileNameFromUser snapshot:andQuit:embedded:)
('ui' confirmRemovalOf:on: inspectGlobals)
('browsing' browseAllAccessesTo:from: browseAllCallsOn: browseAllCallsOn:and: browseAllCallsOn:localTo: browseAllCallsOnClass: browseAllImplementorsOf: browseAllImplementorsOf:localTo: browseAllImplementorsOfList: browseAllImplementorsOfList:title: browseAllMethodsInCategory: browseAllObjectReferencesTo:except:ifNone: browseAllSelect: browseAllSelect:name:autoSelect: browseAllStoresInto:from: browseAllUnSentMessages browseAllUnimplementedCalls browseClassCommentsWithString: browseClassesWithNamesContaining:caseSensitive: browseInstVarDefs: browseInstVarRefs: browseMessageList:name: browseMessageList:name:autoSelect: browseMethodsWhoseNamesContain: browseMethodsWithSourceString: browseMethodsWithString: browseMethodsWithString:matchCase: browseObsoleteReferences showMenuOf:withFirstItem:ifChosenDo: showMenuOf:withFirstItem:ifChosenDo:withCaption:)
('private' allSymbolsIn:do:)
('Compiler swapping' actualCompiledMethodWithNodeClass actualCompilerClass actualDecompilerClass actualEncoderClass actualMessageNodeClass actualParserClass actualScannerClass)
('Closure measurements' browseMethodsWithClosuresThatAccessOuterTemps browseMethodsWithClosuresThatOnlyReadOuterTemps browseMethodsWithClosuresThatWriteOuterTemps browseMethodsWithClosuresThatWriteOuterTempsButCleanOtherwise browseMethodsWithMoreThanOneClosure browseMethodsWithOnlyCleanClosures eliotsClosureMeasurements eliotsClosureMeasurements2 eliotsClosureMeasurements2On: eliotsClosureMeasurementsOn:over:)
!



More information about the Squeak-dev mailing list