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

commits at source.squeak.org commits at source.squeak.org
Mon Aug 23 19:07:24 UTC 2021


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

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

Name: VMMaker.oscog-eem.3048
Author: eem
Time: 23 August 2021, 12:07:16.741622 pm
UUID: bc51357e-57ea-4cb7-9017-41d4f4ce62ff
Ancestors: VMMaker.oscog-eem.3047

Simulator: make reportPerMethodProfilingOn: easier to digest via reportPerMethodProfilingOn:cutoff:.  Add names of primitives to the per method report.

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

Item was changed:
  ----- 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."
+ 	^self reportPerMethodProfilingOn: aStream cutoff: nil!
- 	| 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 added:
+ ----- Method: CogVMSimulator>>reportPerMethodProfilingOn:cutoff: (in category 'simulation only') -----
+ reportPerMethodProfilingOn: aStream cutoff: cutoffOrNilOrPair
+ 	"Generate a sorted report of bytecodes per method, and instructions per trampoline/cog method/pic.
+ 	 Answer an Array with the four totals. cutoffOrNilOrPair is either nil, or an integer, or a pair of integers,
+ 	 { interpreter cutoff, cogit cutoff }"
+ 	| total cutoff |
+ 	perMethodProfile ifNil:
+ 		[aStream nextPutAll: 'not collecting profile'.
+ 		 ^self].
+ 	cutoff := cutoffOrNilOrPair isArray ifTrue: [cutoffOrNilOrPair first] ifFalse: [cutoffOrNilOrPair].
+ 	total := 0.
+ 	aStream nextPutAll: 'bytecodes dispatched per method'; cr.
+ 	(perMethodProfile associations sorted: [:a1 :a2| a1 value >= a2 value]) do:
+ 		[:assoc| 
+  		total := total + assoc value.
+ 		(cutoff isNil or: [assoc value >= cutoff]) ifTrue:
+ 			[self reportSingleMethodProfile: assoc on: aStream]].
+ 	aStream flush.
+ 	^{total}, (cogit
+ 					reportPerMethodProfilingOn: aStream
+ 					cutoff: (cutoffOrNilOrPair isArray ifTrue: [cutoffOrNilOrPair last] ifFalse: [cutoffOrNilOrPair]))!

Item was added:
+ ----- Method: CogVMSimulator>>reportSingleMethodProfile:on: (in category 'simulation only') -----
+ reportSingleMethodProfile: assoc on: aStream
+ 	"Generate a sorted report of bytecodes per method, and instructions per trampoline/cog method/pic.
+ 	 Answer an Array with the four totals."
+ 	| primIndex literal |
+ 	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.
+ 	primIndex := self primitiveIndexOf: assoc key.
+ 	(primIndex = 0
+ 	or: [(self isQuickPrimitiveIndex: primIndex)
+ 	or: [(primitiveTable at: primIndex + 1) isInteger]]) ifFalse:
+ 		[aStream space; nextPutAll: (primitiveTable at: primIndex + 1).
+ 		 (cogit primitiveGeneratorForPrimitiveIndex: primIndex) ifNotNil:
+ 			[:descriptor|
+ 			 descriptor primitiveGenerator ifNotNil:
+ 				[:generator| aStream space; nextPutAll: generator]].
+ 		 primIndex = PrimNumberExternalCall ifTrue:
+ 			[literal := self literal: 0 ofMethod: assoc key.
+ 			 aStream
+ 				space;
+ 				nextPutAll: (self stringOf: (objectMemory fetchPointer: ExternalCallLiteralModuleNameIndex ofObject: literal));
+ 				space;
+ 				nextPutAll: (self stringOf: (objectMemory fetchPointer: ExternalCallLiteralFunctionNameIndex ofObject: literal))]].
+ 	aStream cr!

Item was changed:
  ----- 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.
+ 		coInterpreter reportSingleMethodProfile: assoc on: aStream].
- 		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 added:
+ ----- Method: Cogit>>reportPerMethodProfilingOn:cutoff: (in category 'analysis') -----
+ reportPerMethodProfilingOn: aStream cutoff: cutoffOrNil
+ 	<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.
+ 		(cutoffOrNil isNil or: [assoc value >= cutoffOrNil]) ifTrue:
+ 			[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.
+ 		(cutoffOrNil isNil or: [assoc value >= cutoffOrNil]) ifTrue:
+ 			[coInterpreter reportSingleMethodProfile: assoc on: aStream]].
+ 	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.
+ 		(cutoffOrNil isNil or: [assoc value >= cutoffOrNil]) ifTrue:
+ 			[aStream tab; print: assoc value; nextPut: $:; tab.
+ 			coInterpreter printStringOf: assoc key on: aStream.
+ 			aStream cr]].
+ 	aStream flush.
+ 	^{tTotal. mTotal. pTotal }!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>marryFrameCopiesTemps (in category 'frame access') -----
  marryFrameCopiesTemps
+ 	^coInterpreter marryFrameCopiesTemps!
- 	^ false!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>primitiveGeneratorForPrimitiveIndex: (in category 'simulation only') -----
+ primitiveGeneratorForPrimitiveIndex: index
+ 	"If there is a generator for the primitive index then answer it;
+ 	 otherwise answer nil."
+ 	<doNotGenerate>
+ 	^(index between: 1 and: MaxCompiledPrimitiveIndex) ifTrue:
+ 		[self class initializationOptions at: #DoNotJIT ifPresent:
+ 			[:excluded| (excluded includes: index) ifTrue: [^nil]].
+ 		 primitiveGeneratorTable at: index]!

Item was changed:
  ----- 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."
+ 	^self reportPerMethodProfilingOn: aStream cutoff: nil!
- 	| 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!

Item was added:
+ ----- Method: StackInterpreterSimulator>>reportPerMethodProfilingOn:cutoff: (in category 'simulation only') -----
+ reportPerMethodProfilingOn: aStream cutoff: cutoffOrNil
+ 	"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.
+ 		(cutoffOrNil isNil
+ 		 or: [assoc value > cutoffOrNil]) ifTrue:
+ 			[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!

Item was added:
+ ----- Method: StackInterpreterSimulator>>reportSingleMethodProfile:on: (in category 'simulation only') -----
+ reportSingleMethodProfile: assoc on: aStream
+ 	"Generate a sorted report of bytecodes per method, and instructions per trampoline/cog method/pic.
+ 	 Answer an Array with the four totals."
+ 	| primIndex literal |
+ 	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.
+ 	primIndex := self primitiveIndexOf: assoc key.
+ 	((self isQuickPrimitiveIndex: primIndex)
+ 	or: [(primitiveTable at: primIndex) isInteger]) ifFalse:
+ 		[aStream space; nextPutAll: (primitiveTable at: primIndex).
+ 		 primIndex = PrimNumberExternalCall ifTrue:
+ 			[literal := self literal: 0 ofMethod: assoc key.
+ 			 aStream
+ 				space;
+ 				nextPutAll: (self stringOf: (objectMemory fetchPointer: ExternalCallLiteralModuleNameIndex ofObject: literal));
+ 				space;
+ 				nextPutAll: (self stringOf: (objectMemory fetchPointer: ExternalCallLiteralFunctionNameIndex ofObject: literal))]].
+ 	aStream cr!



More information about the Vm-dev mailing list