[pypy-commit] lang-smalltalk rstrategies: Cleaned up benchmarks.

anton_gulenko noreply at buildbot.pypy.org
Thu Oct 16 16:56:49 CEST 2014


Author: Anton Gulenko <anton.gulenko at googlemail.com>
Branch: rstrategies
Changeset: r1050:a65eca0466a1
Date: 2014-09-24 14:42 +0200
http://bitbucket.org/pypy/lang-smalltalk/changeset/a65eca0466a1/

Log:	Cleaned up benchmarks.

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
@@ -12631,4 +12631,54 @@
 
 1+1!
 
-----QUIT/NOSAVE----{21 July 2014 . 4:33:15 pm} Squeak4.5-noBitBlt.image priorSource: 15898877!

----STARTUP----{26 July 2014 . 10:25:02 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!EventSensor methodsFor: 'private-I/O' stamp: 'ag 7/26/2014 10:25' prior: 47373772!
fetchMoreEvents
	"Fetch more events from the VM"
	| eventBuffer type |

	"Reset input semaphore so clients can wait for the next events after this one."
	inputSemaphore isSignaled
		ifTrue: [ hasInputSemaphore := true.
			inputSemaphore initSignals ].

	"Remember the last time that I checked for events."
	lastEventPoll := Time millisecondClockValue.

	eventBuffer := Array new: 8.
	[self primGetNextEvent: eventBuffer.
	type := eventBuffer at: 1.
	"type = EventTypeWindow ifTrue: [eventBuffer inspect]."
	type = EventTypeNone]
		whileFalse: [self processEvent: eventBuffer].
! !

----QUIT----{26 July 2014 . 10:25:36 am} Squeak4.5-noBitBlt.image priorSource: 15898877!
\ No newline at end of file
+----QUIT/NOSAVE----{21 July 2014 . 4:33:15 pm} Squeak4.5-noBitBlt.image priorSource: 15898877!

----STARTUP----{26 July 2014 . 10:25:02 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!EventSensor methodsFor: 'private-I/O' stamp: 'ag 7/26/2014 10:25' prior: 47373772!
fetchMoreEvents
	"Fetch more events from the VM"
	| eventBuffer type |

	"Reset input semaphore so clients can wait for the next events after this one."
	inputSemaphore isSignaled
		ifTrue: [ hasInputSemaphore := true.
			inputSemaphore initSignals ].

	"Remember the last time that I checked for events."
	lastEventPoll := Time millisecondClockValue.

	eventBuffer := Array new: 8.
	[self primGetNextEvent: eventBuffer.
	type := eventBuffer at: 1.
	"type = EventTypeWindow ifTrue: [eventBuffer inspect]."
	type = EventTypeNone]
		whileFalse: [self processEvent: eventBuffer].
! !

----QUIT----{26 July 2014 . 10:25:36 am} Squeak4.5-noBitBlt.image priorSource: 15898877!

----STARTUP----{24 September 2014 . 11:02:24 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!SmallInteger methodsFor: 'as yet unclassified' stamp: 'ag 9/24/2014 11:04' prior: 49425360!
printBenchmarks

	^ Benchmarks printAll: self benchmarkIterations! !

----SNAPSHOT----{24 September 2014 . 11:04:31 am} Squeak4.5-noBitBlt.image priorSource: 15899947!

----STARTUP----{24 September 2014 . 11:06:22 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 9/24/2014 11:07' prior: 49426217!
printAll: iterations
	
	^ self print: self allBenchmarks iterations: iterations! !

----SNAPSHOT----{24 September 2014 . 11:08:49 am} Squeak4.5-noBitBlt.image priorSource: 15900308!

----STARTUP----{24 September 2014 . 11:12:12 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 9/24/2014 11:12' prior: 49375352!
allBenchmarks
	
	^ {
	CPBAStarBenchmark.
	CPBBinaryTreeBenchmark.
	CPBBlowfishSuite.
	"CPBChameneosBenchmark." "Commented out because it forks processes."
	CPBDeltaBlueBenchmark.
	CPBMandelbrotBenchmarkSuite.
	CPBNBodyBenchmark.
	"CPBPolymorphyBenchmark." "Commented out because it compiles code in setup."
	CPBRichardsBenchmark.
	CPBSplayTreeBenchmark.
	SimpleMatrixBenchmark.
	}! !

1 printBenchmarks!

----SNAPSHOT----{24 September 2014 . 11:13:48 am} Squeak4.5-noBitBlt.image priorSource: 15900687!

----STARTUP----{24 September 2014 . 11:15:34 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!Benchmarks class methodsFor: 'benchmarks' stamp: 'ag 9/24/2014 11:15' prior: 49455416!
allBenchmarks
	
	^ {
	CPBAStarBenchmark.
	CPBBinaryTreeBenchmark.
	CPBBlowfishSuite.
	"CPBChameneosBenchmark." "Commented out because it forks processes."
	CPBDeltaBlueBenchmark.
	"CPBMandelbrotBenchmarkSuite." "Commented out because it forks processes."
	CPBNBodyBenchmark.
	"CPBPolymorphyBenchmark." "Commented out because it compiles code in setup."
	CPBRichardsBenchmark.
	CPBSplayTreeBenchmark.
	SimpleMatrixBenchmark.
	}! !

----SNAPSHOT----{24 September 2014 . 11:15:58 am} Squeak4.5-noBitBlt.image priorSource: 15901387!

----STARTUP----{24 September 2014 . 11:17:58 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 9/24/2014 11:19' prior: 49269205!
tearDown
+	"allow gc to reclaim the memory
+	 used by the splay tree no matter how we exit the tear down function"
+	
+	| keys length |
+
+	keys := self splayTree exportKeys.
+	self splayTree: nil.
+	
+	"Verify that the splay tree has the right size."
+	"
	length := keys size.
+	Transcript show: length.
+	Transcript show: '';cr.
+	Transcript show: (self splayTreeSize).
+	( length ~= self splayTreeSize ) ifTrue: [
+		Error signal: 'Splay tree has wrong size.'.
+		Transcript show: 'Splay tree has wrongsize.'; cr .
+	].
	"
+
+	"Verify that the splay tree has sorted, unique keys."
+	1 to: (length-1) do: [:i|
+		( (keys at: i) >= (keys at: ( i + 1) )) ifTrue: [
+			Error signal: 'Splay tree not sorted'.
+		].
+	].
+	! !
!CPBSplayTreeBenchmark methodsFor: 'as yet unclassified' stamp: 'ag 9/24/2014 11:19' prior: 49456856!
tearDown
+	"allow gc to reclaim the memory
+	 used by the splay tree no matter how we exit the tear down function"
+	
+	| keys length |
+
+	keys := self splayTree exportKeys.
+	self splayTree: nil.
+	
+	"Verify that the splay tree has the right size."
+	"
	length := keys size.
+	Transcript show: length.
+	Transcript show: '';cr.
+	Transcript show: (self splayTreeSize).
+	( length ~= self splayTreeSize ) ifTrue: [
+		Error signal: 'Splay tree has wrong size.'.
+		Transcript show: 'Splay tree has wrongsize.'; cr .
+	].
	"
+
+	"Verify that the splay tree has sorted, unique keys."
+	"
	1 to: (length-1) do: [:i|
+		( (keys at: i) >= (keys at: ( i + 1) )) ifTrue: [
+			Error signal: 'Splay tree not sorted'.
+		].
+	].
+	"! !

----SNAPSHOT----{24 September 2014 . 11:19:37 am} Squeak4.5-noBitBlt.image priorSource: 15902113!

----STARTUP----{24 September 2014 . 11:26:20 am} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!

!Benchmarks class methodsFor: 'private' stamp: 'ag 9/24/2014 11:27' prior: 49430654!
print: benchmarks iterations: iterations
	
	^ String streamContents: [ :str |
		benchmarks do: [ :bench |
			(self getResults: bench iterations: iterations)
				keysAndValuesDo: [ :name :results |
					str cr; nextPutAll: name; nextPut: $:; cr.
					results
						do: [ :result | str nextPutAll: result total asString ]
						separatedBy: [ str nextPut: $, ] ] ] ]! !
!Benchmarks class methodsFor: 'private' stamp: 'ag 9/24/2014 11:29'!
getResults: benchmark iterations: i
	
	| iterations |
	iterations := i.
	iterations = 0 ifTrue: [  iterations := self defaultIterationsFor: benchmark ].
	^ SMarkRunner getResults: benchmark new with: iterations! !
!Benchmarks class methodsFor: 'private' stamp: 'ag 9/24/2014 11:30'!
execute: benchmark iterations: i
	
	| iterations |
	iterations := i.
	iterations = 0 ifTrue: [  iterations := self defaultIterationsFor: benchmark ].
	^ SMarkRunner execute: benchmark new with: iterations! !
!Benchmarks class methodsFor: 'private' stamp: 'ag 9/24/2014 11:30' prior: 49327061!
run: benchmarks iterations: iterations
	
	^ String streamContents: [ :str |
		benchmarks do: [ :bench |
			str nextPutAll:
				(self execute: bench iterations: iterations) asString ] ]! !
!Benchmarks class methodsFor: 'private' stamp: 'ag 9/24/2014 11:31'!
defaultIterationsFor: benchmark
	
	| d |
	d := Dictionary newFrom: {
		
	}.
	^ d at: benchmark! !

----STARTUP----{24 September 2014 . 2:30:33 pm} as C:\Dev\lang-smalltalk\images\Squeak4.5-noBitBlt.image!


Smalltalk specialObjectsArray!

Smalltalk specialObjectsArray!

c := Smalltalk specialObjectsArray at: 25!

c!

c first class!

Smalltalk specialObjectsArray indexOf: c first class!
\ No newline at end of file
diff --git a/images/Squeak4.5-noBitBlt.image b/images/Squeak4.5-noBitBlt.image
index 09f9fb6fb17051fefa839fb357c4170d285c1c8a..90a12180a6d53dcbef1c3272db0060a7aa533ff3
GIT binary patch

[cut]


More information about the pypy-commit mailing list