Merge
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 21 May 2015 14:35:34 +0100
changeset 465 f729f6cd3c76
parent 463 d4014e0a47a0 (diff)
parent 464 f6d77fee9811 (current diff)
child 466 ac2d987a03d3
Merge
compiler/PPCAbstractCharacterNode.st
compiler/PPCCodeGenerator.st
compiler/PPCCompiler.st
compiler/PPCInliningVisitor.st
compiler/PPCLL1Configuration.st
compiler/PPCMethod.st
compiler/PPCTokenCodeGenerator.st
compiler/PPCTokenizingCodeGenerator.st
compiler/benchmarks/Make.proto
compiler/benchmarks/PPCBenchmark.st
compiler/benchmarks/bc.mak
compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st
compiler/tests/PPCLL1OptimizingTest.st
compiler/tests/PPCLL1Test.st
compiler/tests/PPCNodeTest.st
compiler/tests/PPCPrototype1OptimizingTest.st
compiler/tests/PPCPrototype1Test.st
compiler/tests/PPCompiledExpressionGrammarResource.st
compiler/tests/PPCompiledExpressionGrammarTest.st
compiler/tests/PPExpressionGrammar.st
compiler/tests/PPExpressionGrammarTest.st
compiler/tests/PPLL1ExpressionGrammar.st
compiler/tests/PPLL1ExpressionGrammarTest.st
compiler/tests/PPTokenizedExpressionGrammarResource.st
compiler/tests/PPTokenizedExpressionGrammarTest.st
compiler/tests/PPTokenizedLL1ExpressionGrammarResource.st
compiler/tests/PPTokenizedLL1ExpressionGrammarTest.st
compiler/tests/extras/Make.proto
compiler/tests/extras/Make.spec
compiler/tests/extras/PPCResources.st
compiler/tests/extras/PPCSmalltalkTests.st
compiler/tests/extras/PPTokenizedSmalltalkGrammarResource.st
compiler/tests/extras/abbrev.stc
compiler/tests/extras/bc.mak
compiler/tests/extras/libInit.cc
compiler/tests/extras/stx_goodies_petitparser_compiler_tests_extras.st
--- a/Make.proto	Thu May 21 14:12:22 2015 +0100
+++ b/Make.proto	Thu May 21 14:35:34 2015 +0100
@@ -21,7 +21,7 @@
 INCLUDE_TOP=$(TOP)/..
 
 # subdirectories where targets are to be made:
-SUBDIRS= analyzer tests
+SUBDIRS= analyzer tests parsers/smalltalk parsers/java compiler
 
 
 # subdirectories where Makefiles are to be made:
@@ -74,7 +74,7 @@
 		Class tryLocalSourceFirst: true.				\
 		Smalltalk packagePath add:'$(TOP)/..' .                       \
 		Smalltalk loadPackage:'stx:goodies/petitparser'.              \
-		(Smalltalk at: #'stx_goodies_petitparser') exportAsMczTo: 'mc'."
+		(Smalltalk at: #'stx_goodies_petitparser') monticelloExportTo: 'mc'."
 
 
 
--- a/bmake.bat	Thu May 21 14:12:22 2015 +0100
+++ b/bmake.bat	Thu May 21 14:35:34 2015 +0100
@@ -23,4 +23,25 @@
 @call bmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/smalltalk
+@echo "***********************************"
+@pushd parsers\smalltalk
+@call bmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/java
+@echo "***********************************"
+@pushd parsers\java
+@call bmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call bmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+
--- a/compiler/PPCCodeGenerator.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCCodeGenerator.st	Thu May 21 14:35:34 2015 +0100
@@ -216,7 +216,7 @@
     compiler codeReturn: 'failure'.
     compiler add: '].'.
 
-    "Modified: / 23-04-2015 / 15:59:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 05-05-2015 / 14:39:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitAndNode: node
@@ -318,7 +318,7 @@
     ].
     compiler codeError: 'no choice suitable'.
 
-    "Modified: / 23-04-2015 / 21:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 05-05-2015 / 14:10:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitEndOfFileNode: node
--- a/compiler/PPCCompiler.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCCompiler.st	Thu May 21 14:35:34 2015 +0100
@@ -71,12 +71,12 @@
 !PPCCompiler methodsFor:'cleaning'!
 
 clean: class
-"	Transcript crShow: 'Cleaning time: ',
+"	Transcript show: ('Cleaning time: ',
     [	
 "		self cleanGeneratedMethods: class.
         self cleanInstVars: class.
         self cleanConstants: class.
-"	] timeToRun asMilliSeconds asString, 'ms'."
+"	] timeToRun asMilliSeconds asString, 'ms'); cr. "
 !
 
 cleanConstants: class
--- a/compiler/PPCInliningVisitor.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCInliningVisitor.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Visitors'
 !
 
+
 !PPCInliningVisitor methodsFor:'initialization'!
 
 initialize
@@ -37,6 +38,13 @@
     ^ node
 !
 
+visitActionNode: node
+    node child markForInline.
+    ^ super visitActionNode: node.
+
+    "Created: / 13-05-2015 / 16:25:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 visitCharSetPredicateNode: node
     ^ self markForInline: node
 !
@@ -117,3 +125,10 @@
     ^ node
 ! !
 
+!PPCInliningVisitor class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCSequenceNode.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCSequenceNode.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Nodes'
 !
 
+
 !PPCSequenceNode methodsFor:'accessing'!
 
 prefix
@@ -127,3 +128,10 @@
     ^ visitor visitSequenceNode: self
 ! !
 
+!PPCSequenceNode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCTokenCodeGenerator.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCTokenCodeGenerator.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Visitors'
 !
 
+
 !PPCTokenCodeGenerator methodsFor:'as yet unclassified'!
 
 afterAccept: node retval: retval
@@ -166,3 +167,10 @@
     self fromTokenMode.
 ! !
 
+!PPCTokenCodeGenerator class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCTokenizingCodeGenerator.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCTokenizingCodeGenerator.st	Thu May 21 14:35:34 2015 +0100
@@ -17,11 +17,11 @@
 !
 
 tokenGenerator
-    ^ tokenGenerator isNil 
-        ifTrue: [ tokenGenerator := (PPCTokenCodeGenerator on: compiler)
-            arguments: arguments;
-            yourself ]
-        ifFalse: [ tokenGenerator ]
+    tokenGenerator isNil ifTrue: [ 
+        tokenGenerator := PPCTokenCodeGenerator on: compiler.
+        tokenGenerator arguments: arguments.
+    ].
+    ^ tokenGenerator
 !
 
 tokenGenerator: whatever
--- a/compiler/PPCTokenizingVisitor.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCTokenizingVisitor.st	Thu May 21 14:35:34 2015 +0100
@@ -18,17 +18,17 @@
         tokens addLast: self eofToken.
         tokens do: [ :token | token unmarkForInline  ].
         
-        whitespaceNode := tokens detect: [ :e | e isTrimmingTokenNode ] ifFound: [:token | 
-                token whitespace copy
-                    unmarkForInline;
-                    name: 'consumeWhitespace';
-                    yourself 
-            ] ifNone: [
-         		PPCNilNode new
-                    name: 'consumeWhitespace';
-                    yourself
-            ].
-        
+        whitespaceNode := tokens detect: [ :e | e isTrimmingTokenNode ] ifNone:[nil]. 
+        whitespaceNode notNil ifTrue:[
+            whitespaceNode := whitespaceNode whitespace copy
+                                unmarkForInline;
+                                name: 'consumeWhitespace';
+                                yourself 
+        ] ifFalse:[
+            whitespaceNode := (PPCNilNode new)
+                                name: 'consumeWhitespace';
+                                yourself
+        ].        
         tokenizerNode := PPCTokenChoiceNode new
             children: tokens asArray;
             name: 'nextToken';
@@ -42,7 +42,8 @@
             yourself
     ].
     ^ parserNode
-    
+
+    "Modified: / 12-05-2015 / 01:37:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 eofToken
--- a/compiler/benchmarks/Make.proto	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/Make.proto	Thu May 21 14:35:34 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/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	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/Make.spec	Thu May 21 14:35:34 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	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/PPCBenchmark.st	Thu May 21 14:35:34 2015 +0100
@@ -47,6 +47,20 @@
     "
     PPCBenchmark run: #benchmarkRBParserC
     "
+!
+
+spy: benchmark
+    | 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'!
@@ -370,6 +384,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'>
@@ -384,6 +418,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'!
@@ -565,6 +609,28 @@
     ]
 !
 
+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.
@@ -615,6 +681,35 @@
 
 teardownSmalltalkGrammarTokenized
     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: / 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
@@ -624,6 +719,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	Thu May 21 14:35:34 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	Thu May 21 14:35:34 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	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/abbrev.stc	Thu May 21 14:35:34 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	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/bc.mak	Thu May 21 14:35:34 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\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	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/libInit.cc	Thu May 21 14:35:34 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	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Thu May 21 14:35:34 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,12 +79,10 @@
      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/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:"
     )
 !
 
@@ -101,6 +107,8 @@
     ^ #(
         "<className> or (<className> attributes...) in load order"
         PPCBenchmark
+        PPCSmalltalkNoopParser
+        (PPCSmalltalkNoopParserTests autoload)
         #'stx_goodies_petitparser_compiler_benchmarks'
     )
 !
--- a/compiler/tests/PPCInliningVisitorTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/PPCInliningVisitorTest.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Tests-Visitors'
 !
 
+
 !PPCInliningVisitorTest methodsFor:'as yet unclassified'!
 
 assert: object type: class
@@ -171,3 +172,10 @@
     self assert: result child child type: PPCNilNode.
 ! !
 
+!PPCInliningVisitorTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/PPCLL1VisitorTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/PPCLL1VisitorTest.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Tests-Visitors'
 !
 
+
 !PPCLL1VisitorTest methodsFor:'as yet unclassified'!
 
 setUp
@@ -139,3 +140,10 @@
     
 ! !
 
+!PPCLL1VisitorTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/Make.proto	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/Make.proto	Thu May 21 14:35:34 2015 +0100
@@ -129,9 +129,23 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)PPCCompiledJavaVerificationTest.$(O) PPCCompiledJavaVerificationTest.$(H): PPCCompiledJavaVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCExpressionsVerificationTest.$(O) PPCExpressionsVerificationTest.$(H): PPCExpressionsVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPExpressionGrammar.$(O) PPExpressionGrammar.$(H): PPExpressionGrammar.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/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPLL1ExpressionGrammar.$(O) PPLL1ExpressionGrammar.$(H): PPLL1ExpressionGrammar.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/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCResources.$(O) PPCResources.$(H): PPCResources.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestResource.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSmalltalkTests.$(O) PPCSmalltalkTests.$(H): PPCSmalltalkTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSmalltalkVerificationTest.$(O) PPCSmalltalkVerificationTest.$(H): PPCSmalltalkVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledJavaResource.$(O) PPCompiledJavaResource.$(H): PPCompiledJavaResource.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestResource.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledSmalltalkGrammarResource.$(O) PPCompiledSmalltalkGrammarResource.$(H): PPCompiledSmalltalkGrammarResource.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestResource.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledSmalltalkGrammarTests.$(O) PPCompiledSmalltalkGrammarTests.$(H): PPCompiledSmalltalkGrammarTests.st $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPCompositeParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedSmalltalkGrammarResource.$(O) PPTokenizedSmalltalkGrammarResource.$(H): PPTokenizedSmalltalkGrammarResource.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestResource.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedSmalltalkGrammarTests.$(O) PPTokenizedSmalltalkGrammarTests.$(H): PPTokenizedSmalltalkGrammarTests.st $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPCompositeParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)stx_goodies_petitparser_compiler_tests_extras.$(O) stx_goodies_petitparser_compiler_tests_extras.$(H): stx_goodies_petitparser_compiler_tests_extras.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledExpressionsVerificationTest.$(O) PPCompiledExpressionsVerificationTest.$(H): PPCompiledExpressionsVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras/PPCExpressionsVerificationTest.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledSmalltalkVerificationTest.$(O) PPCompiledSmalltalkVerificationTest.$(H): PPCompiledSmalltalkVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras/PPCSmalltalkVerificationTest.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedExpressionsVerificationTest.$(O) PPTokenizedExpressionsVerificationTest.$(H): PPTokenizedExpressionsVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras/PPCExpressionsVerificationTest.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedSmalltalkVerificationTest.$(O) PPTokenizedSmalltalkVerificationTest.$(H): PPTokenizedSmalltalkVerificationTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras/PPCSmalltalkVerificationTest.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPAbstractParserTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/compiler/tests/extras/Make.spec	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/Make.spec	Thu May 21 14:35:34 2015 +0100
@@ -51,17 +51,45 @@
 STCWARNINGS=-warnNonStandard
 
 COMMON_CLASSES= \
+	PPCCompiledJavaVerificationTest \
+	PPCExpressionsVerificationTest \
 	PPExpressionGrammar \
 	PPLL1ExpressionGrammar \
+	PPCResources \
+	PPCSmalltalkTests \
+	PPCSmalltalkVerificationTest \
+	PPCompiledJavaResource \
+	PPCompiledSmalltalkGrammarResource \
+	PPCompiledSmalltalkGrammarTests \
+	PPTokenizedSmalltalkGrammarResource \
+	PPTokenizedSmalltalkGrammarTests \
 	stx_goodies_petitparser_compiler_tests_extras \
+	PPCompiledExpressionsVerificationTest \
+	PPCompiledSmalltalkVerificationTest \
+	PPTokenizedExpressionsVerificationTest \
+	PPTokenizedSmalltalkVerificationTest \
 
 
 
 
 COMMON_OBJS= \
+    $(OUTDIR_SLASH)PPCCompiledJavaVerificationTest.$(O) \
+    $(OUTDIR_SLASH)PPCExpressionsVerificationTest.$(O) \
     $(OUTDIR_SLASH)PPExpressionGrammar.$(O) \
     $(OUTDIR_SLASH)PPLL1ExpressionGrammar.$(O) \
+    $(OUTDIR_SLASH)PPCResources.$(O) \
+    $(OUTDIR_SLASH)PPCSmalltalkTests.$(O) \
+    $(OUTDIR_SLASH)PPCSmalltalkVerificationTest.$(O) \
+    $(OUTDIR_SLASH)PPCompiledJavaResource.$(O) \
+    $(OUTDIR_SLASH)PPCompiledSmalltalkGrammarResource.$(O) \
+    $(OUTDIR_SLASH)PPCompiledSmalltalkGrammarTests.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedSmalltalkGrammarResource.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedSmalltalkGrammarTests.$(O) \
     $(OUTDIR_SLASH)stx_goodies_petitparser_compiler_tests_extras.$(O) \
+    $(OUTDIR_SLASH)PPCompiledExpressionsVerificationTest.$(O) \
+    $(OUTDIR_SLASH)PPCompiledSmalltalkVerificationTest.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedExpressionsVerificationTest.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedSmalltalkVerificationTest.$(O) \
 
 
 
--- a/compiler/tests/extras/PPCResources.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/PPCResources.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Extras-Tests-Support'
 !
 
+
 !PPCResources methodsFor:'expressions'!
 
 expressionOfSize: size
@@ -53,27 +54,29 @@
         2000 timesRepeat: [ 
             sources add: (self expressionOfSize: 200).
         ].
-        sources	
+        sources 
     ].
 
     ^ cache at: #expressionSourcesBig
-    
+
+    "Modified: / 12-05-2015 / 01:44:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 expressionSourcesMedium
     | sources |
-    
+
     cache at: #expressionSourcesMedium ifAbsentPut: [ 
         sources := OrderedCollection new.
-        
+
         1000 timesRepeat: [ 
             sources add: (self expressionOfSize: 100).
         ].
-        sources	
+        sources 
     ].
 
     ^ cache at: #expressionSourcesMedium
-    
+
+    "Created: / 12-05-2015 / 01:45:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCResources methodsFor:'initialization'!
@@ -90,7 +93,9 @@
     files := self readDirectory: directory.
     files := self files: files withExtension: 'java'.
     
-    ^ files collect: [ :f | (FileStream fileNamed: f) contents ]
+    ^ files collect: [ :f | (FileStream fileNamed: f) contents asString ]
+
+    "Modified: / 12-05-2015 / 01:50:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 javaLangMath
@@ -127,7 +132,14 @@
 !PPCResources methodsFor:'private utilities'!
 
 files: files withExtension: extension
-    ^ files select: [ :f | f extension = extension ] 
+     ( (Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ] ) ifTrue:[ 
+        ^ files select: [ :f | f suffix = extension ] 
+    ] ifFalse:[ 
+        "Assuming Pharo..."   
+        ^ files select: [ :f | f extension = extension ] 
+    ]
+
+    "Modified: / 11-05-2015 / 16:37:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 readDirectory: directory
@@ -164,7 +176,9 @@
     files := self readDirectory: directory.
     files := self files: files withExtension: 'st'.
     
-    ^ files collect: [ :f | (FileStream fileNamed: f) contents ]
+    ^ files collect: [ :f | (FileStream fileNamed: f) contents asString ]
+
+    "Modified: / 11-05-2015 / 16:38:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 smalltalkObjectMethods
@@ -180,3 +194,10 @@
     ^ (self smalltalkInDirectory: '../smalltalk-src/') copyFrom: 1 to: 1000.
 ! !
 
+!PPCResources class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/PPCompiledExpressionsVerificationTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/PPCompiledExpressionsVerificationTest.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Extras-Tests-Expressions'
 !
 
+
 !PPCompiledExpressionsVerificationTest class methodsFor:'as yet unclassified'!
 
 resources
@@ -33,3 +34,10 @@
     ^ super testSanity
 ! !
 
+!PPCompiledExpressionsVerificationTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/PPCompiledJavaSyntaxTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/PPCompiledJavaSyntaxTest.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Extras-Tests-Java'
 !
 
+
 !PPCompiledJavaSyntaxTest class methodsFor:'as yet unclassified'!
 
 resources
@@ -571,3 +572,10 @@
             rule: #methodDeclaration
 ! !
 
+!PPCompiledJavaSyntaxTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/PPCompiledSmalltalkVerificationTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/PPCompiledSmalltalkVerificationTest.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Extras-Tests-Smalltalk'
 !
 
+
 !PPCompiledSmalltalkVerificationTest class methodsFor:'as yet unclassified'!
 
 resources
@@ -37,3 +38,10 @@
     super testSmalltalkObject
 ! !
 
+!PPCompiledSmalltalkVerificationTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/abbrev.stc	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/abbrev.stc	Thu May 21 14:35:34 2015 +0100
@@ -2,8 +2,8 @@
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
 PPCCompiledJavaVerificationTest PPCCompiledJavaVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Java' 1
+PPCResources PPCResources stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Support' 1
 PPCExpressionsVerificationTest PPCExpressionsVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
-PPCResources PPCResources stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Support' 1
 PPCSmalltalkTests PPCSmalltalkTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 PPCSmalltalkVerificationTest PPCSmalltalkVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 PPCompiledExpressionGrammarResource PPCompiledExpressionGrammarResource stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
@@ -23,7 +23,7 @@
 PPTokenizedSmalltalkGrammarResource PPTokenizedSmalltalkGrammarResource stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 PPTokenizedSmalltalkGrammarTests PPTokenizedSmalltalkGrammarTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 stx_goodies_petitparser_compiler_tests_extras stx_goodies_petitparser_compiler_tests_extras stx:goodies/petitparser/compiler/tests/extras '* Projects & Packages *' 3
+PPCompiledSmalltalkVerificationTest PPCompiledSmalltalkVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 PPCompiledExpressionsVerificationTest PPCompiledExpressionsVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
-PPCompiledSmalltalkVerificationTest PPCompiledSmalltalkVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
+PPTokenizedSmalltalkVerificationTest PPTokenizedSmalltalkVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 PPTokenizedExpressionsVerificationTest PPTokenizedExpressionsVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
-PPTokenizedSmalltalkVerificationTest PPTokenizedSmalltalkVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
--- a/compiler/tests/extras/bc.mak	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/bc.mak	Thu May 21 14:35:34 2015 +0100
@@ -76,9 +76,23 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)PPCCompiledJavaVerificationTest.$(O) PPCCompiledJavaVerificationTest.$(H): PPCCompiledJavaVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCExpressionsVerificationTest.$(O) PPCExpressionsVerificationTest.$(H): PPCExpressionsVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPExpressionGrammar.$(O) PPExpressionGrammar.$(H): PPExpressionGrammar.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\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPLL1ExpressionGrammar.$(O) PPLL1ExpressionGrammar.$(H): PPLL1ExpressionGrammar.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\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCResources.$(O) PPCResources.$(H): PPCResources.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestResource.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSmalltalkTests.$(O) PPCSmalltalkTests.$(H): PPCSmalltalkTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSmalltalkVerificationTest.$(O) PPCSmalltalkVerificationTest.$(H): PPCSmalltalkVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledJavaResource.$(O) PPCompiledJavaResource.$(H): PPCompiledJavaResource.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestResource.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledSmalltalkGrammarResource.$(O) PPCompiledSmalltalkGrammarResource.$(H): PPCompiledSmalltalkGrammarResource.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestResource.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledSmalltalkGrammarTests.$(O) PPCompiledSmalltalkGrammarTests.$(H): PPCompiledSmalltalkGrammarTests.st $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPCompositeParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedSmalltalkGrammarResource.$(O) PPTokenizedSmalltalkGrammarResource.$(H): PPTokenizedSmalltalkGrammarResource.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestResource.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedSmalltalkGrammarTests.$(O) PPTokenizedSmalltalkGrammarTests.$(H): PPTokenizedSmalltalkGrammarTests.st $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPCompositeParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)stx_goodies_petitparser_compiler_tests_extras.$(O) stx_goodies_petitparser_compiler_tests_extras.$(H): stx_goodies_petitparser_compiler_tests_extras.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledExpressionsVerificationTest.$(O) PPCompiledExpressionsVerificationTest.$(H): PPCompiledExpressionsVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras\PPCExpressionsVerificationTest.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCompiledSmalltalkVerificationTest.$(O) PPCompiledSmalltalkVerificationTest.$(H): PPCompiledSmalltalkVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras\PPCSmalltalkVerificationTest.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedExpressionsVerificationTest.$(O) PPTokenizedExpressionsVerificationTest.$(H): PPTokenizedExpressionsVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras\PPCExpressionsVerificationTest.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedSmalltalkVerificationTest.$(O) PPTokenizedSmalltalkVerificationTest.$(H): PPTokenizedSmalltalkVerificationTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras\PPCSmalltalkVerificationTest.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPAbstractParserTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/compiler/tests/extras/libInit.cc	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/libInit.cc	Thu May 21 14:35:34 2015 +0100
@@ -27,9 +27,23 @@
 void _libstx_goodies_petitparser_compiler_tests_extras_Init(pass, __pRT__, snd)
 OBJ snd; struct __vmData__ *__pRT__; {
 __BEGIN_PACKAGE2__("libstx_goodies_petitparser_compiler_tests_extras", _libstx_goodies_petitparser_compiler_tests_extras_Init, "stx:goodies/petitparser/compiler/tests/extras");
+_PPCCompiledJavaVerificationTest_Init(pass,__pRT__,snd);
+_PPCExpressionsVerificationTest_Init(pass,__pRT__,snd);
 _PPExpressionGrammar_Init(pass,__pRT__,snd);
 _PPLL1ExpressionGrammar_Init(pass,__pRT__,snd);
+_PPCResources_Init(pass,__pRT__,snd);
+_PPCSmalltalkTests_Init(pass,__pRT__,snd);
+_PPCSmalltalkVerificationTest_Init(pass,__pRT__,snd);
+_PPCompiledJavaResource_Init(pass,__pRT__,snd);
+_PPCompiledSmalltalkGrammarResource_Init(pass,__pRT__,snd);
+_PPCompiledSmalltalkGrammarTests_Init(pass,__pRT__,snd);
+_PPTokenizedSmalltalkGrammarResource_Init(pass,__pRT__,snd);
+_PPTokenizedSmalltalkGrammarTests_Init(pass,__pRT__,snd);
 _stx_137goodies_137petitparser_137compiler_137tests_137extras_Init(pass,__pRT__,snd);
+_PPCompiledExpressionsVerificationTest_Init(pass,__pRT__,snd);
+_PPCompiledSmalltalkVerificationTest_Init(pass,__pRT__,snd);
+_PPTokenizedExpressionsVerificationTest_Init(pass,__pRT__,snd);
+_PPTokenizedSmalltalkVerificationTest_Init(pass,__pRT__,snd);
 
 
 __END_PACKAGE__();
--- a/compiler/tests/extras/stx_goodies_petitparser_compiler_tests_extras.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/tests/extras/stx_goodies_petitparser_compiler_tests_extras.st	Thu May 21 14:35:34 2015 +0100
@@ -10,6 +10,32 @@
 !
 
 
+!stx_goodies_petitparser_compiler_tests_extras class methodsFor:'accessing'!
+
+additionalClassAttributesFor: aClass
+    "Answers additional set of class attributes for given class
+     Individual project definitions may override this method, but
+     overriding method should always merge its attributes with result
+     of 'super additionalClassAttributesFor: aClass'.
+
+     Here, we add #autoload attributes to all test cases and
+     test resources, as they are not neccessary for the package
+     and should not be compiled (because of unwanted dependency
+     on stx:goodies/sunit package)
+
+     But not make them autoloaded when the package is separate
+     test-package - by conventions such package should by named
+     #'module:package/subpackage/tests'
+    "
+    (TestCase notNil and:[aClass inheritsFrom: TestCase]) ifTrue:[^#()].
+    (TestResource notNil and:[aClass inheritsFrom: TestResource]) ifTrue:[^#()].
+
+
+    ^ super additionalClassAttributesFor: aClass
+
+    "Created: / 10-05-2015 / 14:17:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !stx_goodies_petitparser_compiler_tests_extras class methodsFor:'accessing - monticello'!
 
 monticelloLastMergedVersionInfo
@@ -76,7 +102,9 @@
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
+        #'stx:goodies/petitparser'    "PPFailure - referenced by PPCResources>>workingJavaInDirectory:"
         #'stx:goodies/petitparser/compiler'    "PPCArguments - referenced by PPCSmalltalkTests>>setUp"
+        #'stx:goodies/petitparser/compiler/tests'    "PPCompiledExpressionGrammarResource - referenced by PPCompiledExpressionsVerificationTest class>>resources"
         #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCSmalltalkVerificationTest>>smalltalkGrammar"
         #'stx:libbasic2'    "Random - referenced by PPCResources>>expressionOfSize:stream:"
     )
@@ -102,32 +130,22 @@
 
     ^ #(
         "<className> or (<className> attributes...) in load order"
-        (PPCCompiledJavaVerificationTest autoload)
-        (PPCExpressionsVerificationTest autoload)
-        (PPCResources autoload)
-        (PPCSmalltalkTests autoload)
-        (PPCSmalltalkVerificationTest autoload)
-        (PPCompiledExpressionGrammarResource autoload)
-        (PPCompiledExpressionGrammarTest autoload)
-        (PPCompiledJavaResource autoload)
+        PPCCompiledJavaVerificationTest
+        PPCResources
+        PPCExpressionsVerificationTest
+        PPCSmalltalkTests
+        PPCSmalltalkVerificationTest
+        PPCompiledJavaResource
         (PPCompiledJavaSyntaxTest autoload)
-        (PPCompiledSmalltalkGrammarResource autoload)
-        (PPCompiledSmalltalkGrammarTests autoload)
-        PPExpressionGrammar
-        (PPExpressionGrammarTest autoload)
-        PPLL1ExpressionGrammar
-        (PPLL1ExpressionGrammarTest autoload)
-        (PPTokenizedExpressionGrammarResource autoload)
-        (PPTokenizedExpressionGrammarTest autoload)
-        (PPTokenizedLL1ExpressionGrammarResource autoload)
-        (PPTokenizedLL1ExpressionGrammarTest autoload)
-        (PPTokenizedSmalltalkGrammarResource autoload)
-        (PPTokenizedSmalltalkGrammarTests autoload)
+        PPCompiledSmalltalkGrammarResource
+        PPCompiledSmalltalkGrammarTests
+        PPTokenizedSmalltalkGrammarResource
+        PPTokenizedSmalltalkGrammarTests
         #'stx_goodies_petitparser_compiler_tests_extras'
-        (PPCompiledExpressionsVerificationTest autoload)
-        (PPCompiledSmalltalkVerificationTest autoload)
-        (PPTokenizedExpressionsVerificationTest autoload)
-        (PPTokenizedSmalltalkVerificationTest autoload)
+        PPCompiledSmalltalkVerificationTest
+        PPCompiledExpressionsVerificationTest
+        PPTokenizedSmalltalkVerificationTest
+        PPTokenizedExpressionsVerificationTest
     )
 !
 
--- a/lccmake.bat	Thu May 21 14:12:22 2015 +0100
+++ b/lccmake.bat	Thu May 21 14:35:34 2015 +0100
@@ -19,4 +19,25 @@
 @call lccmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/smalltalk
+@echo "***********************************"
+@pushd parsers\smalltalk
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/java
+@echo "***********************************"
+@pushd parsers\java
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+
--- a/mingwmake.bat	Thu May 21 14:12:22 2015 +0100
+++ b/mingwmake.bat	Thu May 21 14:35:34 2015 +0100
@@ -27,4 +27,25 @@
 @call mingwmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/smalltalk
+@echo "***********************************"
+@pushd parsers\smalltalk
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/java
+@echo "***********************************"
+@pushd parsers\java
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+
--- a/parsers/java/Make.proto	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/Make.proto	Thu May 21 14:35:34 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/tests -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic2
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/petitparser -I$(INCLUDE_TOP)/stx/goodies/petitparser/tests -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
--- a/parsers/java/PJEndOfLineCommentsNode.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/PJEndOfLineCommentsNode.st	Thu May 21 14:35:34 2015 +0100
@@ -23,7 +23,7 @@
 !
 
 printOn: aStream
-	.^	aStream 
+	^	aStream 
 		nextPutAll: 'EndOfLineComment value ==> ';
 		nextPutAll: self comment.
  
--- a/parsers/java/PJPackageDeclarationNode.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/PJPackageDeclarationNode.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitJava-AST'
 !
 
+
 !PJPackageDeclarationNode methodsFor:'accessing'!
 
 nameNode
@@ -26,3 +27,10 @@
 	aVisitor visitPackageDeclarationNode: self
 ! !
 
+!PJPackageDeclarationNode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/parsers/java/PJSyntaxNode.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/PJSyntaxNode.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,3 @@
 	category:'PetitJava-AST'
 !
 
-PJSyntaxNode comment:''
-!
-
--- a/parsers/java/PPJavaLexicon.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/PPJavaLexicon.st	Thu May 21 14:35:34 2015 +0100
@@ -1,1 +1,547 @@
-"{ Package: 'stx:goodies/petitparser/parsers/java' }"

"{ NameSpace: Smalltalk }"

PPCompositeParser subclass:#PPJavaLexicon
	instanceVariableNames:'unicodeEscape rawInputCharacter unicodeMarker hexDigit
		lineTerminator unicodeInputCharacter inputElements sub
		inputElement whiteSpace comment javaToken keyword literal
		separator operator identifier traditionalComment endOfLineComment
		commentTail charactersInLine commentTailStar notStar
		notStarNotSlash inputCharacter booleanLiteral nullLiteral
		identifierChars javaLetter javaLetterOrDigit keywords
		floatingPointLiteral integerLiteral characterLiteral
		stringLiteral hexIntegerLiteral octalIntegerLiteral
		decimalIntegerLiteral decimalNumeral integerTypeSuffix hexNumeral
		octalNumeral nonZeroDigit digits hexDigits octalDigits octalDigit
		hexadecimalFloatingPointLiteral decimalFloatingPointLiteral
		exponentPart floatTypeSuffix exponentIndicator signedInteger sign
		hexSignificand binaryExponent binaryExponentIndicator
		escapeSequence singleCharacter stringCharacters stringCharacter
		octalEscape zeroToThree input operators separators trueToken
		falseToken nullToken'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitJava-Core'
!

PPJavaLexicon comment:'A parser with a definitions for some basic Java gramar parts

Grammar rules follow as closely as possible the specification found in "The Java Language Specification Third Edition"

URL = '
!


!PPJavaLexicon class methodsFor:'accessing'!

ignoredNames
	"Answer a collection of instance-variables that should not be automatically initialized with productions, but that are used internal to the composite parser."

	| newArray |	
	newArray := Array new: ((self namesToIgnore size) + (super ignoredNames size)).
	newArray
		replaceFrom: 1
		to: self namesToIgnore size
		with: self namesToIgnore.
	newArray
		replaceFrom: (self namesToIgnore size + 1)
		to: newArray size
		with: super ignoredNames.	
	^newArray
!

namesToIgnore

	^#('keywords' 'operators' 'separators')
! !

!PPJavaLexicon methodsFor:'accessing'!

start
	"Default start production."

	^ input end
! !

!PPJavaLexicon methodsFor:'grammar-comments'!

charactersInLine   

	^ inputCharacter plus
!

comment
	"traditional -> /*
	 endOfLine -> //"
	^ traditionalComment / endOfLineComment
!

commentTail

	^ 	('*' asParser , commentTailStar ) /
		(notStar , commentTail)
!

commentTailStar 

	^ ('/' asParser ) /
	  ('*' asParser , commentTailStar ) /
	  (notStarNotSlash , commentTail )
!

endOfLineComment 

	^ '//' asParser , charactersInLine optional
!

notStar

	^  ('*' asParser not , inputCharacter)/lineTerminator
!

notStarNotSlash  

	^ lineTerminator / ((PPPredicateObjectParser anyOf: '*/') not , inputCharacter )
!

traditionalComment

	^ '/*' asParser , commentTail
! !

!PPJavaLexicon methodsFor:'grammar-identifiers'!

identifier 

	^  self asToken: (((keyword not) , (booleanLiteral not) , (nullLiteral not) , identifierChars ))
!

identifierChars
	
	^ javaLetter plus , javaLetterOrDigit star
!

javaLetter

	^ (#letter asParser) / (PPPredicateObjectParser anyOf: '_$')
!

javaLetterOrDigit

	^ javaLetter / (#digit asParser)
! !

!PPJavaLexicon methodsFor:'grammar-input'!

input

	^ (inputElements optional) , (sub optional)
!

inputElement

	^ whiteSpace / comment / javaToken
!

inputElements

	^ inputElement plus
!

javaToken


	^ identifier / keyword / literal / separator / operator
!

sub

	^ (Character value: 26) asParser 
! !

!PPJavaLexicon methodsFor:'grammar-keywords'!

keyword

        | keywordParsers |
        
        keywordParsers := keywords keys asSortedCollection collect: [:eachKey | keywords at: eachKey ].
        ^ self asToken: ( (keywordParsers reduce: [ :a :b | a / b ]) )

    "Modified (format): / 21-04-2015 / 15:27:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPJavaLexicon methodsFor:'grammar-lineTerminators'!

inputCharacter 

	^(lineTerminator not) , unicodeInputCharacter ==> #second
!

lineTerminator

    self flag: 'Hack alert - should be fixed immediately in PJTraditionalCommentsNode>>comment:'.

        ^ (((Character codePoint: 10) asParser) ==> [ :lf | Array with: lf with: nil ])
          / (((Character codePoint: 13) asParser , ((Character codePoint: 10) asParser ) optional )) ==> [ :nodes | Array with: nodes first with: nil ]

    "Modified: / 21-04-2015 / 17:16:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPJavaLexicon methodsFor:'grammar-literals'!

literal
	"a literal must be a single token. Whitespaces are not allowed inside the literal"
	
	^ nullLiteral / booleanLiteral / floatingPointLiteral / integerLiteral / characterLiteral / stringLiteral
! !

!PPJavaLexicon methodsFor:'grammar-literals-boolean'!

booleanLiteral 

 ^ trueToken / falseToken
!

falseToken
	^ ('false' asParser , #word asParser not) javaToken
!

nullToken
	^ ('null' asParser , #word asParser not) javaToken
!

trueToken
	^ ('true' asParser , #word asParser not) javaToken
! !

!PPJavaLexicon methodsFor:'grammar-literals-character'!

characterLiteral 

 ^ ($' asParser , ( escapeSequence / singleCharacter ), $' asParser) javaToken
!

singleCharacter 	

	^( PPPredicateObjectParser anyOf: '''\') not , inputCharacter ==> #second
! !

!PPJavaLexicon methodsFor:'grammar-literals-escape'!

escapeSequence 

	^ ($\ asParser , (PPPredicateObjectParser anyOf: 'btnfr""''\' ) ) /
	   octalEscape 
!

octalEscape

	^ $\ asParser , ( (zeroToThree , octalDigit , octalDigit) / (octalDigit , octalDigit optional) )
!

zeroToThree

	^PPPredicateObjectParser anyOf: '0123'
! !

!PPJavaLexicon methodsFor:'grammar-literals-floating'!

binaryExponent

 ^ binaryExponentIndicator , signedInteger
!

binaryExponentIndicator

  ^ PPPredicateObjectParser anyOf: 'pP'
!

decimalFloatingPointLiteral

	|dot|
	dot := $. asParser.

 ^ ( ( (dot , digits) 
        / 
        (digits , dot , digits optional)) , 
			exponentPart optional , floatTypeSuffix optional ) 
  	/ 
  	(digits , 
		( (exponentPart , floatTypeSuffix optional) 
		  /
		  (exponentPart optional , floatTypeSuffix) ))
!

exponentIndicator

  ^ PPPredicateObjectParser anyOf: 'eE'
!

exponentPart

 ^ exponentIndicator , signedInteger
!

floatTypeSuffix

	^ PPPredicateObjectParser anyOf: 'fFdD'
!

floatingPointLiteral

  ^ (hexadecimalFloatingPointLiteral / decimalFloatingPointLiteral) javaToken
!

hexSignificand 
	|dot|
	dot := $. asParser.

 ^  (hexNumeral , dot optional) /
    ($0 asParser , (PPPredicateObjectParser anyOf: 'xX') , hexDigits optional , dot , hexDigits )
!

hexadecimalFloatingPointLiteral

 ^ hexSignificand , binaryExponent , floatTypeSuffix optional
!

sign

  ^PPPredicateObjectParser anyOf: '-+'
!

signedInteger

  ^ sign optional , digits
! !

!PPJavaLexicon methodsFor:'grammar-literals-integer'!

decimalIntegerLiteral

 ^ decimalNumeral , (integerTypeSuffix optional)
!

decimalNumeral 

	^($0 asParser) / (nonZeroDigit , digits optional) 
!

digits 
	"digit is already defined, no need to redefine it"
	^#digit asParser plus
!

hexDigits 

	^hexDigit plus
!

hexIntegerLiteral 

  ^ hexNumeral , (integerTypeSuffix optional)
!

hexNumeral 

	^$0 asParser, (PPPredicateObjectParser anyOf: 'xX' ), hexDigits
!

integerLiteral

  ^ (hexIntegerLiteral / octalIntegerLiteral / decimalIntegerLiteral) javaToken
!

integerTypeSuffix

	^ PPPredicateObjectParser anyOf: 'lL'
!

nonZeroDigit 

	^PPPredicateObjectParser anyOf: '123456789'.
!

octalDigit 

	^PPPredicateObjectParser anyOf: '01234567'
!

octalDigits

	^ octalDigit plus
!

octalIntegerLiteral 

 ^ octalNumeral , (integerTypeSuffix optional)
!

octalNumeral 

	^($0 asParser) , octalDigits
! !

!PPJavaLexicon methodsFor:'grammar-literals-null'!

nullLiteral 

 ^ nullToken
! !

!PPJavaLexicon methodsFor:'grammar-literals-string'!

stringCharacter
		
	^ ( ( PPPredicateObjectParser anyOf: '"\') not , inputCharacter ==> #second ) /
	   escapeSequence 
!

stringCharacters

	^ stringCharacter plus
!

stringLiteral 

 ^ ($" asParser , stringCharacters optional , $" asParser) javaToken
! !

!PPJavaLexicon methodsFor:'grammar-operators'!

operator
        | operatorParsers |
        
        operatorParsers := operators keys asSortedCollection collect: [:eachKey | operators at: eachKey ].                                                
        ^self asToken:  (operatorParsers reduce: [ :a :b | a / b ])

    "Modified: / 21-04-2015 / 15:26:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPJavaLexicon methodsFor:'grammar-separators'!

separator	
	^self asToken: (PPPredicateObjectParser anyOf: '(){}[];,.' )
! !

!PPJavaLexicon methodsFor:'grammar-unicode-escapes'!

hexDigit 

	^#hex asParser
!

rawInputCharacter

	^#any asParser
!

unicodeEscape

	^ $\ asParser , unicodeMarker , hexDigit , hexDigit , hexDigit , hexDigit
!

unicodeInputCharacter
	 ^ unicodeEscape / rawInputCharacter
!

unicodeMarker

	^$u asParser plus
! !

!PPJavaLexicon methodsFor:'grammar-whiteSpace'!

whiteSpace

	^ (Character space asParser ) /
	  (Character tab asParser ) /
	  ((Character value: 12) asParser ) /
		lineTerminator 
! !

!PPJavaLexicon methodsFor:'initialization'!

initialize

	super initialize.
	
	self initializeKeywords.
	self initializeOperators.
	self initializeSeparators.
!

initializeKeywords

	| values |
	keywords := Dictionary new.
	values := #('abstract' 'assert' 'boolean' 'break' 'byte' 'case'  'catch' 'char' 'class' 'const'
	   'continue' 'default' 'do' 'double' 'else' 'enum' 'extends' 'final'  'finally' 'float'
	   'for' 'if' 'goto' 'implements' 'import' 'instanceof' 'int' 'interface' 'long' 'native'
	   'new' 'package' 'private' 'protected' 'public' 'return' 'short' 'static' 'strictfp' 'super'
	   'switch' 'synchronized' 'this' 'throw' 'throws' 'transient' 'try' 'void' 'volatile' 'while').
	
	values do: [:eachKeyword |
		keywords at: eachKeyword 
			put: (PPUnresolvedParser named: ('keyword', eachKeyword first asUppercase asString , eachKeyword allButFirst))		
		].
	
	keywords keysAndValuesDo:  [:key :value |
		(keywords at: key) def: (key asParser ,  #word asParser not)]
!

initializeOperators

	| values |
	operators := Dictionary new.
	values := #(	'>>>=' '>>>' '>>=' '>>' '>=' '>'	'<<=' '<<' '<=' '<'	'++' '+=' '+'	'--' '-=' '-'	'&&' '&=' '&'
					'||' '|=' '|'	'*=' '*'	'%=' '%'	'/=' '/'	'^=' '^'	'!!=' '!!'	'==' '='	'~'	'?'	':'	'@' ).
	" @ ? perhaps for annotation but not in the doc "
	values do: [:eachOperator |
		operators at: eachOperator 
			put: (PPUnresolvedParser named: ('operator', eachOperator asString))		
		].
	
	operators  keysAndValuesDo:  [:key :value |
		(operators at: key) def: (key asParser)]
!

initializeSeparators

	| values |
	separators := Dictionary new.
	values := #( '(' ')' '{' '}' '[' ']' ';' ',' '.' ).
	
	values do: [:eachSeparator |
		separators at: eachSeparator 
			put: (PPUnresolvedParser named: ('separator', eachSeparator asString))		
		].
	
	separators  keysAndValuesDo:  [:key :value |
		(separators at: key) def: (key asParser)]
! !

!PPJavaLexicon methodsFor:'utility'!

asToken: aParser

	^aParser javaToken
!

emptySquaredParenthesis

	^ self asToken: (((self tokenFor: '['), (self tokenFor: ']')))
!

tokenFor: aString

	^self asToken: (keywords at: aString 
						ifAbsent: [separators at: aString 
							ifAbsent: [operators at: aString] ])
! !

!PPJavaLexicon class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !
\ No newline at end of file
+"{ Package: 'stx:goodies/petitparser/parsers/java' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCompositeParser subclass:#PPJavaLexicon
+	instanceVariableNames:'unicodeEscape rawInputCharacter unicodeMarker hexDigit
+		lineTerminator unicodeInputCharacter inputElements sub
+		inputElement whiteSpace comment javaToken keyword literal
+		separator operator identifier traditionalComment endOfLineComment
+		commentTail charactersInLine commentTailStar notStar
+		notStarNotSlash inputCharacter booleanLiteral nullLiteral
+		identifierChars javaLetter javaLetterOrDigit keywords
+		floatingPointLiteral integerLiteral characterLiteral
+		stringLiteral hexIntegerLiteral octalIntegerLiteral
+		decimalIntegerLiteral decimalNumeral integerTypeSuffix hexNumeral
+		octalNumeral nonZeroDigit digits hexDigits octalDigits octalDigit
+		hexadecimalFloatingPointLiteral decimalFloatingPointLiteral
+		exponentPart floatTypeSuffix exponentIndicator signedInteger sign
+		hexSignificand binaryExponent binaryExponentIndicator
+		escapeSequence singleCharacter stringCharacters stringCharacter
+		octalEscape zeroToThree input operators separators trueToken
+		falseToken nullToken'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitJava-Core'
+!
+
+PPJavaLexicon comment:'A parser with a definitions for some basic Java gramar parts

Grammar rules follow as closely as possible the specification found in "The Java Language Specification Third Edition"

URL = '
+!
+
+
+!PPJavaLexicon class methodsFor:'accessing'!
+
+ignoredNames
+	"Answer a collection of instance-variables that should not be automatically initialized with productions, but that are used internal to the composite parser."
+
+	| newArray |	
+	newArray := Array new: ((self namesToIgnore size) + (super ignoredNames size)).
+	newArray
+		replaceFrom: 1
+		to: self namesToIgnore size
+		with: self namesToIgnore.
+	newArray
+		replaceFrom: (self namesToIgnore size + 1)
+		to: newArray size
+		with: super ignoredNames.	
+	^newArray
+!
+
+namesToIgnore
+
+	^#('keywords' 'operators' 'separators')
+! !
+
+!PPJavaLexicon methodsFor:'accessing'!
+
+start
+	"Default start production."
+
+	^ input end
+! !
+
+!PPJavaLexicon methodsFor:'grammar-comments'!
+
+charactersInLine   
+
+	^ inputCharacter plus
+!
+
+comment
+	"traditional -> /*
+	 endOfLine -> //"
+	^ traditionalComment / endOfLineComment
+!
+
+commentTail
+
+	^ 	('*' asParser , commentTailStar ) /
+		(notStar , commentTail)
+!
+
+commentTailStar 
+
+	^ ('/' asParser ) /
+	  ('*' asParser , commentTailStar ) /
+	  (notStarNotSlash , commentTail )
+!
+
+endOfLineComment 
+
+	^ '//' asParser , charactersInLine optional
+!
+
+notStar
+
+	^  ('*' asParser not , inputCharacter)/lineTerminator
+!
+
+notStarNotSlash  
+
+	^ lineTerminator / ((PPPredicateObjectParser anyOf: '*/') not , inputCharacter )
+!
+
+traditionalComment
+
+	^ '/*' asParser , commentTail
+! !
+
+!PPJavaLexicon methodsFor:'grammar-identifiers'!
+
+identifier 
+
+	^  self asToken: (((keyword not) , (booleanLiteral not) , (nullLiteral not) , identifierChars ))
+!
+
+identifierChars
+	
+	^ javaLetter plus , javaLetterOrDigit star
+!
+
+javaLetter
+
+	^ (#letter asParser) / (PPPredicateObjectParser anyOf: '_$')
+!
+
+javaLetterOrDigit
+
+	^ javaLetter / (#digit asParser)
+! !
+
+!PPJavaLexicon methodsFor:'grammar-input'!
+
+input
+
+	^ (inputElements optional) , (sub optional)
+!
+
+inputElement
+
+	^ whiteSpace / comment / javaToken
+!
+
+inputElements
+
+	^ inputElement plus
+!
+
+javaToken
+
+
+	^ identifier / keyword / literal / separator / operator
+!
+
+sub
+
+	^ (Character value: 26) asParser 
+! !
+
+!PPJavaLexicon methodsFor:'grammar-keywords'!
+
+keyword
+
+        | keywordParsers |
+        
+        keywordParsers := keywords keys asSortedCollection collect: [:eachKey | keywords at: eachKey ].
+        ^ self asToken: ( (keywordParsers reduce: [ :a :b | a / b ]) )
+
+    "Modified (format): / 21-04-2015 / 15:27:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPJavaLexicon methodsFor:'grammar-lineTerminators'!
+
+inputCharacter 
+
+	^(lineTerminator not) , unicodeInputCharacter ==> #second
+!
+
+lineTerminator
+
+    self flag: 'Hack alert - should be fixed immediately in PJTraditionalCommentsNode>>comment:'.
+
+        ^ (((Character codePoint: 10) asParser) ==> [ :lf | Array with: lf with: nil ])
+          / (((Character codePoint: 13) asParser , ((Character codePoint: 10) asParser ) optional )) ==> [ :nodes | Array with: nodes first with: nil ]
+
+    "Modified: / 21-04-2015 / 17:16:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals'!
+
+literal
+	"a literal must be a single token. Whitespaces are not allowed inside the literal"
+	
+	^ nullLiteral / booleanLiteral / floatingPointLiteral / integerLiteral / characterLiteral / stringLiteral
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-boolean'!
+
+booleanLiteral 
+
+ ^ trueToken / falseToken
+!
+
+falseToken
+	^ ('false' asParser , #word asParser not) javaToken
+!
+
+nullToken
+	^ ('null' asParser , #word asParser not) javaToken
+!
+
+trueToken
+	^ ('true' asParser , #word asParser not) javaToken
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-character'!
+
+characterLiteral 
+
+ ^ ($' asParser , ( escapeSequence / singleCharacter ), $' asParser) javaToken
+!
+
+singleCharacter 	
+
+	^( PPPredicateObjectParser anyOf: '''\') not , inputCharacter ==> #second
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-escape'!
+
+escapeSequence 
+
+	^ ($\ asParser , (PPPredicateObjectParser anyOf: 'btnfr""''\' ) ) /
+	   octalEscape 
+!
+
+octalEscape
+
+	^ $\ asParser , ( (zeroToThree , octalDigit , octalDigit) / (octalDigit , octalDigit optional) )
+!
+
+zeroToThree
+
+	^PPPredicateObjectParser anyOf: '0123'
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-floating'!
+
+binaryExponent
+
+ ^ binaryExponentIndicator , signedInteger
+!
+
+binaryExponentIndicator
+
+  ^ PPPredicateObjectParser anyOf: 'pP'
+!
+
+decimalFloatingPointLiteral
+
+	|dot|
+	dot := $. asParser.
+
+ ^ ( ( (dot , digits) 
+        / 
+        (digits , dot , digits optional)) , 
+			exponentPart optional , floatTypeSuffix optional ) 
+  	/ 
+  	(digits , 
+		( (exponentPart , floatTypeSuffix optional) 
+		  /
+		  (exponentPart optional , floatTypeSuffix) ))
+!
+
+exponentIndicator
+
+  ^ PPPredicateObjectParser anyOf: 'eE'
+!
+
+exponentPart
+
+ ^ exponentIndicator , signedInteger
+!
+
+floatTypeSuffix
+
+	^ PPPredicateObjectParser anyOf: 'fFdD'
+!
+
+floatingPointLiteral
+
+  ^ (hexadecimalFloatingPointLiteral / decimalFloatingPointLiteral) javaToken
+!
+
+hexSignificand 
+	|dot|
+	dot := $. asParser.
+
+ ^  (hexNumeral , dot optional) /
+    ($0 asParser , (PPPredicateObjectParser anyOf: 'xX') , hexDigits optional , dot , hexDigits )
+!
+
+hexadecimalFloatingPointLiteral
+
+ ^ hexSignificand , binaryExponent , floatTypeSuffix optional
+!
+
+sign
+
+  ^PPPredicateObjectParser anyOf: '-+'
+!
+
+signedInteger
+
+  ^ sign optional , digits
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-integer'!
+
+decimalIntegerLiteral
+
+ ^ decimalNumeral , (integerTypeSuffix optional)
+!
+
+decimalNumeral 
+
+	^($0 asParser) / (nonZeroDigit , digits optional) 
+!
+
+digits 
+	"digit is already defined, no need to redefine it"
+	^#digit asParser plus
+!
+
+hexDigits 
+
+	^hexDigit plus
+!
+
+hexIntegerLiteral 
+
+  ^ hexNumeral , (integerTypeSuffix optional)
+!
+
+hexNumeral 
+
+	^$0 asParser, (PPPredicateObjectParser anyOf: 'xX' ), hexDigits
+!
+
+integerLiteral
+
+  ^ (hexIntegerLiteral / octalIntegerLiteral / decimalIntegerLiteral) javaToken
+!
+
+integerTypeSuffix
+
+	^ PPPredicateObjectParser anyOf: 'lL'
+!
+
+nonZeroDigit 
+
+	^PPPredicateObjectParser anyOf: '123456789'.
+!
+
+octalDigit 
+
+	^PPPredicateObjectParser anyOf: '01234567'
+!
+
+octalDigits
+
+	^ octalDigit plus
+!
+
+octalIntegerLiteral 
+
+ ^ octalNumeral , (integerTypeSuffix optional)
+!
+
+octalNumeral 
+
+	^($0 asParser) , octalDigits
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-null'!
+
+nullLiteral 
+
+ ^ nullToken
+! !
+
+!PPJavaLexicon methodsFor:'grammar-literals-string'!
+
+stringCharacter
+		
+	^ ( ( PPPredicateObjectParser anyOf: '"\') not , inputCharacter ==> #second ) /
+	   escapeSequence 
+!
+
+stringCharacters
+
+	^ stringCharacter plus
+!
+
+stringLiteral 
+
+ ^ ($" asParser , stringCharacters optional , $" asParser) javaToken
+! !
+
+!PPJavaLexicon methodsFor:'grammar-operators'!
+
+operator
+        | operatorParsers |
+        
+        operatorParsers := operators keys asSortedCollection collect: [:eachKey | operators at: eachKey ].                                                
+        ^self asToken:  (operatorParsers reduce: [ :a :b | a / b ])
+
+    "Modified: / 21-04-2015 / 15:26:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PPJavaLexicon methodsFor:'grammar-separators'!
+
+separator	
+	^self asToken: (PPPredicateObjectParser anyOf: '(){}[];,.' )
+! !
+
+!PPJavaLexicon methodsFor:'grammar-unicode-escapes'!
+
+hexDigit 
+
+	^#hex asParser
+!
+
+rawInputCharacter
+
+	^#any asParser
+!
+
+unicodeEscape
+
+	^ $\ asParser , unicodeMarker , hexDigit , hexDigit , hexDigit , hexDigit
+!
+
+unicodeInputCharacter
+	 ^ unicodeEscape / rawInputCharacter
+!
+
+unicodeMarker
+
+	^$u asParser plus
+! !
+
+!PPJavaLexicon methodsFor:'grammar-whiteSpace'!
+
+whiteSpace
+
+	^ (Character space asParser ) /
+	  (Character tab asParser ) /
+	  ((Character value: 12) asParser ) /
+		lineTerminator 
+! !
+
+!PPJavaLexicon methodsFor:'initialization'!
+
+initialize
+
+	super initialize.
+	
+	self initializeKeywords.
+	self initializeOperators.
+	self initializeSeparators.
+!
+
+initializeKeywords
+
+	| values |
+	keywords := Dictionary new.
+	values := #('abstract' 'assert' 'boolean' 'break' 'byte' 'case'  'catch' 'char' 'class' 'const'
+	   'continue' 'default' 'do' 'double' 'else' 'enum' 'extends' 'final'  'finally' 'float'
+	   'for' 'if' 'goto' 'implements' 'import' 'instanceof' 'int' 'interface' 'long' 'native'
+	   'new' 'package' 'private' 'protected' 'public' 'return' 'short' 'static' 'strictfp' 'super'
+	   'switch' 'synchronized' 'this' 'throw' 'throws' 'transient' 'try' 'void' 'volatile' 'while').
+	
+	values do: [:eachKeyword |
+		keywords at: eachKeyword 
+			put: (PPUnresolvedParser named: ('keyword', eachKeyword first asUppercase asString , eachKeyword allButFirst))		
+		].
+	
+	keywords keysAndValuesDo:  [:key :value |
+		(keywords at: key) def: (key asParser ,  #word asParser not)]
+!
+
+initializeOperators
+
+	| values |
+	operators := Dictionary new.
+	values := #(	'>>>=' '>>>' '>>=' '>>' '>=' '>'	'<<=' '<<' '<=' '<'	'++' '+=' '+'	'--' '-=' '-'	'&&' '&=' '&'
+					'||' '|=' '|'	'*=' '*'	'%=' '%'	'/=' '/'	'^=' '^'	'!!=' '!!'	'==' '='	'~'	'?'	':'	'@' ).
+	" @ ? perhaps for annotation but not in the doc "
+	values do: [:eachOperator |
+		operators at: eachOperator 
+			put: (PPUnresolvedParser named: ('operator', eachOperator asString))		
+		].
+	
+	operators  keysAndValuesDo:  [:key :value |
+		(operators at: key) def: (key asParser)]
+!
+
+initializeSeparators
+
+	| values |
+	separators := Dictionary new.
+	values := #( '(' ')' '{' '}' '[' ']' ';' ',' '.' ).
+	
+	values do: [:eachSeparator |
+		separators at: eachSeparator 
+			put: (PPUnresolvedParser named: ('separator', eachSeparator asString))		
+		].
+	
+	separators  keysAndValuesDo:  [:key :value |
+		(separators at: key) def: (key asParser)]
+! !
+
+!PPJavaLexicon methodsFor:'utility'!
+
+asToken: aParser
+
+	^aParser javaToken
+!
+
+emptySquaredParenthesis
+
+	^ self asToken: (((self tokenFor: '['), (self tokenFor: ']')))
+!
+
+tokenFor: aString
+
+	^self asToken: (keywords at: aString 
+						ifAbsent: [separators at: aString 
+							ifAbsent: [operators at: aString] ])
+! !
+
+!PPJavaLexicon class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/parsers/java/PPJavaTokenParser.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/PPJavaTokenParser.st	Thu May 21 14:35:34 2015 +0100
@@ -12,29 +12,31 @@
 !PPJavaTokenParser methodsFor:'parsing'!
 
 parseComments: anArray on: aStream
-	
-	| start comments |
-	comments := anArray.
-	[ 
-		| peekTwice |
-	[ aStream atEnd not and: [ aStream peek isSeparator ] ]
-		whileTrue: [ aStream next ].
-	peekTwice := aStream peekTwice.	
-	  ((peekTwice  first = $/) and: 
-		[ (peekTwice second = $*) or: [peekTwice second = $/]])] whileTrue: [
-"		
-		Transcript show: ('position ', aStream position asString, ' char ', aStream next asString); cr.
-"		
-		aStream next.
-		start := aStream position.
-		(aStream next = $*) 
-			ifTrue: [ aStream upToAll: '*/' ]
-			ifFalse: [ 
-				| position |
-				position := aStream position.
-				aStream upToAnyOf: CharacterSet crlf].
-		comments := comments copyWith: (start to: aStream position) ].
-	^ comments
+        
+        | start comments |
+        comments := anArray.
+        [ 
+                | peekTwice |
+        [ aStream atEnd not and: [ aStream peek isSeparator ] ]
+                whileTrue: [ aStream next ].
+        peekTwice := aStream peekTwice. 
+          ((peekTwice  first = $/) and: 
+                [ (peekTwice second = $*) or: [peekTwice second = $/]])] whileTrue: [
+"               
+                Transcript show: ('position ', aStream position asString, ' char ', aStream next asString); cr.
+"               
+                aStream next.
+                start := aStream position.
+                (aStream next = $*) 
+                        ifTrue: [ aStream upToAll: '*/' ]
+                        ifFalse: [ 
+                                | position |
+                                position := aStream position.
+                                aStream upToAnyOf: (String with: (Character codePoint: 13) with: (Character codePoint: 10))].
+                comments := comments copyWith: (start to: aStream position) ].
+        ^ comments
+
+    "Modified: / 21-04-2015 / 17:23:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parseOn: aPPContext
--- a/parsers/java/PPJavaWhitespaceParser.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/PPJavaWhitespaceParser.st	Thu May 21 14:35:34 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitJava-Core'
 !
 
+
 !PPJavaWhitespaceParser methodsFor:'as yet unclassified'!
 
 acceptsEpsilon
@@ -36,25 +37,27 @@
 !
 
 parseOn: context
-	
-	| start |
+        
+        | start |
 
-	[ 
-		| peekTwice |
-		[ context atEnd not and: [ context peek isSeparator ] ]
-			whileTrue: [ context next ].
-		peekTwice := context peekTwice.	
-	  	((peekTwice  first = $/) and: 
-		[ (peekTwice second = $*) or: [peekTwice second = $/]])
-	] whileTrue: [
-		context next.
-		start := context position.
-		(context next = $*) 
-			ifTrue: [ context upToAll: '*/' ]
-			ifFalse: [ 
-				| position |
-				position := context position.
-				context upToAnyOf: CharacterSet crlf].
-	 ].
+        [ 
+                | peekTwice |
+                [ context atEnd not and: [ context peek isSeparator ] ]
+                        whileTrue: [ context next ].
+                peekTwice := context peekTwice. 
+                ((peekTwice  first = $/) and: 
+                [ (peekTwice second = $*) or: [peekTwice second = $/]])
+        ] whileTrue: [
+                context next.
+                start := context position.
+                (context next = $*) 
+                        ifTrue: [ context upToAll: '*/' ]
+                        ifFalse: [ 
+                                | position |
+                                position := context position.
+                                context upToAnyOf: String crlf].
+         ].
+
+    "Modified: / 10-05-2015 / 07:57:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/parsers/java/abbrev.stc	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/abbrev.stc	Thu May 21 14:35:34 2015 +0100
@@ -22,7 +22,6 @@
 PJTypeNode PJTypeNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJVariableDeclaratorNode PJVariableDeclaratorNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PPJavaSyntax PPJavaSyntax stx:goodies/petitparser/parsers/java 'PetitJava-Core' 0
-PPJavaSyntaxTest PPJavaSyntaxTest stx:goodies/petitparser/parsers/java 'PetitJava-Tests' 1
 PJAbstractTypeDeclarationNode PJAbstractTypeDeclarationNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJAnnotationNode PJAnnotationNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJArrayTypeNode PJArrayTypeNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
@@ -45,7 +44,6 @@
 PJStringLiteralNode PJStringLiteralNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJWhileStatementNode PJWhileStatementNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PPJavaParser PPJavaParser stx:goodies/petitparser/parsers/java 'PetitJava-Core' 0
-PPJavaParserTest PPJavaParserTest stx:goodies/petitparser/parsers/java 'PetitJava-Tests' 1
 PJConstructorDeclarationNode PJConstructorDeclarationNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJEndOfLineCommentsNode PJEndOfLineCommentsNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJMethodDeclarationNode PJMethodDeclarationNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 1
@@ -53,3 +51,5 @@
 PJSimpleNameNode PJSimpleNameNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJTraditionalCommentsNode PJTraditionalCommentsNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
 PJTypeDeclarationNode PJTypeDeclarationNode stx:goodies/petitparser/parsers/java 'PetitJava-AST' 0
+PPJavaParserTest PPJavaParserTest stx:goodies/petitparser/parsers/java 'PetitJava-Tests' 1
+PPJavaSyntaxTest PPJavaSyntaxTest stx:goodies/petitparser/parsers/java 'PetitJava-Tests' 1
--- a/parsers/java/bc.mak	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/bc.mak	Thu May 21 14:35:34 2015 +0100
@@ -35,7 +35,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\petitparser -I$(INCLUDE_TOP)\stx\goodies\petitparser\tests -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic2
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\petitparser -I$(INCLUDE_TOP)\stx\goodies\petitparser\tests -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
--- a/parsers/java/extensions.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/extensions.st	Thu May 21 14:35:34 2015 +0100
@@ -11,10 +11,14 @@
 				ifFalse: [ aString ]])
 ! !
 
-!PPParser methodsFor:'*petitjava-operations'!
+!PPParser methodsFor:'*petitcompiler'!
 
 javaToken
-	^ PPJavaTokenParser on: self
+    | ws |
+    ws := PPJavaWhitespaceParser new.
+    ^ ((ws, ((PPTokenParser on: self) tokenClass: PPJavaToken; yourself), ws) ==> #second)
+        propertyAt: #'trimmingToken' put: true;
+        yourself
 ! !
 
 !stx_goodies_petitparser_parsers_java class methodsFor:'documentation'!
--- a/parsers/java/stx_goodies_petitparser_parsers_java.st	Thu May 21 14:12:22 2015 +0100
+++ b/parsers/java/stx_goodies_petitparser_parsers_java.st	Thu May 21 14:35:34 2015 +0100
@@ -73,7 +73,6 @@
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:libbasic2'    "CharacterSet - referenced by PPJavaTokenParser>>parseComments:on:"
     )
 !
 
@@ -126,7 +125,6 @@
         PJTypeNode
         PJVariableDeclaratorNode
         PPJavaSyntax
-        (PPJavaSyntaxTest autoload)
         PJAbstractTypeDeclarationNode
         PJAnnotationNode
         PJArrayTypeNode
@@ -149,7 +147,6 @@
         PJStringLiteralNode
         PJWhileStatementNode
         PPJavaParser
-        (PPJavaParserTest autoload)
         PJConstructorDeclarationNode
         PJEndOfLineCommentsNode
         PJMethodDeclarationNode
@@ -157,6 +154,8 @@
         PJSimpleNameNode
         PJTraditionalCommentsNode
         PJTypeDeclarationNode
+        (PPJavaParserTest autoload)
+        (PPJavaSyntaxTest autoload)
     )
 !
 
--- a/stx_goodies_petitparser.st	Thu May 21 14:12:22 2015 +0100
+++ b/stx_goodies_petitparser.st	Thu May 21 14:35:34 2015 +0100
@@ -112,7 +112,10 @@
     ^ #(
         #'stx:goodies/petitparser/analyzer'
         #'stx:goodies/petitparser/tests'
-    )
+        #'stx:goodies/parsers/smalltalk'
+        #'stx:goodies/parsers/java'
+        #'stx:goodies/compiler'
+)
 ! !
 
 !stx_goodies_petitparser class methodsFor:'description - compilation'!
@@ -129,7 +132,7 @@
 		Class tryLocalSourceFirst: true.				\
 		Smalltalk packagePath add:''$(TOP)/..'' .                       \
 		Smalltalk loadPackage:''stx:goodies/petitparser''.              \
-		(Smalltalk at: #''stx_goodies_petitparser'') exportAsMczTo: ''mc''."
+		(Smalltalk at: #''stx_goodies_petitparser'') monticelloExportTo: ''mc''."
 
 '
 
@@ -286,7 +289,7 @@
 
 !stx_goodies_petitparser class methodsFor:'utilities - monticello'!
 
-exportAsMczTo: directory
+monticelloExportTo: directory
     "Export .mcz packages to given directory"
 
     | packages exporter mcrepo |
@@ -301,10 +304,14 @@
         'stx:goodies/petitparser/tests'
         'stx:goodies/petitparser/analyzer'
         'stx:goodies/petitparser/analyzer/tests'
+
         'stx:goodies/petitparser/parsers/smalltalk'
         'stx:goodies/petitparser/parsers/smalltalk/tests'
+        'stx:goodies/petitparser/parsers/java'
+
         'stx:goodies/petitparser/compiler'
         'stx:goodies/petitparser/compiler/tests'
+        'stx:goodies/petitparser/compiler/tests/extras'
         'stx:goodies/petitparser/compiler/benchmarks'
     ).
 
@@ -317,7 +324,8 @@
         mcwc := mcpkg workingCopy.
         mcvi := HGMCVersionInfo forPackage: pkgnm.
         [
-           mcversion := mcwc newVersion
+           mcversion := mcwc newVersion.
+           mcversion snapshot includeExtrasForSTX: false.
         ] on: MCVersionNameAndMessageRequest do:[:ex |
             ex resume: (Array with: mcvi name with: mcvi message)
         ].
@@ -329,7 +337,7 @@
     packages do: exporter.
 
     "
-    stx_goodies_petitparser exportAsMczTo: '/tmp'
+    stx_goodies_petitparser monticelloExportTo: '/tmp'
     "
 
     "Created: / 04-10-2014 / 21:30:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/tests/PPArithmeticParserTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/tests/PPArithmeticParserTest.st	Thu May 21 14:35:34 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCompositeParserTest subclass:#PPArithmeticParserTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/tests/PPCompositeParserTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/tests/PPCompositeParserTest.st	Thu May 21 14:35:34 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPAbstractParserTest subclass:#PPCompositeParserTest
 	instanceVariableNames:'parser result'
 	classVariableNames:''
--- a/tests/PPExpressionParserTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/tests/PPExpressionParserTest.st	Thu May 21 14:35:34 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPArithmeticParserTest subclass:#PPExpressionParserTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/tests/PPLambdaParserTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/tests/PPLambdaParserTest.st	Thu May 21 14:35:34 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCompositeParserTest subclass:#PPLambdaParserTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/tests/PPParserResource.st	Thu May 21 14:12:22 2015 +0100
+++ b/tests/PPParserResource.st	Thu May 21 14:35:34 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 TestResource subclass:#PPParserResource
 	instanceVariableNames:'parsers'
 	classVariableNames:''
--- a/tests/PPScriptingTest.st	Thu May 21 14:12:22 2015 +0100
+++ b/tests/PPScriptingTest.st	Thu May 21 14:35:34 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPAbstractParserTest subclass:#PPScriptingTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/vcmake.bat	Thu May 21 14:12:22 2015 +0100
+++ b/vcmake.bat	Thu May 21 14:35:34 2015 +0100
@@ -31,4 +31,25 @@
 @call vcmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/smalltalk
+@echo "***********************************"
+@pushd parsers\smalltalk
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parsers/java
+@echo "***********************************"
+@pushd parsers\java
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+