Less than a Millisecond

Andres Valloud avalloud at exobox.com
Tue May 9 21:17:11 UTC 2000


>    Is there a way to measure things that take less than a millisecond?
>
>

Yes. Here's a way to do it.
Andres.

-------------- next part --------------
'From Squeak2.6 of 11 October 1999 [latest update: #1578] on 11 April 2000 at 12:19:14 pm'!
"Change Set:		Profiling
Date:			10 April 2000
Author:			Andres Valloud

A profiling tool. It provides nice
access to Time millisecondsToRun:
and other common practices.

It also includes a nice expression
profiler that will determine the
execution time of aBlock with
nanosecond precision.

The general usage is

	Profiler query: aBlock,

where the query is one of the
queries in the querying instance
method category in Profiler.

It can also check when a block
starts evaluating faster than
another block. Tres cool.

Enjoy!!
SqR!!
"!

Object subclass: #Profiler
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Others-Profiler'!
Profiler class
	instanceVariableNames: 'current '!

!Profiler reorganize!
('Printing' beautify:)
('Quering' compare:with: compare:with:in: evalsPerSecond: measure: measure:value: msToRun: msToRun:times: msToRun:times:value: quickCompare:with: quickCompare:with:in: quickMeasure: quickMeasure:value: stopWatch: stopWatch:times: tallyBlock: tallyMeasure: tallyStopWatch:)
!


!Profiler methodsFor: 'Printing'!
beautify: anInteger
	"Answer anInteger milliseconds in a readable fashion"

	| output add |

	anInteger < 0 ifTrue: [^('-', (self beautify: anInteger abs)) asSymbol].
	(add _ (anInteger // 86400000) printString) = '0' 
		ifTrue: [output _ String new] ifFalse: [output _ add, 'd '].
	(add _ (anInteger / 3600000 \\ 24) truncated printString) = '0' 
		ifFalse: [output _ output, add, 'h '].
	(add _ ((anInteger // 60000) \\ 60) truncated printString) = '0' 
		ifFalse: [output _ output, add, 'm '].
	(add _ (anInteger / 1000 \\ 60) truncated printString) = '0' 
		ifFalse: [output _ output, add, 's '].
	(add _ (anInteger \\ 1000) truncated printString) = '0' 
		ifFalse: [output _ output, add, 'ms '].
	(add _ (anInteger * 1000 \\ 1000) truncated printString) = '0' 
		ifFalse: [output _ output, add, 'mus '].
	(add _ (anInteger // (1 / 1000000) \\ 1000) printString) = '0' 
		ifFalse: [output _ output, add, 'ns '].
	output size == 0 ifFalse: [^output asSymbol] ifTrue: [^'0ms' asSymbol]! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/10/2000 08:37'!
compare: aBlock with: bBlock
	"Tres cool!! Compare execution times of
	aBlock with those of bBlock"

	| report |

	report _ ReadWriteStream on: String new.
	report cr nextPutAll: 'First block', Character tab asString, 'Second block'; cr.
	report nextPutAll: (self measure: aBlock) printString, Character tab asString.
	report nextPutAll: (self measure: bBlock) printString; cr.
	^report contents asSymbol! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/10/2000 08:59'!
compare: aBlock with: bBlock in: aCollection
	"Tres cool!! Compare execution times of
	aBlock with those of bBlock, informing
	when aBlock is faster than bBlock and
	viceversa. Evaluate the blocks at the
	items in aCollection."

	| report |

	report _ ReadWriteStream on: String new.
	report cr nextPutAll: 'Value', Character tab asString, 'First block', 
							Character tab asString, 'Second block'; cr.
	aCollection
		do: [:each |
				report nextPutAll: each printString, Character tab asString.
				report nextPutAll: (self measure: aBlock value: each) printString,
										Character tab asString.
				report nextPutAll: (self measure: bBlock value: each) printString; cr.
			].
	^report contents asSymbol! !

!Profiler methodsFor: 'Quering'!
evalsPerSecond: aBlock
	"Answer more or less the amount
	of evaluations of aBlock possible
	per second"

	| evals time |

	evals _ 1.
	[(time _ self msToRun: evals times: aBlock) > 1000]
		whileFalse: [evals _ evals * 2].
	^(1000 * evals / time roundTo: 0.001) asFloat! !

!Profiler methodsFor: 'Quering'!
measure: aBlock
	"Answer more or less the time required
	to evaluate aBlock"

	| evals time |

	evals _ 1.
	[(time _ self msToRun: evals times: aBlock) > 5000]
		whileFalse: [evals _ evals * 2].
	^self beautify: time / evals! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/10/2000 08:31'!
measure: aBlock value: anObject
	"Answer more or less the time required
	to evaluate aBlock value: anObject"

	| evals time |

	evals _ 1.
	[(time _ self msToRun: evals times: aBlock value: anObject) > 5000]
		whileFalse: [evals _ evals * 2].
	^self beautify: time / evals! !

!Profiler methodsFor: 'Quering'!
msToRun: aBlock
	"Answer how many milliseconds
	does it take to evaluate aBlock"

	^Time millisecondsToRun: aBlock! !

!Profiler methodsFor: 'Quering'!
msToRun: anInteger times: aBlock
	"Answer how many milliseconds	does it take 
	to evaluate aBlock anInteger times"

	^(Time millisecondsToRun: [1 to: anInteger do: [:each | aBlock value]]) -
		(Time millisecondsToRun: [1 to: anInteger do: [:each | ]]) max: 0! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/10/2000 08:31'!
msToRun: anInteger times: aBlock value: anObject
	"Answer how many milliseconds	does it take 
	to evaluate aBlock value: anObject anInteger times"

	^(Time millisecondsToRun: [1 to: anInteger do: [:each | aBlock value: anObject]]) -
		(Time millisecondsToRun: [1 to: anInteger do: [:each | ]]) max: 0! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/11/2000 12:18'!
quickCompare: aBlock with: bBlock
	"Tres cool!! Compare execution times of
	aBlock with those of bBlock. Use quick
	measures"

	| report |

	report _ ReadWriteStream on: String new.
	report cr nextPutAll: 'First block', Character tab asString, 'Second block'; cr.
	report nextPutAll: (self quickMeasure: aBlock) printString, Character tab asString.
	report nextPutAll: (self quickMeasure: bBlock) printString; cr.
	^report contents asSymbol! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/10/2000 08:38'!
quickCompare: aBlock with: bBlock in: aCollection
	"Tres cool!! Compare execution times of
	aBlock with those of bBlock, informing
	when aBlock is faster than bBlock and
	viceversa. Evaluate the blocks at the
	items in aCollection. Use quick compares"

	| report |

	report _ ReadWriteStream on: String new.
	report cr nextPutAll: 'Value', Character tab asString, 'First block', 
							Character tab asString, 'Second block'; cr.
	aCollection
		do: [:each |
				report nextPutAll: each printString, Character tab asString.
				report nextPutAll: (self quickMeasure: aBlock value: each) printString,
										Character tab asString.
				report nextPutAll: (self quickMeasure: bBlock value: each) printString; cr.
			].
	^report contents asSymbol! !

!Profiler methodsFor: 'Quering'!
quickMeasure: aBlock
	"Answer more or less the time required
	to evaluate aBlock. Method by Leandro 
	Caniglia"

	| eval time sum |

	eval _ 1.
	[(time _ self msToRun: eval times: aBlock) > 100] whileFalse: [eval _ eval * 2].
	sum _ (self msToRun: 2 * eval times: aBlock) + time.
	sum _ (self msToRun: 3 * eval times: aBlock) + sum.
	^self beautify: sum / 6 / eval
! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 4/10/2000 08:39'!
quickMeasure: aBlock value: anObject
	"Answer more or less the time required
	to evaluate aBlock value: anObject. 
	Method by Leandro Caniglia"

	| eval time sum |

	eval _ 1.
	[(time _ self msToRun: eval times: aBlock value: anObject) > 100] 
		whileFalse: [eval _ eval * 2].
	sum _ (self msToRun: 2 * eval times: aBlock value: anObject) + time.
	sum _ (self msToRun: 3 * eval times: aBlock value: anObject) + sum.
	^self beautify: sum / 6 / eval
! !

!Profiler methodsFor: 'Quering'!
stopWatch: aBlock
	"Answer how many milliseconds does it
	take to evaluate aBlock. Neat presentation"

	^self beautify: (self msToRun: aBlock)! !

!Profiler methodsFor: 'Quering'!
stopWatch: anInteger times: aBlock
	"Answer how many milliseconds does it take to evaluate 
	aBlock anInteger times. Neat presentation"

	^self beautify: (self msToRun: anInteger times: aBlock)! !

!Profiler methodsFor: 'Quering'!
tallyBlock: aBlock
	"Perform a message tally on aBlock"

	MessageTally spyOn: aBlock! !

!Profiler methodsFor: 'Quering'!
tallyMeasure: aBlock
	"Perform a message tally while measuring aBlock"

	| answer |

	MessageTally spyOn: [answer _ self measure: aBlock].
	^answer! !

!Profiler methodsFor: 'Quering'!
tallyStopWatch: aBlock
	"Perform a message tally while stopWatching aBlock"

	| answer |

	MessageTally spyOn: [answer _ self stopWatch: aBlock].
	^answer! !


!Profiler class reorganize!
('Instance creation' new)
('Private' doesNotUnderstand:)
!


!Profiler class methodsFor: 'Instance creation'!
new
	"Answer a new instance of the receiver"

	current isNil ifTrue: [current _ super new].
	^current! !

!Profiler class methodsFor: 'Private'!
doesNotUnderstand: aMessage
	"Redirect the query? to the lone instance of the receiver"

	^self new perform: aMessage selector withArguments: aMessage arguments! !




More information about the Squeak-dev mailing list