VM Maker: CogTools-sk.84.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: CogTools-sk.84.mcz

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

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

Name: CogTools-sk.84
Author: sk
Time: 10 August 2017, 3:07:12.537347 pm
UUID: ca5d0d4f-6228-49da-9853-0f10c4234217
Ancestors: CogTools-sk.83

* take into account the modified primitive collectCogCodeConstituents to display the differenciation open/closedPICs
* remove unused method (VMFileSystem, which has been replaced)

To do :
* In the textual report, the display of the number of samples and the cumulated percentages tends to get messy (non aligned) for no reason. I'll try to fix it later

=============== Diff against CogTools-sk.83 ===============

Item was removed:
- VMFileSystem subclass: #PharoVMFileSystem
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'CogTools-VMProfiler'!

Item was removed:
- ----- Method: PharoVMFileSystem>>deleteContentsOf: (in category 'as yet unclassified') -----
- deleteContentsOf: aDirectory
-
- aDirectory deleteAll.
- !

Item was removed:
- ----- Method: PharoVMFileSystem>>ensureExistenceOfDirectory: (in category 'public') -----
- ensureExistenceOfDirectory: aDirName
- ^ aDirName ensureCreateDirectory !

Item was removed:
- ----- Method: PharoVMFileSystem>>exists: (in category 'public') -----
- exists: aFilename
-
- ^ aFilename asFileReference exists!

Item was removed:
- ----- Method: PharoVMFileSystem>>nameFordirPath:plus: (in category 'as yet unclassified') -----
- nameFordirPath: aDirPath plus: aProcessId
-
- ^ (aDirPath, aProcessId) asFileReference   !

Item was removed:
- ----- Method: PharoVMFileSystem>>nameOfFile:in: (in category 'as yet unclassified') -----
- nameOfFile: aFilename in: aDirectory
-
- ^ aFilename asFileReference basename !

Item was removed:
- ----- Method: PharoVMFileSystem>>parentPathOfFile: (in category 'as yet unclassified') -----
- parentPathOfFile: aFilename
-
- ^ (aFilename asFileReference) parent pathString  !

Item was removed:
- ----- Method: PharoVMFileSystem>>round:downTo: (in category 'as yet unclassified') -----
- round: anInteger downTo: decimalPlaces
-
- ^ anInteger printShowingDecimalPlaces: decimalPlaces!

Item was changed:
  VMProfiler subclass: #PharoVMProfiler
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'CogTools-VMProfiler'!
 
+ !PharoVMProfiler commentStamp: 'sk 8/10/2017 14:55' prior: 0!
- !PharoVMProfiler commentStamp: 'sk 5/29/2017 11:56' prior: 0!
  I am the VMProfiler called when using a Pharo image.
 
  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].
- Try inspecting on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s ]
 
  !

Item was removed:
- VMFileSystem subclass: #SqueakVMFileSystem
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'CogTools-VMProfiler'!

Item was removed:
- ----- Method: SqueakVMFileSystem>>deleteContentsOf: (in category 'as yet unclassified') -----
- deleteContentsOf: aDirectory
-
- aDirectory recursiveDelete!

Item was removed:
- ----- Method: SqueakVMFileSystem>>ensureExistenceOfDirectory: (in category 'public') -----
- ensureExistenceOfDirectory: aDirName
-
- ^ aDirName assureExistence!

Item was removed:
- ----- Method: SqueakVMFileSystem>>exists: (in category 'public') -----
- exists: aFilename
-
- ^FileDirectory default fileExists: aFilename !

Item was removed:
- ----- Method: SqueakVMFileSystem>>nameFordirPath:plus: (in category 'as yet unclassified') -----
- nameFordirPath: aDirPath plus: aProcessId
-
- ^ FileDirectory on: aDirPath, aProcessId!

Item was removed:
- ----- Method: SqueakVMFileSystem>>nameOfFile:in: (in category 'as yet unclassified') -----
- nameOfFile: aFilename in: aDirectory
-
- ^ aDirectory localNameFor: aFilename !

Item was removed:
- ----- Method: SqueakVMFileSystem>>parentPathOfFile: (in category 'as yet unclassified') -----
- parentPathOfFile: aFilename
-
- ^ FileDirectory dirPathFor: aFilename !

Item was removed:
- ----- Method: SqueakVMFileSystem>>round:downTo: (in category 'as yet unclassified') -----
- round: anInteger downTo: decimalPlaces
-
- ^ anInteger printShowingMaxDecimalPlaces: decimalPlaces!

Item was changed:
  VMProfiler subclass: #SqueakVMProfiler
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'CogTools-VMProfiler'!
 
+ !SqueakVMProfiler commentStamp: 'sk 8/10/2017 14:54' prior: 0!
- !SqueakVMProfiler commentStamp: 'sk 5/29/2017 11:56' 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].
- - headful (WorldMenu>open>VMProfiler)
- - or headless : for instance, inspect on : String streamContents: [ :s | VMProfiler headlessSpyOn: [ 1 to: 10000000 do: [ :i | Object new ] ] reportOn: s ]
  !

Item was removed:
- Object subclass: #VMFileSystem
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'CogTools-VMProfiler'!
-
- !VMFileSystem commentStamp: 'sk 5/29/2017 11:27' prior: 0!
- I dispatch between the file systems of Pharo (FileSystem) and Squeak (FileDirectory)!

Item was removed:
- ----- Method: VMFileSystem>>deleteContentsOf: (in category 'as yet unclassified') -----
- deleteContentsOf: aDirectory
- self subclassResponsability!

Item was removed:
- ----- Method: VMFileSystem>>ensureExistenceOfDirectory: (in category 'public') -----
- ensureExistenceOfDirectory: aDirName
- self subclassResponsibility !

Item was removed:
- ----- Method: VMFileSystem>>exists: (in category 'public') -----
- exists: aFilename
- self subclassResponsibility !

Item was removed:
- ----- Method: VMFileSystem>>nameFordirPath:plus: (in category 'as yet unclassified') -----
- nameFordirPath: aDirPath plus: aProcessId
- "answers a FileSystem/Directory object representing a directory. The name of this directory is its path+the name of a process id"
-
- self subclassResponsibility !

Item was removed:
- ----- Method: VMFileSystem>>nameOfFile:in: (in category 'as yet unclassified') -----
- nameOfFile: aFilename in: aDirectory
-
- self subclassResponsibility !

Item was removed:
- ----- Method: VMFileSystem>>parentPathOfFile: (in category 'as yet unclassified') -----
- parentPathOfFile: aFilename
-
- self subclassResponsibility !

Item was removed:
- ----- Method: VMFileSystem>>round:downTo: (in category 'as yet unclassified') -----
- round: anInteger downTo: decimalPlaces
-
- self subclassResponsability!

Item was changed:
  ----- Method: VMProfiler>>computeCogCodeModule (in category 'Cog compiled code') -----
  computeCogCodeModule
  cogCodeConstituents ifNil: [^self].
  symbolManager computeCogCodeModule: cogCodeConstituents.
  self changed: #symbolList
 
  "Compute average cog method size:
  (| cogCodeConstituents i1 i2 |
  cogCodeConstituents :=  VMProfiler basicNew primitiveCollectCogCodeConstituents.
  i1 := cogCodeConstituents indexOf: 'methodZoneBase'.
  i2 := cogCodeConstituents indexOf: 'CCFree'.
  (cogCodeConstituents at: i2 + 1) - (cogCodeConstituents at: i1 + 1) / (i2 - i1 / 2.0))"!

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 == #'insufficient object memory' ifTrue:
+ [^self retryPrimitiveCollectCogCodeConstituents: withDetails].
+ self primitiveFailed
- ^ec ifNotNil: [self primitiveFailed]
 
  "self basicNew primitiveCollectCogCodeConstituents"!

Item was changed:
  ----- 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 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>>put:paddedTo:tabWidth:on: (in category 'reports') -----
  put: aString paddedTo: compositionWidth tabWidth: tabWidth on: aStream
  | fittedString size width |
  fittedString := aString.
  size := fittedString size.
  [(width := self widthInDefaultFontOf: fittedString) > compositionWidth] whileTrue:
  [size := size - 2.
  fittedString := aString contractTo: size].
  aStream
  nextPutAll: fittedString;
  tab: compositionWidth - width + (width \\ tabWidth) // tabWidth!

Item was added:
+ ----- Method: VMProfiler>>retryPrimitiveCollectCogCodeConstituents: (in category 'primitives') -----
+ retryPrimitiveCollectCogCodeConstituents: withDetails
+ "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:
+ ----- Method: VMProfilerSymbolsManager>>analyzeClosedPIC: (in category 'Constituents naming') -----
+ analyzeClosedPIC: aClosedPIC
+
+ ^ Dictionary new
+ at: 'selector' put: aClosedPIC first;
+ at: 'nbOfCases' put: aClosedPIC size -1;
+ at: 'listOfCases' put: ((aClosedPIC allButFirst collect: [ :each | each methodClass name ]) asSet);
+ yourself.!

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);
- name: (thing isCompiledMethod
- ifTrue: [thing methodClass name, '>>', thing selector]
- ifFalse: [thing class == cogCodeConstituents first class
- ifTrue: [thing]
- ifFalse: ['PIC ', (thing isString
- ifTrue: [thing]
- ifFalse: [thing printString])]]);
  address: (self extractAddress: (cogCodeConstituents at: i + 1));
  mcpcbcpcmap: (cogCodeConstituents at: i + 1);
  limit: (self extractAddress: (cogCodeConstituents at: i + 3 ifAbsent: [cogCodeConstituents last]))].
  self addCogModuleSymbols: symbols!

Item was added:
+ ----- Method: VMProfilerSymbolsManager>>getClosedPICLabel: (in category 'Constituents naming') -----
+ getClosedPICLabel: aThing
+ "(= 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, ')' ]!

Item was changed:
+ ----- Method: VMProfilerSymbolsManager>>initialize (in category 'initialize-release') -----
- ----- Method: VMProfilerSymbolsManager>>initialize (in category 'as yet unclassified') -----
  initialize
  "Initialize the receiver, parsing the symbols in the background for faster startup."
  self initializeMost.
  self parseAsynchronously!

Item was added:
+ ----- Method: VMProfilerSymbolsManager>>nameOf:cogCodeModule: (in category 'Constituents naming') -----
+ nameOf: thing cogCodeModule: cogCodeConstituents
+
+ thing isCompiledMethod ifTrue: [ ^ thing methodClass name , '>>' , thing selector ].
+ thing class == cogCodeConstituents first class ifTrue: [ ^thing ].
+   ^ thing isArray  
+ ifTrue: [self getClosedPICLabel: (self analyzeClosedPIC: thing)]
+ ifFalse: ['OpenPIC ',(thing isString
+ ifTrue: [ thing ]
+ ifFalse: [ thing printString ])] !