Added benchmark of a smalltalk parser with empty actions.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sat, 16 May 2015 19:21:00 +0100
changeset 462 89464ab03518
parent 461 5986bf6d7d60
child 463 d4014e0a47a0
Added benchmark of a smalltalk parser with empty actions. This is used to check the cost of compiled actions
compiler/benchmarks/Make.proto
compiler/benchmarks/Make.spec
compiler/benchmarks/PPCBenchmark.st
compiler/benchmarks/PPCSmalltalkNoopParser.st
compiler/benchmarks/PPCSmalltalkNoopParserTests.st
compiler/benchmarks/abbrev.stc
compiler/benchmarks/bc.mak
compiler/benchmarks/libInit.cc
compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st
--- a/compiler/benchmarks/Make.proto	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/Make.proto	Sat May 16 19:21:00 2015 +0100
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/petitparser -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/java -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/libbasic
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/petitparser -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/java -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk/tests -I$(INCLUDE_TOP)/stx/goodies/petitparser/tests -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
@@ -102,6 +102,16 @@
 # build all mandatory prerequisite packages (containing superclasses) for this package
 prereq:
 	cd ../../../../libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../../refactoryBrowser/parser && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../../../libbasic2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../../../libbasic3 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../../../libview && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../ && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../../../libview2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../parsers/smalltalk && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../../sunit && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../tests && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../../parsers/smalltalk/tests && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 
 
 
@@ -122,6 +132,7 @@
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)PPCBenchmark.$(O) PPCBenchmark.$(H): PPCBenchmark.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSmalltalkNoopParser.$(O) PPCSmalltalkNoopParser.$(H): PPCSmalltalkNoopParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPCompositeParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk/PPSmalltalkGrammar.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)stx_goodies_petitparser_compiler_benchmarks.$(O) stx_goodies_petitparser_compiler_benchmarks.$(H): stx_goodies_petitparser_compiler_benchmarks.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/compiler/benchmarks/Make.spec	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/Make.spec	Sat May 16 19:21:00 2015 +0100
@@ -52,6 +52,7 @@
 
 COMMON_CLASSES= \
 	PPCBenchmark \
+	PPCSmalltalkNoopParser \
 	stx_goodies_petitparser_compiler_benchmarks \
 
 
@@ -59,6 +60,7 @@
 
 COMMON_OBJS= \
     $(OUTDIR_SLASH)PPCBenchmark.$(O) \
+    $(OUTDIR_SLASH)PPCSmalltalkNoopParser.$(O) \
     $(OUTDIR_SLASH)stx_goodies_petitparser_compiler_benchmarks.$(O) \
 
 
--- a/compiler/benchmarks/PPCBenchmark.st	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/PPCBenchmark.st	Sat May 16 19:21:00 2015 +0100
@@ -50,9 +50,17 @@
 !
 
 spy: benchmark
-    ^ (BenchmarkInstance class:self selector:benchmark) spy
+    | benchmarkInstanceClass |
+
+    benchmarkInstanceClass := Smalltalk at: #BenchmarkInstance.
+    benchmarkInstanceClass isNil ifTrue:[
+        self error: 'CalipeL is not loaded.'
+    ].   
+
+    ^ (benchmarkInstanceClass class:self selector:benchmark) spy
 
     "Created: / 11-05-2015 / 16:31:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-05-2015 / 19:19:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCBenchmark methodsFor:'benchmark support'!
@@ -369,6 +377,26 @@
     input do: [ :source | parser parse: source withContext: context ]
 !
 
+benchmarkSmalltalkNoopParserCompiledC
+    <setup: #setupSmalltalkNoopParserCompiled>
+    <teardown: #teardownSmalltalkNoopParserCompiled>
+    <benchmark: 'Petit Smalltalk Parser (noop)- Compiled'>
+    
+    input do: [ :source | parser parse: source withContext: context ]
+
+    "Created: / 16-05-2015 / 09:45:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+benchmarkSmalltalkNoopParserTokenizedC
+    <setup: #setupSmalltalkNoopParserTokenized>
+    <teardown: #teardownSmalltalkNoopParserTokenized>
+    <benchmark: 'Petit Smalltalk Parser (noop) - Tokenized'>
+    
+    input do: [ :source | parser parse: source withContext: context ]
+
+    "Created: / 16-05-2015 / 09:46:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 benchmarkSmalltalkParserC
     <setup: #setupSmalltalkParser>
     <benchmark: 'Petit Smalltalk Parser - Standard'>
@@ -383,6 +411,16 @@
     
     input do: [ :source | parser parse: source withContext: context ]
     
+!
+
+benchmarkSmalltalkParserTokenizedC
+    <setup: #setupSmalltalkParserTokenized>
+    <teardown: #teardownSmalltalkParserTokenized>
+    <benchmark: 'Petit Smalltalk Parser - Tokenized'>
+    
+    input do: [ :source | parser parse: source withContext: context ]
+
+    "Created: / 16-05-2015 / 09:45:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCBenchmark methodsFor:'intitialization'!
@@ -542,6 +580,28 @@
     input := sources smalltalkSourcesBig.
 !
 
+setupSmalltalkNoopParserCompiled
+
+    configuration := PPCConfiguration universal.
+    parser := PPCSmalltalkNoopParser new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources smalltalkSourcesBig.
+
+    "Created: / 16-05-2015 / 09:44:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setupSmalltalkNoopParserTokenized
+
+    configuration := PPCConfiguration LL1.
+    parser := PPCSmalltalkNoopParser new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources smalltalkSourcesBig.
+
+    "Created: / 16-05-2015 / 09:44:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 setupSmalltalkParser
     
     parser := PPSmalltalkParser new.
@@ -601,6 +661,28 @@
     "Created: / 11-05-2015 / 16:33:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+teardownSmalltalkNoopParserCompiled
+    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'.
+"
+
+    "Created: / 16-05-2015 / 09:44:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+teardownSmalltalkNoopParserTokenized
+    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'.
+"
+
+    "Created: / 16-05-2015 / 09:44:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 teardownSmalltalkParserCompiled
     parser class removeFromSystem.
 "	
@@ -608,6 +690,17 @@
     Transcript crShow: 'Compiled Grammar time: ', time asString.
     Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
 "
+!
+
+teardownSmalltalkParserTokenized
+    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'.
+"
+
+    "Created: / 16-05-2015 / 09:47:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCBenchmark class methodsFor:'documentation'!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/benchmarks/PPCSmalltalkNoopParser.st	Sat May 16 19:21:00 2015 +0100
@@ -0,0 +1,346 @@
+"{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPSmalltalkGrammar subclass:#PPCSmalltalkNoopParser
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Benchmarks-Parsers'
+!
+
+!PPCSmalltalkNoopParser methodsFor:'accessing'!
+
+startExpression
+	"Make the sequence node has a method node as its parent and that the source is set."
+
+	^ ([ :stream | stream collection ] asParser and , super startExpression) map: [ :source :node | 
+		(RBMethodNode selector: #doIt body: node)
+			source: source.
+		(node statements size = 1 and: [ node temporaries isEmpty ])
+			ifTrue: [ node statements first ]
+			ifFalse: [ node ] ]
+!
+
+startMethod
+        "Make sure the method node has the source code properly set."
+        
+        ^ ([ :stream | stream collection ] asParser and , super startMethod)
+                map: [ :source :node | ]
+
+    "Modified: / 16-05-2015 / 09:47:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPCSmalltalkNoopParser methodsFor:'grammar'!
+
+array
+        ^ super array map: [ :openNode :statementNodes :closeNode | ]
+
+    "Modified: / 15-05-2015 / 08:54:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+expression
+        ^ super expression map: [ :variableNodes :expressionNodes |  ]
+
+    "Modified: / 15-05-2015 / 08:55:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+method
+        ^ super method map: [ :methodNode :bodyNode | ]
+
+    "Modified (format): / 15-05-2015 / 08:55:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+methodDeclaration
+        ^ super methodDeclaration ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:55:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+methodSequence
+        ^ super methodSequence map: [ :periodNodes1 :pragmaNodes1 :periodNodes2 :tempNodes :periodNodes3 :pragmaNodes2 :periodNodes4 :statementNodes | ]
+
+    "Modified: / 15-05-2015 / 08:55:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+parens
+        ^ super parens map: [ :openToken :expressionNode :closeToken |  ]
+
+    "Modified: / 15-05-2015 / 08:55:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+pragma
+        ^ super pragma ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:55:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+return
+        ^ super return map: [ :token :expressionNode |  ]
+
+    "Modified: / 15-05-2015 / 08:55:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+sequence
+        ^ super sequence map: [ :tempNodes :periodNodes :statementNodes |  ]
+
+    "Modified: / 15-05-2015 / 08:56:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+variable
+        ^ super variable ==> [ :token |  ]
+
+    "Modified: / 15-05-2015 / 08:56:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPCSmalltalkNoopParser methodsFor:'grammar-blocks'!
+
+block
+        ^ super block map: [ :leftToken :blockNode :rightToken | ]
+
+    "Modified: / 15-05-2015 / 08:56:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+blockArgument
+	^ super blockArgument ==> #second
+!
+
+blockBody
+        ^ super blockBody
+                ==> [ :nodes |  ]
+
+    "Modified: / 15-05-2015 / 08:56:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPCSmalltalkNoopParser methodsFor:'grammar-literals'!
+
+arrayLiteral
+        ^ super arrayLiteral ==> [ :nodes | nodes ]
+
+    "Modified (format): / 15-05-2015 / 08:56:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+arrayLiteralArray
+        ^ super arrayLiteralArray ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:56:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+byteLiteral
+        ^ super byteLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:56:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+byteLiteralArray
+        ^ super byteLiteralArray ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:56:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+charLiteral
+        ^ super charLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+falseLiteral
+        ^ super falseLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nilLiteral
+        ^ super nilLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+numberLiteral
+    ^ super numberLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+stringLiteral
+        ^ super stringLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+symbolLiteral
+        ^ super symbolLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+symbolLiteralArray
+        ^ super symbolLiteralArray ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+trueLiteral
+        ^ super trueLiteral ==> [ :nodes | nodes ]
+
+    "Modified: / 15-05-2015 / 08:57:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPCSmalltalkNoopParser methodsFor:'grammar-messages'!
+
+binaryExpression
+        ^ super binaryExpression map: [ :receiverNode :messageNodes |  ]
+
+    "Modified: / 15-05-2015 / 08:57:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+cascadeExpression
+        ^ super cascadeExpression map: [ :receiverNode :messageNodes | ]
+
+    "Modified: / 15-05-2015 / 08:57:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+keywordExpression
+        ^ super keywordExpression map: [ :receiveNode :messageNode | ]
+
+    "Modified: / 15-05-2015 / 08:58:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+unaryExpression
+        ^ super unaryExpression map: [ :receiverNode :messageNodes | ]
+
+    "Modified: / 15-05-2015 / 08:58:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPCSmalltalkNoopParser methodsFor:'private'!
+
+addStatements: aCollection into: aNode
+	aCollection isNil 
+		ifTrue: [ ^ aNode ].
+	aCollection do: [ :each |
+		each class == PPSmalltalkToken
+			ifFalse: [ aNode addNode:  each ]
+			ifTrue: [
+				aNode statements isEmpty
+					ifTrue: [ aNode addComments: each comments ]
+					ifFalse: [ aNode statements last addComments: each comments ].
+				aNode periods: (aNode periods asOrderedCollection
+					addLast: each start;
+					yourself) ] ].
+	^ aNode
+!
+
+build: aNode assignment: anArray
+	^ anArray isEmpty
+		ifTrue: [ aNode ]
+		ifFalse: [
+			anArray reverse 
+				inject: aNode
+				into: [ :result :each |
+					RBAssignmentNode 
+						variable: each first
+						value: result
+						position: each second start ] ]
+!
+
+build: aNode cascade: anArray 
+	| messages semicolons |
+	^ (anArray isNil or: [ anArray isEmpty ]) 
+		ifTrue: [ aNode ]
+		ifFalse: [
+			messages := OrderedCollection new: anArray size + 1.
+			messages addLast: aNode.
+			semicolons := OrderedCollection new.
+			anArray do: [ :each | 
+				messages addLast: (self 
+					build: aNode receiver
+					messages: (Array with: each second)).
+				semicolons addLast: each first start ].
+			RBCascadeNode messages: messages semicolons: semicolons ]
+!
+
+build: aNode messages: anArray 
+	^ (anArray isNil or: [ anArray isEmpty ]) 
+		ifTrue: [ aNode ]
+		ifFalse: [
+			anArray 
+				inject: aNode
+				into: [ :rec :msg | 
+					msg isNil 
+						ifTrue: [ rec ]
+						ifFalse: [
+							RBMessageNode 
+								receiver: rec
+								selectorParts: msg first
+								arguments: msg second ] ] ]
+!
+
+build: aTempCollection sequence: aStatementCollection
+	| result |
+	result := self
+		addStatements: aStatementCollection
+		into: RBSequenceNode new.
+	aTempCollection isEmpty ifFalse: [
+		result
+			leftBar: aTempCollection first start
+			temporaries: aTempCollection second
+			rightBar: aTempCollection last start ].
+	^ result
+!
+
+buildArray: aStatementCollection
+	^ self addStatements: aStatementCollection into: RBArrayNode new
+!
+
+buildMethod: aMethodNode
+	aMethodNode selectorParts 
+		do: [ :each | aMethodNode addComments: each comments ].
+	aMethodNode arguments
+		do: [ :each | aMethodNode addComments: each token comments ].
+	aMethodNode pragmas do: [ :pragma |
+		aMethodNode addComments: pragma comments.
+		pragma selectorParts 
+			do: [ :each | aMethodNode addComments: each comments ].
+		pragma arguments do: [ :each | 
+			each isLiteralArray
+				ifFalse: [ aMethodNode addComments: each token comments ] ].
+		pragma comments: nil ].
+	^ aMethodNode
+!
+
+buildString: aString 
+	(aString isEmpty or: [ aString first ~= $' or: [ aString last ~= $' ] ])
+		ifTrue: [ ^ aString ].
+	^ (aString 
+		copyFrom: 2
+		to: aString size - 1) 
+		copyReplaceAll: ''''''
+		with: ''''
+! !
+
+!PPCSmalltalkNoopParser methodsFor:'token'!
+
+binaryToken
+        ^ super binaryToken ==> [ :token | token ]
+
+    "Modified: / 15-05-2015 / 08:54:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+identifierToken
+        ^ super identifierToken ==> [ :token | token ]
+
+    "Modified: / 15-05-2015 / 08:54:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+keywordToken
+        ^ super keywordToken ==> [ :token | token ]
+
+    "Modified: / 15-05-2015 / 08:54:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+unaryToken
+        ^ super unaryToken ==> [ :token | token ]
+
+    "Modified: / 15-05-2015 / 08:54:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/benchmarks/PPCSmalltalkNoopParserTests.st	Sat May 16 19:21:00 2015 +0100
@@ -0,0 +1,19 @@
+"{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPSmalltalkGrammarTests subclass:#PPCSmalltalkNoopParserTests
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Benchmarks-Parsers-Tests'
+!
+
+!PPCSmalltalkNoopParserTests methodsFor:'accessing'!
+
+parserClass
+        ^ PPCSmalltalkNoopParser
+
+    "Created: / 15-05-2015 / 09:00:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/compiler/benchmarks/abbrev.stc	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/abbrev.stc	Sat May 16 19:21:00 2015 +0100
@@ -2,4 +2,6 @@
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
 PPCBenchmark PPCBenchmark stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Core' 0
+PPCSmalltalkNoopParser PPCSmalltalkNoopParser stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Parsers' 0
+PPCSmalltalkNoopParserTests PPCSmalltalkNoopParserTests stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Parsers-Tests' 1
 stx_goodies_petitparser_compiler_benchmarks stx_goodies_petitparser_compiler_benchmarks stx:goodies/petitparser/compiler/benchmarks '* Projects & Packages *' 3
--- a/compiler/benchmarks/bc.mak	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/bc.mak	Sat May 16 19:21:00 2015 +0100
@@ -35,7 +35,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\petitparser -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\java -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\libbasic
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\petitparser -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\java -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk\tests -I$(INCLUDE_TOP)\stx\goodies\petitparser\tests -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
@@ -52,6 +52,16 @@
 # build all mandatory prerequisite packages (containing superclasses) for this package
 prereq:
 	pushd ..\..\..\..\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\refactoryBrowser\parser & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\..\libbasic2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\..\libbasic3 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\..\libview & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\.. & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\..\libview2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\parsers\smalltalk & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\sunit & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\tests & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\parsers\smalltalk\tests & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 
 
 
@@ -69,6 +79,7 @@
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)PPCBenchmark.$(O) PPCBenchmark.$(H): PPCBenchmark.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSmalltalkNoopParser.$(O) PPCSmalltalkNoopParser.$(H): PPCSmalltalkNoopParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPCompositeParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk\PPSmalltalkGrammar.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)stx_goodies_petitparser_compiler_benchmarks.$(O) stx_goodies_petitparser_compiler_benchmarks.$(H): stx_goodies_petitparser_compiler_benchmarks.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/compiler/benchmarks/libInit.cc	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/libInit.cc	Sat May 16 19:21:00 2015 +0100
@@ -28,6 +28,7 @@
 OBJ snd; struct __vmData__ *__pRT__; {
 __BEGIN_PACKAGE2__("libstx_goodies_petitparser_compiler_benchmarks", _libstx_goodies_petitparser_compiler_benchmarks_Init, "stx:goodies/petitparser/compiler/benchmarks");
 _PPCBenchmark_Init(pass,__pRT__,snd);
+_PPCSmalltalkNoopParser_Init(pass,__pRT__,snd);
 _stx_137goodies_137petitparser_137compiler_137benchmarks_Init(pass,__pRT__,snd);
 
 
--- a/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Tue May 12 01:57:37 2015 +0100
+++ b/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Sat May 16 19:21:00 2015 +0100
@@ -44,7 +44,10 @@
      my classes is considered to be a prerequisite package."
 
     ^ #(
+
     )
+
+    "Modified: / 16-05-2015 / 19:19:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 mandatoryPreRequisites
@@ -56,6 +59,11 @@
      by searching along the inheritance chain of all of my classes."
 
     ^ #(
+        #'stx:goodies/petitparser'    "PPCompositeParser - superclass of PPCSmalltalkNoopParser"
+        #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - superclass of PPCSmalltalkNoopParser"
+        #'stx:goodies/petitparser/parsers/smalltalk/tests'    "PPSmalltalkGrammarTests - superclass of PPCSmalltalkNoopParserTests"
+        #'stx:goodies/petitparser/tests'    "PPAbstractParserTest - superclass of PPCSmalltalkNoopParserTests"
+        #'stx:goodies/sunit'    "TestAsserter - superclass of PPCSmalltalkNoopParserTests"
         #'stx:libbasic'    "LibraryDefinition - superclass of stx_goodies_petitparser_compiler_benchmarks"
     )
 !
@@ -71,13 +79,11 @@
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:goodies/petitparser'    "PPContext - referenced by PPCBenchmark>>benchmarkSmalltalkParser"
         #'stx:goodies/petitparser/compiler'    "PPCConfiguration - referenced by PPCBenchmark>>benchmarkSmalltalkParserCompiled"
         #'stx:goodies/petitparser/compiler/tests'    "PPExpressionGrammar - referenced by PPCBenchmark>>setupExpressionGrammar"
         #'stx:goodies/petitparser/compiler/tests/extras'    "PPCResources - referenced by PPCBenchmark>>initialize"
         #'stx:goodies/petitparser/parsers/java'    "PPJavaSyntax - referenced by PPCBenchmark>>benchmarkJavaSyntax"
-        #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCBenchmark>>setupSmalltalkGrammar"
-        #'stx:goodies/refactoryBrowser/parser'    "RBParser - referenced by PPCBenchmark>>benchmarkRBParserC"
+        #'stx:goodies/refactoryBrowser/parser'    "RBArrayNode - referenced by PPCSmalltalkNoopParser>>buildArray:"
     )
 !
 
@@ -102,6 +108,8 @@
     ^ #(
         "<className> or (<className> attributes...) in load order"
         PPCBenchmark
+        PPCSmalltalkNoopParser
+        (PPCSmalltalkNoopParserTests autoload)
         #'stx_goodies_petitparser_compiler_benchmarks'
     )
 !