TerseMan challenge

Andres Valloud sqrmax at cvtci.com.ar
Wed Jan 12 01:36:30 UTC 2000


Hi Travis.

> > I have found this class incredibly useful for my number crunching.
> I played around with this for a while and didn't get the same results. 
> First of all baselined the 10 factorial send. I was getting values 
> (for 10000 iterations) of about 578 mills. Then I ran your code:

Ohhh... those are just examples of usage... the real benefit comes when
you want to find out the value of say 1000!... that's why I was
mentioning 3 * 2^1000 and 64! * 65. For instance, when calculating 100!,
here are the numbers I get...

i _ (1 to: 100) asArray.
Time millisecondsToRun: [CollectionProduct seqCollection: i] 15
Time millisecondsToRun: [t _ 1. i do: [:each | t _ t * each]] 46
Time millisecondsToRun: [t _ 1. 1 to: 100 do: [:each | t _ t * (i at:
each)]] 46

The results for 1000! are consistent with these figures:

i _ (1 to: 1000) asArray.
Time millisecondsToRun: [CollectionProduct seqCollection: i] 3735
Time millisecondsToRun: [t _ 1. i do: [:each | t _ t * each]] 11875
Time millisecondsToRun: [t _ 1. 1 to: 1000 do: [:each | t _ t * (i at:
each)]] 11312

> 2 * 3 * 4 * 5 * 6 * 7 * 8 * 9

We should try with something that pushes us into the LargeIntegers.
CollectionProduct uses the argument that the multiplication function for
multiple precision integers is most efficient when squaring. If you then
assume that this function's complexity is somewhat "continuous", then
efficiency is high when multiplying numbers of similar bit size. As you
can see, it's roughly 3 times faster even for 100!. 

Where's the tie between those methods? We could try with lower
factorials such as 20!. But 20! is too fast for millisecondsToRun:. I
have built a profiler for these things. With the Profiler, we can see
what goes on throwing parenthesis:

Doing 1*2*3*...*20 takes 1ms 75mus 805ns. 

But (1*2)*(3*4)...(19*20) takes 629mus 394ns. 

And grouping those in pairs, ((1*2)*(3*4)) *... takes 407mus 226ns. 

Grouping again we obtain 385mus 253ns. 

The next and last grouping takes 411mus 926ns.

We have 3 methods. CollectionProduct, do:, and to:do: (see above).

factorial	CP		do:		  to:do:
20!		453mus 918ns	1ms 239mus 746ns  1ms 136mus 718ns 
30!		451mus 965ns	3ms 280mus 761ns  3ms 51mus 757ns 
40!		1ms 274mus 169ns 6ms 606mus 445ns 5ms 584mus 960ns 
50!		3ms 769mus 42ns 9ms 826mus 171ns  9ms 337mus 890ns 
60!		5ms 157mus 226ns 15ms 960mus 937ns 15ms 136mus 718ns 
etc...

If we replace the amount of the factorial by i size in the last one, add
more execution time. We could also make it faster by saying 1 to: n do:
[:each | t _ t * each], yet, the bulk of the execution time comes from
multiplications in the LargeIntegers.

What you have shown is that Integer>>factorial should have all
factorials cached up to somewhere. From then on, though, it should use
CollectionProduct.

Here are some numbers with low factorials:

i _ (1 to: 10) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 63mus 659ns 
Profiler measure: [t _ 1. i do: [:each | t _ t * each]] 46mus 134ns 
Profiler measure: [t _ 1. 1 to: 10 do: [:each | t _ t * each]] 19mus
248ns 

n _ 11. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 60mus 798ns 
Profiler measure: [t _ 1. i do: [:each | t _ t * each]] 53mus 520ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 21mus
816ns 

n _ 12. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 72mus 242ns 
Profiler measure: [t _ 1. i do: [:each | t _ t * each]] 60mus 554ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 23mus
662ns 

13! is in the LargeIntegers and it shows:

n _ 13. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 222mus 686ns 
Profiler measure: [t _ 1. i do: [:each | t _ t * each]] 196mus 472ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 143mus
35ns 

n _ 14. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 271mus 820ns 
Profiler measure: [t _ 1. i do: [:each | t _ t * each]] 336mus 669ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 256mus
500ns 

The second line is evidently slower than the 3rd and now it is losing
against CollectionProduct, so we drop it.

n _ 15. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 225mus 524ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 388mus
122ns 

A better grouping makes CollectionProduct start winning. Does this
happen for 16?

n _ 16. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 246mus 551ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 413mus
940ns 

n _ 17. i _ (1 to: n) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 314mus 697ns 
Profiler measure: [t _ 1. 1 to: n do: [:each | t _ t * each]] 671mus
386ns 

Ouch. It seems that from 15! and on, CollectionProduct is faster. This
is consistent with the figures we got before. The CollectionProduct
comments also includes a descendent power from 24 to 15. Let's examine
how much time does it take comparing CP and to:do:

i _ (15 to: 24) asArray.
Profiler measure: [CollectionProduct seqCollection: i] 316mus 650ns 
Profiler measure: [t _ 1. 15 to: 24 do: [:each | t _ t * each]] 401mus
550ns 

The comments also have a prime factorial like this:

i _ #(2 3 5 7 11 13 17 19 23 29).
Profiler measure: [CollectionProduct seqCollection: i] 193mus 145ns 
Profiler measure: [t _ 1. i do: [:each | t _ t * each]] 201mus 202ns 

Overall, CP is faster very soon after the result is in the
LargeIntegers.

Andres.
-------------- next part --------------
'From Squeak 2.3 of January 14, 1999 on 10 January 2000 at 10:32:42 pm'!
"Change Set:		Profiling
Date:			14 July 1999
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.

Enjoy!!
SqR!!
"!

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

!Profiler reorganize!
('Printing' beautify:)
('Quering' evalsPerSecond: measure: msToRun: msToRun:times: quickMeasure: stopWatch: stopWatch:times: tallyBlock: tallyMeasure: tallyStopWatch:)
!


!Profiler methodsFor: 'Printing' stamp: 'SqR!!!! 7/14/1999 17:38'!
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!!!!!!!! 8/8/1998 22:22'!
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' stamp: 'SqR!!!! 7/14/1999 17:39'!
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!!!!!!!! 8/8/1998 22:03'!
msToRun: aBlock
	"Answer how many milliseconds
	does it take to evaluate aBlock"

	^Time millisecondsToRun: aBlock! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!!!!!! 8/8/1998 22:48'!
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!!!! 7/14/1999 17:40'!
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 _ time.
	sum _ (self msToRun: 2 * eval times: aBlock) + sum.
	sum _ (self msToRun: 3 * eval times: aBlock) + sum.
	^self beautify: sum * 6 / eval
! !

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 7/14/1999 17:40'!
stopWatch: aBlock
	"Answer how many milliseconds does it
	take to evaluate aBlock. Neat presentation"

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

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 7/14/1999 17:40'!
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' stamp: 'SqR!!!! 2/26/1999 17:44'!
tallyMeasure: aBlock
	"Perform a message tally while measuring aBlock"

	| answer |

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

!Profiler methodsFor: 'Quering' stamp: 'SqR!!!! 2/26/1999 22:19'!
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' stamp: 'SqR!!!!!!!! 8/8/1998 22:12'!
new
	"Answer a new instance of the receiver"

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

!Profiler class methodsFor: 'Private' stamp: 'SqR!!!!!!!! 8/16/1998 16:57'!
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