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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 24 00:56:42 UTC 2021


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

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

Name: CogTools-eem.91
Author: eem
Time: 23 August 2021, 5:56:40.624079 pm
UUID: 4b95c5fc-8165-4db7-bbe1-5502f8927b02
Ancestors: CogTools-eem.90

Fixes to PluggableListMorphOfManyAlt gratefully received from Marcel.
Recategorizations, and a big fix to findSymbol:event:.

=============== Diff against CogTools-eem.90 ===============

Item was changed:
+ ----- Method: PharoVMProfiler>>createParagraph (in category 'reports') -----
- ----- Method: PharoVMProfiler>>createParagraph (in category 'as yet unclassified') -----
  createParagraph
  	
  	^Paragraph new!

Item was changed:
+ ----- Method: PharoVMProfiler>>getVMParameters (in category 'reports') -----
- ----- Method: PharoVMProfiler>>getVMParameters (in category 'as yet unclassified') -----
  getVMParameters
  
  	^Smalltalk vm getParameters !

Item was removed:
- ----- Method: PluggableListMorphOfManyAlt>>getList (in category 'model access') -----
- getList
- 	"Answer the list to be displayed.  Caches the returned list in the 'list' ivar"
- 	getListSelector == nil ifTrue: [^ #()].
- 	list := model perform: getListSelector.
- 	list == nil ifTrue: [^ #()].
- 	getListElementSelector ifNil:
- 		[list := list collect: [ :item | item asStringOrText ]].
- 	^ list!

Item was changed:
  ----- Method: PluggableListMorphOfManyAlt>>itemSelectedAmongMultiple: (in category 'model access') -----
+ itemSelectedAmongMultiple: viewIndex
+ 	^self listSelectionAt: (self modelIndexFor: viewIndex)!
- itemSelectedAmongMultiple: index
- 	^self listSelectionAt: index!

Item was removed:
- ----- Method: PluggableListMorphOfManyAlt>>list: (in category 'initialization') -----
- list: listOfStrings
- 	scroller removeAllMorphs.
- 	list := listOfStrings ifNil: [Array new].
- 	list isEmpty ifTrue: [^ self selectedMorph: nil].
- 	super list: listOfStrings.
- 
- 	"At this point first morph is sensitized, and all morphs share same handler."
- 	scroller firstSubmorph on: #mouseEnterDragging
- 						send: #mouseEnterDragging:onItem:
- 						to: self.
- 	scroller firstSubmorph on: #mouseUp
- 						send: #mouseUp:onItem:
- 						to: self.
- 	"This should add this behavior to the shared event handler thus affecting all items"!

Item was changed:
  ----- Method: PluggableListMorphOfManyAlt>>mouseDown: (in category 'event handling') -----
  mouseDown: event
+ 	| row index |
- 	| oldIndex oldVal row |
- 	Transcript cr; show: 'mouseDown:'.
  	event yellowButtonPressed ifTrue: [^ self yellowButtonActivity: event shiftPressed].
  	row := self rowAtLocation: event position.
  
  	row = 0 ifTrue: [^super mouseDown: event].
+ 	index := self modelIndexFor: row.
+ 	
- 
  	model okToChange ifFalse: [^ self].  "No change if model is locked"
- 
- 	"Set meaning for subsequent dragging of selection"
- 	dragOnOrOff := (self listSelectionAt: row) not.
  	currentRow := row.
- 	oldIndex := self getCurrentSelectionIndex.
- 	oldVal := oldIndex ~= 0 ifTrue: [self listSelectionAt: oldIndex] ifFalse: [false].
  
+ 	self changeModelSelection: index.
- 	"Need to restore the old one, due to how model works, and set new one."
- 	oldIndex ~= 0 ifTrue: [self listSelectionAt: oldIndex put: oldVal].
  
+ 	"Set meaning for subsequent dragging of selection"
+ 	self
+ 		listSelectionAt: index
+ 		put: (dragOnOrOff := (self listSelectionAt: index) not)
+ !
- 	"Set or clear new primary selection (listIndex)"
- 	self listSelectionAt: row put: oldVal not!

Item was changed:
  ----- Method: PluggableListMorphOfManyAlt>>mouseMove: (in category 'event handling') -----
  mouseMove: event 
  	"The mouse has moved, as characterized by the event provided.  Adjust the scrollbar, and alter the selection as appropriate"
  
+ 	| row index |
- 	| row |
- 	Transcript cr; show: 'mouseMove:'.
  	event position y < self top 
  		ifTrue: 
  			[scrollBar scrollUp: 1.
  			row := self rowAtLocation: scroller topLeft + (1 @ 1)]
  		ifFalse: 
  			[row := event position y > self bottom 
  				ifTrue: 
  					[scrollBar scrollDown: 1.
  					self rowAtLocation: scroller bottomLeft + (1 @ -1)]
  				ifFalse: [ self rowAtLocation: event position]].
  	row = 0 ifTrue: [^super mouseDown: event].
+ 	index := self modelIndexFor: row.
  
  	model okToChange ifFalse: [^self].	"No change if model is locked"
+ 	currentRow = row ifTrue: [^self].
  
- 	currentRow = row ifTrue:
- 		[^self].
- 
  	currentRow := row.
  
+ 	dragOnOrOff ifNil: [
- 	dragOnOrOff ifNil: 
- 		["Don't treat a mouse move immediately after a mouse down to the same index."
- 		row = self getCurrentSelectionIndex ifTrue: [^self].
- 
  		"Was not set at mouse down, which means the mouse must have gone down in an area where there was no list item"
+ 		dragOnOrOff := (self listSelectionAt: index) not].
- 		 dragOnOrOff := (self listSelectionAt: row) not].
  
+ 	self changeModelSelection: index.
+ 	self listSelectionAt: index put: dragOnOrOff.!
- 	"Set or clear new primary selection (listIndex)"
- 	dragOnOrOff 
- 		ifTrue: [self changeModelSelection: row]
- 		ifFalse: [self changeModelSelection: 0].
- 
- 	row changed!

Item was changed:
  ----- Method: PluggableListMorphOfManyAlt>>mouseUp: (in category 'event handling') -----
  mouseUp: event
  
+ 	dragOnOrOff := nil.  "So improperly started drags will have not effect"
+ 	currentRow := nil.	"So mouseMove won't trigger more than once"
+ 
+ 	event hand newKeyboardFocus: self. 
+ 	hasFocus := true.
+ 	Cursor normal show.!
- 	dragOnOrOff := nil.  "So improperly started drags will have no effect"
- 	currentRow := nil	"So mouseMove won't trigger more than once"!

Item was removed:
- ----- Method: PluggableListMorphOfManyAlt>>scrollSelectionIntoView (in category 'selection') -----
- scrollSelectionIntoView
- 	"Make sure that the current selection is visible.
- 	 If the selections() will fit in the scroll region then scroll the selection(s)
- 	 to the middle of the visible region.  If it is larger, make the first part visible."
- 	| row rowBounds innerBounds i |
- 	(row := self getCurrentSelectionIndex) = 0 ifTrue:
- 		[^self].
- 	rowBounds := self listMorph drawBoundsForRow: row.
- 	innerBounds := self innerBounds.
- 	i := row + 1.
- 	[(model perform: getSelectionListSelector with: i)
- 	 and: [(self listMorph drawBoundsForRow: i) bottom - rowBounds top < innerBounds height]] whileTrue:
- 		[i := i + 1].
- 	rowBounds := rowBounds merge: (self listMorph drawBoundsForRow: i - 1).
- 	self scrollToShow: (innerBounds align: innerBounds center with: rowBounds center)!

Item was changed:
  ----- Method: PluggableListMorphOfManyAlt>>update: (in category 'updating') -----
  update: aSymbol 
+ 
+ 	aSymbol == #allSelections ifTrue: [
+ 		"Convenient - yet hard-coded - way to refresh all selections."
+ 		super update: getIndexSelector.
+ 		^ self changed].
+ 	aSymbol == getSelectionListSelector ifTrue: [
+ 		^ self changed].
+ 	
+ 	super update: aSymbol.!
- 	aSymbol == #allSelections ifTrue:
- 		[^self updateList; selectionIndex: self getCurrentSelectionIndex].
- 	^super update: aSymbol!

Item was changed:
+ ----- Method: SqueakVMProfiler>>createParagraph (in category 'reports') -----
- ----- Method: SqueakVMProfiler>>createParagraph (in category 'as yet unclassified') -----
  createParagraph
  	
  	^NewParagraph new!

Item was changed:
  ----- Method: SqueakVMProfiler>>findSymbol:event: (in category 'menus') -----
  findSymbol: typeOrNil event: event
  	| pattern matches selection anIndex |
  	previousPattern ifNil:
  		[previousPattern := '*'].
  	pattern := UIManager default
  					request: 'Symbol or pattern to find'
  					initialAnswer: previousPattern.
  	pattern isEmpty ifTrue: [^self].
  	previousPattern := pattern.
  	matches := symbolManager symbolsSelect:
  					(typeOrNil
  						ifNotNil:
  							[(pattern includesAnyOf: '#*')
  								ifTrue: [[:sym|
  										 sym type == typeOrNil
  										 and: [sym nameMatches: pattern]]]
  								ifFalse: [[:sym|
  										 sym type == typeOrNil
  										 and: [sym name
  												includesSubstring: pattern
  												caseSensitive: false]]]]
  						ifNil:
  							[(pattern includesAnyOf: '#*')
  								ifTrue: [[:sym| sym nameMatches: pattern]]
  								ifFalse: [[:sym| sym name
  												includesSubstring: pattern
  												caseSensitive: false]]]).
  	matches isEmpty ifTrue:
  		[^UIManager inform: 'No symbols match your query'].
  	matches size = 1
  		ifTrue: [selection := matches first]
  		ifFalse:
  			[matches := matches asSortedCollection:
  					[:s1 :s2| | sd1 sd2 |
  					(sd1 := s1 displayText) asString < (sd2 := s2 displayText) asString
  					or: [sd1 = sd2 and: [s1 address <= s2 address]]].
  			 selection := (SelectionMenu
  							labelList: {'Choose symbol'},
  									  (matches collect:
  										[:ea|
  										ea type == #module
  											ifTrue: [ea displayText]
  											ifFalse: [ea displayText, ' @', (ea address printStringRadix: 16),
+ 													((symbolManager moduleFor: ea) ifNotNil: [:m| ' in ', m displayText] ifNil: [''])]])
- 													' in ', (symbolManager moduleFor: ea) displayText]])
  							lines: {1}
  							selections: {nil}, matches) startUp.
  			selection ifNil: [^self]].
  	(symbolTypes includes: selection type) ifFalse:
  		[self toggleShowing: selection type].
  	minSelectionIndex := 0.
  	1 to: symbolList size do:
  		[:i|
  		selections
  			at: i
  			put: (((symbolList at: i) address >= selection address
  				  and: [(symbolList at: i) limit <= selection limit])
  					ifTrue: [minSelectionIndex = 0 ifTrue: [minSelectionIndex := i].
  							maxSelectionIndex := i.
  							1]
  					ifFalse: [0])].
  	self changed: #symbolList.
  	self addToHistory.
  	"If selecting a label make sure there's not a zero address range so
  	 select from the previous non-label symbol to the following non-label symbol"
  	selection address = selection limit
  		ifTrue: [anIndex := minSelectionIndex.
  				[(symbolList at: anIndex) type == #label
  				and: [anIndex > 1]] whileTrue: [anIndex := anIndex - 1].
  				lowAddress := (symbolList at: anIndex) address.
  				anIndex := maxSelectionIndex.
  				[(symbolList at: anIndex) type == #label
  				and: [anIndex < symbolList size]] whileTrue: [anIndex := anIndex + 1].
  				highAddress := (symbolList at: anIndex) address]
  		ifFalse:
  			[lowAddress := selection address.
  			 highAddress := selection limit]. 
  	self updateAddressDependents;
  		updateButtons;
  		plotGraph!

Item was changed:
+ ----- Method: SqueakVMProfiler>>getVMParameters (in category 'reports') -----
- ----- Method: SqueakVMProfiler>>getVMParameters (in category 'as yet unclassified') -----
  getVMParameters
  
  	^Smalltalk getVMParameters !

Item was changed:
  ----- Method: SqueakVMProfiler>>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: nil
- 						changePrimarySelection: #toggleListIndex:
  						listSelection: #symbolSelectionAt:
  						changeListSelection: #symbolSelectionAt:put:
- 						getListElement: #listEntryForIndex:
  						menu: #symbolListMenu:.
  	symbolListMorph hScrollBarPolicy: #whenNeeded. "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.
  
  	self updateButtons. "weird!!"
  	buttons do: [:buttonMorph| buttonMorph color: Color black]. "otherwise labels don't show :("
  	window openInWorld.
  	self toggleShowing: #module.
  	^window!

Item was changed:
+ ----- Method: VMProfiler>>createParagraph (in category 'reports') -----
- ----- Method: VMProfiler>>createParagraph (in category 'as yet unclassified') -----
  createParagraph
  	
  	self subclassResponsibility !

Item was changed:
+ ----- Method: VMProfiler>>filterSamples: (in category 'reports') -----
- ----- 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>>gcPriorToProfile (in category 'reports') -----
- ----- Method: VMProfiler>>gcPriorToProfile (in category 'as yet unclassified') -----
  gcPriorToProfile
  	^gcPriorToProfile!

Item was changed:
+ ----- Method: VMProfiler>>getVMParameters (in category 'reports') -----
- ----- Method: VMProfiler>>getVMParameters (in category 'as yet unclassified') -----
  getVMParameters
  
  	self subclassResponsibility !

Item was removed:
- ----- Method: VMProfiler>>listEntryForIndex: (in category 'accessing') -----
- listEntryForIndex: index
- 	^(symbolList at: index ifAbsent: [^nil]) displayText!

Item was changed:
+ ----- Method: VMProfiler>>toggleShowing: (in category 'selecting') -----
- ----- Method: VMProfiler>>toggleShowing: (in category 'as yet unclassified') -----
  toggleShowing: aSymbol
  	(symbolTypes includes: aSymbol)
  		ifTrue: [symbolTypes remove: aSymbol]
  		ifFalse: [symbolTypes add: aSymbol].
  	symbolTypes isEmpty ifTrue:
  		[symbolTypes add: #module.
  		 self changed: #showingModules.
  		 aSymbol == #module ifTrue:
  			[^self]].
  	self changed: #showingModules;
  		changed: #showingPublicFunctions;
  		changed: #showingPrivateFunctions;
  		changed: #showingLabels.
  	symbolList := symbolManager symbolsWithTypes: symbolTypes.
  	selections := ByteArray new: symbolList size.
  	self selectSymbolsInRange.
  	self changed: #symbolList;
  		changed: #positionedLabels!

Item was changed:
+ ----- Method: VMProfiler>>withDetails (in category 'accessing') -----
- ----- Method: VMProfiler>>withDetails (in category 'as yet unclassified') -----
  withDetails
  
  	^ withDetails!

Item was changed:
+ ----- Method: VMProfiler>>withDetails: (in category 'accessing') -----
- ----- Method: VMProfiler>>withDetails: (in category 'as yet unclassified') -----
  withDetails: aBoolean
  "is the boolean is set to true, then the profiler will provide a detailed report (with bytecode ranges within a function)"
  
  	withDetails:= aBoolean!



More information about the Vm-dev mailing list