[pypy-commit] lang-smalltalk storage: Added some code to the Matrix benchmark.

anton_gulenko noreply at buildbot.pypy.org
Mon Jul 7 13:17:08 CEST 2014


Author: Anton Gulenko <anton.gulenko at googlemail.com>
Branch: storage
Changeset: r867:d1dfa8569637
Date: 2014-07-04 10:14 +0200
http://bitbucket.org/pypy/lang-smalltalk/changeset/d1dfa8569637/

Log:	Added some code to the Matrix benchmark.

diff --git a/images/Squeak4.5-noBitBlt.changes b/images/Squeak4.5-noBitBlt.changes
--- a/images/Squeak4.5-noBitBlt.changes
+++ b/images/Squeak4.5-noBitBlt.changes
@@ -12208,4 +12208,4 @@
 	].
 
 	"self footer."
-	^ self! !

----QUIT----{2 April 2014 . 11:59:41 am} Squeak4.5-noBitBlt.image priorSource: 15812182!

----STARTUP----{3 July 2014 . 11:14:14 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


SystemOrganization addCategory: #Anton!

Object subclass: #AntonMatrix
	instanceVariableNames: 'fields columns rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Anton'!

Object subclass: #AntonMatrix
	instanceVariableNames: 'fields columns rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Anton'!
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:17'!
at: point
	
	^ self x: point x y: point y! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:16'!
at: point put: number
	
	^ self x: point x y: point y put: number! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:12'!
columns
	
	^ columns! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:55'!
fieldsDo: block
	
	(1 to: self rows) do: [ :row |
		(1 to: self columns) do: [ :column |
			block value: row value: column ] ].! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:56'!
fill: block
	
	self fieldsDo: [ :x :y |
		self x: x y: y put: (block value: x value: y) ].! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:12'!
rows
	
	^ rows! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:17'!
x: x y: y
	
	^ fields at: (self offsetX: x y: y)! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:17'!
x: x y: y put: number
	
	fields at: (self offsetX: x y: y) put: number! !
!AntonMatrix methodsFor: 'private' stamp: 'ag 7/3/2014 10:44'!
offsetX: x y: y
	
	^ (y-1) * columns + x! !
!AntonMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 10:43'!
initializeFields: f rows: r	
	
	rows := r.
	(f size \\ r) = 0 ifFalse: [ self error: 'Illegal initialization.' ].
	columns := f size / r.
	fields := f.! !
!AntonMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 10:18'!
initializeRows: r columns: c
	
	rows := r.
	columns := c.
	fields := Array new: rows * columns.! !
!AntonMatrix methodsFor: 'math' stamp: 'ag 7/3/2014 10:30'!
* other
	
	| result |
	(self columns = other rows and: [ self rows = other columns ])
		ifFalse: [ ^ self error: 'Cannot multiply, wrong dimensions.' ].
	result := AntonMatrix rows: self rows columns: other columns.
	(1 to: self rows) do: [ :row |
		(1 to: other columns) do: [ :column | | value |
			value := 0.
			
			(1 to: self columns) do: [ :i |
				value := value + ((self x: i y: row) * (other x: column y: i)) ].
			
			result x: column y: row put: value ] ].
	^ result! !
!AntonMatrix methodsFor: 'printing' stamp: 'ag 7/3/2014 10:47'!
printOn: s
	
	(1 to: self rows) do: [ :row |
		(1 to: self columns) do: [ :column |
			s nextPutAll: (self x: column y: row) asString.
			s nextPutAll: ' ' ].
		s nextPutAll: String cr ].! !
!AntonMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:01'!
fillRandomFloats: generator
	
	| max |
	max := SmallInteger maxVal sqrt asInteger.
	self fill: [ :x :y | max atRandom: generator ].! !
!AntonMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:02'!
fillRandomInts: generator
	"Fill with SmallInteger values small enough to stay SmallIntegers after multiplication."
	
	self fill: [ :x :y | generator next * 100 ].! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AntonMatrix class
	instanceVariableNames: ''!
!AntonMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:13'!
benchFloats: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := AntonMatrix rows: r columns: c.
		b := AntonMatrix rows: r columns: c.
		a fillRandomFloats: generator.
		b fillRandomFloats: generator.
		mults timesRepeat: [ a * b ] ].! !
!AntonMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:03'!
benchInts: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := AntonMatrix rows: r columns: c.
		b := AntonMatrix rows: r columns: c.
		a fillRandomInts: generator.
		b fillRandomInts: generator.
		mults timesRepeat: [ a * b ] ].! !
!AntonMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 10:35'!
fields: fields rows: r
	
	^ self basicNew
		initializeFields: fields rows: r! !
!AntonMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 10:19'!
rows: r columns: c

	^ self basicNew
		initializeRows: r columns: c;
		yourself! !

Object subclass: #AntonMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Anton'!

Object subclass: #AntonMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Anton'!
!AntonMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:19'!
benchFloats
	
	AntonMatrix benchFloats: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !
!AntonMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:18'!
benchInts
	
	AntonMatrix benchInts: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AntonMatrixBenchmark class
	instanceVariableNames: ''!
!AntonMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:24'!
config: spec
	
	| tokens nextInt |
	tokens := spec findTokens: ' '.
	nextInt := [ :default |
		(tokens ifEmpty: [ nil ] ifNotEmptyDo: #removeFirst) asInteger ifNil: [ default ] ].
	NumOfRuns := nextInt value: 10.
	Mults := nextInt value: 100.
	Rows := nextInt value: 100.
	Cols := nextInt value: 100.! !
!AntonMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:20'!
initialize
	
	super initialize.
	NumOfRuns := 10.
	Mults := 100.
	Cols := 100.
	Rows := 100.! !

AntonMatrixBenchmark initialize!

----End fileIn of C:\Dev\lang-smalltalk\Anton.st----!
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:27'!
benchMatrixInt: spec
	
	AntonMatrixBenchmark config: spec.
	! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:28' prior: 49374034!
benchMatrixInt: spec
	
	AntonMatrixBenchmark config: spec.
	^ Benchmarks runMatching: 'AntonMatrix' iterations: self benchmarkIterations! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:28'!
benchMatrix: spec
	
	AntonMatrixBenchmark config: spec.
	^ Benchmarks runMatching: 'AntonMatrix' iterations: self benchmarkIterations! !

SystemOrganization renameCategory: #Anton toBe: #'Matrix-Benchmarks'!

Smalltalk renameClassNamed: #AntonMatrix as: #BenchMatrix!

Object subclass: #SimpleMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

Smalltalk removeClassNamed: #SimpleMatrixBenchmark!

Smalltalk renameClassNamed: #AntonMatrixBenchmark as: #SimpleMatrixBenchmark!

SmallInteger removeSelector: #benchMatrixInt:!
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:30' prior: 49374406!
benchMatrix: spec
	
	SimpleMatrixBenchmark config: spec.
	^ Benchmarks runMatching: 'SimpleMatrixBenchmark' iterations: self benchmarkIterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/3/2014 11:31' prior: 49367383!
allBenchmarks
	
	^ {
	CPBAStarBenchmark.
	CPBBinaryTreeBenchmark.
	CPBBlowfishSuite.
	CPBChameneosBenchmark.
	CPBDeltaBlueBenchmark.
	CPBMandelbrotBenchmarkSuite.
	CPBNBodyBenchmark.
	"CPBPolymorphyBenchmark." "Commented out because it compiled code in setup."
	CPBRichardsBenchmark.
	CPBSplayTreeBenchmark.
	SimpleMatrixBenchmark.
	}! !

----QUIT----{3 July 2014 . 11:32:10 am} Squeak4.5-noBitBlt.image priorSource: 15813551!

----STARTUP----{3 July 2014 . 11:34:49 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


SMarkSuite subclass: #SimpleMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!
!SimpleMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:37' prior: 49372902!
benchFloats
	
	BenchMatrix benchFloats: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !
!SimpleMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:37' prior: 49373080!
benchInts
	
	BenchMatrix benchInts: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !

SimpleMatrixBenchmark config: '5 5 5 5'!

Benchmarks runMatching: 'SimpleMatrixBenchmark' iterations: 1!
!SimpleMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:38' prior: 49373773!
initialize
	
	super initialize.
	NumOfRuns := 10.
	Mults := 10.
	Cols := 10.
	Rows := 10.! !

self initialize!
!SimpleMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:39' prior: 49376651!
initialize
	"self initialize"
	
	super initialize.
	NumOfRuns := 10.
	Mults := 10.
	Cols := 10.
	Rows := 10.! !

----QUIT----{3 July 2014 . 11:39:08 am} Squeak4.5-noBitBlt.image priorSource: 15821257!

----STARTUP----{3 July 2014 . 11:48:06 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!BenchMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:49' prior: 49371447!
benchFloats: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := BenchMatrix rows: r columns: c.
		b := BenchMatrix rows: c columns: r.
		a fillRandomFloats: generator.
		b fillRandomFloats: generator.
		mults timesRepeat: [ a * b ] ].! !
!BenchMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:49' prior: 49371861!
benchInts: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := BenchMatrix rows: r columns: c.
		b := BenchMatrix rows: c columns: r.
		a fillRandomInts: generator.
		b fillRandomInts: generator.
		mults timesRepeat: [ a * b ] ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 11:51' prior: 49368902!
fieldsDo: block
	
	(1 to: self rows) do: [ :row |
		(1 to: self columns) do: [ :column |
			block value: column value: row ] ].! !

1 benchMatrix: '1 10 100 10'!

1 benchMatrix: '1 10 100 10'!

1 benchMatrix: '1 10 10 100'!

1 benchMatrix: '1 10 10 1000'!

----QUIT----{3 July 2014 . 11:51:44 am} Squeak4.5-noBitBlt.image priorSource: 15822543!

----STARTUP----{3 July 2014 . 12:30:20 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'columns rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

BenchMatrix removeSelector: #at:!

BenchMatrix removeSelector: #at:put:!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:31' prior: 49368813!
columns
	
	^ self size / rows! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:31' prior: 49379008!
columns
	
	^ self size / rows! !

11/2!

11//2!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:33' prior: 49378103!
fieldsDo: block
	
	(1 to: self size) do: [ :i |
		block value: i \\ rows value: i // rows ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:34' prior: 49379251!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows value: i // rows ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:34' prior: 49369340!
x: x y: y
	
	^ self at: (self offsetX: x y: y)! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:34' prior: 49369457!
x: x y: y put: number
	
	self at: (self offsetX: x y: y) put: number! !

a := BenchMatrix fields: #( 3 2 1 1 0 2 ) rows: 2!

b := BenchMatrix fields: #( 1 2 0 1 4 0 ) rows: 3!

a!

a!

a rows!

a columns!

BenchMatrix removeSelector: #initializeRows:columns:!
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:36'!
initializeRows: r
	
	rows := r.! !

BenchMatrix removeSelector: #initializeFields:rows:!
!BenchMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 12:37' prior: 49372274!
fields: fields rows: r
	
	| columns f rows |
	rows := r.
	(f size \\ r) = 0 ifFalse: [ self error: 'Illegal initialization.' ].
	columns := f size / r.
"	fields := f."
	
	^ self basicNew
		initializeFields: fields rows: r! !
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:37'!
rows: r
	
	rows := r.! !

BenchMatrix removeSelector: #initializeRows:!

Array withAll: #(1 2 3)!
!BenchMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 12:39' prior: 49380248!
fields: fields rows: r
	
	(fields size \\ r) = 0 ifFalse: [ self error: 'Illegal initialization.' ].
	^ (self withAll: fields)
		rows: r;
		yourself! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:39' prior: 49379122!
columns
	
	^ self size // rows! !
!BenchMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 12:40' prior: 49372433!
rows: r columns: c

	^ (self new: r * c)
		rows: r;
		fillZeros;
		yourself! !
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:40'!
fillZeros
	
	self fill: [ :x :y | 0 ].! !

i!

i \\ rows!

i //rows!

rows!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:42' prior: 49379428!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

x := BenchMatrix rows: 4 columns: 3.!

x!

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:43' prior: 49381404!
fieldsDo: block
	
	0 to: self size do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!

x := BenchMatrix rows: 4 columns: 3.!

x!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:44' prior: 49381705!
fieldsDo: block
	
	0 to: self size + 1 do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

x := BenchMatrix rows: 4 columns: 3.!

x!

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!

o size!

x size!

o size!

o asSet size!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:46' prior: 49382006!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!

o size!

o !

1 \\ 4!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:46' prior: 49382353!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows value: i // rows + 1 ].! !

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o size!

o !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:50' prior: 49382634!
fieldsDo: block
	
	| columns |
	columns := self columns.
	1 to: self size do: [ :i |
		block value: i \\ columns value: i // columns + 1 ].! !

Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'rows columns'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'rows columns'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:51' prior: 49382898!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ columns value: i // columns + 1 ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:51' prior: 49380969!
columns
	
	^ columns! !
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:51' prior: 49380543!
rows: r
	
	rows := r.
	columns := self size // r.! !

x := BenchMatrix rows: 4 columns: 3.!

x!

o := OrderedCollection new.
x fieldsDo: [ :x :y | o add: x -> y ].
!

ox!

o!
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:52' prior: 49381247!
fillZeros
	
	self atAllPut: 0.! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:53' prior: 49383432!
fieldsDo: block
	
	0 to: self size - 1 do: [ :i |
		block value: i \\ columns + 1 value: i // columns + 1 ].! !

o := OrderedCollection new.
x fieldsDo: [ :x :y | o add: x -> y ].!

o size!

o!

a := BenchMatrix fields: #( 3 2 1 1 0 2 ) rows: 2!

b := BenchMatrix fields: #( 1 2 0 1 4 0 ) rows: 3!
!BenchMatrix methodsFor: 'math' stamp: 'ag 7/3/2014 12:55' prior: 49370092!
* other
	
	| result |
	(self columns = other rows and: [ self rows = other columns ])
		ifFalse: [ ^ self error: 'Cannot multiply, wrong dimensions.' ].
	result := BenchMatrix rows: self rows columns: other columns.
	(1 to: self rows) do: [ :row |
		(1 to: other columns) do: [ :column | | value |
			value := 0.
			
			(1 to: self columns) do: [ :i |
				value := value + ((self x: i y: row) * (other x: column y: i)) ].
			
			result x: column y: row put: value ] ].
	^ result! !

a * b!

self assert: (Array withAll: (a * b)) = #(7 8 9 2)!

BenchMatrix class organization addCategory: #test!
!BenchMatrix class methodsFor: 'test' stamp: 'ag 7/3/2014 12:57'!
tinyTest
	"self tinyTest"
	
	| a b |
	a := BenchMatrix fields: #( 3 2 1 1 0 2 ) rows: 2.
	b := BenchMatrix fields: #( 1 2 0 1 4 0 ) rows: 3.
	self assert: (Array withAll: (a * b)) = #(7 8 9 2).! !

self tinyTest!

1 benchMatrix: '1 3 5 5'!

1 benchMatrix: '1 10 5 5'!

----QUIT----{3 July 2014 . 12:58:52 pm} Squeak4.5-noBitBlt.image priorSource: 15823926!

----STARTUP----{3 July 2014 . 1:05:04 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.!

(a collect: #class) asSet!

(b collect: #class) asSet!

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomFloats: generator.
b fillRandomInts: generator.!

(b collect: #class) asSet!

(a collect: #class) asSet!
!BenchMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 13:08' prior: 49371100!
fillRandomInts: generator
	"Fill with SmallInteger values small enough to stay SmallIntegers after multiplication."
	
	| max |
	max := SmallInteger maxVal sqrt asInteger.
	self fill: [ :x :y | max atRandom: generator ].
	! !
!BenchMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 13:08' prior: 49370897!
fillRandomFloats: generator
	
	self fill: [ :x :y | generator next * 100 ].! !

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomFloats: generator.
b fillRandomInts: generator.

(a collect: #class) asSet
!

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomFloats: generator.
b fillRandomInts: generator.

(b collect: #class) asSet
!

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.

!

c := a * b!

(c collect: #class) asSet!
!BenchMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 13:09' prior: 49386143!
fillRandomInts: generator
	"Fill with SmallInteger values small enough to stay SmallIntegers after multiplication."
	
	| max |
	max := 1000.
	self fill: [ :x :y | max atRandom: generator ].
	! !

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.

c := a * b.
(c collect: #class) asSet!

----QUIT----{3 July 2014 . 1:09:37 pm} Squeak4.5-noBitBlt.image priorSource: 15830973!
\ No newline at end of file
+	^ self! !

----QUIT----{2 April 2014 . 11:59:41 am} Squeak4.5-noBitBlt.image priorSource: 15812182!

----STARTUP----{3 July 2014 . 11:14:14 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


SystemOrganization addCategory: #Anton!

Object subclass: #AntonMatrix
	instanceVariableNames: 'fields columns rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Anton'!

Object subclass: #AntonMatrix
	instanceVariableNames: 'fields columns rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Anton'!
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:17'!
at: point
	
	^ self x: point x y: point y! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:16'!
at: point put: number
	
	^ self x: point x y: point y put: number! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:12'!
columns
	
	^ columns! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:55'!
fieldsDo: block
	
	(1 to: self rows) do: [ :row |
		(1 to: self columns) do: [ :column |
			block value: row value: column ] ].! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:56'!
fill: block
	
	self fieldsDo: [ :x :y |
		self x: x y: y put: (block value: x value: y) ].! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:12'!
rows
	
	^ rows! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:17'!
x: x y: y
	
	^ fields at: (self offsetX: x y: y)! !
!AntonMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 10:17'!
x: x y: y put: number
	
	fields at: (self offsetX: x y: y) put: number! !
!AntonMatrix methodsFor: 'private' stamp: 'ag 7/3/2014 10:44'!
offsetX: x y: y
	
	^ (y-1) * columns + x! !
!AntonMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 10:43'!
initializeFields: f rows: r	
	
	rows := r.
	(f size \\ r) = 0 ifFalse: [ self error: 'Illegal initialization.' ].
	columns := f size / r.
	fields := f.! !
!AntonMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 10:18'!
initializeRows: r columns: c
	
	rows := r.
	columns := c.
	fields := Array new: rows * columns.! !
!AntonMatrix methodsFor: 'math' stamp: 'ag 7/3/2014 10:30'!
* other
	
	| result |
	(self columns = other rows and: [ self rows = other columns ])
		ifFalse: [ ^ self error: 'Cannot multiply, wrong dimensions.' ].
	result := AntonMatrix rows: self rows columns: other columns.
	(1 to: self rows) do: [ :row |
		(1 to: other columns) do: [ :column | | value |
			value := 0.
			
			(1 to: self columns) do: [ :i |
				value := value + ((self x: i y: row) * (other x: column y: i)) ].
			
			result x: column y: row put: value ] ].
	^ result! !
!AntonMatrix methodsFor: 'printing' stamp: 'ag 7/3/2014 10:47'!
printOn: s
	
	(1 to: self rows) do: [ :row |
		(1 to: self columns) do: [ :column |
			s nextPutAll: (self x: column y: row) asString.
			s nextPutAll: ' ' ].
		s nextPutAll: String cr ].! !
!AntonMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:01'!
fillRandomFloats: generator
	
	| max |
	max := SmallInteger maxVal sqrt asInteger.
	self fill: [ :x :y | max atRandom: generator ].! !
!AntonMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:02'!
fillRandomInts: generator
	"Fill with SmallInteger values small enough to stay SmallIntegers after multiplication."
	
	self fill: [ :x :y | generator next * 100 ].! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AntonMatrix class
	instanceVariableNames: ''!
!AntonMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:13'!
benchFloats: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := AntonMatrix rows: r columns: c.
		b := AntonMatrix rows: r columns: c.
		a fillRandomFloats: generator.
		b fillRandomFloats: generator.
		mults timesRepeat: [ a * b ] ].! !
!AntonMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:03'!
benchInts: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := AntonMatrix rows: r columns: c.
		b := AntonMatrix rows: r columns: c.
		a fillRandomInts: generator.
		b fillRandomInts: generator.
		mults timesRepeat: [ a * b ] ].! !
!AntonMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 10:35'!
fields: fields rows: r
	
	^ self basicNew
		initializeFields: fields rows: r! !
!AntonMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 10:19'!
rows: r columns: c

	^ self basicNew
		initializeRows: r columns: c;
		yourself! !

Object subclass: #AntonMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Anton'!

Object subclass: #AntonMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Anton'!
!AntonMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:19'!
benchFloats
	
	AntonMatrix benchFloats: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !
!AntonMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:18'!
benchInts
	
	AntonMatrix benchInts: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AntonMatrixBenchmark class
	instanceVariableNames: ''!
!AntonMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:24'!
config: spec
	
	| tokens nextInt |
	tokens := spec findTokens: ' '.
	nextInt := [ :default |
		(tokens ifEmpty: [ nil ] ifNotEmptyDo: #removeFirst) asInteger ifNil: [ default ] ].
	NumOfRuns := nextInt value: 10.
	Mults := nextInt value: 100.
	Rows := nextInt value: 100.
	Cols := nextInt value: 100.! !
!AntonMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:20'!
initialize
	
	super initialize.
	NumOfRuns := 10.
	Mults := 100.
	Cols := 100.
	Rows := 100.! !

AntonMatrixBenchmark initialize!

----End fileIn of C:\Dev\lang-smalltalk\Anton.st----!
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:27'!
benchMatrixInt: spec
	
	AntonMatrixBenchmark config: spec.
	! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:28' prior: 49374034!
benchMatrixInt: spec
	
	AntonMatrixBenchmark config: spec.
	^ Benchmarks runMatching: 'AntonMatrix' iterations: self benchmarkIterations! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:28'!
benchMatrix: spec
	
	AntonMatrixBenchmark config: spec.
	^ Benchmarks runMatching: 'AntonMatrix' iterations: self benchmarkIterations! !

SystemOrganization renameCategory: #Anton toBe: #'Matrix-Benchmarks'!

Smalltalk renameClassNamed: #AntonMatrix as: #BenchMatrix!

Object subclass: #SimpleMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

Smalltalk removeClassNamed: #SimpleMatrixBenchmark!

Smalltalk renameClassNamed: #AntonMatrixBenchmark as: #SimpleMatrixBenchmark!

SmallInteger removeSelector: #benchMatrixInt:!
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 11:30' prior: 49374406!
benchMatrix: spec
	
	SimpleMatrixBenchmark config: spec.
	^ Benchmarks runMatching: 'SimpleMatrixBenchmark' iterations: self benchmarkIterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/3/2014 11:31' prior: 49367383!
allBenchmarks
	
	^ {
	CPBAStarBenchmark.
	CPBBinaryTreeBenchmark.
	CPBBlowfishSuite.
	CPBChameneosBenchmark.
	CPBDeltaBlueBenchmark.
	CPBMandelbrotBenchmarkSuite.
	CPBNBodyBenchmark.
	"CPBPolymorphyBenchmark." "Commented out because it compiled code in setup."
	CPBRichardsBenchmark.
	CPBSplayTreeBenchmark.
	SimpleMatrixBenchmark.
	}! !

----QUIT----{3 July 2014 . 11:32:10 am} Squeak4.5-noBitBlt.image priorSource: 15813551!

----STARTUP----{3 July 2014 . 11:34:49 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


SMarkSuite subclass: #SimpleMatrixBenchmark
	instanceVariableNames: ''
	classVariableNames: 'Cols Mults NumOfRuns Rows'
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!
!SimpleMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:37' prior: 49372902!
benchFloats
	
	BenchMatrix benchFloats: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !
!SimpleMatrixBenchmark methodsFor: 'bench' stamp: 'ag 7/3/2014 11:37' prior: 49373080!
benchInts
	
	BenchMatrix benchInts: NumOfRuns multiplicationsPerRun: Mults rows: Rows columns: Cols.! !

SimpleMatrixBenchmark config: '5 5 5 5'!

Benchmarks runMatching: 'SimpleMatrixBenchmark' iterations: 1!
!SimpleMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:38' prior: 49373773!
initialize
	
	super initialize.
	NumOfRuns := 10.
	Mults := 10.
	Cols := 10.
	Rows := 10.! !

self initialize!
!SimpleMatrixBenchmark class methodsFor: 'initialization' stamp: 'ag 7/3/2014 11:39' prior: 49376651!
initialize
	"self initialize"
	
	super initialize.
	NumOfRuns := 10.
	Mults := 10.
	Cols := 10.
	Rows := 10.! !

----QUIT----{3 July 2014 . 11:39:08 am} Squeak4.5-noBitBlt.image priorSource: 15821257!

----STARTUP----{3 July 2014 . 11:48:06 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!BenchMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:49' prior: 49371447!
benchFloats: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := BenchMatrix rows: r columns: c.
		b := BenchMatrix rows: c columns: r.
		a fillRandomFloats: generator.
		b fillRandomFloats: generator.
		mults timesRepeat: [ a * b ] ].! !
!BenchMatrix class methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 11:49' prior: 49371861!
benchInts: numOfRuns multiplicationsPerRun: mults rows: r columns: c
	
	| generator |
	generator := Random seed: 23456432.
	numOfRuns timesRepeat: [ | a b |
		a := BenchMatrix rows: r columns: c.
		b := BenchMatrix rows: c columns: r.
		a fillRandomInts: generator.
		b fillRandomInts: generator.
		mults timesRepeat: [ a * b ] ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 11:51' prior: 49368902!
fieldsDo: block
	
	(1 to: self rows) do: [ :row |
		(1 to: self columns) do: [ :column |
			block value: column value: row ] ].! !

1 benchMatrix: '1 10 100 10'!

1 benchMatrix: '1 10 100 10'!

1 benchMatrix: '1 10 10 100'!

1 benchMatrix: '1 10 10 1000'!

----QUIT----{3 July 2014 . 11:51:44 am} Squeak4.5-noBitBlt.image priorSource: 15822543!

----STARTUP----{3 July 2014 . 12:30:20 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'columns rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'rows'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

BenchMatrix removeSelector: #at:!

BenchMatrix removeSelector: #at:put:!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:31' prior: 49368813!
columns
	
	^ self size / rows! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:31' prior: 49379008!
columns
	
	^ self size / rows! !

11/2!

11//2!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:33' prior: 49378103!
fieldsDo: block
	
	(1 to: self size) do: [ :i |
		block value: i \\ rows value: i // rows ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:34' prior: 49379251!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows value: i // rows ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:34' prior: 49369340!
x: x y: y
	
	^ self at: (self offsetX: x y: y)! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:34' prior: 49369457!
x: x y: y put: number
	
	self at: (self offsetX: x y: y) put: number! !

a := BenchMatrix fields: #( 3 2 1 1 0 2 ) rows: 2!

b := BenchMatrix fields: #( 1 2 0 1 4 0 ) rows: 3!

a!

a!

a rows!

a columns!

BenchMatrix removeSelector: #initializeRows:columns:!
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:36'!
initializeRows: r
	
	rows := r.! !

BenchMatrix removeSelector: #initializeFields:rows:!
!BenchMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 12:37' prior: 49372274!
fields: fields rows: r
	
	| columns f rows |
	rows := r.
	(f size \\ r) = 0 ifFalse: [ self error: 'Illegal initialization.' ].
	columns := f size / r.
"	fields := f."
	
	^ self basicNew
		initializeFields: fields rows: r! !
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:37'!
rows: r
	
	rows := r.! !

BenchMatrix removeSelector: #initializeRows:!

Array withAll: #(1 2 3)!
!BenchMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 12:39' prior: 49380248!
fields: fields rows: r
	
	(fields size \\ r) = 0 ifFalse: [ self error: 'Illegal initialization.' ].
	^ (self withAll: fields)
		rows: r;
		yourself! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:39' prior: 49379122!
columns
	
	^ self size // rows! !
!BenchMatrix class methodsFor: 'instance creation' stamp: 'ag 7/3/2014 12:40' prior: 49372433!
rows: r columns: c

	^ (self new: r * c)
		rows: r;
		fillZeros;
		yourself! !
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:40'!
fillZeros
	
	self fill: [ :x :y | 0 ].! !

i!

i \\ rows!

i //rows!

rows!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:42' prior: 49379428!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

x := BenchMatrix rows: 4 columns: 3.!

x!

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:43' prior: 49381404!
fieldsDo: block
	
	0 to: self size do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!

x := BenchMatrix rows: 4 columns: 3.!

x!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:44' prior: 49381705!
fieldsDo: block
	
	0 to: self size + 1 do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

x := BenchMatrix rows: 4 columns: 3.!

x!

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!

o size!

x size!

o size!

o asSet size!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:46' prior: 49382006!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows + 1 value: i // rows + 1 ].! !

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o!

o size!

o !

1 \\ 4!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:46' prior: 49382353!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ rows value: i // rows + 1 ].! !

o := OrderedCollection new.!

x fieldsDo: [ :x :y | o add: x -> y ].!

o size!

o !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:50' prior: 49382634!
fieldsDo: block
	
	| columns |
	columns := self columns.
	1 to: self size do: [ :i |
		block value: i \\ columns value: i // columns + 1 ].! !

Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'rows columns'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!

Array variableSubclass: #BenchMatrix
	instanceVariableNames: 'rows columns'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Matrix-Benchmarks'!
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:51' prior: 49382898!
fieldsDo: block
	
	1 to: self size do: [ :i |
		block value: i \\ columns value: i // columns + 1 ].! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:51' prior: 49380969!
columns
	
	^ columns! !
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:51' prior: 49380543!
rows: r
	
	rows := r.
	columns := self size // r.! !

x := BenchMatrix rows: 4 columns: 3.!

x!

o := OrderedCollection new.
x fieldsDo: [ :x :y | o add: x -> y ].
!

ox!

o!
!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 12:52' prior: 49381247!
fillZeros
	
	self atAllPut: 0.! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 12:53' prior: 49383432!
fieldsDo: block
	
	0 to: self size - 1 do: [ :i |
		block value: i \\ columns + 1 value: i // columns + 1 ].! !

o := OrderedCollection new.
x fieldsDo: [ :x :y | o add: x -> y ].!

o size!

o!

a := BenchMatrix fields: #( 3 2 1 1 0 2 ) rows: 2!

b := BenchMatrix fields: #( 1 2 0 1 4 0 ) rows: 3!
!BenchMatrix methodsFor: 'math' stamp: 'ag 7/3/2014 12:55' prior: 49370092!
* other
	
	| result |
	(self columns = other rows and: [ self rows = other columns ])
		ifFalse: [ ^ self error: 'Cannot multiply, wrong dimensions.' ].
	result := BenchMatrix rows: self rows columns: other columns.
	(1 to: self rows) do: [ :row |
		(1 to: other columns) do: [ :column | | value |
			value := 0.
			
			(1 to: self columns) do: [ :i |
				value := value + ((self x: i y: row) * (other x: column y: i)) ].
			
			result x: column y: row put: value ] ].
	^ result! !

a * b!

self assert: (Array withAll: (a * b)) = #(7 8 9 2)!

BenchMatrix class organization addCategory: #test!
!BenchMatrix class methodsFor: 'test' stamp: 'ag 7/3/2014 12:57'!
tinyTest
	"self tinyTest"
	
	| a b |
	a := BenchMatrix fields: #( 3 2 1 1 0 2 ) rows: 2.
	b := BenchMatrix fields: #( 1 2 0 1 4 0 ) rows: 3.
	self assert: (Array withAll: (a * b)) = #(7 8 9 2).! !

self tinyTest!

1 benchMatrix: '1 3 5 5'!

1 benchMatrix: '1 10 5 5'!

----QUIT----{3 July 2014 . 12:58:52 pm} Squeak4.5-noBitBlt.image priorSource: 15823926!

----STARTUP----{3 July 2014 . 1:05:04 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.!

(a collect: #class) asSet!

(b collect: #class) asSet!

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomFloats: generator.
b fillRandomInts: generator.!

(b collect: #class) asSet!

(a collect: #class) asSet!
!BenchMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 13:08' prior: 49371100!
fillRandomInts: generator
	"Fill with SmallInteger values small enough to stay SmallIntegers after multiplication."
	
	| max |
	max := SmallInteger maxVal sqrt asInteger.
	self fill: [ :x :y | max atRandom: generator ].
	! !
!BenchMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 13:08' prior: 49370897!
fillRandomFloats: generator
	
	self fill: [ :x :y | generator next * 100 ].! !

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomFloats: generator.
b fillRandomInts: generator.

(a collect: #class) asSet
!

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomFloats: generator.
b fillRandomInts: generator.

(b collect: #class) asSet
!

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.

!

c := a * b!

(c collect: #class) asSet!
!BenchMatrix methodsFor: 'benchmarking' stamp: 'ag 7/3/2014 13:09' prior: 49386143!
fillRandomInts: generator
	"Fill with SmallInteger values small enough to stay SmallIntegers after multiplication."
	
	| max |
	max := 1000.
	self fill: [ :x :y | max atRandom: generator ].
	! !

a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.

c := a * b.
(c collect: #class) asSet!

----QUIT----{3 July 2014 . 1:09:37 pm} Squeak4.5-noBitBlt.image priorSource: 15830973!

----STARTUP----{3 July 2014 . 8:26:43 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


a := BenchMatrix rows: 20 columns: 20.
b := BenchMatrix rows: 20 columns: 20.
generator := Random seed: 13243456.
a fillRandomInts: generator.
b fillRandomInts: generator.!

c := a * b.!

(c collect: #class) asSet!

c!
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 20:27'!
testMatrix
	
	! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/3/2014 20:28' prior: 49388134!
testMatrix
	
	| a b c generator |
	a := BenchMatrix rows: 20 columns: 20.
	b := BenchMatrix rows: 20 columns: 20.
	generator := Random seed: 13243456.
	a fillRandomInts: generator.
	b fillRandomInts: generator.
	
	c := a * b.
	^ (c collect: #class) asSet asString! !

5 testMatrix!

----SNAPSHOT----{3 July 2014 . 8:28:40 pm} Squeak4.5-noBitBlt.1.image priorSource: 15833215!

----QUIT----{3 July 2014 . 8:28:49 pm} Squeak4.5-noBitBlt.1.image priorSource: 15834093!

----STARTUP----{3 July 2014 . 9:02:43 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!BenchMatrix methodsFor: 'initialization' stamp: 'ag 7/3/2014 21:03' prior: 49383727!
rows: r
	
	rows := r asFloat.
	columns := (self size // r) asFloat.! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 21:03' prior: 49369257!
rows
	
	^ rows asInteger! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 21:03' prior: 49383617!
columns
	
	^ columns asInteger! !
!BenchMatrix methodsFor: 'accessing' stamp: 'ag 7/3/2014 21:04' prior: 49384103!
fieldsDo: block
	
	0 to: self size - 1 do: [ :i |
		block value: i \\ self columns + 1 value: i // self columns + 1 ].! !

----QUIT----{3 July 2014 . 9:04:33 pm} Squeak4.5-noBitBlt.image priorSource: 15834187!
\ No newline at end of file
diff --git a/images/Squeak4.5-noBitBlt.image b/images/Squeak4.5-noBitBlt.image
index 901620a8a8d4d194528f72a369392610813925a4..46e8d064f5b9b3ded5cfa05ee2ff1651286c82e7
GIT binary patch

[cut]



More information about the pypy-commit mailing list