[Vm-dev] VM Maker: CogTools-eem.69.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jun 17 17:30:37 UTC 2014


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

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

Name: CogTools-eem.69
Author: eem
Time: 17 June 2014, 10:30:28.054 am
UUID: e345c4d7-b9af-4c49-977e-e949fd349418
Ancestors: CogTools-eem.68

Revamp reporting for Squeak 4.5 (float printing) and Spur.
Fix bug for spyOn: report printing last canned benchmark
instead of block that is profiled.

=============== Diff against CogTools-eem.68 ===============

Item was added:
+ ----- Method: VMProfiler class>>amOnSpur (in category 'reports') -----
+ amOnSpur
+ 	^(Smalltalk vmParameterAt: 41) anyMask: 16!

Item was changed:
  ----- Method: VMProfiler class>>report: (in category 'spying') -----
  report: aStream
+ 	"Compatibility with MessageTally and AndreasSystemProfiler instance side spyOn: & report:"
- 	"Compatibility with MessageTally and QSystemProfiler instance side spyOn: & report:"
  	^self openInstance report: aStream!

Item was changed:
  ----- Method: VMProfiler class>>reportGCStats:upTime:on: (in category 'reports') -----
  reportGCStats: gcStatsArray upTime: elapsedMilliseconds on: str
  	| oldSpaceEnd youngSpaceEnd memoryEnd fullGCs fullGCTime incrGCs incrGCTime tenureCount rootOverflows |
  	gcStatsArray ifNil: [^self].
  
+ 	oldSpaceEnd	:= gcStatsArray at: 1. "a.k.a. oldSpace size on Spur"
- 	oldSpaceEnd	:= gcStatsArray at: 1.
- 	youngSpaceEnd	:= gcStatsArray at: 2.
- 	memoryEnd		:= gcStatsArray at: 3.
  	fullGCs			:= gcStatsArray at: 7.
  	fullGCTime		:= gcStatsArray at: 8.
  	incrGCs			:= gcStatsArray at: 9.
  	incrGCTime		:= gcStatsArray at: 10.
+ 	tenureCount	:= gcStatsArray at: 11.
- 	tenureCount		:= gcStatsArray at: 11.
  	rootOverflows	:= gcStatsArray at: 22.
  
+ 	str	cr.
- 	str cr.
  	str	nextPutAll: '**Memory**'; cr.
  	str	nextPutAll:	'	old			';
  		nextPutAll: oldSpaceEnd asStringWithCommasSigned; nextPutAll: ' bytes'; cr.
+ 	self amOnSpur
+ 		ifTrue:
+ 			[(gcStatsArray at: 54) ifNotNil:
+ 				[:freeSpace|
+ 				 str	nextPutAll: '	free		';
+ 					nextPutAll: freeSpace asStringWithCommasSigned; nextPutAll: ' bytes'; cr]]
+ 		ifFalse:
+ 			[youngSpaceEnd	:= gcStatsArray at: 2.
+ 			 memoryEnd		:= gcStatsArray at: 3.
+ 			 str	nextPutAll: '	young		';
+ 				nextPutAll: (youngSpaceEnd - oldSpaceEnd) asStringWithCommasSigned; nextPutAll: ' bytes'; cr.
+ 			 str	nextPutAll: '	used		';
+ 				nextPutAll: youngSpaceEnd asStringWithCommasSigned; nextPutAll: ' bytes'; cr.
+ 			 str	nextPutAll: '	free		';
+ 				nextPutAll: (memoryEnd - youngSpaceEnd) asStringWithCommasSigned; nextPutAll: ' bytes'; cr].
- 	str	nextPutAll: '	young		';
- 		nextPutAll: (youngSpaceEnd - oldSpaceEnd) asStringWithCommasSigned; nextPutAll: ' bytes'; cr.
- 	str	nextPutAll: '	used		';
- 		nextPutAll: youngSpaceEnd asStringWithCommasSigned; nextPutAll: ' bytes'; cr.
- 	str	nextPutAll: '	free		';
- 		nextPutAll: (memoryEnd - youngSpaceEnd) asStringWithCommasSigned; nextPutAll: ' bytes'; cr.
  
+ 	str	cr.
- 	str cr.
  	str	nextPutAll: '**GCs**'; cr.
  	str	nextPutAll: '	full			';
  		print: fullGCs; nextPutAll: ' totalling '; nextPutAll: fullGCTime asStringWithCommas; nextPutAll: 'ms (';
+ 		print: fullGCTime / elapsedMilliseconds * 100 maxDecimalPlaces: 3;
- 		print: ((fullGCTime / elapsedMilliseconds * 100) rounded);
  		nextPutAll: '% elapsed time)'.
  	fullGCs = 0 ifFalse:
+ 		[str	nextPutAll: ', avg '; print: fullGCTime / fullGCs maxDecimalPlaces: 3; nextPutAll: 'ms'].
- 		[str	nextPutAll: ', avg '; print: (fullGCTime / fullGCs roundTo: 0.1); nextPutAll: 'ms'].
  	str	cr.
+ 	str	nextPutAll: (self amOnSpur ifTrue: ['	scavenges	'] ifFalse: ['	incr			']);
- 	str	nextPutAll: '	incr		';
  		print: incrGCs; nextPutAll: ' totalling '; nextPutAll: incrGCTime asStringWithCommas; nextPutAll: 'ms (';
+ 		print: incrGCTime / elapsedMilliseconds * 100 maxDecimalPlaces: 3;
- 		print: ((incrGCTime / elapsedMilliseconds * 100) roundTo: 0.1);
  		nextPutAll: '% elapsed time)'.
  	incrGCs = 0 ifFalse:
+ 		[str nextPutAll:', avg '; print: incrGCTime / incrGCs maxDecimalPlaces: 3; nextPutAll: 'ms'].
- 		[str nextPutAll:', avg '; print: (incrGCTime / incrGCs roundTo: 0.01); nextPutAll: 'ms'].
  	str cr.
  	str	nextPutAll: '	tenures		';
  		nextPutAll: tenureCount asStringWithCommas.
  	tenureCount = 0 ifFalse:
  		[str nextPutAll: ' (avg '; print: (incrGCs / tenureCount) asInteger; nextPutAll: ' GCs/tenure)'].
  	str	cr.
  	str	nextPutAll: '	root table	';
  		nextPutAll: rootOverflows asStringWithCommas; nextPutAll:' overflows'.
  	str cr.
  
  	(gcStatsArray size >= 63 and: [(gcStatsArray at: 63) isInteger]) ifTrue:
  		[| numCompactions compactionMsecs |
  		str cr; nextPutAll: '**Compiled Code Compactions**'; cr.
  		numCompactions := gcStatsArray at: 62.
  		compactionMsecs := gcStatsArray at: 63.
  		str	tab;
  			print: numCompactions; nextPutAll: ' totalling ';
  			nextPutAll: compactionMsecs asStringWithCommas; nextPutAll: 'ms (';
+ 			print: compactionMsecs / elapsedMilliseconds * 100 maxDecimalPlaces: 3;
- 			print: ((compactionMsecs / elapsedMilliseconds * 100) rounded);
  			nextPutAll: '% elapsed time)'.
  		numCompactions = 0 ifFalse:
+ 			[str	nextPutAll: ', avg '; print: compactionMsecs / numCompactions maxDecimalPlaces: 3; nextPutAll: 'ms'].
- 			[str	nextPutAll: ', avg '; print: (compactionMsecs / numCompactions roundTo: 0.1); nextPutAll: 'ms'].
  		str	cr].
  
  	gcStatsArray size >= 61 ifTrue:
  		[str cr; nextPutAll: '**Events**'; cr.
  		(56 to: 61)
  			with: #('Process switches' 'ioProcessEvents calls' 'Interrupt checks' 'Event checks' 'Stack overflows' 'Stack page divorces')
+ 			do: [:index :eventName| | value n |
- 			do: [:index :eventName| | value |
  				value := gcStatsArray at: index.
+ 				n := 22 - eventName size // 4 + 1.
+ 				str	nextPutAll: eventName; tab: n; print: value; nextPutAll: ' (';
- 				str	nextPutAll: eventName; tab; print: value; nextPutAll: ' (';
  					print: (value * 1000 / elapsedMilliseconds) rounded; nextPutAll: ' per second)'; cr]]!

Item was changed:
  ----- Method: VMProfiler class>>spyOn: (in category 'spying') -----
  spyOn: aBlock
+ 	"Compatibility with MessageTally and AndreasSystemProfiler instance side spyOn: & report:"
- 	"Compatibility with MessageTally and QSystemProfiler instance side spyOn: & report:"
  	^Cursor execute showWhile:
  		[self openInstance spyOn: aBlock]!

Item was changed:
  ----- Method: VMProfiler>>report: (in category 'reports') -----
  report: s
+ 	self totalsDo:
+ 		[:vmTotals :cogTotals :nonVMTotals
+ 		 :samplesInVM :samplesInCog :samplesInNonVMModules :samplesInNonVM |
+ 		self putReportPreambleOn: s.
+ 		s print: samplesInVM + samplesInCog; nextPutAll: ' samples in the VM'; tab; nextPut: $(;
+ 		   print: total; nextPutAll: ' samples in the entire program)  '.
+ 		self printPercentage: samplesInVM + samplesInCog total: total on: s.
+ 		s nextPutAll: ' of total'; cr; cr.
+ 		cogTotals isEmpty ifFalse:
+ 			[s print: samplesInCog; nextPutAll: ' samples in generated vm code '.
+ 			 self printPercentage: samplesInCog total: samplesInVM + samplesInCog on: s.
+ 			 s nextPutAll: ' of entire vm ('.
+ 			 self printPercentage: samplesInCog total: total on: s.
+ 			 s nextPutAll: ' of total)'; cr.
+ 			 s print: samplesInVM; nextPutAll: ' samples in vanilla vm code '.
+ 			 self printPercentage: samplesInVM total: samplesInVM + samplesInCog on: s.
+ 			 s nextPutAll: ' of entire vm ('.
+ 			 self printPercentage: samplesInVM total: total on: s.
+ 			 s nextPutAll: ' of total)'; cr; cr.
+ 			 self printSymbolTotals: cogTotals labelled: 'generated vm code' on: s sumTotal: samplesInCog].
+ 		vmTotals isEmpty ifFalse:
+ 			[self printSymbolTotals: vmTotals labelled: 'vanilla vm code' on: s sumTotal: samplesInVM].
+ 		(samplesInNonVM * 100 >= total
+ 		 and: [nonVMTotals notEmpty]) ifTrue:
+ 			[s print: samplesInNonVM; nextPutAll: ' samples in the rest  '.
+ 			 self printPercentage: samplesInNonVM total: total on: s.
+ 			 s nextPutAll: ' of total'; cr; cr.
+ 			 self printSymbolTotals: nonVMTotals labelled: 'rest' on: s sumTotal: samplesInNonVM].
+ 		self class reportGCStats: elapsedStats upTime: elapsedTime on: s]!
- 	| vmTotals cogTotals nonVMTotals
- 	  samplesInVM samplesInCog samplesInNonVMModules samplesInNonVM |
- 	vmTotals := Dictionary new.
- 	cogTotals := Dictionary new.
- 	nonVMTotals := Dictionary new.
- 	samplesInVM := samplesInCog := samplesInNonVMModules := 0.
- 	Cursor execute showWhile:
- 		[(symbolManager symbolsInModule: symbolManager vmModule) do:
- 			[:sym| | samples |
- 			(#(publicFunction privateFunction) includes: sym type) ifTrue:
- 				[samples := 0.
- 				 sym address to: sym limit - 1 do:
- 					[:a| samples := samples + (highResSamples at: a)].
- 				 samples > 0 ifTrue:
- 					[vmTotals at: sym put: samples.
- 					 samplesInVM := samplesInVM + samples]]].
- 		 (symbolManager symbolsInModule: symbolManager cogModule) do:
- 			[:sym| | samples |
- 			(#(publicFunction privateFunction) includes: sym type) ifTrue:
- 				[samples := 0.
- 				 sym address to: sym limit - 1 do:
- 					[:a| samples := samples + (highResSamples at: a)].
- 				 samples > 0 ifTrue:
- 					[cogTotals at: sym put: samples.
- 					 samplesInCog := samplesInCog + samples]]].
- 		 ((symbolManager modules
- 				copyWithout: symbolManager vmModule)
- 					copyWithout: symbolManager cogModule) do:
- 			[:module|
- 			(symbolManager symbolsInModule: module) do:
- 				[:sym| | samples |
- 				((#(publicFunction privateFunction) includes: sym type)
- 				and: [(sym address // lowResolution to: sym limit // lowResolution) anySatisfy:
- 						[:pc| (lowResSamples at: pc + 1) > 0]]) ifTrue:
- 					[samples := 0.
- 					 sym address to: sym limit - 1 do:
- 						[:a| samples := samples + (highResSamples at: a)].
- 					 samples > 0 ifTrue:
- 						[nonVMTotals at: sym put: samples.
- 						 samplesInNonVMModules := samplesInNonVMModules + samples]]]]].
- 	samplesInNonVM := total - samplesInVM - samplesInCog.
- 	nonVMTotals
- 		at: 'Samples Not In Any Function'
- 		put: samplesInNonVM - samplesInNonVMModules.
- 	self putReportPreambleOn: s.
- 	s print: samplesInVM + samplesInCog; nextPutAll: ' samples in the VM'; tab; nextPut: $(;
- 	   print: total; nextPutAll: ' samples in the entire program)  '.
- 	self printPercentage: samplesInVM + samplesInCog total: total on: s.
- 	s nextPutAll: ' of total'; cr; cr.
- 	cogTotals isEmpty ifFalse:
- 		[s print: samplesInCog; nextPutAll: ' samples in generated vm code '.
- 		 self printPercentage: samplesInCog total: samplesInVM + samplesInCog on: s.
- 		 s nextPutAll: ' of entire vm ('.
- 		 self printPercentage: samplesInCog total: total on: s.
- 		 s nextPutAll: ' of total)'; cr.
- 		 s print: samplesInVM; nextPutAll: ' samples in vanilla vm code '.
- 		 self printPercentage: samplesInVM total: samplesInVM + samplesInCog on: s.
- 		 s nextPutAll: ' of entire vm ('.
- 		 self printPercentage: samplesInVM total: total on: s.
- 		 s nextPutAll: ' of total)'; cr; cr.
- 		 self printSymbolTotals: cogTotals labelled: 'generated vm code' on: s sumTotal: samplesInCog].
- 	vmTotals isEmpty ifFalse:
- 		[self printSymbolTotals: vmTotals labelled: 'vanilla vm code' on: s sumTotal: samplesInVM].
- 	(samplesInNonVM * 100 >= total
- 	and: [nonVMTotals notEmpty]) ifTrue:
- 		[s print: samplesInNonVM; nextPutAll: ' samples in the rest  '.
- 		 self printPercentage: samplesInNonVM total: total on: s.
- 		 s nextPutAll: ' of total'; cr; cr.
- 		 self printSymbolTotals: nonVMTotals labelled: 'rest' on: s sumTotal: samplesInNonVM].
- 	self class reportGCStats: elapsedStats upTime: elapsedTime on: s!

Item was changed:
  ----- Method: VMProfiler>>spyOn: (in category 'spying') -----
  spyOn: aBlock
  	| blockToProfile r |
  	blockToProfile := forkProfile
  						ifTrue:
  							[| sem fr |
  							 sem := Semaphore new.
  							 [[fr := aBlock value. sem signal] fork.
  							   sem wait.
  							   fr]]
  						ifFalse: [aBlock].
+ 	self selectBenchmark: aBlock sourceString.
  	self startProfiling.
  	r := blockToProfile ensure: [self stopProfiling].
  	WorldState addDeferredUIMessage:
  		[self plotGraph].
  	^r!

Item was added:
+ ----- Method: VMProfiler>>totalsDo: (in category 'reports') -----
+ totalsDo: septuaryBlock
+ 	"Evaluate aBlock with 
+ 		a Dictionary of symbol -> total for the functions in the VM (excluding generated code)
+ 		a Dictionary of symbol -> total for the generated code in the VM
+ 		a Dictionary of symbol -> total for the functions in other code
+ 		total number of samples in functions in the VM (excluding generated code)
+ 		total number of samples in generated code in the VM
+ 		total number of samples in generated code in the VM
+ 		total number of samples in functions in other code
+ 		total number of samples not in VM or VM-generated code (incudes code not in any function)"
+ 	| vmTotals cogTotals nonVMTotals
+ 	  samplesInVM samplesInCog samplesInNonVMModules samplesInNonVM |
+ 	vmTotals := Dictionary new.
+ 	cogTotals := Dictionary new.
+ 	nonVMTotals := Dictionary new.
+ 	samplesInVM := samplesInCog := samplesInNonVMModules := 0.
+ 	(symbolManager symbolsInModule: symbolManager vmModule) do:
+ 		[:sym| | samples |
+ 		(#(publicFunction privateFunction) includes: sym type) ifTrue:
+ 			[samples := 0.
+ 			 sym address to: sym limit - 1 do:
+ 				[:a| samples := samples + (highResSamples at: a)].
+ 			 samples > 0 ifTrue:
+ 				[vmTotals at: sym put: samples.
+ 				 samplesInVM := samplesInVM + samples]]].
+ 	 (symbolManager symbolsInModule: symbolManager cogModule) do:
+ 		[:sym| | samples |
+ 		(#(publicFunction privateFunction) includes: sym type) ifTrue:
+ 			[samples := 0.
+ 			 sym address to: sym limit - 1 do:
+ 				[:a| samples := samples + (highResSamples at: a)].
+ 			 samples > 0 ifTrue:
+ 				[cogTotals at: sym put: samples.
+ 				 samplesInCog := samplesInCog + samples]]].
+ 	 ((symbolManager modules
+ 			copyWithout: symbolManager vmModule)
+ 				copyWithout: symbolManager cogModule) do:
+ 		[:module|
+ 		(symbolManager symbolsInModule: module) do:
+ 			[:sym| | samples |
+ 			((#(publicFunction privateFunction) includes: sym type)
+ 			and: [(sym address // lowResolution to: sym limit // lowResolution) anySatisfy:
+ 					[:pc| (lowResSamples at: pc + 1) > 0]]) ifTrue:
+ 				[samples := 0.
+ 				 sym address to: sym limit - 1 do:
+ 					[:a| samples := samples + (highResSamples at: a)].
+ 				 samples > 0 ifTrue:
+ 					[nonVMTotals at: sym put: samples.
+ 					 samplesInNonVMModules := samplesInNonVMModules + samples]]]].
+ 	samplesInNonVM := total - samplesInVM - samplesInCog.
+ 	nonVMTotals
+ 		at: 'Samples Not In Any Function'
+ 		put: samplesInNonVM - samplesInNonVMModules.
+ 	septuaryBlock valueWithArguments:
+ 		{vmTotals.
+ 		 cogTotals.
+ 		 nonVMTotals.
+ 		 samplesInVM.
+ 		 samplesInCog.
+ 		 samplesInNonVMModules.
+ 		 samplesInNonVM}!



More information about the Vm-dev mailing list