[squeak-dev] The Trunk: System-ul.258.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Feb 22 16:08:03 UTC 2010


Levente Uzonyi uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-ul.258.mcz

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

Name: System-ul.258
Author: ul
Time: 22 February 2010, 4:58:39.586 pm
UUID: f24f63f8-4483-904a-bf5f-531565242b22
Ancestors: System-mtf.257

- integrate MessageTally fixes from Cuis (by Juan Vuletich)

=============== Diff against System-mtf.257 ===============

Item was changed:
  ----- Method: MessageTally>>spyEvery:onProcess:forMilliseconds: (in category 'initialize-release') -----
  spyEvery: millisecs onProcess: aProcess forMilliseconds: msecDuration 
  	"Create a spy and spy on the given process at the specified rate."
  	| myDelay time0 endTime observedProcess sem |
  	(aProcess isKindOf: Process)
  		ifFalse: [self error: 'spy needs a Process here'].
  	self class: aProcess suspendedContext receiver class method: aProcess suspendedContext method.
  	"set up the probe"
  	observedProcess := aProcess.
  	myDelay := Delay forMilliseconds: millisecs.
  	time0 := Time millisecondClockValue.
  	endTime := time0 + msecDuration.
  	sem := Semaphore new.
  	gcStats := SmalltalkImage current getVMParameters.
+ 	Timer ifNotNil: [ self error: 'it seems a tally is already running' ].
- 	Timer ifNotNil: [ Timer terminate ].
  	Timer := [
  			[
  				| startTime |
  				startTime := Time millisecondClockValue.
  				myDelay wait.
  				self
  					tally: Processor preemptedProcess suspendedContext
+ 					in: (observedProcess == Processor preemptedProcess 
+ 						ifTrue: [ observedProcess ]
+ 						ifFalse: [ nil ])
- 					in: (observedProcess == Processor preemptedProcess ifTrue: [observedProcess] ifFalse: [nil])
  					"tally can be > 1 if ran a long primitive"
  					by: (Time millisecondClockValue - startTime) // millisecs.
  				startTime < endTime
  			] whileTrue.
  			sem signal.
  		] newProcess.
  	Timer priority: Processor timingPriority-1.
  		"activate the probe and evaluate the block"
  	Timer resume.
  	"activate the probe and wait for it to finish"
  	sem wait.
  	"Collect gc statistics"
  	SmalltalkImage current getVMParameters keysAndValuesDo: [ :idx :gcVal | 
  		gcStats at: idx put: (gcVal - gcStats at: idx)].
  	time := Time millisecondClockValue - time0!

Item was changed:
  ----- Method: MessageTally class>>tallySendsTo:inBlock:showTree: (in category 'spying') -----
  tallySendsTo: receiver inBlock: aBlock showTree: treeOption
  	"
  	MessageTally tallySends: [3.14159 printString]
  	"
  	"This method uses the simulator to count the number of calls on each method
  	invoked in evaluating aBlock. If receiver is not nil, then only sends
  	to that receiver are tallied.
  	Results are presented as leaves, sorted by frequency,
  	preceded, optionally, by the whole tree."
  	| prev tallies startTime totalTime |
  	startTime := Time millisecondClockValue.
  	tallies := MessageTally new class: aBlock receiver class method: aBlock method.
  	tallies reportOtherProcesses: true.	"Do NOT filter nodes with nil process"
  	prev := aBlock.
  	thisContext sender
  		runSimulated: aBlock
+ 		contextAtEachStep: [ :current |
+ 			current == prev ifFalse: [ "call or return"
+ 				prev sender == nil ifFalse: [ "call only"
+ 					(receiver == nil or: [ current receiver == receiver ])
+ 						ifTrue: [ tallies tally: current by: 1 ] ].
+ 				prev := current ] ].
- 		contextAtEachStep:
- 			[:current |
- 			current == prev ifFalse: 
- 				["call or return"
- 				prev sender == nil ifFalse: 
- 					["call only"
- 					(receiver == nil or: [current receiver == receiver])
- 						ifTrue: [tallies tally: current by: 1]].
- 				prev := current]].
  
  	totalTime := Time millisecondClockValue - startTime // 1000.0 roundTo: 0.01.
  	(StringHolder new contents:
  		(String streamContents:
  			[:s |
  			s nextPutAll: 'This simulation took ' , totalTime printString
  							, ' seconds.'; cr.
  			treeOption
  				ifTrue: [ tallies fullPrintExactOn: s ]
  				ifFalse: [ tallies leavesPrintExactOn: s ].
  			tallies close ]))
  		openLabel: 'Spy Results'!

Item was changed:
  ----- Method: MessageTally>>spyAllEvery:on: (in category 'initialize-release') -----
  spyAllEvery: millisecs on: aBlock
  	"Create a spy and spy on the given block at the specified rate."
  	"Spy all the system processes"
  
  	| myDelay time0 |
+ 	aBlock isBlock
+ 		ifFalse: [ self error: 'spy needs a block here' ].
- 	(aBlock isMemberOf: BlockClosure)
- 		ifFalse: [self error: 'spy needs a block here'].
  	self class: aBlock receiver class method: aBlock method.
  		"set up the probe"
  	myDelay := Delay forMilliseconds: millisecs.
  	time0 := Time millisecondClockValue.
  	gcStats := SmalltalkImage current getVMParameters.
+ 	Timer ifNotNil: [ self error: 'it seems a tally is already running' ].
- 	Timer ifNotNil: [ Timer terminate ].
  	Timer := [
  		[true] whileTrue: [
  			| observedProcess startTime |
  			startTime := Time millisecondClockValue.
  			myDelay wait.
  			observedProcess := Processor preemptedProcess.
  			self
  				tally: observedProcess suspendedContext
  				in: observedProcess
  				"tally can be > 1 if ran a long primitive"
  				by: (Time millisecondClockValue - startTime) // millisecs].
  		nil] newProcess.
  	Timer priority: Processor timingPriority-1.
  		"activate the probe and evaluate the block"
  	Timer resume.
  	^ aBlock ensure: [
- 		"Collect gc statistics"
- 		SmalltalkImage current getVMParameters keysAndValuesDo: [ :idx :gcVal | 
- 			gcStats at: idx put: (gcVal - (gcStats at: idx))].
  		"cancel the probe and return the value"
+ 		"Could have already been terminated. See #terminateTimerProcess"
  		Timer ifNotNil: [
  			Timer terminate.
  			Timer := nil ].
+ 		"Collect gc statistics"
+ 		SmalltalkImage current getVMParameters keysAndValuesDo: [ :idx :gcVal | 
+ 			gcStats at: idx put: (gcVal - (gcStats at: idx))].
  		time := Time millisecondClockValue - time0]!

Item was changed:
  ----- Method: MessageTally>>spyEvery:on: (in category 'initialize-release') -----
  spyEvery: millisecs on: aBlock
  	"Create a spy and spy on the given block at the specified rate."
  	"Spy only on the active process (in which aBlock is run)"
  
  	| myDelay time0 observedProcess |
+ 	aBlock isBlock
+ 		ifFalse: [ self error: 'spy needs a block here' ].
- 	(aBlock isMemberOf: BlockClosure)
- 		ifFalse: [self error: 'spy needs a block here'].
  	self class: aBlock receiver class method: aBlock method.
  		"set up the probe"
  	observedProcess := Processor activeProcess.
  	myDelay := Delay forMilliseconds: millisecs.
  	time0 := Time millisecondClockValue.
  	gcStats := SmalltalkImage current getVMParameters.
+ 	Timer ifNotNil: [ self error: 'it seems a tally is already running' ].
+ 	Timer := [
+ 		[ true ] whileTrue: [
- 	Timer ifNotNil: [ Timer terminate ].
- 	Timer := [ 
- 		[true] whileTrue: [
  			| startTime |
  			startTime := Time millisecondClockValue.
  			myDelay wait.
  			self
  				tally: Processor preemptedProcess suspendedContext
  				in: (observedProcess == Processor preemptedProcess ifTrue: [observedProcess] ifFalse: [nil])
  				"tally can be > 1 if ran a long primitive"
  				by: (Time millisecondClockValue - startTime) // millisecs].
  		nil] newProcess.
  	Timer priority: Processor timingPriority-1.
  		"activate the probe and evaluate the block"
  	Timer resume.
  	^ aBlock ensure: [
- 		"Collect gc statistics"
- 		SmalltalkImage current getVMParameters keysAndValuesDo: [ :idx :gcVal | 
- 			gcStats at: idx put: (gcVal - (gcStats at: idx))].
  		"cancel the probe and return the value"
+ 		"Could have already been terminated. See #terminateTimerProcess"
  		Timer ifNotNil: [
  			Timer terminate.
  			Timer := nil ].
+ 		"Collect gc statistics"
+ 		SmalltalkImage current getVMParameters keysAndValuesDo: [ :idx :gcVal | 
+ 			gcStats at: idx put: (gcVal - (gcStats at: idx))].
  		time := Time millisecondClockValue - time0]!

Item was changed:
  ----- Method: MessageTally class>>spyOnProcess:forMilliseconds: (in category 'spying') -----
  spyOnProcess: aProcess forMilliseconds: msecDuration 
+ 	"
+ 	Spy on aProcess for a certain amount of time
- 	"Spy on aProcess for a certain amount of time
  	| p1 p2 |  
  	p1 := [100000 timesRepeat: [3.14159 printString. Processor yield]] newProcess.  
  	p2 := [100000 timesRepeat: [3.14159 printString. Processor yield]] newProcess.
  	p1 resume.
  	p2 resume.  
  	(Delay forMilliseconds: 100) wait.  
  	MessageTally spyOnProcess: p1 forMilliseconds: 1000
  	"
+ 	
+ 	^self 
+ 		spyOnProcess: aProcess
+ 		forMilliseconds: msecDuration
+ 		reportOtherProcesses: ShowProcesses
- 	^self spyOnProcess: aProcess forMilliseconds: msecDuration reportOtherProcesses: ShowProcesses
  !

Item was changed:
  ----- Method: MessageTally class>>spyAllOn: (in category 'spying') -----
  spyAllOn: aBlock
  	"Spy on all the processes in the system
  	
  	[1000 timesRepeat: [3.14159 printString. Processor yield]] fork.
  	[1000 timesRepeat: [20 factorial. Processor yield]] fork.
  	[1000 timesRepeat: [20 factorial. Processor yield]] fork.
  	MessageTally spyAllOn: [ (Delay forMilliseconds: 100) wait]
  	
  	"
  	| node result |
  	node := self new.
+ 	node reportOtherProcesses: true. "Irrelevant in this case. All processes will be reported on their own."
- 	node reportOtherProcesses: true.
  	result := node spyAllEvery: self defaultPollPeriod on: aBlock.
  	self showReport: node.
  	^ result!

Item was changed:
  ----- Method: MessageTally class>>spyOn:toFileNamed: (in category 'spying') -----
  spyOn: aBlock toFileNamed: fileName 
  	"Spy on the evaluation of aBlock. Write the data collected on a file
  	named fileName."
  
+ 	| value node |
- 	| file value node |
  	node := self new.
  	value := node spyEvery: self defaultPollPeriod on: aBlock.
+ 	FileStream newFileNamed: fileName do: [ :file |
+ 		node report: file ].
- 	file := FileStream newFileNamed: fileName.
- 	node report: file; close.
- 	file close.
  	^value!

Item was changed:
  ----- Method: MessageTally class>>showReport: (in category 'spying') -----
  showReport: node
  	"Open a string holder with the reports from the given node"
  	(StringHolder new contents: 
+ 		(String streamContents: [:s | node report: s ]))
- 		(String streamContents: [:s | node report: s; close]))
  			openLabel: 'Spy Results'!

Item was changed:
  ----- Method: MessageTally class>>spyOnProcess:forMilliseconds:reportOtherProcesses: (in category 'spying') -----
  spyOnProcess: aProcess forMilliseconds: msecDuration reportOtherProcesses: aBoolean
+ 	"
+ 	Spy on aProcess for a certain amount of time
- 	"Spy on aProcess for a certain amount of time
  	| p1 p2 |  
  	p1 := [100000 timesRepeat: [3.14159 printString. Processor yield]] newProcess.  
  	p2 := [100000 timesRepeat: [3.14159 printString. Processor yield]] newProcess.
  	p1 resume.
  	p2 resume.  
  	(Delay forMilliseconds: 100) wait.  
  	MessageTally spyOnProcess: p1 forMilliseconds: 1000 reportOtherProcesses: true
  	"
  	| node |
  	node := self new.
  	node reportOtherProcesses: aBoolean.
  	node
  		spyEvery: self defaultPollPeriod
  		onProcess: aProcess
  		forMilliseconds: msecDuration.
  	self showReport: node.!

Item was changed:
  ----- Method: MessageTally class>>spyOn:reportOtherProcesses: (in category 'spying') -----
  spyOn: aBlock reportOtherProcesses: aBoolean
+ 	"
+ 	Spy on aBlock, in the current process. Can include or not statistics on other processes in the report.
- 	"Spy on aBlock, in the current process. Can include or not statistics on other processes in the report.
  	[1000 timesRepeat: [
  		100 timesRepeat: [120 factorial].
  		(Delay forMilliseconds: 10) wait
  		]] forkAt: 45 named: '45'.
  	MessageTally spyOn: [10000 timesRepeat: [1.23 printString]] reportOtherProcesses: true
  	"
  	| node result |
  	node := self new.
  	node reportOtherProcesses: aBoolean.
  	result := node spyEvery: self defaultPollPeriod on: aBlock.
  	self showReport: node.
  	^ result!

Item was changed:
  ----- Method: MessageTally>>close (in category 'initialize-release') -----
  close
  
+ 	self deprecated: 'Use MessageTally >> #terminateTimerProcess'.
  	Timer ifNotNil: [ Timer terminate ].
  	Timer := nil.
  	class := method := tally := receivers := nil!

Item was changed:
  ----- Method: MessageTally class>>spyOnProcess:forMilliseconds:toFileNamed: (in category 'spying') -----
  spyOnProcess: aProcess forMilliseconds: msecDuration toFileNamed: fileName 
  	"Spy on the evaluation of aProcess. Write the data collected on a file  
  	named fileName. Will overwrite fileName"
+ 	| node |
- 	| file node |
  	node := self new.
  	node
  		spyEvery: self defaultPollPeriod
  		onProcess: aProcess
  		forMilliseconds: msecDuration.
+ 	FileStream fileNamed: fileName do: [ :file |
+ 		node report: file ]!
- 	file := FileStream fileNamed: fileName.
- 	node report: file;
- 		 close.
- 	file close!

Item was added:
+ ----- Method: MessageTally class>>terminateTimerProcess (in category 'as yet unclassified') -----
+ terminateTimerProcess
+ 
+ 	Timer ifNotNil: [
+ 		Timer terminate.
+ 		Timer := nil ].
+ !




More information about the Squeak-dev mailing list