[Vm-dev] VM Maker: VMMaker.oscog-eem.3044.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Aug 21 00:15:00 UTC 2021


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.3044.mcz

==================== Summary ====================

Name: VMMaker.oscog-eem.3044
Author: eem
Time: 20 August 2021, 5:14:50.787529 pm
UUID: b33db89a-93e2-4370-b78f-97773632689c
Ancestors: VMMaker.oscog-eem.3043

Implement accurate per-method profiling.  This shoud be helpful in trqacking down the comiulation performancer regression but is useful in its own right.  For the CoInterpreter/Cogit profiles are broken down as bytecodes interpreted per method, and instructions executed per trampoline, per (cogged) method, and per selector (PIC).  Using the image startup + Morph compileAll test, 88% of 5466976 instructions are for methods, with 6% in trampolines and 6% in PICs, while 31k bytecodes are evaluated.

=============== Diff against VMMaker.oscog-eem.3043 ===============

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue effectiveCogCodeSize expectedSends expecting inputSemaphoreIndex zeroNextProfileTickCount perMethodProfile'
- 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue effectiveCogCodeSize expectedSends expecting inputSemaphoreIndex zeroNextProfileTickCount'
  	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends NLRFailures NLRSuccesses StackAlteringPrimitives'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was changed:
  ----- Method: CogVMSimulator>>aboutToDispatchBytecode (in category 'interpreter shell') -----
  aboutToDispatchBytecode
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| pmp at: method put: (pmp at: method ifAbsent: 0) + 1].
  	self incrementByteCount.
  	self assertValidExecutionPointers.
  	atEachStepBlock value "N.B. may be nil"!

Item was added:
+ ----- Method: CogVMSimulator>>enablePerMethodProfiling (in category 'simulation only') -----
+ enablePerMethodProfiling
+ 	perMethodProfile := Dictionary new.
+ 	cogit enablePerMethodProfiling!

Item was changed:
  ----- Method: CogVMSimulator>>loadNewPlugin: (in category 'plugin support') -----
  loadNewPlugin: pluginString
  	(breakSelector notNil
+ 	 and: [pluginString size = breakSelector size
+ 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0]]) ifTrue:
- 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0]) ifTrue:
  		[self halt: pluginString].
  	^(self tryLoadNewPlugin: pluginString pluginEntries: mappedPluginEntries) ifNotNil:
  		[:entry|
  		 pluginList := pluginList copyWith: entry.
  		 entry]!

Item was changed:
+ ----- Method: CogVMSimulator>>mapInterpreterOops (in category 'object memory support') -----
- ----- Method: CogVMSimulator>>mapInterpreterOops (in category 'multi-threading simulation switch') -----
  mapInterpreterOops
+ 	"Override both to elide the CoInterpreterMT version if not running MT,
+ 	 and to update perMethodProfile if in use."
+ 	self perform: #mapInterpreterOops
- 	"This method includes or excludes CoInterpreterMT methods as required.
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
- 	^self perform: #mapInterpreterOops
  		withArguments: {}
+ 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT]).
+ 
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| | map |
+ 		 "The tricky thing here is that a method may get remapped to another method already in the profile, etc..."
+ 		 map := Dictionary new.
+ 		 perMethodProfile keysAndValuesDo:
+ 			[:methodOop :count|
+ 			(objectMemory shouldRemapOop: methodOop) ifTrue:
+ 				[map at: methodOop put: {objectMemory remapObj: methodOop. count}]].
+ 		 map isEmpty ifFalse:
+ 			[map keysAndValuesDo:
+ 				[:newOop :tuple|
+ 				 [:oldOop :count|
+ 				  (map includesKey: oldOop) ifFalse:
+ 					[perMethodProfile removeKey: oldOop].
+ 				  perMethodProfile at: newOop put: count] valueWithArguments: tuple]]]!
- 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was added:
+ ----- Method: CogVMSimulator>>reportPerMethodProfilingOn: (in category 'simulation only') -----
+ reportPerMethodProfilingOn: aStream
+ 	"Generate a sorted report of bytecodes per method, and instructions per trampoline/cog method/pic.
+ 	 Answer an Array with the four totals."
+ 	| total |
+ 	perMethodProfile ifNil:
+ 		[aStream nextPutAll: 'not collecting profile'.
+ 		 ^self].
+ 	total := 0.
+ 	aStream nextPutAll: 'bytecodes dispatched per method'; cr.
+ 	(perMethodProfile associations sorted: [:a1 :a2| a1 value >= a2 value]) do:
+ 		[:assoc|
+  		total := total + assoc value.
+ 		aStream tab; print: assoc value; nextPut: $:; tab.
+ 		self printNameOfClass: (self methodClassOf: assoc key) count: 2 on: aStream.
+ 		aStream next: 2 put: $>.
+ 		self printStringOf: (self findSelectorOfMethod: assoc key) on: aStream.
+ 		aStream cr].
+ 	aStream flush.
+ 	^{total}, (cogit reportPerMethodProfilingOn: aStream)!

Item was changed:
  CogClass subclass: #Cogit
(excessive size, no diff calculated)

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| backEnd |
  	backEnd := CogCompilerClass basicNew.
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses' 'ioHighResClock'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'processorFrameValid' 'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep'
+ 		'codeZoneIsExecutableNotWritable' 'debugAPISelector' 'shortCutTrampolineBlocks'
+ 		'perMethodProfile' 'currentProfileMethod') do:
+ 			[:simulationVariableUnusedByRealVM|
+ 			aCCodeGenerator removeVariable: simulationVariableUnusedByRealVM].
- 		'codeZoneIsExecutableNotWritable' 'debugAPISelector' 'shortCutTrampolineBlocks') do:
- 			[:simulationVariableNotNeededForRealVM|
- 			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	"N.B. We *do not* include sq.h; it pulls in conflicting definitions now that sqVirtualMachine.h
  	 declares cointerp's functions, and declares some of them inaccurately for histrical reasons.
  	 We pull in CoInterpreter's api via cointerp.h which is accurate."
  	aCCodeGenerator
  		addHeaderFile:'"sqConfig.h"'; "config.h must be first on linux"
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'<stdio.h>';
  		addHeaderFile:'<stdlib.h>';
  		addHeaderFile:'<string.h>';
  		addHeaderFile:'"sqPlatformSpecific.h"'; "e.g. solaris overrides things for sqCogStackAlignment.h"
  		addHeaderFile:'"sqMemoryAccess.h"';
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetFP
  			declareC: 'usqIntptr_t (*ceGetFP)(void)';
  		var: #ceGetSP
  			declareC: 'usqIntptr_t (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceInvokeInterpret
  			declareC: 'void (*ceInvokeInterpret)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *';
  		var: 'enumeratingCogMethod' type: #'CogMethod *'.
  	
  	aCCodeGenerator
  		var: #ceTryLockVMOwner
  		declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(usqIntptr_t)\#endif'.
  
  	backEnd numICacheFlushOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceFlushICache
  				declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)'].
  	aCCodeGenerator
  		var: #ceFlushDCache
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif';
  		var: #codeToDataDelta
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static sqInt codeToDataDelta\#else\# define codeToDataDelta 0\#endif'.
  
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					fullBlockNoContextSwitchEntry fullBlockEntry
  					picMNUAbort picInterpretAbort  endCPICCase0 endCPICCase1 cPICEndOfCodeLabel)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #cPICPrototype type: #'CogMethod *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *';
  		declareVar: #methodZoneBase type: #usqInt.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'.
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[aCCodeGenerator
  			var: #directedSuperSendTrampolines
  				declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  			var: #directedSuperBindingSendTrampolines
  				declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]'].
  	NewspeakVM ifTrue:
  		[aCCodeGenerator
  			var: #selfSendTrampolines
  				declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  			var: #dynamicSuperSendTrampolines
  				declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  			var: #implicitReceiverSendTrampolines
  				declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  			var: #outerSendTrampolines
  				declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]'].
  	aCCodeGenerator
  		addConstantForBinding: self bindingForNumTrampolines;
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #minValidCallAddress type: #'usqIntptr_t'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size printString, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltalk generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'.
  	self declareFlagVarsAsByteIn: aCCodeGenerator!

Item was added:
+ ----- Method: Cogit>>collectProfile (in category 'analysis') -----
+ collectProfile
+ 	<doNotGenerate>
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| | pc thang |
+ 		(pc := processor pc) < methodZoneBase
+ 			ifTrue: [thang := self codeEntryFor: pc]
+ 			ifFalse:
+ 				[(currentProfileMethod notNil
+ 				 and: [currentProfileMethod containsAddress: pc]) ifFalse:
+ 					["inline cogMethodContaining: to avoid useful assert there-in..."
+ 					 | cogMethod prevMethod |
+ 					 cogMethod := self cogMethodSurrogateAt: methodZoneBase.
+ 					 [cogMethod asUnsignedInteger < pc] whileTrue:
+ 						[prevMethod := cogMethod.
+ 						 cogMethod := methodZone methodAfter: cogMethod].
+ 					 currentProfileMethod := prevMethod].
+ 				thang := currentProfileMethod address].
+ 		pmp at: thang put: (pmp at: thang ifAbsent: 0) + 1]!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assertValidDualZone.
  	self assert: self noCogMethodsMaximallyMarked.
  
+ 	self moveProfileToMethods.
+ 
  	self ensureWritableCodeZone.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self compactPICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	methodZone relocateMethodsPreCompaction.
  	self assertValidDualZone.
  	methodZone compactCompiledCode.
  
  	backEnd
  		stopsFrom: methodZone freeStart to: methodZone youngReferrers - 1;
  		flushICacheFrom: methodZoneBase asUnsignedInteger
  			to: methodZone youngReferrers asUnsignedInteger.
  
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
  	self assertValidDualZone!

Item was added:
+ ----- Method: Cogit>>enablePerMethodProfiling (in category 'analysis') -----
+ enablePerMethodProfiling
+ 	<doNotGenerate>
+ 	perMethodProfile := Dictionary new.
+ 	currentProfileMethod := nil.
+ 	singleStep := true!

Item was changed:
  ----- Method: Cogit>>freeCogMethod: (in category 'jit - api') -----
  freeCogMethod: cogMethod
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
+ 	self moveProfileToMethods.
  	methodZone freeMethod: cogMethod.
  	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: Cogit>>freeUnmarkedMachineCode (in category 'jit - api') -----
  freeUnmarkedMachineCode
  	"Free machine-code methods whose compiled methods are unmarked
  	 and open PICs whose selectors are not marked, and closed PICs that
  	 refer to unmarked objects."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod freedMethod |
+ 	self moveProfileToMethods. "simulation only..."
+ 
- 	<var: #cogMethod type: #'CogMethod *'>
  	freedMethod := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMMethod
  		  and: [(objectMemory isMarked: cogMethod methodObject) not]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector) not
  		  and: [(objectMemory isMarked: cogMethod selector) not]]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 (cogMethod cmType = CMClosedPIC
  		  and: [self closedPICRefersToUnmarkedObject: cogMethod]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedMethod ifTrue:
  		[self unlinkSendsToFree]!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCode: (in category 'jit - api') -----
  mapObjectReferencesInMachineCode: gcMode
  	<api>
  	"Update all references to objects in machine code."
  	gcMode caseOf: {
  		[GCModeNewSpace]	-> ["N.B. do *not* ensureWritableCodeZone for every scavenge."
  									self mapObjectReferencesInMachineCodeForYoungGC].
  		[GCModeFull]			-> [self ensureWritableCodeZone.
  									self mapObjectReferencesInMachineCodeForFullGC].
  		[GCModeBecome]		-> [self ensureWritableCodeZone.
  									self mapObjectReferencesInMachineCodeForBecome] }.
  
+ 	self mapPerMethodProfile. "simulation only..."
+ 
  	(self asserta: methodZone freeStart <= methodZone youngReferrers) ifFalse:
  		[self error: 'youngReferrers list overflowed']!

Item was added:
+ ----- Method: Cogit>>mapPerMethodProfile (in category 'analysis') -----
+ mapPerMethodProfile
+ 	"Simulation only counting of instructions per method/pic/trampoline..."
+ 	<cmacro: '() 0'>
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| | map |
+ 		 "The tricky thing here is that a method may get remapped to another method already in the profile, etc..."
+ 		 map := Dictionary new.
+ 		 pmp keysAndValuesDo:
+ 			[:methodOopOrCodeThang :count|
+ 			(methodOopOrCodeThang >= objectMemory startOfMemory
+ 			 and: [objectMemory shouldRemapOop: methodOopOrCodeThang]) ifTrue:
+ 				[map at: methodOopOrCodeThang put: {objectMemory remapObj: methodOopOrCodeThang. count}]].
+ 		 map isEmpty ifFalse:
+ 			[map keysAndValuesDo:
+ 				[:newOop :tuple|
+ 				 [:oldOop :count|
+ 				  (map includesKey: oldOop) ifFalse:
+ 					[pmp removeKey: oldOop].
+ 				  pmp at: newOop put: count] valueWithArguments: tuple]]]!

Item was added:
+ ----- Method: Cogit>>moveProfileToMethods (in category 'analysis') -----
+ moveProfileToMethods
+ 	"Simulation only counting of instructions per method/pic/trampoline..."
+ 	<cmacro: '() 0'>
+ 	"Whenever a change in the code zone is about to occur (e.g. compact code zone, free a method)
+ 	 move all counts to the corresponding Smalltalk objects."
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| | update |
+ 		 update := Dictionary new.
+ 		 pmp keysAndValuesDo:
+ 			[:methodOopOrCodeThang :count|
+ 			(methodOopOrCodeThang between: methodZoneBase and: methodZone limitZony) ifTrue:
+ 			 	[update at: methodOopOrCodeThang put: count]].
+ 		 update keysAndValuesDo:
+ 			[:cogMethodAddress :count| | cogMethod |
+ 			pmp removeKey: cogMethodAddress.
+ 			cogMethod := self cogMethodSurrogateAt: cogMethodAddress.
+ 			cogMethod cmType = CMMethod ifTrue:
+ 				[pmp at: cogMethod methodObject put: (pmp at: cogMethod methodObject ifAbsent: 0) + count].
+ 			(cogMethod cmType = CMClosedPIC
+ 			or: [cogMethod cmType = CMOpenPIC]) ifTrue:
+ 				[pmp at: cogMethod selector put: (pmp at: cogMethod selector ifAbsent: 0) + count]]]!

Item was changed:
  ----- Method: Cogit>>recordProcessing (in category 'simulation only') -----
  recordProcessing
  	| inst |
+ 	self collectProfile.
  	self recordRegisters.
  	inst := self recordLastInstruction.
  	"Set RRRName ito the selector that accesses ReceiverResultReg (RRR) to alter instruction printing to add the value of RRR as a suffix
  		(RRRName := #rdx)
  		(RRRName := #edx)
  		(RRRName := nil)"
  	printRegisters ifTrue:
  		[RRRName ifNil: [processor printRegistersOn: coInterpreter transcript].
  		 printInstructions ifFalse:
  			[coInterpreter transcript cr]].
  	printInstructions ifTrue:
  		[printRegisters ifTrue:
  			[coInterpreter transcript cr].
  		 coInterpreter transcript nextPutAll: inst.
  		 RRRName ifNotNil:
  			[coInterpreter transcript space; nextPutAll: RRRName; space.
  			 (processor perform: RRRName) printOn: coInterpreter transcript base: 16 length: 8 padded: false].
  		 coInterpreter transcript cr; flush]!

Item was added:
+ ----- Method: Cogit>>reportPerMethodProfilingOn: (in category 'analysis') -----
+ reportPerMethodProfilingOn: aStream
+ 	<doNotGenerate>
+ 	| mTotal pTotal tTotal |
+ 	perMethodProfile ifNil:
+ 		[aStream nextPutAll: 'not collecting profile'.
+ 		 ^self].
+ 	self moveProfileToMethods.
+ 	aStream nextPutAll: 'instructions dispatched per trampoline'; cr.
+ 	tTotal := 0.
+ 	((perMethodProfile associations select: [:assoc| assoc key < methodZoneBase]) sorted: [:a1 :a2| a1 value >= a2 value]) do:
+ 		[:assoc|
+ 		tTotal := tTotal + assoc value.
+ 		aStream tab; print: assoc value; nextPut: $:; tab; nextPutAll: (self codeEntryNameFor: assoc key); cr].
+ 	aStream nextPutAll: 'instructions dispatched per method'; cr.
+ 	mTotal := 0.
+ 	((perMethodProfile associations
+ 			select: [:assoc| assoc key >= objectMemory startOfMemory and: [objectMemory isCompiledMethod: assoc key]])
+ 			sorted: [:a1 :a2| a1 value >= a2 value]) do:
+ 		[:assoc|
+ 		mTotal := mTotal + assoc value.
+ 		aStream tab; print: assoc value; nextPut: $:; tab.
+ 		coInterpreter printNameOfClass: (coInterpreter methodClassOf: assoc key) count: 2 on: aStream.
+ 		aStream next: 2 put: $>.
+ 		coInterpreter printStringOf: (coInterpreter findSelectorOfMethod: assoc key) on: aStream.
+ 		aStream cr].
+ 	aStream nextPutAll: 'instructions dispatched per pic'; cr.
+ 	pTotal := 0.
+ 	((perMethodProfile associations
+ 			select: [:assoc| assoc key >= objectMemory startOfMemory and: [(objectMemory isCompiledMethod: assoc key) not]])
+ 			sorted: [:a1 :a2| a1 value >= a2 value]) do:
+ 		[:assoc|
+ 		pTotal := pTotal + assoc value.
+ 		aStream tab; print: assoc value; nextPut: $:; tab.
+ 		coInterpreter printStringOf: assoc key on: aStream.
+ 		aStream cr].
+ 	aStream flush.
+ 	^{tTotal. mTotal. pTotal }!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES primTraceLog breakBlock inputSemaphoreIndex perMethodProfile'
- 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES primTraceLog breakBlock inputSemaphoreIndex'
  	classVariableNames: 'ByteCountsPerMicrosecond'
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !StackInterpreterSimulator commentStamp: 'eem 9/3/2013 11:05' prior: 0!
  This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(StackInterpreterSimulator new openOn: Smalltalk imageName) test
  
  	((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
  		openOn: 'ns101.image') test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example of what Eliot uses to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  | vm |
  vm := StackInterpreterSimulator newWithOptions: #().
  vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
  vm setBreakSelector: #&.
  vm openAsMorph; run!

Item was changed:
  ----- Method: StackInterpreterSimulator>>aboutToDispatchBytecode (in category 'interpreter shell') -----
  aboutToDispatchBytecode
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| pmp at: method put: (pmp at: method ifAbsent: 0) + 1].
  	self incrementByteCount.
  	self assertValidExecutionPointers.
  	atEachStepBlock value "N.B. may be nil"!

Item was added:
+ ----- Method: StackInterpreterSimulator>>enablePerMethodProfiling (in category 'simulation only') -----
+ enablePerMethodProfiling
+ 	perMethodProfile := Dictionary new!

Item was changed:
  ----- Method: StackInterpreterSimulator>>loadNewPlugin: (in category 'plugin support') -----
  loadNewPlugin: pluginString
+ 	(breakSelector notNil
+ 	 and: [pluginString size = breakSelector size
+ 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0]]) ifTrue:
+ 		[self halt: pluginString].
- 	breakSelector ifNotNil:
- 		[(self strncmp: pluginString _: breakSelector _: pluginString size) = 0 ifTrue:
- 			[self halt: pluginString]].
  	^(self tryLoadNewPlugin: pluginString pluginEntries: mappedPluginEntries) ifNotNil:
  		[:entry|
  		 pluginList := pluginList copyWith: entry.
  		 entry]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>mapInterpreterOops (in category 'object memory support') -----
+ mapInterpreterOops
+ 	super mapInterpreterOops.
+ 	perMethodProfile ifNotNil:
+ 		[:pmp| | map |
+ 		 "The tricky thing here is that a method may get remapped to another method already in the profile, etc..."
+ 		 map := Dictionary new.
+ 		 perMethodProfile keysAndValuesDo:
+ 			[:methodOop :count|
+ 			(objectMemory shouldRemapOop: methodOop) ifTrue:
+ 				[map at: methodOop put: {objectMemory remapObj: methodOop. count}]].
+ 		 map isEmpty ifFalse:
+ 			[map keysAndValuesDo:
+ 				[:newOop :tuple|
+ 				 [:oldOop :count|
+ 				  (map includesKey: oldOop) ifFalse:
+ 					[perMethodProfile removeKey: oldOop].
+ 				  perMethodProfile at: newOop put: count] valueWithArguments: tuple]]]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>reportPerMethodProfilingOn: (in category 'simulation only') -----
+ reportPerMethodProfilingOn: aStream
+ 	"Generate a sorted report of bytecodes per method, and instructions per trampoline/cog method/pic.
+ 	 Answer the total number of bytecodes executed."
+ 	| total |
+ 	perMethodProfile ifNil:
+ 		[aStream nextPutAll: 'not collecting profile'.
+ 		 ^self].
+ 	total := 0.
+ 	aStream nextPutAll: 'bytecodes dispatched per method'; cr.
+ 	(perMethodProfile associations sorted: [:a1 :a2| a1 value >= a2 value]) do:
+ 		[:assoc|
+  		total := total + assoc value.
+ 		aStream tab; print: assoc value; nextPut: $:; tab.
+ 		self printNameOfClass: (self methodClassOf: assoc key) count: 2 on: aStream.
+ 		aStream next: 2 put: $>.
+ 		self printStringOf: (self findSelectorOfMethod: assoc key) on: aStream.
+ 		aStream cr].
+ 	aStream flush.
+ 	^total!



More information about the Vm-dev mailing list