compiler/benchmarks/PPCBenchmark.st
changeset 464 f6d77fee9811
parent 459 4751c407bb40
child 465 f729f6cd3c76
child 502 1e45d3c96ec5
--- a/compiler/benchmarks/PPCBenchmark.st	Tue May 12 01:24:03 2015 +0100
+++ b/compiler/benchmarks/PPCBenchmark.st	Thu May 21 14:12:22 2015 +0100
@@ -4,7 +4,7 @@
 
 Object subclass:#PPCBenchmark
 	instanceVariableNames:'sources report contextClass compile parser context input
-		configuration'
+		configuration profile'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Benchmarks-Core'
@@ -57,7 +57,8 @@
 
 measure: aParser on: anInput name: aString
     | time result p |
-    context := self createContext.
+    self halt: 'deprecated?'.
+    context := self context.
     
     p := compile ifTrue: [ 
         aParser end compile
@@ -92,12 +93,16 @@
 "
 !
 
-reportInput: input time: time name: name
+reportInput: anInput time: time name: name
     | size |
-    size := input inject: 0 into: [:r :e | r + e size  ].
+    size := anInput inject: 0 into: [:r :e | r + e size  ].
     Transcript crShow: 'Size: ', size asString.
     Transcript crShow: name, ' time: ', time asString.
     Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
+    
+    (context isKindOf: PPCProfilingContext) ifTrue: [ 
+        context inspect.
+    ]
 ! !
 
 !PPCBenchmark methodsFor:'benchmarks'!
@@ -130,85 +135,6 @@
     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
     
     self reportInput: input time: time name: 'Java Syntax Compiled'.
-!
-
-benchmarkOpalCompiler
-    | parser time input |
-    parser := OpalCompiler new.
-    input := sources smalltalkSourcesBig.
-    time := [ input do: [ :source | parser parse: source ]] timeToRun asMilliseconds.
-    
-    self reportInput: input time: time name: 'Opal'
-!
-
-benchmarkSmalltalkGrammar
-    | time |
-
-    self setupSmalltalkGrammar.
-
-    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
-    
-    self reportInput: input time: time name: 'Smalltalk Grammar'.
-!
-
-benchmarkSmalltalkGrammarCompiled
-    | time  |
-
-    self setupSmalltalkGrammarCompiled.
-
-    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
-    
-    self reportInput: input time: time name: 'Compiled Smalltalk Grammar'.
-
-"	
-    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'.
-"
-!
-
-benchmarkSmalltalkGrammarTokenized
-    | time   |
-
-    self setupSmalltalkGrammarTokenized.
-    
-    time := [ input do: [ :source | 
-            parser parse: source withContext: context ] 
-    ] timeToRun asMilliSeconds.
-    
-    self reportInput: input time: time name: 'Tokenized Smalltalk Grammar'.
-
-"	
-    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'.
-"
-!
-
-benchmarkSmalltalkParser
-    | time |
-    parser := PPSmalltalkParser new.
-    context := PPContext new.
-    context initializeFor: parser.
-    input := sources smalltalkSourcesBig.
-
-    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
-    
-    self reportInput: input time: time name: 'Smalltalk Parser'.
-!
-
-benchmarkSmalltalkParserCompiled
-    | time |
-    
-    configuration := PPCConfiguration default.
-    parser := PPSmalltalkParser new compileWithConfiguration: configuration.
-    context := PPCContext new.
-    context initializeFor: parser.
-    input := sources smalltalkSourcesBig.
-
-    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
-    
-        self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
 ! !
 
 !PPCBenchmark methodsFor:'benchmarks - expression grammar'!
@@ -297,6 +223,87 @@
     self measure: parser on: (sources changesSized: 1000*1000) name: #token.
 ! !
 
+!PPCBenchmark methodsFor:'benchmarks - smalltalk'!
+
+benchmarkOpalCompiler
+    | parser time input |
+    parser := OpalCompiler new.
+    input := sources smalltalkSourcesBig.
+    time := [ input do: [ :source | parser parse: source ]] timeToRun asMilliseconds.
+    
+    self reportInput: input time: time name: 'Opal'
+!
+
+benchmarkSmalltalkGrammar
+    | time |
+
+    self setupSmalltalkGrammar.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Smalltalk Grammar'.
+!
+
+benchmarkSmalltalkGrammarCompiled
+    | time  |
+
+    self setupSmalltalkGrammarCompiled.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Compiled Smalltalk Grammar'.
+
+"	
+    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'.
+"
+!
+
+benchmarkSmalltalkGrammarTokenized
+    | time   |
+
+    self setupSmalltalkGrammarTokenized.
+    
+    time := [ input do: [ :source | 
+            parser parse: source withContext: context ] 
+    ] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Tokenized Smalltalk Grammar'.
+
+"	
+    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'.
+"
+!
+
+benchmarkSmalltalkParser
+    | time |
+    parser := PPSmalltalkParser new.
+    context := PPContext new.
+    context initializeFor: parser.
+    input := sources smalltalkSourcesBig.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Smalltalk Parser'.
+!
+
+benchmarkSmalltalkParserCompiled
+    | time |
+    
+    configuration := PPCConfiguration default.
+    parser := PPSmalltalkParser new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources smalltalkSourcesBig.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+        self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
+! !
+
 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
 
 benchmarkExpressionGrammarC
@@ -381,7 +388,7 @@
 
 !PPCBenchmark methodsFor:'intitialization'!
 
-createContext
+context
     ^ contextClass new
 !
 
@@ -389,7 +396,9 @@
     super initialize.
     sources := PPCResources current.
     contextClass := PPCContext.
+
     compile := false.
+    profile := false.
 ! !
 
 !PPCBenchmark methodsFor:'meta'!
@@ -424,12 +433,19 @@
     ^ #letter asParser, (#letter asParser / #digit asParser) star trim
 ! !
 
+!PPCBenchmark methodsFor:'profiling'!
+
+profile
+    contextClass := PPCProfilingContext.
+    profile := true.
+! !
+
 !PPCBenchmark methodsFor:'setup & teardown'!
 
 setupExpressionGrammar
     
     parser := PPExpressionGrammar new.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources expressionSourcesMedium.
 !
@@ -439,17 +455,17 @@
     configuration := PPCConfiguration universal.
     configuration arguments name: #PPCompiledExpressionGrammar.
     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources expressionSourcesMedium.
 !
 
 setupExpressionGrammarTokenized
     
-    configuration := PPCConfiguration LL1.
-    configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
-    parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    configuration := PPCConfiguration tokenizing.
+    configuration arguments name: #PPTokenizedExpressionGrammar.
+    parser := PPExpressionGrammar new compileWithConfiguration: configuration.
+    context := self context.
     context initializeFor: parser.
     input := sources expressionSourcesMedium.
 !
@@ -457,14 +473,14 @@
 setupJavaSyntax
     
     parser := PPJavaSyntax new.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources javaSourcesBig.
 !
 
 setupJavaSyntaxCompiled
     parser := PPJavaSyntax new compile.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources javaSourcesBig.
 
@@ -478,7 +494,7 @@
 setupLL1ExpressionGrammar
     
     parser := PPLL1ExpressionGrammar new.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources expressionSourcesBig.
 !
@@ -488,17 +504,17 @@
     configuration := PPCConfiguration universal.
     configuration arguments name: #PPCompiledLL1ExpressionGrammar.
     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources expressionSourcesBig.
 !
 
 setupLL1ExpressionGrammarTokenized
     
-    configuration := PPCConfiguration universal.
+    configuration := PPCConfiguration tokenizing.
     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources expressionSourcesBig.
 !
@@ -511,7 +527,7 @@
 setupSmalltalkGrammar
     
     parser := PPSmalltalkGrammar new.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources smalltalkSourcesBig.
 !
@@ -520,26 +536,39 @@
 
     configuration := PPCConfiguration universal.
     configuration arguments name: #PPCompiledSmalltalkGrammar.
+    configuration arguments profile: profile.
+    
     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
-    input := sources smalltalkSourcesBig.
+    
+    profile ifTrue: [ 
+        input := sources smalltalkSourcesSmall.	
+    ] ifFalse: [ 
+        input := sources smalltalkSourcesBig.	
+    ]
 !
 
 setupSmalltalkGrammarTokenized
 
-    configuration := PPCConfiguration LL1.
+    configuration := PPCConfiguration tokenizing.
     configuration arguments name: #PPTokenizedSmalltalkGrammar.
+    configuration arguments profile: profile.
+    
     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
-    input := sources smalltalkSourcesBig.
+    profile ifTrue: [ 
+        input := sources smalltalkSourcesSmall.	
+    ] ifFalse: [ 
+        input := sources smalltalkSourcesBig.	
+    ]
 !
 
 setupSmalltalkParser
     
     parser := PPSmalltalkParser new.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources smalltalkSourcesBig.
 !
@@ -548,16 +577,16 @@
 
     configuration := PPCConfiguration universal.
     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources smalltalkSourcesBig.
 !
 
 setupSmalltalkParserTokenized
 
-    configuration := PPCConfiguration LL1.
+    configuration := PPCConfiguration tokenizing.
     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
-    context := PPCContext new.
+    context := self context.
     context initializeFor: parser.
     input := sources smalltalkSourcesBig.
 !