[squeak-dev] The Trunk: System-eem.699.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jan 29 00:50:15 UTC 2015


Eliot Miranda uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-eem.699.mcz

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

Name: System-eem.699
Author: eem
Time: 28 January 2015, 4:49:52.494 pm
UUID: 7aa9dbe2-e1cf-4547-bee4-c122268381d9
Ancestors: System-eem.698

Add block nesting to MessageTally.  c.f.
AndreasProfiler-eem.10

=============== Diff against System-eem.698 ===============

Item was changed:
  Magnitude subclass: #MessageTally
+ 	instanceVariableNames: 'class method blockNesting process tally receivers senders time gcStats maxClassNameSize maxClassPlusSelectorSize maxTabs reportOtherProcesses time0 startTime endTime preHibernationCopy'
- 	instanceVariableNames: 'class method process tally receivers senders time gcStats maxClassNameSize maxClassPlusSelectorSize maxTabs reportOtherProcesses time0 startTime endTime preHibernationCopy'
  	classVariableNames: 'DefaultPollPeriod ShowProcesses Timer'
  	poolDictionaries: ''
  	category: 'System-Tools'!
  
  !MessageTally commentStamp: 'eem 7/16/2012 17:10' prior: 0!
  My instances observe and report the amount of time spent in methods.
  
  NOTE: a higher-level user interface (combining the MessageTally result tree with a method browser) is available from TimeProfileBrowser. Note that TimeProfileBrowser was not fancy with the different setting possibilities.
  
  	TimeProfileBrowser spyOn:  [20 timesRepeat: 
  			[Transcript show: 100 factorial printString]]
  	
  
  Strategies
  -----------
  MessageTally provides two different strategies available for profiling:
  
  * spyOn: and friends use a high-priority Process to interrupt the block or process being spied on at periodic intervals. The interrupted call stack is then examined for caller information. See below for an example showing different settings
  
  * tallySends: and friends use the interpreter simulator to run the block, recording every method call.
  
  The two give you different results:
  
  	* spyOn: gives you a view of where the time is being spent in your program, at least on a rough statistical level (assuming you've run the 	block for long enough and have a high enough poll rate). If you're trying to optimize your code, start here and optimize the methods where 	most of the time is being spent first.
  
  	* tallySends: gives you accurate counts of how many times methods get called, and by exactly which route. If you're debugging, or trying to 	figure out if a given method is getting called too many times, this is your tool.
  
  Q: How do you interpret MessageTally>>tallySends
  A: The methods #tallySends and #spyOn: measure two very different quantities, but broken down in the same who-called-who format.  #spyOn: is approximate, but more indicative of real time spent, whereas #tallySends is exact and a precise record of how many times each method got executed.
  
  Examples
  ----------
  
  Here you can see all the processes computation time
  	
  		[1000 timesRepeat: [3.14159 printString. Processor yield]] fork.
  		[1000 timesRepeat: [30 factorial. Processor yield]] fork.
  		[1000 timesRepeat: [30 factorial. Processor yield]] fork.
  		MessageTally spyAllOn: [ (Delay forMilliseconds: 100) wait] 
  
  This profiles across a snapshot, writing the output to {imageName}.N.profile
  	| fn |
  	fn := (FileDirectory baseNameFor: Smalltalk image imageName), '.profile'.
  	[MessageTally
  			spyOn: [Smalltalk image snapshot: true andQuit: true]
  			toFileNamed: fn
  			reportOtherProcesses: true]
  		on: FileExistsException
  		do: [:ex|
  			ex resume:
  				(FileStream forceNewFileNamed: 
  					(FileDirectory default
  						nextNameFor:
  							(FileDirectory localNameFor: 
  								(FileDirectory baseNameFor: fn))
  						extension: 'profile'))]
  
  Settings
  ---------
  You can change the printing format (that is, the whitespace and string compression) by using these instance methods: 
  	maxClassNameSize:
  	maxClassPlusSelectorSize:
  	maxTabs:
  
  You can change the default polling period (initially set to 1) by calling
  	MessageTally defaultPollPeriod: numberOfMilliseconds
  
  
  To understand the difference
  ----------------------------------
  Here we see all the processes
  	[1000 timesRepeat: [
  		100 timesRepeat: [120 factorial].
  		(Delay forMilliseconds: 10) wait
  		]] forkAt: 45 named: '45'.
  	MessageTally spyAllOn: [10000 timesRepeat: [1.23 printString]]
  	
  	
  Here we only see the execution of the expression [10000 timesRepeat: [1.23 printString]
  	[1000 timesRepeat: [
  		100 timesRepeat: [120 factorial].
  		(Delay forMilliseconds: 10) wait
  		]] forkAt: 45 named: '45'.
  	MessageTally spyOn: [10000 timesRepeat: [1.23 printString]]
  	
  Here we only check the exact message sends: this is not a pc-sampling approach
  	[1000 timesRepeat: [
  		100 timesRepeat: [120 factorial].
  		(Delay forMilliseconds: 10) wait
  		]] forkAt: 45 named: '45'.
  	MessageTally tallySends: [10000 timesRepeat: [1.23 printString]]
  	
  
  
  !

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

Item was added:
+ ----- Method: MessageTally>>blockNestingCountOf: (in category 'tallying') -----
+ blockNestingCountOf: context
+ 	| count nest |
+ 	count := 0.
+ 	nest := context.
+ 	[nest closure notNil] whileTrue:
+ 		[count := count + 1.
+ 		 nest := nest closure outerContext].
+ 	^count!

Item was changed:
  ----- Method: MessageTally>>class:method: (in category 'private') -----
  class: aClass method: aMethod
  
  	class := aClass.
  	method := aMethod.
+ 	tally := blockNesting := 0.
+ 	receivers := {}!
- 	tally := 0.
- 	receivers := Array new: 0!

Item was added:
+ ----- Method: MessageTally>>class:method:nesting: (in category 'private') -----
+ class: aClass method: aMethod nesting: blockNestingCount
+ 
+ 	class := aClass.
+ 	method := aMethod.
+ 	blockNesting := blockNestingCount.
+ 	tally := 0.
+ 	receivers := {}!

Item was changed:
  ----- Method: MessageTally>>copyWithTally: (in category 'private') -----
  copyWithTally: hitCount
+ 	^ (MessageTally new class: class method: method nesting: blockNesting)
- 	^ (MessageTally new class: class method: method)
  		reportOtherProcesses: reportOtherProcesses;
  		process: process;
  		bump: hitCount!

Item was changed:
  ----- Method: MessageTally>>into:fromSender: (in category 'collecting leaves') -----
  into: leafDict fromSender: senderTally
  	| leafNode |
+ 	leafNode := leafDict
+ 					at: method
+ 					ifAbsentPut:
+ 						[(self class new class: class method: method nesting: blockNesting)
+ 							process: process;
+ 							reportOtherProcesses: reportOtherProcesses].
- 	leafNode := leafDict at: method
- 		ifAbsentPut: [(self class new class: class method: method)
- 				process: process;
- 				reportOtherProcesses: reportOtherProcesses].
  	leafNode bump: tally fromSender: senderTally!

Item was changed:
  ----- Method: MessageTally>>printOn: (in category 'printing') -----
  printOn: aStream 
  	| className |
  	(class isNil or: [method isNil]) ifTrue: [^super printOn: aStream].
  	className := method methodClass name contractTo: self maxClassNameSize.
+ 	blockNesting ifNotNil:
+ 		[blockNesting timesRepeat:
+ 			[aStream nextPutAll: '[] in ']].
  	aStream
  		nextPutAll: className;
  		nextPutAll: ' >> ';
  		nextPutAll: (method selector contractTo: self maxClassPlusSelectorSize - className size)!

Item was changed:
  ----- Method: MessageTally>>printOn:total:totalTime:tallyExact: (in category 'printing') -----
  printOn: aStream total: total totalTime: totalTime tallyExact: isExact 
  	| aSelector className myTally aClass percentage |
  	isExact 
  		ifTrue: 
  			[myTally := tally.
  			receivers == nil 
  				ifFalse: [receivers do: [:r | myTally := myTally - r tally]].
  			aStream
  				print: myTally;
  				space]
  		ifFalse: 
  			[percentage := tally asFloat / total * 100.0.
  			aStream
  				nextPutAll: (percentage printShowingDecimalPlaces: 1);
  				nextPutAll: '% {';
  				print: (percentage * totalTime / 100) rounded;
  				nextPutAll: 'ms} '].
  	receivers == nil 
  		ifTrue: 
  			[aStream
  				nextPutAll: 'primitives';
  				cr]
  		ifFalse: 
  			[aSelector := method selector.
  			aClass := method methodClass.
  			className := aClass name contractTo: self maxClassNameSize.
+ 			blockNesting > 0 ifTrue:
+ 				[aStream
+ 					next: blockNesting put: $[;
+ 					next: blockNesting put: $];
+ 					space].
  			aStream
  				nextPutAll: class name;
  				nextPutAll: (aClass = class 
  							ifTrue: ['>>']
  							ifFalse: ['(' , aClass name , ')>>']);
  				nextPutAll: (aSelector 
  							contractTo: self maxClassPlusSelectorSize - className size);
  				cr]!

Item was changed:
  ----- Method: MessageTally>>sonsOver: (in category 'comparing') -----
  sonsOver: threshold
  
  	| hereTally last sons |
+ 	receivers basicSize = 0 ifTrue: [^#()].
- 	(receivers == nil or: [receivers size = 0]) ifTrue: [^#()].
  	hereTally := tally.
  	sons := receivers select:  "subtract subNode tallies for primitive hits here"
  		[:son |
  		hereTally := hereTally - son tally.
  		son tally > threshold].
+ 	hereTally > threshold ifTrue:
+ 		[last := MessageTally new class: class method: method nesting: blockNesting.
+ 		 last process: process.
+ 		 last reportOtherProcesses: reportOtherProcesses.
+ 		 ^sons copyWith: (last primitives: hereTally)].
- 	hereTally > threshold
- 		ifTrue: [
- 			last := MessageTally new class: class method: method.
- 			last process: process.
- 			last reportOtherProcesses: reportOtherProcesses.
- 			^sons copyWith: (last primitives: hereTally)].
  	^sons!

Item was changed:
  ----- Method: MessageTally>>tally:in:by: (in category 'tallying') -----
  tally: context in: aProcess by: count
  	"Explicitly tally the specified context and its stack."
+ 	| sender nesting |
+ 	nesting := self blockNestingCountOf: context.
- 	| sender |
  
  	"Add to this node if appropriate"
+ 	(context method == method
+ 	 and: [blockNesting = nesting]) ifTrue:
+ 		[^self bumpBy: count].
- 	context method == method ifTrue: [^self bumpBy: count].
  	
  	"No sender? Add new branch to the tree."
+ 	(sender := context sender) ifNil:
+ 		[^(self bumpBy: count) tallyPath: context in: aProcess by: count].
- 	(sender :=  context sender) ifNil: [
- 		^ (self bumpBy: count) tallyPath: context in: aProcess by: count].
  	
  	"Find the node for the sending context (or add it if necessary)"
  	^ (self tally: sender in: aProcess by: count) tallyPath: context in: aProcess by: count!

Item was changed:
  ----- Method: MessageTally>>tallyPath:by: (in category 'tallying') -----
  tallyPath: context by: count
+ 	| aMethod nesting path |
- 	| aMethod path |
  	aMethod := context method.
+ 	nesting := self blockNestingCountOf: context.
+ 
- 	
  	"Find the correct child (if there)"
+ 	path := receivers
+ 				detect: [:oldTally | 
+ 					oldTally method == aMethod
+ 					and: [oldTally blockNesting = nesting]]
+ 				ifNone: [].
- 	receivers do: [ :oldTally | 
- 		oldTally method == aMethod ifTrue: [path := oldTally]].
  	
  	"Add new child if needed"
+ 	path ifNil:
+ 		[path := MessageTally new class: context receiver class method: aMethod nesting: nesting.
- 	path ifNil: [
- 		path := MessageTally new class: context receiver class method: aMethod.
  		path reportOtherProcesses: reportOtherProcesses.
  		receivers := receivers copyWith: path].
  	
  	^ path bumpBy: count!

Item was changed:
  ----- Method: MessageTally>>tallyPath:in:by: (in category 'tallying') -----
  tallyPath: context in: aProcess by: count
+ 	| aMethod nesting path |
- 	| aMethod path |
  	aMethod := context method.
+ 	nesting := self blockNestingCountOf: context.
+ 
- 	
  	"Find the correct child (if there)"
+ 	path := receivers
+ 				detect: [:oldTally | 
+ 					oldTally method == aMethod
+ 					and: [oldTally process == aProcess
+ 					and: [oldTally blockNesting = nesting]]]
+ 				ifNone: [].
+ 
- 	receivers do: [ :oldTally | 
- 		(oldTally method == aMethod and: [oldTally process == aProcess])
- 			ifTrue: [path := oldTally]].
- 		
  	"Add new child if needed"
+ 	path ifNil:
+ 		[path := MessageTally new
+ 					class: context receiver class method: aMethod nesting: nesting;
+ 					process: aProcess;
+ 					reportOtherProcesses: reportOtherProcesses;
+ 					maxClassNameSize: maxClassNameSize;
+ 					maxClassPlusSelectorSize: maxClassPlusSelectorSize;
+ 					maxTabs: maxTabs.
- 	path ifNil:[
- 		path := MessageTally new class: context receiver class method: aMethod;
- 			process: aProcess;
- 			reportOtherProcesses: reportOtherProcesses;
- 			maxClassNameSize: maxClassNameSize;
- 			maxClassPlusSelectorSize: maxClassPlusSelectorSize;
- 			maxTabs: maxTabs.
  		receivers := receivers copyWith: path].
  
+ 	^path bumpBy: count!
- 	^ path bumpBy: count!



More information about the Squeak-dev mailing list