compiler/benchmarks/PPCBenchmark.st
changeset 421 7e08b31e0dae
parent 420 b2f2f15cef26
child 422 116d2b2af905
--- a/compiler/benchmarks/PPCBenchmark.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/benchmarks/PPCBenchmark.st	Mon Nov 24 00:09:23 2014 +0000
@@ -4,9 +4,10 @@
 	instanceVariableNames:'sources report contextClass compile parser context input'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Benchmarks'
+	category:'PetitCompiler-Benchmarks-Core'
 !
 
+
 !PPCBenchmark class methodsFor:'instance creation'!
 
 new
@@ -188,6 +189,36 @@
 	self measure: parser on: sources javaLangMath name: #java.
 !
 
+benchmarkJavaSyntax
+	| time |
+	
+	self assert: '../java-src' asFileReference exists description: '../java-src directory with java sources expected'.
+
+	parser := PPJavaSyntax new.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources javaSourcesBig.
+
+	time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+	
+	self reportInput: input time: time name: 'Java Syntax'.
+!
+
+benchmarkJavaSyntaxCompiled
+	| time |
+	
+	self assert: '../java-src' asFileReference exists description: '../java-src directory with java sources expected'.
+
+	parser := PPJavaSyntax new compile.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources javaSourcesBig.
+
+	time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+	
+	self reportInput: input time: time name: 'Java Syntax Compiled'.
+!
+
 benchmarkNegate
 "
 	self measure: self anyStar on: sources petitParserPackage.
@@ -286,6 +317,22 @@
 
 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
 
+benchmarkJavaSyntaxC
+	<setup: #setupJavaSyntaxC>
+	<benchmark: 'Petit Java Parser - Standard'>
+	
+	input do: [ :source | parser parse: source withContext: context ]
+!
+
+benchmarkJavaSyntaxCompiledC
+	<setup: #setupJavaSyntaxCompiledC>
+	<teardown: #teardownJavaSyntaxCompiledC>
+	<benchmark: 'Petit Java Parser - Compiled'>
+	
+	input do: [ :source | parser parse: source withContext: context ]
+	
+!
+
 benchmarkRBParserC
 	<setup: #setupRBParserC>
 	<benchmark: 'RB Smalltalk Parser'>
@@ -293,6 +340,22 @@
 	input do: [ :source | RBParser parseMethod: source ]
 !
 
+benchmarkSmalltalkGrammarC
+	<setup: #setupSmalltalkGrammarC>
+	<benchmark: 'Petit Smalltalk Grammar - Standard'>
+	
+	input do: [ :source | parser parse: source withContext: context ]
+!
+
+benchmarkSmalltalkGrammarCompiledC
+	<setup: #setupSmalltalkGrammarCompiledC>
+	<teardown: #teardownSmalltalkGrammarCompiledC>
+	<benchmark: 'Petit Smalltalk Grammar - Compiled'>
+	
+	
+	input do: [ :source | parser parse: source withContext: context ]
+!
+
 benchmarkSmalltalkParserC
 	<setup: #setupSmalltalkParserC>
 	<benchmark: 'Petit Smalltalk Parser - Standard'>
@@ -302,7 +365,7 @@
 
 benchmarkSmalltalkParserCompiledC
 	<setup: #setupSmalltalkParserCompiledC>
-	<teaddown: #teardownSmalltalkParserCompiledC>
+	<teardown: #teardownSmalltalkParserCompiledC>
 	<benchmark: 'Petit Smalltalk Parser - Compiled'>
 	
 	input do: [ :source | parser parse: source withContext: context ]
@@ -352,6 +415,14 @@
 
 !PPCBenchmark methodsFor:'setup & teardown-CalipeL'!
 
+setupJavaSyntaxC
+	
+	parser := PPJavaSyntax new.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources javaSourcesBig.
+!
+
 setupJavaSyntaxCompiledC
 	parser := PPJavaSyntax new compile.
 	context := PPCContext new.
@@ -370,6 +441,27 @@
 	input := sources smalltalkSourcesBig.
 !
 
+setupSmalltalkGrammarC
+	
+	parser := PPSmalltalkGrammar new.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources smalltalkSourcesBig.
+!
+
+setupSmalltalkGrammarCompiledC
+	parser := PPSmalltalkGrammar new compile.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources smalltalkSourcesBig.
+
+"	
+	size := input inject: 0 into: [:r :e | r + e size  ].
+	Transcript crShow: 'Compiled Grammar time: ', time asString.
+	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
+"
+!
+
 setupSmalltalkParserC
 	
 	parser := PPSmalltalkParser new.
@@ -400,6 +492,15 @@
 "
 !
 
+teardownSmalltalkGrammarCompiledC
+	parser class removeFromSystem.
+"	
+	size := input inject: 0 into: [:r :e | r + e size  ].
+	Transcript crShow: 'Compiled Grammar time: ', time asString.
+	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
+"
+!
+
 teardownSmalltalkParserCompiledC
 	parser class removeFromSystem.
 "	
@@ -433,3 +534,10 @@
 	self endSuite.
 ! !
 
+!PPCBenchmark class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+