[pypy-commit] lang-smalltalk storage: Changes to the benchmarks. We really should put this on Monticello or something.

anton_gulenko noreply at buildbot.pypy.org
Fri Jul 18 14:08:59 CEST 2014


Author: Anton Gulenko <anton.gulenko at googlemail.com>
Branch: storage
Changeset: r916:30a053f8596e
Date: 2014-07-16 11:07 +0200
http://bitbucket.org/pypy/lang-smalltalk/changeset/30a053f8596e/

Log:	Changes to the benchmarks. We really should put this on Monticello
	or something.

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
@@ -12348,4 +12348,276 @@
 	<primitive: 'primitiveCopyBuffer' module: 'B2DPlugin'>
 	^ 0! !
!BalloonEngine methodsFor: 'primitives-misc' stamp: 'tfel 7/2/2014 17:13' prior: 17242774!
primInitializeBuffer: buffer
 	<primitive: 'primitiveInitializeBuffer' module: 'B2DPlugin'>
-	^ 0! !
!BalloonEngine methodsFor: 'profiling' stamp: 'ar 11/11/1998 21:16' prior: 17242962!
doAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList matrix: aMatrix
	"Note: This method is for profiling the overhead of loading a compressed shape into the engine."
	^self primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList matrix: aMatrix! !
!BalloonEngine methodsFor: 'as yet unclassified' stamp: 'tfel 1/7/2014 18:07' prior: 47363563!
error: aString

	^self! !

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

BalloonEngine class
	instanceVariableNames: ''!
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/25/1998 17:37' prior: 17243620!
debug: aBoolean
	"BalloonEngine debug: true"
	"BalloonEngine debug: false"
	Debug := aBoolean! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47' prior: 17243791!
doProfileStats: aBool
	"Note: On Macintosh systems turning on profiling can significantly
	degrade the performance of Balloon since we're using the high
	accuracy timer for measuring."
	"BalloonEngine doProfileStats: true"
	"BalloonEngine doProfileStats: false"
	<primitive: 'primitiveDoProfileStats' module: 'B2DPlugin'>
	^false! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57' prior: 17244200!
printBezierStats
	"BalloonEngine printBezierStats"
	"BalloonEngine resetBezierStats"
	Transcript 
		cr; nextPutAll:'Bezier statistics:';
		crtab; print: (BezierStats at: 1); tab; nextPutAll:' non-monoton curves splitted';
		crtab; print: (BezierStats at: 2); tab; nextPutAll:' curves splitted for numerical accuracy';
		crtab; print: (BezierStats at: 3); tab; nextPutAll:' curves splitted to avoid integer overflow';
		crtab; print: (BezierStats at: 4); tab; nextPutAll:' curves internally converted to lines';
	endEntry.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:59' prior: 17244801!
printStat: time count: n string: aString
	Transcript
		cr;
		print: time; tab;
		nextPutAll:' mSecs -- ';
		print: n; tab;
		nextPutAll:' ops -- ';
		print: ((time asFloat / (n max: 1) asFloat) roundTo: 0.01); tab;
		nextPutAll: ' avg. mSecs/op -- ';
		nextPutAll: aString.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 1/12/1999 10:52' prior: 17245153!
printStats
	"BalloonEngine doProfileStats: true"
	"BalloonEngine printStats"
	"BalloonEngine resetStats"
	Transcript cr; nextPutAll:'/************** BalloonEngine statistics ****************/'.
	self printStat: (Times at: 1) count: (Counts at: 1) string: 'Initialization'.
	self printStat: (Times at: 2) count: (Counts at: 2) string: 'Finish test'.
	self printStat: (Times at: 3) count: (Counts at: 3) string: 'Fetching/Adding GET entries'.
	self printStat: (Times at: 4) count: (Counts at: 4) string: 'Adding AET entries'.
	self printStat: (Times at: 5) count: (Counts at: 5) string: 'Fetching/Computing fills'.
	self printStat: (Times at: 6) count: (Counts at: 6) string: 'Merging fills'.
	self printStat: (Times at: 7) count: (Counts at: 7) string: 'Displaying span buffer'.
	self printStat: (Times at: 8) count: (Counts at: 8) string: 'Fetching/Updating AET entries'.
	self printStat: (Times at: 9) count: (Counts at: 9) string: 'Changing AET entries'.
	Transcript cr; print: Times sum; nextPutAll:' mSecs for all operations'.
	Transcript cr; print: Counts sum; nextPutAll: ' overall operations'.
	Transcript endEntry.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57' prior: 17246355!
resetBezierStats
	BezierStats := WordArray new: 4.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:38' prior: 17246485!
resetStats
	Times := WordArray new: 10.
	Counts := WordArray new: 10.! !
!BalloonEngine class methodsFor: 'class initialization' stamp: 'ar 11/11/1998 22:49' prior: 17246646!
initialize
	"BalloonEngine initialize"
	BufferCache := WeakArray new: 1.
	Smalltalk garbageCollect. "Make the cache old"
	CacheProtect := Semaphore forMutualExclusion.
	Times := WordArray new: 10.
	Counts := WordArray new: 10.
	BezierStats := WordArray new: 4.
	Debug ifNil:[Debug := false].! !
!BalloonEngine class methodsFor: 'private' stamp: 'ar 11/11/1998 22:50' prior: 17247016!
allocateOrRecycleBuffer: initialSize
	"Try to recycly a buffer. If this is not possibly, create a new one."
	| buffer |
	CacheProtect critical:[
		buffer := BufferCache at: 1.
		BufferCache at: 1 put: nil.
	].
	^buffer ifNil:[BalloonBuffer new: initialSize]! !
!BalloonEngine class methodsFor: 'private' stamp: 'ar 5/28/2000 22:17' prior: 17247350!
primitiveSetBitBltPlugin: pluginName
	<primitive: 'primitiveSetBitBltPlugin' module: 'B2DPlugin'>
	^nil! !
!BalloonEngine class methodsFor: 'private' stamp: 'eem 6/11/2008 13:00' prior: 55068329!
recycleBuffer: balloonBuffer
	"Try to keep the buffer for later drawing operations."

	CacheProtect critical:[ | buffer |
		buffer := BufferCache at: 1.
		(buffer isNil or:[buffer size < balloonBuffer size] )
			ifTrue:[BufferCache at: 1 put: balloonBuffer].
	].! !

BalloonEngine initialize!

----End fileIn of C:\Dev\lang-smalltalk\images\BalloonEngine.st----!

----SNAPSHOT----{10 July 2014 . 3:48:10 pm} Squeak4.5-noBitBlt.image priorSource: 15835154!

----SNAPSHOT----{10 July 2014 . 1:49:32 pm} Squeak4.5-noBitBlt.image priorSource: 15870393!
\ No newline at end of file
+	^ 0! !
!BalloonEngine methodsFor: 'profiling' stamp: 'ar 11/11/1998 21:16' prior: 17242962!
doAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList matrix: aMatrix
	"Note: This method is for profiling the overhead of loading a compressed shape into the engine."
	^self primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList matrix: aMatrix! !
!BalloonEngine methodsFor: 'as yet unclassified' stamp: 'tfel 1/7/2014 18:07' prior: 47363563!
error: aString

	^self! !

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

BalloonEngine class
	instanceVariableNames: ''!
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/25/1998 17:37' prior: 17243620!
debug: aBoolean
	"BalloonEngine debug: true"
	"BalloonEngine debug: false"
	Debug := aBoolean! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47' prior: 17243791!
doProfileStats: aBool
	"Note: On Macintosh systems turning on profiling can significantly
	degrade the performance of Balloon since we're using the high
	accuracy timer for measuring."
	"BalloonEngine doProfileStats: true"
	"BalloonEngine doProfileStats: false"
	<primitive: 'primitiveDoProfileStats' module: 'B2DPlugin'>
	^false! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57' prior: 17244200!
printBezierStats
	"BalloonEngine printBezierStats"
	"BalloonEngine resetBezierStats"
	Transcript 
		cr; nextPutAll:'Bezier statistics:';
		crtab; print: (BezierStats at: 1); tab; nextPutAll:' non-monoton curves splitted';
		crtab; print: (BezierStats at: 2); tab; nextPutAll:' curves splitted for numerical accuracy';
		crtab; print: (BezierStats at: 3); tab; nextPutAll:' curves splitted to avoid integer overflow';
		crtab; print: (BezierStats at: 4); tab; nextPutAll:' curves internally converted to lines';
	endEntry.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:59' prior: 17244801!
printStat: time count: n string: aString
	Transcript
		cr;
		print: time; tab;
		nextPutAll:' mSecs -- ';
		print: n; tab;
		nextPutAll:' ops -- ';
		print: ((time asFloat / (n max: 1) asFloat) roundTo: 0.01); tab;
		nextPutAll: ' avg. mSecs/op -- ';
		nextPutAll: aString.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 1/12/1999 10:52' prior: 17245153!
printStats
	"BalloonEngine doProfileStats: true"
	"BalloonEngine printStats"
	"BalloonEngine resetStats"
	Transcript cr; nextPutAll:'/************** BalloonEngine statistics ****************/'.
	self printStat: (Times at: 1) count: (Counts at: 1) string: 'Initialization'.
	self printStat: (Times at: 2) count: (Counts at: 2) string: 'Finish test'.
	self printStat: (Times at: 3) count: (Counts at: 3) string: 'Fetching/Adding GET entries'.
	self printStat: (Times at: 4) count: (Counts at: 4) string: 'Adding AET entries'.
	self printStat: (Times at: 5) count: (Counts at: 5) string: 'Fetching/Computing fills'.
	self printStat: (Times at: 6) count: (Counts at: 6) string: 'Merging fills'.
	self printStat: (Times at: 7) count: (Counts at: 7) string: 'Displaying span buffer'.
	self printStat: (Times at: 8) count: (Counts at: 8) string: 'Fetching/Updating AET entries'.
	self printStat: (Times at: 9) count: (Counts at: 9) string: 'Changing AET entries'.
	Transcript cr; print: Times sum; nextPutAll:' mSecs for all operations'.
	Transcript cr; print: Counts sum; nextPutAll: ' overall operations'.
	Transcript endEntry.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57' prior: 17246355!
resetBezierStats
	BezierStats := WordArray new: 4.! !
!BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:38' prior: 17246485!
resetStats
	Times := WordArray new: 10.
	Counts := WordArray new: 10.! !
!BalloonEngine class methodsFor: 'class initialization' stamp: 'ar 11/11/1998 22:49' prior: 17246646!
initialize
	"BalloonEngine initialize"
	BufferCache := WeakArray new: 1.
	Smalltalk garbageCollect. "Make the cache old"
	CacheProtect := Semaphore forMutualExclusion.
	Times := WordArray new: 10.
	Counts := WordArray new: 10.
	BezierStats := WordArray new: 4.
	Debug ifNil:[Debug := false].! !
!BalloonEngine class methodsFor: 'private' stamp: 'ar 11/11/1998 22:50' prior: 17247016!
allocateOrRecycleBuffer: initialSize
	"Try to recycly a buffer. If this is not possibly, create a new one."
	| buffer |
	CacheProtect critical:[
		buffer := BufferCache at: 1.
		BufferCache at: 1 put: nil.
	].
	^buffer ifNil:[BalloonBuffer new: initialSize]! !
!BalloonEngine class methodsFor: 'private' stamp: 'ar 5/28/2000 22:17' prior: 17247350!
primitiveSetBitBltPlugin: pluginName
	<primitive: 'primitiveSetBitBltPlugin' module: 'B2DPlugin'>
	^nil! !
!BalloonEngine class methodsFor: 'private' stamp: 'eem 6/11/2008 13:00' prior: 55068329!
recycleBuffer: balloonBuffer
	"Try to keep the buffer for later drawing operations."

	CacheProtect critical:[ | buffer |
		buffer := BufferCache at: 1.
		(buffer isNil or:[buffer size < balloonBuffer size] )
			ifTrue:[BufferCache at: 1 put: balloonBuffer].
	].! !

BalloonEngine initialize!

----End fileIn of C:\Dev\lang-smalltalk\images\BalloonEngine.st----!

----SNAPSHOT----{10 July 2014 . 3:48:10 pm} Squeak4.5-noBitBlt.image priorSource: 15835154!

----SNAPSHOT----{10 July 2014 . 1:49:32 pm} Squeak4.5-noBitBlt.image priorSource: 15870393!

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

!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 11:59' prior: 49367231!
runBenchmarks

	^ Benchmarks printAllResults: self benchmarkIterations! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:00'!
printBenchmarks

	^ Benchmarks printAllResults: self benchmarkIterations! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:00'!
printBenchmarks: substring
	
	^ Benchmarks printMatching: substring iterations: self benchmarkIterations! !
!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:00' prior: 49425209!
runBenchmarks

	^ Benchmarks printAll: self benchmarkIterations! !

SmallInteger removeSelector: #testMatrix!

SmallInteger removeSelector: #withArgsFoo!
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:01'!
printAll
	
	^ self printAll: 5! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:02'!
printAll: iterations
	
	^ self print: self allBenchmarks iterations: iterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:02' prior: 49426046!
printAll: iterations
	
	^ self printMatching: self allBenchmarks iterations: iterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:02'!
printMatching: substring iterations: iterations
	
	| benchmarks |
	benchmarks := self selectBenchmarks: substring.
	benchmarks ifEmpty: [ 
		^ String streamContents: [ :str |
				str
					nextPutAll: 'No benchmarks matched "';
					nextPutAll: substring;
					nextPutAll: '"';
					cr;
					nextPutAll: 'Available benchmarks:'.
				self allBenchmarkNames do: [ :name | str cr; nextPutAll: name ] ] ].
	^ self run: benchmarks iterations: iterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:03' prior: 49426380!
printMatching: substring iterations: iterations
	
	| benchmarks |
	benchmarks := self selectBenchmarksOrString: substring.
	benchmarks isString ifTrue: [ ^ benchmarks ].
	^ self run: benchmarks iterations: iterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:04'!
selectBenchmarksOrString: substring
	
	| benchmarks |
	benchmarks := self selectBenchmarks: substring.
	benchmarks ifEmpty: [ 
		^ String streamContents: [ :str |
				str
					nextPutAll: 'No benchmarks matched "';
					nextPutAll: substring;
					nextPutAll: '"';
					cr;
					nextPutAll: 'Available benchmarks:'.
				self allBenchmarkNames do: [ :name | str cr; nextPutAll: name ] ] ].
	^ benchmarks! !
!Benchmarks class methodsFor: 'private' stamp: 'ag 7/15/2014 12:04' prior: 49427211!
selectBenchmarksOrString: substring
	
	| benchmarks |
	benchmarks := self selectBenchmarks: substring.
	benchmarks ifEmpty: [ 
		^ String streamContents: [ :str |
				str
					nextPutAll: 'No benchmarks matched "';
					nextPutAll: substring;
					nextPutAll: '"';
					cr;
					nextPutAll: 'Available benchmarks:'.
				self allBenchmarkNames do: [ :name | str cr; nextPutAll: name ] ] ].
	^ benchmarks! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:04' prior: 49286631!
runMatching: substring iterations: iterations
	
	| benchmarks |
	benchmarks := self selectBenchmarksOrString: substring.
	benchmarks isString ifTrue: [ ^ benchmarks ].
	^ self run: benchmarks iterations: iterations! !
!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 12:05' prior: 49426919!
printMatching: substring iterations: iterations
	
	| benchmarks |
	benchmarks := self selectBenchmarksOrString: substring.
	benchmarks isString ifTrue: [ ^ benchmarks ].
	^ self print: benchmarks iterations: iterations! !

{'a'. 'b'}. ','. 'a,b'!

{'a'. 'b'}. ','. 'a,b'!
!Benchmarks class methodsFor: 'private' stamp: 'ag 7/15/2014 12:12'!
print: benchmarks iterations: iterations
	
	^ String streamContents: [ :str |
		benchmarks do: [ :bench | | instance |
			instance := bench new.
			str nextPutAll: String cr, instance name.
			str nextPutAll: ':', String cr.
			(SMarkRunner getResults: instance with: iterations)
				do: [ :result | str nextPutAll: result asString]
				separatedBy: [ str nextPut: $, ] ] ]! !
!Benchmarks class methodsFor: 'private' stamp: 'ag 7/15/2014 12:12' prior: 49428843!
print: benchmarks iterations: iterations
	
	^ String streamContents: [ :str |
		benchmarks do: [ :bench | | instance |
			instance := bench new.
			str nextPutAll: String cr, instance name.
			str nextPutAll: ':', String cr.
			(SMarkRunner getResults: instance with: iterations)
				do: [ :result | str nextPutAll: result asString ]
				separatedBy: [ str nextPut: $, ] ] ]! !
!SMarkRunner class methodsFor: 'benchmarking' stamp: 'ag 7/15/2014 12:14'!
getResults: aSuite with: nIterations
+	
+	^ (self execute: aSuite with: nIterations) results! !

----QUIT----{15 July 2014 . 12:14:32 pm} Squeak4.5-noBitBlt.image priorSource: 15870393!

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


SMarkRunner getResults: CPBBinaryTreeBenchmark new with: 5!

results := SMarkRunner getResults: CPBBinaryTreeBenchmark new with: 5!

results!

results values anyOne!

results values anyOne first!

results values anyOne first!

results values anyOne first total!

a := nil.!

results do: [ :key | a := key ]!

a!

results keysDo: [ :key | a := key ]!

results keysDo: [ :key | a := key ]!

a!

b := nil.!

results keysAndValuesDo: [ :key :value | a := key. b:= value ]!

a!

b!

String streamContents: [ :str |
		str cr ]!
!Benchmarks class methodsFor: 'private' stamp: 'ag 7/15/2014 12:21' prior: 49429305!
print: benchmarks iterations: iterations
	
	^ String streamContents: [ :str |
		benchmarks do: [ :bench |
			(SMarkRunner getResults: bench new with: iterations)
				keysAndValuesDo: [ :name :results |
					str cr; nextPutAll: name; nextPut: $:; cr.
					results
						do: [ :result | str nextPutAll: result total asString ]
						separatedBy: [ str nextPut: $, ] ] ] ]! !

----QUIT----{15 July 2014 . 12:22:06 pm} Squeak4.5-noBitBlt.image priorSource: 15875419!

----STARTUP----{15 July 2014 . 12:22:48 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


Smalltalk garbageCollect!
!SMarkRunner methodsFor: 'benchmarking' stamp: 'ag 7/15/2014 12:23' prior: 49235421!
performBenchmark: aSelector
+	currentBenchmark := aSelector.
+	
+	1 to: numIterations do: [:i|
+		"self timedBenchmarkExecution: aSelector."
+		Smalltalk garbageCollect.
		suite runBenchmark: aSelector.  
+	].	
+	
+	currentBenchmark := nil.
+	
+	^ results at: (suite benchmarkNameForSelector: aSelector)! !

----QUIT----{15 July 2014 . 12:24:01 pm} Squeak4.5-noBitBlt.image priorSource: 15876594!

----STARTUP----{15 July 2014 . 12:25:13 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


		Smalltalk garbageCollectMost.!
!SMarkRunner methodsFor: 'benchmarking' stamp: 'ag 7/15/2014 12:25' prior: 49431333!
performBenchmark: aSelector
+	currentBenchmark := aSelector.
+	
+	1 to: numIterations do: [:i|
+		"self timedBenchmarkExecution: aSelector."
+		Smalltalk garbageCollectMost.
		suite runBenchmark: aSelector.  
+	].	
+	
+	currentBenchmark := nil.
+	
+	^ results at: (suite benchmarkNameForSelector: aSelector)! !

----QUIT----{15 July 2014 . 12:25:31 pm} Squeak4.5-noBitBlt.image priorSource: 15877197!

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

!CPBAStarBenchmark methodsFor: 'initialize-release' stamp: 'ag 7/15/2014 12:31' prior: 48592510!
benchAStar
	astar 
		graph: graph1;
		findPath;
		reset .
	astar
		graph: graph2;
		findPath;
		reset.! !
!CPBAStarBenchmark methodsFor: 'initialize-release' stamp: 'ag 7/15/2014 12:32'!
benchAStarGraph1
	astar 
		graph: graph1;
		findPath;
		reset .! !
!CPBAStarBenchmark methodsFor: 'initialize-release' stamp: 'ag 7/15/2014 12:32'!
benchAStarGraph2
	astar 
		graph: graph2;
		findPath;
		reset .! !

CPBAStarBenchmark removeSelector: #benchAStar!
!CPBBinaryTreeBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 12:33' prior: 48678079!
benchBinaryTree
+	"starts the binary tree benchmark"
+	
+	self binarytrees: 30 .! !

----QUIT----{15 July 2014 . 12:33:52 pm} Squeak4.5-noBitBlt.image priorSource: 15877811!

----STARTUP----{15 July 2014 . 12:34:45 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!CPBBinaryTreeBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 12:34' prior: 49433076!
benchBinaryTree
+	"starts the binary tree benchmark"
+	
+	self binarytrees: 20 .! !

----SNAPSHOT----{15 July 2014 . 12:34:56 pm} Squeak4.5-noBitBlt.image priorSource: 15878724!
!CPBBinaryTreeBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 12:36' prior: 49433442!
benchBinaryTree
+	"starts the binary tree benchmark"
+	
+	self binarytrees: 12 .! !

----QUIT----{15 July 2014 . 12:36:45 pm} Squeak4.5-noBitBlt.image priorSource: 15879090!

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

!CPBBinaryTreeBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 12:37' prior: 49433708!
benchBinaryTree
+	"starts the binary tree benchmark"
+	
+	self binarytrees: 11 .! !

----SNAPSHOT----{15 July 2014 . 12:37:16 pm} Squeak4.5-noBitBlt.image priorSource: 15879356!
!CPBBinaryTreeBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 12:37' prior: 49434071!
benchBinaryTree
+	"starts the binary tree benchmark"
+	
+	self binarytrees: 12 .! !

----SNAPSHOT----{15 July 2014 . 12:37:42 pm} Squeak4.5-noBitBlt.image priorSource: 15879719!

#('0000000000000000' 'FFFFFFFFFFFFFFFF' '3000000000000000' '1111111111111111' '0123456789ABCDEF' '1111111111111111' '0000000000000000' 'FEDCBA9876543210' '7CA110454A1A6E57' '0131D9619DC1376E' '07A1133E4A0B2686' '3849674C2602319E' '04B915BA43FEB5B6' '0113B970FD34F2CE' '0170F175468FB5E6' '43297FAD38E373FE' '07A7137045DA2A16' '04689104C2FD3B2F' '37D06BB516CB7546' '1F08260D1AC2465E' '584023641ABA6176' '025816164629B007' '49793EBC79B3258F' '4FB05E1515AB73A7' '49E95D6D4CA229BF' '018310DC409B26D6' '1C587F1C13924FEF' '0101010101010101' '1F1F1F1F0E0E0E0E' 'E0FEE0FEF1FEF1FE' '0000000000000000' 'FFFFFFFFFFFFFFFF' '0123456789ABCDEF' 'FEDCBA9876543210') size!
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:44' prior: 48762750!
longDecryptionTest
+	"(1 to: keys size)"
+	(27 to: keys size)
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish decrypt: cipherText with: key ]! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:45' prior: 48763107!
longEncryptionTest
+	"(1 to: keys size)"
+	(27 to: keys size)
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish encrypt: clearText with: key ]! !

----SNAPSHOT----{15 July 2014 . 12:45:24 pm} Squeak4.5-noBitBlt.image priorSource: 15879985!
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:46' prior: 49435642!
longEncryptionTest
+	"(1 to: keys size)"
+	(31 to: keys size)
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish encrypt: clearText with: key ]! !
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:46'!
benchBlowfishDecryption
+	blowfish longDecryptionTest.! !
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:46'!
benchBlowfishEncryption
+	blowfish longEncryptionTest.
! !

CPBBlowfishSuite removeSelector: #benchBlowfish!
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:46' prior: 49436460!
benchBlowfishDecryption
+	blowfish longDecryptionTest: 5.! !
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:46' prior: 49436805!
benchBlowfishDecryption
+	blowfish decryptionTest: 5.! !
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:47' prior: 49436599!
benchBlowfishEncryption
+	blowfish encryptionTest: 5.
! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:47'!
encryptionTest: numKeys
+	(1 to: (numKeys max: keys size))
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish encrypt: clearText with: key ]! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:48'!
decryptionTest: numKeys
+	(1 to: (numKeys max: keys size))
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish decrypt: cipherText with: key ]! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:48' prior: 49435269!
longDecryptionTest
+	(1 to: keys size)
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish decrypt: cipherText with: key ]! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:48' prior: 49436108!
longEncryptionTest
+	self decryptionTest: keys size! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:48' prior: 49438329!
longEncryptionTest
+	self encryptionTest: keys size! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:48' prior: 49437979!
longDecryptionTest
+	self decryptionTest: keys size! !

----SNAPSHOT----{15 July 2014 . 12:49 pm} Squeak4.5-noBitBlt.image priorSource: 15881480!
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:53' prior: 48759322!
initialize
+	super initialize.
+	self
+		initializeClear;
+		initializeEncrypted;
+		initializeKeys.
	clear removeFirst: 5.
	encrypted removeFirst: 5.
	keys removeFirst: 5.! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:53' prior: 49438888!
initialize

	| removedKeys |
+	super initialize.
+	self
+		initializeClear;
+		initializeEncrypted;
+		initializeKeys.
	removedKeys := 8.
	clear removeFirst: removedKeys.
	encrypted removeFirst: removedKeys.
	keys removeFirst: removedKeys.! !

----SNAPSHOT----{15 July 2014 . 12:53:59 pm} Squeak4.5-noBitBlt.image priorSource: 15884263!
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:55' prior: 49436963!
benchBlowfishDecryption
+	blowfish decryptionTest: 1.! !
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:55' prior: 49437117!
benchBlowfishEncryption
+	blowfish encryptionTest: 1.
! !

----SNAPSHOT----{15 July 2014 . 12:55:59 pm} Squeak4.5-noBitBlt.image priorSource: 15884974!
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:58' prior: 49437611!
decryptionTest: numKeys
+	(1 to: (numKeys min: keys size))
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish decrypt: cipherText with: key ]! !
!CPBBlowfishProfiling methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 12:58' prior: 49437260!
encryptionTest: numKeys
+	(1 to: (numKeys min: keys size))
+		do: [ :each | 
+			| key clearText cipherText enc |
+			key := keys at: each.
+			clearText := clear at: each.
+			cipherText := encrypted at: each.
+			enc := CPBBlowfish encrypt: clearText with: key ]! !

----SNAPSHOT----{15 July 2014 . 12:59:56 pm} Squeak4.5-noBitBlt.image priorSource: 15885377!
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 13:00' prior: 49439598!
benchBlowfishDecryption
+	blowfish decryptionTest: 3.! !
!CPBBlowfishSuite methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 13:00' prior: 49439752!
benchBlowfishEncryption
+	blowfish encryptionTest: 3.
! !

----SNAPSHOT----{15 July 2014 . 1:01:31 pm} Squeak4.5-noBitBlt.image priorSource: 15886206!

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

!CPBPlanner class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 17:32' prior: 48911172!
standardBenchmark
+        "This the combined benchmark."
+        "Planner standardBenchmark"
+
+         self chainTest: 100.
+         self projectionTest: 100! !

----SNAPSHOT----{15 July 2014 . 5:32:20 pm} Squeak4.5-noBitBlt.image priorSource: 15886609!
!CPBPlanner class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 17:33' prior: 48908366!
chainTest: n
+        "Do chain-of-equality-constraints performance tests."
+
+        | vars editConstraint plan planner |
+        planner := CPBPlanner new.
+        vars := (1 to: n+1) collect: [ :i | CPBVariable new].
+
+        "thread a chain of equality constraints through the variables"
+        1 to: n do:
+                [ :i || v1 v2 |
+                 v1 := vars at: i.
+                 v2 := vars at: i + 1.
+                 CPBEqualityConstraint var: v1 var: v2 strength: #required].
+
+        CPBStayConstraint var: vars last strength: #strongDefault.
+        editConstraint := CPBEditConstraint var: (vars first) strength: #preferred.
+        plan := planner extractPlanFromConstraints: (Array with: editConstraint).
+        1 to: n do: [ :v |
+                vars first value: v.
+                plan execute.
+                vars last value ~= v ifTrue: [self error: 'Chain test failed!!']].
+        editConstraint destroyConstraint! !
!CPBPlanner class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 17:33' prior: 49441326!
standardBenchmark
+        "This the combined benchmark."
+        "Planner standardBenchmark"
+
+         self chainTest: 400.
+         self projectionTest: 400! !

----SNAPSHOT----{15 July 2014 . 5:33:57 pm} Squeak4.5-noBitBlt.image priorSource: 15887059!

----SNAPSHOT----{15 July 2014 . 5:34 pm} Squeak4.5-noBitBlt.image priorSource: 15888463!
!CPBPlanner class methodsFor: 'benchmarks' stamp: 'ag 7/15/2014 17:34' prior: 49442730!
standardBenchmark
+        "This the combined benchmark."
+        "Planner standardBenchmark"
+
+         self chainTest: 1000.
+         self projectionTest: 1000! !

----SNAPSHOT----{15 July 2014 . 5:34:58 pm} Squeak4.5-noBitBlt.image priorSource: 15888556!
!CPBNBodyBenchmark methodsFor: 'nbody' stamp: 'ag 7/15/2014 17:51' prior: 49054097!
benchNBody
+	"helper method to run the n body benchmark"
+	
+	self runBenchmarkFor: 2500 withStep: 0.01d0 .! !

----SNAPSHOT----{15 July 2014 . 5:51:16 pm} Squeak4.5-noBitBlt.image priorSource: 15888902!
!CPBNBodyBenchmark methodsFor: 'nbody' stamp: 'ag 7/15/2014 17:52' prior: 49443512!
benchNBody
+	"helper method to run the n body benchmark"
+	
+	self runBenchmarkFor: 3500 withStep: 0.01d0 .! !

----SNAPSHOT----{15 July 2014 . 5:52:12 pm} Squeak4.5-noBitBlt.image priorSource: 15889190!
!CPBRichardsBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 17:57'!
executeExampleSchedule
+	| scheduler queue |
+	scheduler := CPBScheduler new .
+	scheduler addIdleTask: (CPBScheduler idIdle) withPriority: 0 withQueue: nil times: (CPBRichardsBenchmark iterations) .
+
+	queue := CPBPacket link: nil id: (CPBScheduler idWorker) kind: (CPBPacket kindWork) .
+	queue := CPBPacket link: queue id: (CPBScheduler idWorker) kind: (CPBPacket kindWork) .
+	scheduler addWorkerTask: (CPBScheduler idWorker) withPriority: 1000 withQueue: queue .
+	
+	queue := CPBPacket link: nil id: (CPBScheduler idDeviceA) kind: (CPBPacket kindDevice) .
+	queue := CPBPacket link: queue id: (CPBScheduler idDeviceA) kind: (CPBPacket kindDevice) .
+	queue := CPBPacket link: queue id: (CPBScheduler idDeviceA) kind: (CPBPacket kindDevice) .
+	scheduler addHandlerTask: (CPBScheduler idHandlerA) withPriority: 2000 withQueue: queue .
+	
+	queue := CPBPacket link: nil id: (CPBScheduler idDeviceB) kind: (CPBPacket kindDevice) .
+	queue := CPBPacket link: queue id: (CPBScheduler idDeviceB) kind: (CPBPacket kindDevice) .
+	queue := CPBPacket link: queue id: (CPBScheduler idDeviceB) kind: (CPBPacket kindDevice) .
+	scheduler addHandlerTask: (CPBScheduler idHandlerB) withPriority: 3000 withQueue: queue .	
+
+	scheduler addDeviceTask: (CPBScheduler idDeviceA) withPriority: 4000 withQueue: nil .
+	scheduler addDeviceTask: (CPBScheduler idDeviceB) withPriority: 5000 withQueue: nil .
+	
+	scheduler schedule .
+	
+	((scheduler queueCount ~~ (CPBRichardsBenchmark expectedQueueCount)) or: 
+	(scheduler holdCount ~~ (CPBRichardsBenchmark expectedHoldCount))) ifTrue: [
+		Transcript 
+			show: 'Error during execution: queueCount= ';
+			show: (scheduler queueCount);
+			show: ', holdCount=';
+			show: (scheduler holdCount);
+			show: '.';
+			cr .
+	] .
+! !
!CPBRichardsBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 17:58' prior: 49197044!
benchRichards
	
	50 timesRepeat: [ self executeExampleSchedule ].! !
!CPBRichardsBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 17:58' prior: 49445901!
benchRichards
	
	100 timesRepeat: [ self executeExampleSchedule ].! !

----SNAPSHOT----{15 July 2014 . 5:58:28 pm} Squeak4.5-noBitBlt.image priorSource: 15889478!
!CPBRichardsBenchmark methodsFor: 'testing' stamp: 'ag 7/15/2014 17:59' prior: 49446059!
benchRichards
	
	200 timesRepeat: [ self executeExampleSchedule ].! !

----SNAPSHOT----{15 July 2014 . 5:59:34 pm} Squeak4.5-noBitBlt.image priorSource: 15891696!
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 18:05' prior: 49268315!
setUp	
+	splayTree := nil.
+	kSplayTreeSize := 1000. "8000"
+	kSplayTreeModifications := 80. "80."
+	kSplayTreePayloadDepth := 5.
+	keyCounter := 0.
+	
+	Transcript showln: 'entering SplayTree setup'.
+	
+	self splayTree: (CPBSplaytree new).
+	
+	1 to: self splayTreeSize do: [:i |
+		self insertNewNode.
+	]! !

----SNAPSHOT----{15 July 2014 . 6:05:51 pm} Squeak4.5-noBitBlt.image priorSource: 15891948!
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 18:06' prior: 49446576!
setUp	
+	splayTree := nil.
+	kSplayTreeSize := 1000. "8000"
+	kSplayTreeModifications := 300. "80."
+	kSplayTreePayloadDepth := 5.
+	keyCounter := 0.
+	
+	Transcript showln: 'entering SplayTree setup'.
+	
+	self splayTree: (CPBSplaytree new).
+	
+	1 to: self splayTreeSize do: [:i |
+		self insertNewNode.
+	]! !

----SNAPSHOT----{15 July 2014 . 6:06:41 pm} Squeak4.5-noBitBlt.image priorSource: 15892442!
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 18:07' prior: 49447070!
setUp	
+	splayTree := nil.
+	kSplayTreeSize := 1000. "8000"
+	kSplayTreeModifications := 600. "80."
+	kSplayTreePayloadDepth := 5.
+	keyCounter := 0.
+	
+	Transcript showln: 'entering SplayTree setup'.
+	
+	self splayTree: (CPBSplaytree new).
+	
+	1 to: self splayTreeSize do: [:i |
+		self insertNewNode.
+	]! !
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 18:08' prior: 49447565!
setUp	
+	splayTree := nil.
+	kSplayTreeSize := 1000. "8000"
+	kSplayTreeModifications := 500. "80."
+	kSplayTreePayloadDepth := 10.
+	keyCounter := 0.
+	
+	Transcript showln: 'entering SplayTree setup'.
+	
+	self splayTree: (CPBSplaytree new).
+	
+	1 to: self splayTreeSize do: [:i |
+		self insertNewNode.
+	]! !

----SNAPSHOT----{15 July 2014 . 6:08:20 pm} Squeak4.5-noBitBlt.image priorSource: 15892937!
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 18:09' prior: 49447967!
setUp	
+	splayTree := nil.
+	kSplayTreeSize := 1000. "8000"
+	kSplayTreeModifications := 500. "80."
+	kSplayTreePayloadDepth := 7.
+	keyCounter := 0.
+	
+	Transcript showln: 'entering SplayTree setup'.
+	
+	self splayTree: (CPBSplaytree new).
+	
+	1 to: self splayTreeSize do: [:i |
+		self insertNewNode.
+	]! !

----SNAPSHOT----{15 July 2014 . 6:09:41 pm} Squeak4.5-noBitBlt.image priorSource: 15893835!
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 7/15/2014 18:10' prior: 49448463!
setUp	
+	splayTree := nil.
+	kSplayTreeSize := 1000. "8000"
+	kSplayTreeModifications := 500. "80."
+	kSplayTreePayloadDepth := 6.
+	keyCounter := 0.
+	
+	Transcript showln: 'entering SplayTree setup'.
+	
+	self splayTree: (CPBSplaytree new).
+	
+	1 to: self splayTreeSize do: [:i |
+		self insertNewNode.
+	]! !

----SNAPSHOT----{15 July 2014 . 6:10:56 pm} Squeak4.5-noBitBlt.image priorSource: 15894330!
\ No newline at end of file
diff --git a/images/Squeak4.5-noBitBlt.image b/images/Squeak4.5-noBitBlt.image
index 175e9df2180e298a4db4f8f60698e45e1b468425..ed92c78c940799d91bb94a8ed8527076db6816c7
GIT binary patch

[cut]



More information about the pypy-commit mailing list