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

commits at source.squeak.org commits at source.squeak.org
Mon May 2 18:44:35 UTC 2016


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

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

Name: CogTools-eem.72
Author: eem
Time: 2 May 2016, 11:44:23.50556 am
UUID: 463bb727-3742-4a23-9487-3a9f6e440a2d
Ancestors: CogTools-eem.71

Fix the VMProfiler for Squeak 5 and Mavericks and later Mac OS X
- aSet = (Set with: #module) no lonfer works for Set and IdentitySet, use size & anyOne.
- the symbol parser gets confused by IsMenuBarVisible which is in HIToolbox and the MacMenubarPlugin.  CoreAUC has a huge chunk of data in its text segment.  So for now simply filter-out problematic modules.
- the alignment morph used to provide the window background (cuz paneColor: no longer works :-( ) must be added first, not last.
- add support for 64-bits on Mac OS X.

=============== Diff against CogTools-eem.71 ===============

Item was changed:
  ----- Method: VMProfiler>>openInWindow (in category 'opening') -----
  openInWindow
  	"VMProfiler open"
  	| window symbolListMorph labelsMorph buttons |
  	(window := SystemWindow new)
  		setProperty: #allowPaneSplitters toValue: false;
  		model: self;
  		setLabel: self class name;
  		fillStyle: Color white;
  		paneColor: Color white;
  		color: Color white.
  	(window respondsTo: #allowPaneSplitters:) ifTrue:
  		[window allowPaneSplitters: false].
+ 	"Cope with Squeak 4.1 SystemWindow background color changes"
+ 	window addMorph: (AlignmentMorph new color: Color white; yourself) frame: (0 at 0 corner: 1 at 1).
  	symbolListMorph := PluggableListMorphOfManyAlt
  						on: self
  						list: #symbolList
  						primarySelection: #symbolIndex
  						changePrimarySelection: #toggleListIndex:
  						listSelection: #symbolSelectionAt:
  						changeListSelection: #symbolSelectionAt:put:
  						getListElement: #listEntryForIndex:
  						menu: #symbolListMenu:.
  	symbolListMorph showHScrollBarOnlyWhenNeeded: false. "buggy misnamed selector :)"
  	labelsMorph := VMProfileGraphLabelMorph model: self font: self labelFont getLabels: #positionedLabels.
  	expressionTextMorph := PluggableTextMorph
  								on: self
  								text: nil accept: nil
  								readSelection: #selectionRange
  								menu: #expressionTextMenu:.
  	expressionTextMorph
  		setProperty: #alwaysAccept toValue: true;
  		askBeforeDiscardingEdits: false;
  		setBalloonText: 'type an expression to profile here'.
  	buttons := OrderedCollection new.
  	window
  		addMorph: symbolListMorph frame: (0 at 0 corner: 0.15 at 1);
  		addMorph: (graph := VMProfilePlotMorph model: self) frame: (0.15 at 0 corner: 1.0 at 0.7);
  		addMorph: labelsMorph frame: (0.15 at 0.7 corner: 1.0 at 0.85);
  		"address boxes"
  		addMorph: (self addressTextMorph:'Type the low address of the histogram here'
  						get: #lowAddressText
  						set: #lowAddressText:)
  			frame: (0.16 at 0.86 corner: 0.27 at 0.91);
  		addMorph: (self addressTextMorph:'Type the high address of the histogram here'
  						get: #highAddressText
  						set: #highAddressText:)
  			frame: (0.88 at 0.86 corner: 0.99 at 0.91);
  		addMorph: (self totalTextMorph: 'Shows the total number of samples' get: #totalText)
  			frame: (0.88 at 0.92 corner: 0.99 at 0.98);
  		"symbol list check-box filters"
  		addMorph: (self checkMorph: 'show module symbols'
  						get: #showingModules
  						set: #toggleShowModules)
  			frame: (0.16 at 0.915 corner: 0.175 at 0.93);
  		addMorph: (buttons addLast: (StringMorph contents: 'modules'))
  			frame: (0.19 at 0.915 corner: 0.27 at 0.93);
  		addMorph: (self checkMorph: 'show extern symbols'
  						get: #showingPublicFunctions
  						set: #toggleShowPublicFunctions)
  			frame: (0.16 at 0.935 corner: 0.175 at 0.95);
  		addMorph: (buttons addLast: (StringMorph contents: 'externs'))
  			frame: (0.19 at 0.935 corner: 0.27 at 0.95);
  		addMorph: (self checkMorph: 'show static symbols'
  						get: #showingPrivateFunctions
  						set: #toggleShowPrivateFunctions)
  			frame: (0.16 at 0.955 corner: 0.175 at 0.97);
  		addMorph: (buttons addLast: (StringMorph contents: 'statics'))
  			frame: (0.19 at 0.955 corner: 0.27 at 0.97);
  		addMorph: (self checkMorph: 'show static symbols'
  						get: #showingLabels
  						set: #toggleShowLabels)
  			frame: (0.16 at 0.975 corner: 0.175 at 0.99);
  		addMorph: (buttons addLast: (StringMorph contents: 'labels'))
  			frame: (0.19 at 0.975 corner: 0.27 at 0.99);
  		"history buttons"
  		addMorph: (self historyButtonMorph: #backwardsButton help: 'go back to previous selection'
  						set: #regress enable: #hasHistory color: #hasHistoryColor)
  			frame: (0.28 at 0.86 corner: 0.315 at 0.90);
  		addMorph: (self historyButtonMorph: #forwardsButton help: 'go forward to next selection'
  						set: #progress enable: #hasFuture color: #hasFutureColor)
  			frame: (0.32 at 0.86 corner: 0.355 at 0.90);
  		"profiling buttons"
  		addMorph: (self buttonMorph: #drawButton help: 'plot the graph'
  						set: #plotGraph enable: #notProfilingAndData color: #clearColor)
  			frame: (0.37 at 0.86 corner: 0.45 at 0.91);
  		addMorph: (self buttonMorph: #clearButton help: 'clear the histogram data'
  						set: #clearProfile enable: #notProfiling color: #clearColor)
  			frame: (0.46 at 0.86 corner: 0.54 at 0.91);
  		addMorph: (self buttonMorph: #startButton help: 'start the profiler'
  						set: #startProfiling enable: #notProfiling color: #profileColor)
  			frame: (0.28 at 0.915 corner: 0.36 at 0.96);
  		addMorph: (self buttonMorph: #stopButton help: 'stop the profiler'
  						set: #stopProfiling enable: #profiling color: #stopColor)
  			frame: (0.37 at 0.915 corner: 0.45 at 0.96);
  		addMorph: (self buttonMorph: #profileExpressionButton help: 'compile and profile the expression to the right'
  						set: #profileExpression enable: #notProfiling color: #profileColor)
  			frame: (0.46 at 0.915 corner: 0.54 at 0.96);
  		addMorph: expressionTextMorph
  			frame: (0.55 at 0.86 corner: 0.87 at 0.98);
  		addMorph: (self checkMorph: 'Run the full garbage collector prior to profiling'
  						get: #gcPriorToProfile
  						set: #toggleGcPriorToProfile)
  			frame: (0.28 at 0.97 corner: 0.295 at 0.985);
  		addMorph: (buttons addLast: (StringMorph contents: 'gc prior'))
  			frame: (0.30 at 0.97 corner: 0.365 at 0.995);
  		addMorph: (self checkMorph: 'Clear the profile prior to profiling'
  						get: #clearPriorToProfile
  						set: #toggleClearPriorToProfile)
  			frame: (0.37 at 0.97 corner: 0.385 at 0.985);
  		addMorph: (buttons addLast: (StringMorph contents: 'clear prior'))
  			frame: (0.39 at 0.97 corner: 0.455 at 0.995);
  		addMorph: (self checkMorph: 'Run the profiled expression in its own process'
  						get: #forkProfile
  						set: #toggleForkProfile)
  			frame: (0.46 at 0.97 corner: 0.475 at 0.985);
  		addMorph: (buttons addLast: (StringMorph contents: 'fork profile'))
  			frame: (0.48 at 0.97 corner: 0.545 at 0.995).
  .
  	"A Color transparent fillStyle used to be the default.  What a
  	 pain that things change so radically from release to release!!"
  	graph fillStyle: Color transparent.
- 	"Cope with Squeak 4.1 SystemWindow background color changes"
- 	window addMorph: (AlignmentMorph new color: Color white; yourself) frame: (0 at 0 corner: 1 at 1).
  
  	self updateButtons. "weird!!"
  	buttons do: [:buttonMorph| buttonMorph color: Color black]. "otherwise labels don't show :("
  	window openInWorld.
  	self toggleShowing: #module.
  	^window!

Item was added:
+ ----- Method: VMProfilerMacSymbolsManager>>filter: (in category 'initialize-release') -----
+ filter: moduleList
+ 	"Some modules are giving us parsing problems at the moment.  Just ignore them for now."
+ 	^moduleList reject: [:t| #('CoreAUC' 'FaceCore' 'HIToolbox' 'VideoToolbox') anySatisfy: [:s| t name includesSubstring: s]]!

Item was changed:
  ----- Method: VMProfilerMacSymbolsManager>>initializeMost (in category 'initialize-release') -----
  initializeMost
  	| shortNames |
  	initialized := false.
  	maxAddressMask := (2 raisedToInteger: 32) - 1.
  	modulesByName := Dictionary new.
  	symbolsByModule := Dictionary new.
  	shortNames := Set new.
  	modules := self primitiveExecutableModulesAndOffsets.
  	(tempDir := self class tempDirectory) assureExistence.
  	modules := (1 to: modules size by: 4) collect:
  					[:i| | shortName counter |
  					shortName := tempDir localNameFor: (modules at: i).
  					counter := 0.
  					[shortNames includes: shortName] whileTrue:
  						[counter := counter + 1.
  						 shortName := (tempDir localNameFor: (modules at: i)), counter printString].
  					shortNames add: shortName.
  					(modulesByName
  						at: (modules at: i)
  						put: VMPExecutableModuleSymbol new)
  								name: (modules at: i);
  								shortName: shortName;
  								vmshift: (modules at: i + 1);
  								address: (maxAddressMask bitAnd: (modules at: i + 2) + (modules at: i + 1));
  								size: (modules at: i + 3)].
+ 	modules := self filter: modules.
  	"The primitive always answers the VM info in the first entry."
  	vmModule := modules first.
  	modules := modules asSortedCollection: [:m1 :m2| m1 address <= m2 address]!

Item was changed:
  ----- Method: VMProfilerMacSymbolsManager>>parseSymbolsFor: (in category 'parsing') -----
  parseSymbolsFor: module
  	| arch proc symtab symStream |
+ 	arch := (Smalltalk image getSystemAttribute: 1003) caseOf: {
+ 				['intel']	->	['i386'].
+ 				['x64']	->	['x86_64'].
+ 				}.
- 	arch := 'i386'. "for now; needs to be fetched from a systemAttribute sometime soon."
  	(tempDir fileExists: module shortName) ifFalse:
  		[proc := OSProcess thisOSProcess command:
  						'cd ', tempDir fullName,
  						';nm -n -arch ', arch, ' -f "', module name, '" | grep -v " [aAU] " >"', module shortName, '"'].
  	symStream := (Array new: 1000) writeStream.
  	symStream nextPut: module.
  	proc ifNotNil:
  		[[proc isComplete] whileFalse: [(Delay forMilliseconds: 25) wait]].
  	symtab := [StandardFileStream readOnlyFileNamed: (tempDir fullNameFor: module shortName)]
  					on: Error
  					do: [:ex| "Handle flaky OSProcess stuff by reporting error and failing to parse"
  						Transcript print: ex; flush.
  						^nil].
+ 	module shortName = 'HIToolbox' ifTrue: [self halt].
  	[| prev |
  	 prev := self parseSymbolsFrom: symtab to: symStream.
+ 	"CoreAUC has a huge chunk of data at the end of its text segment that causes the profiler to spend ages
+ 	 counting zeros.  Hack fix by setting the end of the last symbol in the text segment to a little less than 1Mb." 
+ 	"00000000000f1922    retq" "Mavericks 13.4"
+ 	"00000000000f3b21    retq" "Yosemite 14.5"
+ 	module shortName = 'CoreAUC' ifTrue: [prev limit: 16rf8000].
  	 symbolsByModule
  		at: module
  		put: (self relocateSymbols: symStream contents allButFirst inModule: module).
  	 (prev notNil
  	  and: [prev limit isNil]) ifTrue: [prev limit: module limit]]
  		ensure: [symtab close]!

Item was changed:
  ----- Method: VMProfilerSymbolsManager>>symbolsWithTypes: (in category 'accessing') -----
  symbolsWithTypes: aSet
  	| size stream |
+ 	(aSet size = 1 and: [aSet anyOne == #module]) ifTrue:
- 	aSet = (Set with: #module) ifTrue:
  		[^modules].
  	size := symbolsByModule inject: 0 into: [:sum :symbols| sum + symbols size].
  	stream := (Array new: size) writeStream.
  	modules do:
  		[:module|
  		(symbolsByModule at: module) do:
  			[:sym|
  			(aSet includes: sym type) ifTrue:
  				[stream nextPut: sym]]].
  	^stream contents!



More information about the Vm-dev mailing list