[Vm-dev] VM Maker: CogTools-sk.85.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 24 14:07:03 UTC 2017


Sophie Kaleba uploaded a new version of CogTools to project VM Maker:
http://source.squeak.org/VMMaker/CogTools-sk.85.mcz

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

Name: CogTools-sk.85
Author: sk
Time: 24 August 2017, 4:06:51.492365 pm
UUID: cee97bb3-1489-4731-9b22-3fe257071b6b
Ancestors: CogTools-sk.84

* UI for Pharo
* add some comments

=============== Diff against CogTools-sk.84 ===============

Item was changed:
  VMProfiler subclass: #PharoVMProfiler
+ 	instanceVariableNames: 'reportTree result'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CogTools-VMProfiler'!
  
+ !PharoVMProfiler commentStamp: 'sk 8/24/2017 15:24' prior: 0!
- !PharoVMProfiler commentStamp: 'sk 8/10/2017 14:55' prior: 0!
  I am the VMProfiler called when using a Pharo image.
  
+ I can be used 
+ 1) headful : for instance, by typing : VMProfiler spyOn: [1 to: 10000000 do: [ :i | Object new ]].
+ 2) headless : for instance, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s ]
- I can only be used headless for the moment.
- * for instance, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s ]
- * If you want to get a profiling report providing detailed data about the time spent in a function, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s withDetails: true].
  
+ If you want to get a bytecode level profiling report, providing detailed data about the time spent in a function, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s withDetails: true]. This detailed report is available by default in the headful version.
+ 
  !

Item was changed:
+ ----- Method: PharoVMProfiler class>>spyOn: (in category 'spying') -----
- ----- Method: PharoVMProfiler class>>spyOn: (in category 'as yet unclassified') -----
  spyOn: aBlock
  
+ 	"^self headlessSpyOn: aBlock reportOn: '' writeStream  withDetails:true. "
+ 
+ 	^ self new
+ 			selectBenchmark: (CompatibilityClass convertAsString: aBlock);
+ 			withDetails: true;
+ 			reportTree: VMProfilerResultRoot create;
+ 			headlessSpyOn: aBlock;
+ 			fillResults;
+ 			fillReportTree;  
+ 			yourself.
+ 	
+ !
- 	self shouldBeImplemented!

Item was added:
+ ----- Method: PharoVMProfiler>>fillAnalysisPartOfReportTreePart:for:and: (in category 'ui elements') -----
+ fillAnalysisPartOfReportTreePart: aPart for: samplesAssoc and: samplesTotals 
+ "fill the reportTree for either the generated vm code or the vanilla vm code part. samplesAssoc refers to the Dictionary associating a VMPSymbol and its number of samples, samplesTotals refers to the total number of samples you want to compute the percentage from"
+ 
+ 	| generated substantial label cumulated node name |
+ 	generated := self filterSamples: samplesAssoc.
+ 	substantial := generated at: 1.
+ 	cumulated := 0.
+ 	substantial do: [ :func | 
+ 						cumulated := cumulated + func value.
+ 						name := func key isString ifTrue: [ func key ] ifFalse: [func key name].
+ 						label := String streamContents: [:s | 
+ 									self printPercentage: (func value) total:  samplesTotals on: s.
+ 									s nextPutAll: ' ('.
+ 									self printPercentage: (func value) total:  total on: s.
+ 									s nextPutAll: ') ',name,' (',func value asString,') ('.
+ 									self printPercentage: cumulated total:  samplesTotals on: s.
+ 									s nextPutAll: ')'].
+ 						aPart addNode: (func key isString ifTrue: [VMProfilerResult name: name label: label] ifFalse: [(node := VMProfilerResultCM name: name label: label content: func key cm)]) .
+ 						
+ 						(result at: 'cogMethodMaps') at: func key ifPresent: 
+ 									[node addNode: (VMProfilerResult name: func key name label: (String streamContents: [ :s | self printInnerDetails: func with: (result at: 'cogMethodMaps') on: s ])).]]
+ 						" ]."
+ 	!

Item was added:
+ ----- Method: PharoVMProfiler>>fillCompactionPartOfReportTree (in category 'ui elements') -----
+ fillCompactionPartOfReportTree
+ 
+ 	| labelCompaction |
+ 	labelCompaction := String streamContents: [ :s | 
+ 			s nextPutAll: (result at: 'numCompactions') asString; 
+ 			   nextPutAll: ' totalling ';
+ 			   nextPutAll: (result at: 'compactionMsecs') asStringWithCommas; 
+ 			   nextPutAll: 'ms (';
+ 			   nextPutAll: (CompatibilityClass print: (result at: 'compactionMsecs') / elapsedTime * 100 showingDecimalPlaces: 3);
+ 			nextPutAll: '% elapsed time)'.
+ 	(result at: 'numCompactions') = 0 ifFalse:
+ 			[s nextPutAll: ', avg '; 
+ 			   nextPutAll: (CompatibilityClass print: (result at: 'compactionMsecs') / (result at: 'numCompactions') showingDecimalPlaces:3); 
+ 			   nextPutAll: 'ms']].
+ 	
+ 	reportTree compactions addNode: (VMProfilerResult name: 'compactions' label: labelCompaction)
+ 	
+ 
+ 	!

Item was added:
+ ----- Method: PharoVMProfiler>>fillEventPartOfReportTree (in category 'ui elements') -----
+ fillEventPartOfReportTree
+ 
+ #('Process switches' 'ioProcessEvents calls' 'Interrupt checks' 'Event checks' 'Stack overflows' 'Stack page divorces') do: 
+ 	[ :e | reportTree events addNode: (VMProfilerResult name: e label: (e, ' ', (result at: e) asString, ' (', ((((result at: e) * 1000) / elapsedTime) rounded) asString, ' per second)'))]!

Item was added:
+ ----- Method: PharoVMProfiler>>fillGCPartOfReportTree (in category 'ui elements') -----
+ fillGCPartOfReportTree
+ 
+ 	| labelGC labelScavenges labelTenures |
+ 	labelGC := String streamContents: [ :s | s nextPutAll: 'full ', (result at: 'fullGCs') asString, ' totalling ', (result at: 'fullGCTime') asStringWithCommas, 'ms (';
+ 											    nextPutAll: (CompatibilityClass print:( (result at: 'fullGCTime') / elapsedTime * 100) showingDecimalPlaces: 3 );
+ 											    nextPutAll:  '% elapsed time)'.
+ 											(result at: 'fullGCs') = 0 ifFalse: [ s nextPutAll: ', avg '; nextPutAll: (CompatibilityClass print:((result at: 'fullGCTime') / (result at: 'fullGCs')) showingDecimalPlaces: 3); nextPutAll: 'ms' ]].
+ 										
+ 	labelScavenges := String streamContents: [ :s | s nextPutAll: (self class amOnSpur ifTrue: ['scavenges '] ifFalse: ['incr	 ']);
+ 													    print: (result at: 'incrGCs');
+ 													    nextPutAll: ' totalling ';
+ 													    nextPutAll: (result at: 'incrGCTime') asStringWithCommas;
+ 													    nextPutAll: 'ms (';
+ 													   nextPutAll: (CompatibilityClass print: (result at: 'incrGCTime') / elapsedTime  * 100 showingDecimalPlaces: 3);
+ 													   nextPutAll: '% elapsed time)'.
+ 													(result at: 'incrGCs') = 0 ifFalse:
+ 													[s nextPutAll:', avg '; 
+ 													   nextPutAll: (CompatibilityClass print: (result at: 'incrGCTime') / (result  at: 'incrGCs') showingDecimalPlaces:3); 
+ 													   nextPutAll: 'ms']].
+ 												
+ 	labelTenures := String streamContents: [ :s |  s nextPutAll: 'tenures ';
+ 													nextPutAll: (result at: 'tenureCount') asStringWithCommas.
+ 												   (result at: 'tenureCount') = 0 ifFalse:
+ 												 [s nextPutAll: ' (avg '; 
+ 													print: ((result at: 'incrGCs') / (result at: 'tenureCount')) asInteger; 
+ 													nextPutAll: ' GCs/tenure)']].
+ 	
+ 	reportTree gc addNode: (VMProfilerResult name: 'fullGC' label: labelGC);
+ 				     addNode:  (VMProfilerResult name: 'scavenges' label: labelScavenges);
+ 				     addNode: (VMProfilerResult name: 'tenures' label: labelTenures);
+ 				    addNode: (VMProfilerResult name: 'rootTable' label: 'root table ', (result at: 'rootOverflows') asStringWithCommas, ' overflows' ).
+ !

Item was added:
+ ----- Method: PharoVMProfiler>>fillGeneralPartOfReportTree (in category 'ui elements') -----
+ fillGeneralPartOfReportTree
+ 
+ 	reportTree general addNode: (VMProfilerResult name: 'vmPath' label: (result at: 'vmPath'));
+ 			   			addNode: (VMProfilerResult name: 'date' label: (result at: 'date'));
+ 						addNode: (VMProfilerResult name: 'time' label: (result at: 'time'));
+ 						addNode: (VMProfilerResult name: 'edenSize' label: 'eden size: ' , (result at: 'edenSize') asStringWithCommas);
+ 						addNode:(VMProfilerResult name: 'stackPages' label: 'stack pages: ' , (result at: 'stackPages') asString);
+ 						addNode: (VMProfilerResult name: 'codeSize' label: 'code size: ' , (result at: 'codeSize') asStringWithCommas);
+ 						addNode: (VMProfilerResult name: 'profiledBlock' label: (result at: 'profiledBlock'));
+ 						addNode: (VMProfilerResult name: 'elapsedTime' label: (elapsedTime / 1000.0) asString , ' seconds');
+ 						addNode: (VMProfilerResult name: 'frequency' label: 'sampling frequency: ' , (total * 1000 / elapsedTime) rounded asString, ' hz').!

Item was added:
+ ----- Method: PharoVMProfiler>>fillMemoryPartOfReportTree (in category 'ui elements') -----
+ fillMemoryPartOfReportTree
+ 
+ 	reportTree memory addNode: (VMProfilerResult name: 'oldSpaceEnd' label: 'old ',(result at: 'oldSpaceEnd') asStringWithCommasSigned , ' bytes').
+ 	self class amOnSpur 
+ 		ifTrue: [ reportTree memory addNode: (VMProfilerResult name: 'freeSpace' label: 'free ', (result at: 'freeSpace') asStringWithCommasSigned , ' bytes')]
+ 		 ifFalse: 
+ 			[reportTree memory addNode: (VMProfilerResult name: 'youngSpace' label: 'young ', ((result at: 'youngSpaceEnd') - (result at: 'oldSpaceEnd'))  asStringWithCommasSigned , ' bytes');
+ 								addNode: (VMProfilerResult name: 'usedSpace' label: 'used ', (result at: 'youngSpaceEnd') asStringWithCommasSigned , ' bytes');
+ 								addNode: (VMProfilerResult name: 'freeSpace' label: 'free ', ((result at: 'memoryEnd') - (result at: 'youngSpaceEnd')) asStringWithCommasSigned , ' bytes') ].
+ 	
+ 	!

Item was added:
+ ----- Method: PharoVMProfiler>>fillReportTree (in category 'ui elements') -----
+ fillReportTree
+ 
+ 	self fillGeneralPartOfReportTree.
+ 	self fillSamplesPartOfReportTree.  
+ 	self fillAnalysisPartOfReportTreePart: reportTree generated for: (result at: 'cogTotals') and: (result at: 'samplesInCog').
+ 	self fillAnalysisPartOfReportTreePart: reportTree vanilla for: (result at: 'vmTotals') and: (result at: 'samplesInVM'). 
+ 	self fillMemoryPartOfReportTree.
+ 	self fillGCPartOfReportTree.
+ 	self fillCompactionPartOfReportTree.
+ 	self fillEventPartOfReportTree. !

Item was added:
+ ----- Method: PharoVMProfiler>>fillResults (in category 'results') -----
+ fillResults
+ 
+ 	self getDataFromPreambleInResult.
+ 	self getSamplesNumberInResult.  
+ 	self getGCStatsInResult: elapsedStats!

Item was added:
+ ----- Method: PharoVMProfiler>>fillSamplesPartOfReportTree (in category 'ui elements') -----
+ fillSamplesPartOfReportTree
+ 
+ 	reportTree samples addNode: (VMProfilerResult name: 'vmSamples' label: ((result at: 'samplesInVM') + (result at: 'samplesInCog')) asString, ' samples in the VM' );
+ 						  addNode: (VMProfilerResult name: 'totalSamples' 
+ 													   label: total asString, ' samples in the entire program, ', 
+ 															(String streamContents: [ :s | self printPercentage: (result at: 'samplesInEntireVM') total: total on: s]), '% of total');
+ 						addNode: (VMProfilerResult name: 'coglSamples' 
+ 													   label: (result at: 'samplesInCog') asString, ' samples in generated vm code, ', 
+ 															(String streamContents: [ :s | self printPercentage: (result at: 'samplesInCog') total: (result at: 'samplesInEntireVM') on: s]), '% of entire vm (', (String streamContents: [ :s | self printPercentage: (result at: 'samplesInCog') total: total on: s]), '% of total)');
+ 						addNode: (VMProfilerResult name: 'vanillaSamples' label: (result at: 'samplesInVM') asString, ' samples in vanilla vm code, ', (String streamContents: [ :s | self printPercentage: (result at: 'samplesInVM') total: (result at: 'samplesInEntireVM') on: s]), '% of entire vm (', (String streamContents: [ :s | self printPercentage: (result at: 'samplesInVM') total: total on: s]), '% of total)').
+ !

Item was added:
+ ----- Method: PharoVMProfiler>>getDataFromPreambleInResult (in category 'results') -----
+ getDataFromPreambleInResult
+ 
+ 	result at: 'vmPath' put: (SmalltalkImage current getSystemAttribute: 0).
+ 	result at: 'date' put: Date today yyyymmdd.
+ 	result at: 'time' put: Time now print24.
+ 	(startStats size >= 44 
+ 		and: [(startStats at: 44) isNumber]) ifTrue: [ result at: 'edenSize' put: (startStats at: 44).
+ 												 	 result at: 'stackPages' put: (startStats at: 42)].
+ 	(startStats size >= 46
+ 		and: [(startStats at: 46) isNumber
+ 		and: [(startStats at: 46) > 0]]) ifTrue: [ result at: 'codeSize' put: (startStats at: 46) ].
+ 	self trimmedExpressionText notEmpty ifTrue: [ result at: 'profiledBlock' put: self trimmedExpressionText ].
+ !

Item was added:
+ ----- Method: PharoVMProfiler>>getGCStatsInResult: (in category 'results') -----
+ getGCStatsInResult: gcStatsArray
+ 
+ 	gcStatsArray ifNil: [^self class].
+ 	
+ 	result at: 'oldSpaceEnd' put: (gcStatsArray at: 2); "a.k.a. oldSpace size on Spur"
+ 		    at: 'fullGCs' put: (gcStatsArray at: 7);
+ 		    at: 'fullGCTime' put: (gcStatsArray at: 8);
+ 		    at: 'incrGCs' put: (gcStatsArray at: 9);
+ 		    at: 'incrGCTime' put: (gcStatsArray at: 10);
+ 		    at: 'tenureCount' put: (gcStatsArray at: 11);
+ 		    at: 'rootOverflows' put: (gcStatsArray at: 22).
+ 		
+ 	self class amOnSpur
+ 		ifTrue: [(gcStatsArray at: 54) 
+ 						ifNotNil: [:freeSpace| result at: 'freeSpace' put: freeSpace]]				 
+ 		ifFalse:
+ 			[result at: 'youngSpaceEnd'	 put:  (gcStatsArray at: 1).
+ 			 result at: 'memoryEnd' put:  (gcStatsArray at: 3)].
+ 		
+ 	(gcStatsArray size >= 63 and: [(gcStatsArray at: 63) isInteger]) ifTrue:
+ 		[result at: 'numCompactions' put: (gcStatsArray at: 62).
+ 		result at: 'compactionMsecs' put: (gcStatsArray at: 63)].
+ 	
+ 	gcStatsArray size >= 61 ifTrue:
+ 		[(56 to: 61)
+ 			with: #('Process switches' 'ioProcessEvents calls' 'Interrupt checks' 'Event checks' 'Stack overflows' 'Stack page divorces')
+ 			do: [:index :eventName| | value |
+ 				value := gcStatsArray at: index.
+ 				result at: eventName put: value]]!

Item was added:
+ ----- Method: PharoVMProfiler>>getSamplesNumberInResult (in category 'results') -----
+ getSamplesNumberInResult
+ 
+ 	result at: 'vmTotals' put: Dictionary new;
+ 		    at: 'cogTotals' put:  Dictionary new;
+ 		    at: 'nonVMTotals' put: Dictionary new;
+ 		    at: 'cogMethodMaps' put:  Dictionary new;
+ 		    at: 'samplesInVM' put: (self countSymbols: (symbolManager symbolsInModule: symbolManager vmModule) totals: (result at: 'vmTotals'));
+ 		    at: 'samplesInCog' put: (self countSymbols: (symbolManager symbolsInModule: symbolManager cogModule) totals: (result at: 'cogTotals'));
+ 		    at: 'samplesInEntireVM' put: ((result at: 'samplesInVM') + (result at: 'samplesInCog'));
+    		    at: 'samplesInNonVMModules' put: (self countSymbols: self symbolsInNonVMModule totals:  (result at: 'nonVMTotals'));
+ 		    at: 'samplesInNonVM' put: total - (result at: 'samplesInVM') - (result at: 'samplesInCog').
+ 	(result at: 'cogTotals') keysAndValuesDo: 
+ 		[ :key :value |
+ 		value > 10 ifTrue: [ (result at: 'cogMethodMaps') at: key put: (self createMcpcBcpcMapFor: key) ] ].
+ 	(result at: 'nonVMTotals')
+ 		at: 'Samples Not In Any Function'
+ 		put: (result at: 'samplesInNonVM') - (result at: 'samplesInNonVMModules').
+ 	!

Item was added:
+ ----- Method: PharoVMProfiler>>gtInspectorTreeIn: (in category 'ui elements') -----
+ gtInspectorTreeIn: composite
+  <gtInspectorPresentationOrder: 1> 
+ 
+ 	^ reportTree gtInspectorTreeIn: composite!

Item was changed:
  ----- Method: PharoVMProfiler>>initialize (in category 'initialization') -----
  initialize
  
  	self initializeMost.
+ 	reportTree := VMProfilerResultRoot create.
+ 	result := Dictionary new.
  	CompatibilityClass := PharoVMMethodConverter new.
  	self initializeSymbols.!

Item was added:
+ ----- Method: PharoVMProfiler>>reportTree: (in category 'accessing') -----
+ reportTree: aVMProfilerResult
+ 
+ 	reportTree := aVMProfilerResult !

Item was changed:
  VMProfiler subclass: #SqueakVMProfiler
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CogTools-VMProfiler'!
  
+ !SqueakVMProfiler commentStamp: 'sk 8/24/2017 15:25' prior: 0!
- !SqueakVMProfiler commentStamp: 'sk 8/10/2017 14:54' prior: 0!
  I am the VMProfiler called when using a Squeak image.
  
  I can be used 
  1) headful : for instance, either via WorldMenu>open>VMProfiler, or by typing : VMProfiler spyOn: [1 to: 10000000 do: [ :i | Object new ]].
+ 2) headless : for instance, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s ]
+ 
+ If you want to get a profiling report providing detailed data about the time spent in a function, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s withDetails: true]. 
- 2) headless : 
- * for instance, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s ]
- * If you want to get a profiling report providing detailed data about the time spent in a function, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s withDetails: true]. 
  !

Item was changed:
  VMPSymbol subclass: #VMPFunctionSymbol
+ 	instanceVariableNames: 'mcpcbcpcmap cm'
- 	instanceVariableNames: 'mcpcbcpcmap'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CogTools-VMProfiler'!
  
  !VMPFunctionSymbol commentStamp: '<historical>' prior: 0!
  A symbol for a function or procedure (see subclasses)!

Item was added:
+ ----- Method: VMPFunctionSymbol>>cm (in category 'accessing') -----
+ cm
+ 
+ 	^ cm!

Item was added:
+ ----- Method: VMPFunctionSymbol>>cm: (in category 'accessing') -----
+ cm: aCompiledMethod
+ 
+ 	cm := aCompiledMethod !

Item was changed:
  ----- Method: VMProfiler class>>headlessSpyOn:reportOn: (in category 'as yet unclassified') -----
  headlessSpyOn: aBlock reportOn: aStream 
  	"initialize the profiler version (squeak or pharo) and profile headless, writing the results on a given stream"
  
+ 	^VMProfiler new
- 	VMProfiler new
  		selectBenchmark: (CompatibilityClass convertAsString: aBlock);
  		headlessSpyOn: aBlock;
  		report: aStream.
  		 !

Item was changed:
  ----- Method: VMProfiler class>>headlessSpyOn:reportOn:withDetails: (in category 'as yet unclassified') -----
  headlessSpyOn: aBlock reportOn: aStream withDetails: aBoolean
  	"initialize the profiler version (squeak or pharo) and profile headless, writing the results on a given stream"
  
+ 	^VMProfiler new
- 	VMProfiler new
  		withDetails: aBoolean;
  		selectBenchmark: (CompatibilityClass convertAsString: aBlock);
  		headlessSpyOn: aBlock;
  		report: aStream.
  		 !

Item was changed:
  ----- Method: VMProfiler class>>spyOn: (in category 'spying') -----
  spyOn: aBlock
  	
+ 	^VMProfiler new
- 	VMProfiler new
  		class spyOn: aBlock.
  
  	!

Item was added:
+ ----- Method: VMProfiler>>filterSamples: (in category 'as yet unclassified') -----
+ filterSamples: totals	
+ 	
+ 	"Print sorted totals for all symbols with a total greater than 0.01% of the grand total."
+ 	| substantial insubstantial cut labelWidthCut labelledInFull |
+ 	cut := total / 10000.0.
+ 	substantial := totals associations select: [:assoc| assoc value > cut].
+ 	labelWidthCut := total / 1000.0.
+ 	labelledInFull := totals associations select: [:assoc| assoc value > labelWidthCut].
+ 	insubstantial := totals associations
+ 						inject: 0
+ 						into: [:sum :assoc|
+ 							  (assoc value <= cut ifTrue: [assoc value] ifFalse: [0]) + sum].
+ 	substantial := substantial asSortedCollection:
+ 						[:a1 :a2|
+ 						 a1 value > a2 value
+ 						 or: [a1 value = a2 value and: [a1 name < a2 name]]].
+ 	insubstantial > 0 ifTrue:
+ 		[substantial := substantial asArray, {'...others...'->insubstantial}].
+ 	^  {substantial. insubstantial. labelledInFull }
+ 	!

Item was changed:
  ----- Method: VMProfiler>>initializeMost (in category 'initialization') -----
  initializeMost
  	self initializeSamples.
  	self clearHistory.
  	symbolsMode := #byAddress.
  	symbolTypes := IdentitySet new.
  	selections := ByteArray new.
  	withDetails := false.
  	expressionTextMorph := PluggableTextMorph new.
  	highAddress := lowAddress := minSelectionIndex := maxSelectionIndex := 0.
  	aboutToProfile := false.
  	total := rangeTotal := startTime := elapsedTime := 0.
  	gcPriorToProfile := clearPriorToProfile := true.
  	forkProfile := false!

Item was changed:
  ----- Method: VMProfiler>>primitiveCollectCogCodeConstituents: (in category 'primitives') -----
  primitiveCollectCogCodeConstituents: withDetails
  	"Answer the contents of the code zone as an array of pair-wise element, address
  	 in ascending address order.  Answer a string for a runtime routine or abstract label
  	 (beginning, end, etc), a CompiledMethod for a cog machine-code method,
  	 or a selector (presumably a Symbol) for a cog machine-code open or closed PIC.
  	 Fail if this isn't a Cog VM or if out of memory.  If this isn't a Cog VM answer nil.
  	
  	If the parameter is true, answers the mapping between machine code pc and 
  	bytecode pc in relevant methods instead of just the start address.
- 	
- 	If the primitive fails because space is low then the scavenger will run
- 	before trying to send the primitive again.
  	"
  	<primitive: 253 error: ec>
+ 	^ec ifNotNil: [self primitiveFailed]
- 	ec == #'insufficient object memory' ifTrue:
- 		[^self retryPrimitiveCollectCogCodeConstituents: withDetails].
- 	self primitiveFailed
  
  	"self basicNew primitiveCollectCogCodeConstituents"!

Item was changed:
+ ----- Method: VMProfiler>>printSymbolTotals:labelled:on:sumTotal:cogMethodMaps: (in category 'printing') -----
- ----- Method: VMProfiler>>printSymbolTotals:labelled:on:sumTotal:cogMethodMaps: (in category 'reports') -----
  printSymbolTotals: totals labelled: label on: aStream sumTotal: sumTotal cogMethodMaps: cogMethodMaps
  	"Print sorted totals for all symbols with a total greater than 0.01% of the grand total."
+ 	| substantial insubstantial cumulative heading percentageWidth compositionWidth tabWidth labelledInFull filteredSamples |
+ 	filteredSamples := self filterSamples: totals.
+ 	substantial := filteredSamples at: 1.
+ 	insubstantial := filteredSamples at:2.
+ 	labelledInFull := filteredSamples at: 3.
- 	| substantial insubstantial cut cumulative heading percentageWidth compositionWidth tabWidth labelWidthCut labelledInFull |
- 	cut := total / 10000.0.
- 	substantial := totals associations select: [:assoc| assoc value > cut].
- 	labelWidthCut := total / 1000.0.
- 	labelledInFull := totals associations select: [:assoc| assoc value > labelWidthCut].
- 	insubstantial := totals associations
- 						inject: 0
- 						into: [:sum :assoc|
- 							  (assoc value <= cut ifTrue: [assoc value] ifFalse: [0]) + sum].
- 	substantial := substantial asSortedCollection:
- 						[:a1 :a2|
- 						 a1 value > a2 value
- 						 or: [a1 value = a2 value and: [a1 name < a2 name]]].
- 	insubstantial > 0 ifTrue:
- 		[substantial := substantial asArray, {'...others...'->insubstantial}].
  	cumulative := 0.
  	heading := '% of ', label, ' (% of total)'.
  	tabWidth := self widthInDefaultFontOf: (String with: Character tab).
  	percentageWidth := self widthInDefaultFontOf: '99.99%    (99.99%) 	'.
  	compositionWidth := (self longestWidthIn: labelledInFull) + tabWidth
  							max: (self widthInDefaultFontOf: heading) + tabWidth - percentageWidth.
  	self put: heading paddedTo: compositionWidth + percentageWidth tabWidth: tabWidth on: aStream.
  	aStream nextPutAll: '(samples) (cumulative)'; cr.
  	substantial do:
  		[:assoc|
  		self printPercentage: assoc value total: sumTotal on: aStream.
  		aStream space; space; space; space; nextPut: $(.
  		self printPercentage: assoc value total: total on: aStream.
  		aStream nextPut: $); tab.
  		self put: (assoc key isString ifTrue: [assoc key] ifFalse: [assoc key name])
  			paddedTo: compositionWidth
  			tabWidth: tabWidth
  			on: aStream.
  		aStream nextPut: $(; print: assoc value; nextPut: $); tab: (assoc value < 100 ifTrue: [2] ifFalse: [1]); nextPut: $(.
  		cumulative := cumulative + assoc value.
  		self printPercentage: cumulative total: sumTotal on: aStream.
  		aStream nextPut: $); cr.
  		self withDetails ifTrue: [cogMethodMaps at: assoc key ifPresent: [ :i | self printInnerDetails: assoc with: cogMethodMaps on: aStream ]. ].].
  	aStream cr; cr!

Item was changed:
  ----- Method: VMProfiler>>putReportPreambleOn: (in category 'reports') -----
  putReportPreambleOn: s
  	| expr |
  	s nextPutAll: (SmalltalkImage current getSystemAttribute: 0); space; nextPutAll: Date today yyyymmdd; space.
  	Time now print24: true on: s.
  	s cr.
  	(startStats size >= 44
  	 and: [(startStats at: 44) isNumber]) ifTrue:
  		[s nextPutAll: 'eden size: '; nextPutAll: (startStats at: 44) asStringWithCommas.
  		 s nextPutAll: '  stack pages: '; print: (startStats at: 42).
  		 (startStats size >= 46
  		 and: [(startStats at: 46) isNumber
  		 and: [(startStats at: 46) > 0]]) ifTrue:
  			[s nextPutAll: '  code size: '; nextPutAll: (startStats at: 46) asStringWithCommas].
  		s cr].
  	s cr.
  	(expr := self trimmedExpressionText) notEmpty ifTrue:
  		[s nextPutAll: expr; cr; cr].
  	(gcPriorToProfile or: [clearPriorToProfile or: [forkProfile]]) ifTrue:
  		[gcPriorToProfile ifTrue: [s nextPutAll: 'gc prior.  '].
  		 clearPriorToProfile ifTrue: [s nextPutAll: 'clear prior.  '].
  		 forkProfile ifTrue: [s nextPutAll: 'run in separate process.'].
  		 s cr].
  	elapsedTime > 0 ifTrue:
  		[s	print: elapsedTime / 1000.0; nextPutAll: ' seconds; sampling frequency ';
  			print: (total * 1000 / elapsedTime) rounded; nextPutAll: ' hz'; cr]!

Item was changed:
  ----- Method: VMProfiler>>retryPrimitiveCollectCogCodeConstituents: (in category 'primitives') -----
  retryPrimitiveCollectCogCodeConstituents: withDetails
+ 	"if the primitive has failed because of a lack of space, retry (the send of this new message will trigger a gc if needed)
+ 	"
+ 	<primitive: 253 error: ec>
+ 	self primitiveFailed
+ 
+ !
- 	"retryPrimitiveCollectCogCodeConstituents: gets sent after primitiveCollectCogCodeConstituents: has failed and allowed
- 	 a scavenging garbage collection to occur.  The scavenging collection will have happened as the VM is activating the (failing) primitiveCollectCogCodeConstituents.  If
- 	 retryPrimitiveCollectCogCodeConstituents: fails, then we consider the primitive has failed"
- 	
- 	<primitive: 253>
- 	self primitiveFailed!

Item was added:
+ Object subclass: #VMProfilerResult
+ 	instanceVariableNames: 'listOfNodes name label'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CogTools-VMProfiler'!
+ VMProfilerResult class
+ 	instanceVariableNames: 'genData'!
+ 
+ !VMProfilerResult commentStamp: 'SophieKaleba 8/11/2017 11:46' prior: 0!
+ I represent a node in a VMProfiler profiling result tree.
+ This tree structure is used when inspecting the profiling result (AST-like)
+ 
+ listOfNodes : anOrderedCollection of (potentially) other VMProfilerResults node
+ name: aString representing the name of the node. Used to access the node
+ label : aString representing label displayed when inspecting the tree!
+ VMProfilerResult class
+ 	instanceVariableNames: 'genData'!

Item was added:
+ ----- Method: VMProfilerResult class>>name:label: (in category 'as yet unclassified') -----
+ name: aNameString label: aLabelString
+ 
+ 	^ VMProfilerResult new 	
+ 			name: aNameString;
+ 			label: aLabelString;
+ 			yourself. !

Item was added:
+ ----- Method: VMProfilerResult>>addNode: (in category 'adding') -----
+ addNode: aNode
+ 
+ 	listOfNodes add: aNode.!

Item was added:
+ ----- Method: VMProfilerResult>>children (in category 'accessing') -----
+ children 
+ 
+ 	^ listOfNodes !

Item was added:
+ ----- Method: VMProfilerResult>>gtInspectorTreeIn: (in category 'as yet unclassified') -----
+ gtInspectorTreeIn: composite
+     <gtInspectorPresentationOrder: 25> 
+         
+         composite tree
+ 		rootsExpanded ;
+ 		title: 'Report';
+ 		display: [ self ];
+ 		children: [ :each | each children ];
+ 		selectionPopulate: #selectedNode
+ 			on: $o
+ 			entitled: 'Open'
+ 			with: [ :tree | 'toto' ];
+ 		format: [ :each | each printString].!

Item was added:
+ ----- Method: VMProfilerResult>>initialize (in category 'initialization') -----
+ initialize
+ 
+ 	listOfNodes := OrderedCollection new.!

Item was added:
+ ----- Method: VMProfilerResult>>label: (in category 'accessing') -----
+ label: aString
+ 
+ 	label := aString !

Item was added:
+ ----- Method: VMProfilerResult>>name: (in category 'accessing') -----
+ name: aString
+ 
+ 	name := aString.!

Item was added:
+ ----- Method: VMProfilerResult>>printString (in category 'printing') -----
+ printString
+ 
+ 	^ label!

Item was added:
+ VMProfilerResult subclass: #VMProfilerResultCM
+ 	instanceVariableNames: 'method'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'CogTools-VMProfiler'!
+ 
+ !VMProfilerResultCM commentStamp: 'SophieKaleba 8/11/2017 11:49' prior: 0!
+ I represent a specific node in a VMProfiler profiling result tree : the result wrapped in this VMProfilerResultCM is supposed to be a compiled method.
+ 
+ method : the compiledMetod referring to the VMProfilerResult. This way, it is easy to access the compiledMethod data (AST, IR, Bytecode) when inspecting the VMProfilerResult tree. !

Item was added:
+ ----- Method: VMProfilerResultCM class>>name:label:content: (in category 'as yet unclassified') -----
+ name: aName label: aLabel content: aMethod
+ 
+ 	^ VMProfilerResultCM new 
+ 			name: aName ;
+ 			label: aLabel;	
+ 			content: aMethod ;
+ 			yourself.!

Item was added:
+ ----- Method: VMProfilerResultCM>>content: (in category 'accessing') -----
+ content: aMethod
+ 
+ 	method := aMethod !

Item was added:
+ ----- Method: VMProfilerResultCM>>initialize (in category 'initialization') -----
+ initialize
+ 
+ 	super initialize.
+ 	method := nil.!

Item was added:
+ VMProfilerResult subclass: #VMProfilerResultRoot
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'Compactions Events Gc General Generated Memory Samples Vanilla'
+ 	poolDictionaries: ''
+ 	category: 'CogTools-VMProfiler'!
+ 
+ !VMProfilerResultRoot commentStamp: 'SophieKaleba 8/11/2017 12:02' prior: 0!
+ I represent the root of the VMProfilerResult tree.
+ 
+ The different parts of the profiling report are stored as class variables.
+ 
+ compactions, events, gc... vanilla are accessor to the class variables. These class variables are meant to store VMProfilerResult objects.
+ 
+ examples :
+ 
+ VMProfilerResultRoot create 
+ --> instantiate a full tree profiling report with the default parts (Compactions Events Gc General Generated Memory Samples Vanilla). 
+ 
+ VMProfilerResultRoot name: aString label: aString 
+ --> instantiate a VMProfilerResultRoot.
+ 
+ myReportTree general addNode: (VMProfilerResult name: 'vmPath' label: aLabel)
+ --> add a new node in the general section, containing the path of the vm.!

Item was added:
+ ----- Method: VMProfilerResultRoot class>>create (in category 'operations') -----
+ create
+ 	| root  |
+ 	root := VMProfilerResultRoot name: 'root' label: 'Profiling report'.
+ 	General := VMProfilerResult
+ 		name: 'general'
+ 		label: 'General information about the profiling'.
+ 	Samples := VMProfilerResult
+ 		name: 'samplesl'
+ 		label: 'Number of samples'.
+ 	Generated := VMProfilerResult
+ 		name: 'generated'
+ 		label: '% of generated vm code (% of total) (samples) (cumulative)'.
+ 	Vanilla := VMProfilerResult
+ 		name: 'vanilla'
+ 		label: '% of vanilla vm code (% of total) (samples) (cumulative)'.
+ 	Memory := VMProfilerResult name: 'memory' label: '**Memory**'.
+ 	Gc := VMProfilerResult name: 'gc' label: '**GC**'.
+ 	Compactions  := VMProfilerResult
+ 		name: 'compac'
+ 		label: '**Compiled Code Compactions**'.
+ 	Events := VMProfilerResult name: 'events' label: '**Events**'.
+ 	
+ 	root addNode: General ;
+ 		 addNode: Samples;
+ 		 addNode: Generated ;
+ 		 addNode: Vanilla ;	
+ 		 addNode: Memory;
+ 		 addNode: Gc;
+ 		 addNode: Compactions ;
+ 		 addNode: Events. 
+ 
+ 	^ root!

Item was added:
+ ----- Method: VMProfilerResultRoot class>>name:label: (in category 'as yet unclassified') -----
+ name: aNameString label: aLabelString
+ 
+ 	^ VMProfilerResultRoot new 	
+ 			name: aNameString;
+ 			label: aLabelString;
+ 			yourself. !

Item was added:
+ ----- Method: VMProfilerResultRoot>>compactions (in category 'as yet unclassified') -----
+ compactions
+ 	
+ 	^ Compactions!

Item was added:
+ ----- Method: VMProfilerResultRoot>>events (in category 'accessing') -----
+ events
+ 
+ 	^ Events !

Item was added:
+ ----- Method: VMProfilerResultRoot>>gc (in category 'as yet unclassified') -----
+ gc
+ 
+ 	^ Gc!

Item was added:
+ ----- Method: VMProfilerResultRoot>>general (in category 'as yet unclassified') -----
+ general
+ 
+ 	^ General !

Item was added:
+ ----- Method: VMProfilerResultRoot>>generated (in category 'as yet unclassified') -----
+ generated
+ 
+ 	^ Generated !

Item was added:
+ ----- Method: VMProfilerResultRoot>>memory (in category 'as yet unclassified') -----
+ memory
+ 
+ 	^ Memory !

Item was added:
+ ----- Method: VMProfilerResultRoot>>samples (in category 'as yet unclassified') -----
+ samples
+ 
+ 	^ Samples!

Item was added:
+ ----- Method: VMProfilerResultRoot>>vanilla (in category 'as yet unclassified') -----
+ vanilla
+ 
+ 	^ Vanilla!

Item was changed:
  ----- Method: VMProfilerSymbolsManager>>computeCogCodeModule: (in category 'Cog compiled code') -----
  computeCogCodeModule: cogCodeConstituents
  	| symbols |
  	(cogModule := VMPExecutableModuleSymbol new)
  		name: vmModule shortName, '.', cogCodeConstituents first;
  		shortName: cogCodeConstituents first;
  		vmshift: 0;
  		address: cogCodeConstituents second;
  		size: cogCodeConstituents last - cogCodeConstituents second.
  	symbols := (3 to: cogCodeConstituents size - 2 by: 2) collect:
  					[:i| "Declare methods as public; PICs and entries as private"
  					| thing |
  					((thing := cogCodeConstituents at: i) isCompiledMethod
  						ifTrue: [VMPPublicFunctionSymbol]
  						ifFalse: [VMPPrivateFunctionSymbol]) new
  							name: (self nameOf: thing cogCodeModule: cogCodeConstituents);
  							address: (self extractAddress: (cogCodeConstituents at: i + 1));
+ 							cm: thing ;
  							mcpcbcpcmap: (cogCodeConstituents at: i + 1);
  							limit: (self extractAddress: (cogCodeConstituents at: i + 3 ifAbsent: [cogCodeConstituents last]))].
  	self addCogModuleSymbols: symbols!

Item was changed:
  ----- Method: VMProfilerSymbolsManager>>getClosedPICLabel: (in category 'Constituents naming') -----
  getClosedPICLabel: aThing
+ "return a label for the considered closed PIC, listing its selector, its total number of cases, and the concrete classes present in the PIC. The duplicates (if any) among these classes have been deleted in #analyzeClosedPIC: "
- "(= assoc key name )aThing could be either a selector, a trampoline/enilopmart, or a VMPSymbol"
  
  	|list|
  	list := String streamContents: [ :s |(aThing at: 'listOfCases') asStringOn: s delimiter: ', '].
+ 	^ String streamContents: [ :s | s nextPutAll: 'cPIC ', (aThing at: 'selector'), ' - ', (aThing at: 'nbOfCases') asString, ' (', list, ')' ]!
- 	^ String streamContents: [ :s | s nextPutAll: 'cPIC', ' ', (aThing at: 'selector'), ' - ', (aThing at: 'nbOfCases') asString, ' (', list, ')' ]!



More information about the Vm-dev mailing list