Merge
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 12 May 2015 01:33:33 +0100
changeset 460 87a3d30ab570
parent 458 a4da1c24d84a (current diff)
parent 459 4751c407bb40 (diff)
child 461 5986bf6d7d60
Merge
compiler/PPCCodeGenerator.st
compiler/PPCCompiler.st
compiler/PPCMethod.st
compiler/PPCTokenizingCodeGenerator.st
compiler/PPCTokenizingVisitor.st
compiler/benchmarks/PPCBenchmark.st
compiler/tests/PPCInliningVisitorTest.st
compiler/tests/PPCNodeTest.st
compiler/tests/PPCompiledExpressionGrammarResource.st
compiler/tests/extras/Make.proto
compiler/tests/extras/PPCResources.st
compiler/tests/extras/PPCSmalltalkTests.st
compiler/tests/extras/PPCompiledJavaSyntaxTest.st
compiler/tests/extras/PPCompiledSmalltalkVerificationTest.st
compiler/tests/extras/PPTokenizedSmalltalkGrammarResource.st
compiler/tests/extras/bc.mak
compiler/tests/extras/stx_goodies_petitparser_compiler_tests_extras.st
islands/PPWater.st
islands/stx_goodies_petitparser_islands.st
islands/tests/stx_goodies_petitparser_islands_tests.st
--- a/PPLiteralObjectParser.st	Mon May 11 18:31:26 2015 +0100
+++ b/PPLiteralObjectParser.st	Tue May 12 01:33:33 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPLiteralParser subclass:#PPLiteralObjectParser
 	instanceVariableNames:''
 	classVariableNames:''
@@ -8,6 +10,7 @@
 !
 
 
+
 !PPLiteralObjectParser methodsFor:'operators'!
 
 caseInsensitive
@@ -39,6 +42,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPLiteralObjectParser.st,v 1.4 2014-03-04 14:33:00 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: PPLiteralObjectParser.st,v 1.4 2014-03-04 14:33:00 cg Exp $'
 ! !
--- a/PPParser.st	Mon May 11 18:31:26 2015 +0100
+++ b/PPParser.st	Tue May 12 01:33:33 2015 +0100
@@ -20,6 +20,15 @@
 	^ self basicNew initialize
 ! !
 
+
+
+
+
+
+
+
+
+
 !PPParser methodsFor:'accessing'!
 
 children
--- a/analyzer/PPProcessor.st	Mon May 11 18:31:26 2015 +0100
+++ b/analyzer/PPProcessor.st	Tue May 12 01:33:33 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/analyzer' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPProcessor
 	instanceVariableNames:'searches context'
 	classVariableNames:''
@@ -55,5 +57,10 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/goodies/petitparser/analyzer/PPProcessor.st,v 1.2 2014-03-04 20:27:44 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/analyzer/stx_goodies_petitparser_analyzer.st	Mon May 11 18:31:26 2015 +0100
+++ b/analyzer/stx_goodies_petitparser_analyzer.st	Tue May 12 01:33:33 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/analyzer' }"
 
+"{ NameSpace: Smalltalk }"
+
 LibraryDefinition subclass:#stx_goodies_petitparser_analyzer
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,12 +9,6 @@
 	category:'* Projects & Packages *'
 !
 
-!stx_goodies_petitparser_analyzer class methodsFor:'documentation'!
-
-extensionsVersion_HG
-
-    ^ '$Changeset: <not expanded> $'
-! !
 
 !stx_goodies_petitparser_analyzer class methodsFor:'accessing - monticello'!
 
@@ -75,7 +71,10 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
--- a/compiler/Make.proto	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/Make.proto	Tue May 12 01:33:33 2015 +0100
@@ -193,6 +193,7 @@
 $(OUTDIR)PPCSequenceNode.$(O) PPCSequenceNode.$(H): PPCSequenceNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCListNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCSpecializingVisitor.$(O) PPCSpecializingVisitor.$(H): PPCSpecializingVisitor.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNodeVisitor.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCRewritingVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCStarNode.$(O) PPCStarNode.$(H): PPCStarNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenCodeGenerator.$(O) PPCTokenCodeGenerator.$(H): PPCTokenCodeGenerator.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCCodeGenerator.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNodeVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenConsumeNode.$(O) PPCTokenConsumeNode.$(H): PPCTokenConsumeNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenDetector.$(O) PPCTokenDetector.$(H): PPCTokenDetector.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNodeVisitor.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCRewritingVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenNode.$(O) PPCTokenNode.$(H): PPCTokenNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/compiler/Make.spec	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/Make.spec	Tue May 12 01:33:33 2015 +0100
@@ -113,6 +113,7 @@
 	PPCSequenceNode \
 	PPCSpecializingVisitor \
 	PPCStarNode \
+	PPCTokenCodeGenerator \
 	PPCTokenConsumeNode \
 	PPCTokenDetector \
 	PPCTokenNode \
@@ -200,6 +201,7 @@
     $(OUTDIR_SLASH)PPCSequenceNode.$(O) \
     $(OUTDIR_SLASH)PPCSpecializingVisitor.$(O) \
     $(OUTDIR_SLASH)PPCStarNode.$(O) \
+    $(OUTDIR_SLASH)PPCTokenCodeGenerator.$(O) \
     $(OUTDIR_SLASH)PPCTokenConsumeNode.$(O) \
     $(OUTDIR_SLASH)PPCTokenDetector.$(O) \
     $(OUTDIR_SLASH)PPCTokenNode.$(O) \
--- a/compiler/PPCCodeGenerator.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCCodeGenerator.st	Tue May 12 01:33:33 2015 +0100
@@ -11,6 +11,12 @@
 
 !PPCCodeGenerator class methodsFor:'as yet unclassified'!
 
+new
+    ^ self basicNew
+        initialize;
+        yourself 
+!
+
 on: aPPCCompiler
     ^ self new 
         compiler: aPPCCompiler;
@@ -21,6 +27,10 @@
 
 compiler: aPPCCompiler
     compiler := aPPCCompiler 
+!
+
+guards
+    ^ arguments guards
 ! !
 
 !PPCCodeGenerator methodsFor:'hooks'!
@@ -48,7 +58,7 @@
 
 addGuard: node
     |  guard firsts id |
-    (arguments guards not or: [(guard := PPCGuard on: node) makesSense not]) ifTrue: [ ^ self].
+    (self guards not or: [(guard := PPCGuard on: node) makesSense not]) ifTrue: [ ^ self].
 
     id := compiler idFor: node.
     firsts := node firstSetWithTokens.
@@ -245,12 +255,6 @@
         ^ nil
     ].
 
-    "TODO JK: this is is wrong,.. to tired now to fix this :("
-"	(self isCached: child) ifTrue: [ 
-        node replace: child with: (self cachedValue: child).
-        ^ nil
-    ]. 
-"
     ^ self visit: child.
 !
 
@@ -268,7 +272,7 @@
         If we want to compile in guard and the choice starts with trimming token, 
         we should invoke the whitespace parser
     "
-    (arguments guards and: [ firsts allSatisfy: [ :e | e isTrimmingTokenNode ] ]) ifTrue: [  
+    (self guards and: [ firsts allSatisfy: [ :e | e isTrimmingTokenNode ] ]) ifTrue: [  
         self compileTokenWhitespace: firsts anyOne.
         whitespaceConsumed := true.
     ].
@@ -277,7 +281,7 @@
         child := node children at: idx.
         allowGuard := whitespaceConsumed.
                                 
-        (allowGuard and: [arguments guards and: [ (guard := PPCGuard on: child) makesSense ]]) ifTrue: [         
+        (allowGuard and: [self guards and: [ (guard := PPCGuard on: child) makesSense ]]) ifTrue: [         
             guard id: (compiler idFor: guard prefixed: #guard).
             guard compileGuard: compiler.
             compiler add: ' ifTrue: [ '.
--- a/compiler/PPCCompiler.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCCompiler.st	Tue May 12 01:33:33 2015 +0100
@@ -48,6 +48,10 @@
     ^ compiledParserSuperclass ifNil: [ PPCompiledParser ]
 !
 
+currentMethod
+    ^ currentMethod 
+!
+
 currentNonInlineMethod
     ^ compilerStack 
         detect:[:m | m isInline not ] 
@@ -67,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
@@ -82,13 +86,16 @@
 cleanGeneratedMethods: class
     ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
         class methodsDo: [ :mthd |
-            mthd category = #generated ifTrue:[
+            (mthd category beginsWith: 'generated') ifTrue:[
                 class removeSelector: mthd selector.
             ]
         ]
     ] ifFalse: [ 
-        (class allSelectorsInProtocol: #generated) do: [ :selector | 
-            class removeSelectorSilently: selector ].
+        (class allProtocolsUpTo: class) do: [ :protocol |
+            (protocol beginsWith: 'generated') ifTrue: [ 
+                class removeProtocol: protocol.
+            ]
+        ]
     ]
 !
 
@@ -171,9 +178,9 @@
     (variable == #whatever) ifFalse: [ 
         "Do not assign, if somebody does not care!!"
         self add: variable ,' := ', code.
- 	] ifTrue: [ 
+ 		] ifTrue: [ 
         "In case code hava a side effect"
- 		self add: code	
+ 				self add: code	
     ]
 !
 
@@ -208,13 +215,13 @@
 
 codeReturn
    currentMethod isInline ifTrue: [
-		"If inlined, the return variable already holds the value"
-	] ifFalse: [
-		self add: '^ ', currentMethod returnVariable  
+				"If inlined, the return variable already holds the value"
+		] ifFalse: [
+				self add: '^ ', currentMethod returnVariable  
    ].
 
-    "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	"Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	"Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 codeReturn: code
@@ -442,7 +449,7 @@
 
 installMethods
     cache keysAndValuesDo: [ :key :method |
-        compiledParser compileSilently: method code classified: 'generated'.
+        compiledParser compileSilently: method code classified: method category.
     ]
 !
 
--- a/compiler/PPCCompilerTokenizingRememberStrategy.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCCompilerTokenizingRememberStrategy.st	Tue May 12 01:33:33 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Core'
 !
 
+
 !PPCCompilerTokenizingRememberStrategy class methodsFor:'instance creation'!
 
 on: aPPCCompiler
@@ -45,3 +46,10 @@
     compiler codeAssign: mementoName, ' third.' to: 'currentTokenValue'.	
 ! !
 
+!PPCCompilerTokenizingRememberStrategy class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCGuard.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCGuard.st	Tue May 12 01:33:33 2015 +0100
@@ -67,7 +67,7 @@
             id := compiler idFor: (Character value: index) prefixed: #character.
             compiler addConstant: (Character value: index) as: id.
             compiler add: '(context peek = ', id, ')'.
-     	] 
+     		] 
     ] ].
 !
 
@@ -85,12 +85,12 @@
 !
 
 testMessage: selector
- 	classification keysAndValuesDo: [:index :element |
-		(element = ((Character value: index) perform: selector)) ifFalse: [ 
-			^ false 
-		]
-	].
-	^ true
+ 		classification keysAndValuesDo: [:index :element |
+				(element = ((Character value: index) perform: selector)) ifFalse: [ 
+						^ false 
+				]
+		].
+		^ true
 !
 
 testSingleCharacter
--- a/compiler/PPCInliningVisitor.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCInliningVisitor.st	Tue May 12 01:33:33 2015 +0100
@@ -101,5 +101,11 @@
     super visitTokenWhitespaceNode: node.
     self markForInline: node.
     ^ node
+!
+
+visitTokenizingParserNode: node
+    self visit: node tokenizer.
+    self visit: node parser.
+    ^ node
 ! !
 
--- a/compiler/PPCLL1Configuration.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCLL1Configuration.st	Tue May 12 01:33:33 2015 +0100
@@ -9,14 +9,6 @@
 	category:'PetitCompiler-Core'
 !
 
-!PPCLL1Configuration methodsFor:'accessing'!
-
-defaultArguments
- 	^ PPCArguments default
-		guards: false;
-		yourself
-! !
-
 !PPCLL1Configuration methodsFor:'compiling'!
 
 invokePhases
--- a/compiler/PPCMethod.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCMethod.st	Tue May 12 01:33:33 2015 +0100
@@ -3,7 +3,8 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#PPCMethod
-	instanceVariableNames:'buffer variables indentation id profile variableForReturn'
+	instanceVariableNames:'buffer variables indentation id profile variableForReturn
+		category'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Core'
@@ -28,6 +29,18 @@
     ^ PPCBridge on: self methodName.
 !
 
+category
+    ^ category isNil 
+        ifTrue: [ category := 'generated' ]
+        ifFalse: [ category ]
+
+    "Modified (format): / 12-05-2015 / 01:21:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+category: value
+    category := value
+!
+
 code
     ^ self methodName, Character cr asString,  
         self variables, Character cr asString,
@@ -76,14 +89,14 @@
 
 profilingBegin
     self profile ifTrue: [ 
- 		^ '  context methodInvoked: #', id, '.'	
+ 				^ '  context methodInvoked: #', id, '.'	
     ].
     ^ ''
 !
 
 profilingEnd
     self profile ifTrue: [ 
- 		^ '  context methodFinished: #', id, '.'	
+ 				^ '  context methodFinished: #', id, '.'	
     ].
     ^ ''
 ! !
--- a/compiler/PPCNode.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCNode.st	Tue May 12 01:33:33 2015 +0100
@@ -241,7 +241,7 @@
         finite := self.
         infinite := anotherNode.
     ] ifFalse: [ 
- 		finite := anotherNode.
+ 				finite := anotherNode.
         infinite := self.	
     ].
         
--- a/compiler/PPCProfilingContext.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCProfilingContext.st	Tue May 12 01:33:33 2015 +0100
@@ -74,9 +74,9 @@
 
     sender := thisContext sender.
     selector := (sender receiver isKindOf: PPCompiledParser) ifTrue: [ 
- 		sender selector.
+ 				sender selector.
     ] ifFalse: [ 
- 		sender receiver class.	
+ 				sender receiver class.	
     ].
     remembers add: selector.
     ^ super remember
@@ -87,9 +87,9 @@
     
     sender := thisContext sender.
     selector := (sender receiver isKindOf: PPCompiledParser) ifTrue: [ 
- 		sender selector.
+ 				sender selector.
     ] ifFalse: [ 
- 		sender receiver class.	
+ 				sender receiver class.	
     ].
     
     
--- a/compiler/PPCSequenceNode.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCSequenceNode.st	Tue May 12 01:33:33 2015 +0100
@@ -67,7 +67,7 @@
         child recognizedSentences do: [ :suffix |
             retval do: [ :prefix |
                 set add: prefix, suffix.
-         	]
+         		]
         ].
         retval := set.
     ].
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/PPCTokenCodeGenerator.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,88 @@
+"{ Package: 'stx:goodies/petitparser/compiler' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCCodeGenerator subclass:#PPCTokenCodeGenerator
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Visitors'
+!
+
+!PPCTokenCodeGenerator methodsFor:'as yet unclassified'!
+
+afterAccept: node retval: retval
+    | return |
+    return := super afterAccept: node retval: retval.
+    return category: 'generated - tokens'.
+    ^ return
+! !
+
+!PPCTokenCodeGenerator methodsFor:'visiting'!
+
+visitTokenNode: node
+    | id startVar endVar |
+    startVar := compiler allocateTemporaryVariableNamed: 'start'.
+    endVar := compiler allocateTemporaryVariableNamed: 'end'.
+
+    id := compiler idFor: node.
+    compiler rememberStrategy: (PPCCompilerTokenRememberStrategy on: compiler).	
+    
+    compiler codeAssign: 'context position + 1.' to: startVar.
+    compiler codeStoreValueOf: [ self visit: node child ] intoVariable: #whatever.
+    compiler add: 'error ifFalse: [ '.
+    compiler indent.	
+        compiler codeAssign: 'context position.' to: endVar.
+    
+        compiler codeTranscriptShow: 'current token type: ', id storeString.
+        compiler codeAssign: id storeString, '.' to: 'currentTokenType'.
+        compiler codeAssign: node tokenClass asString, ' on: (context collection) 
+                                                                    start: ', startVar, '  
+                                                                    stop: ', endVar, '
+                                                                    value: nil.'
+                    to: 'currentTokenValue := ', self retvalVar.
+        compiler codeReturn.
+    compiler dedent.
+    compiler add: '].'.		
+    compiler rememberStrategy: (PPCCompilerTokenizingRememberStrategy on: compiler).	
+!
+
+visitTrimmingTokenNode: node
+    |  id  startVar endVar |
+    
+    startVar := compiler allocateTemporaryVariableNamed: 'start'.
+    endVar := compiler allocateTemporaryVariableNamed:  'end'.
+    
+    id := compiler idFor: node.
+    compiler rememberStrategy: (PPCCompilerTokenRememberStrategy on: compiler).
+    
+    
+    compiler addComment: 'Consume Whitespace:'.
+    compiler codeStoreValueOf: [ self visit: node whitespace ] intoVariable: #whatever.
+    compiler nl.
+
+    compiler codeAssign: 'context position + 1.' to: startVar.
+    compiler codeStoreValueOf: [ self visit: node child ] intoVariable: #whatever.
+
+    compiler add: 'error ifFalse: [ '.
+    compiler indent.	
+        compiler codeAssign: 'context position.' to: endVar.
+    
+        compiler addComment: 'Consume Whitespace:'.
+        compiler codeStoreValueOf: [ self visit: node whitespace ] intoVariable: #whatever.
+        compiler nl.
+    
+    
+        compiler codeTranscriptShow: 'current token type: ', id storeString.
+        compiler codeAssign: id storeString, '.' to: 'currentTokenType'.
+        compiler codeAssign: node tokenClass asString, ' on: (context collection) 
+                                                                start: ', startVar, ' 
+                                                                stop: ', endVar, '
+                                                                value: nil.'
+                   to: 'currentTokenValue := ', self retvalVar.
+        compiler codeReturn.
+    compiler dedent.																
+    compiler add: '].'	.
+    compiler rememberStrategy: (PPCCompilerTokenizingRememberStrategy on: compiler).
+! !
+
--- a/compiler/PPCTokenVisitor.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCTokenVisitor.st	Tue May 12 01:33:33 2015 +0100
@@ -44,7 +44,7 @@
         ^ node child
     ].
 
- 	self change.
+ 		self change.
     ^ PPCForwardNode new
         child: node child;
         name: node name;
--- a/compiler/PPCTokenizingCodeGenerator.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCTokenizingCodeGenerator.st	Tue May 12 01:33:33 2015 +0100
@@ -3,12 +3,31 @@
 "{ NameSpace: Smalltalk }"
 
 PPCCodeGenerator subclass:#PPCTokenizingCodeGenerator
-	instanceVariableNames:''
+	instanceVariableNames:'tokenGenerator'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Visitors'
 !
 
+!PPCTokenizingCodeGenerator methodsFor:'accessing'!
+
+guards
+    "When tokenizing, do not use guards"
+    ^ false
+!
+
+tokenGenerator
+    tokenGenerator isNil ifTrue: [ 
+        tokenGenerator := PPCTokenCodeGenerator on: compiler.
+        tokenGenerator arguments: arguments.
+    ].
+    ^ tokenGenerator
+!
+
+tokenGenerator: whatever
+    tokenGenerator := whatever
+! !
+
 !PPCTokenizingCodeGenerator methodsFor:'visiting'!
 
 visitChoiceNode: node
@@ -84,12 +103,16 @@
     | trimmingToken |
     self assert: (node children allSatisfy: [ :e | e isMarkedForInline not ]).
     
+    node children do: [ :child |
+        self tokenGenerator visit: child
+    ]
     
+"	
     trimmingToken := node children detect: [ :e | e isTrimmingTokenNode ] ifNone: [ nil ].
     trimmingToken isNil ifFalse: [ 
         compiler codeStoreValueOf: [ self visit: trimmingToken whitespace ] intoVariable: #whatever.
     ].
-    super visitChoiceNode: node.
+    super visitChoiceNode: node."
 !
 
 visitTokenConsumeNode: node
@@ -97,34 +120,12 @@
 !
 
 visitTokenNode: node
-    | id startVar endVar |
-    startVar := compiler allocateTemporaryVariableNamed: 'start'.
-    endVar := compiler allocateTemporaryVariableNamed: 'end'.
-
-    id := compiler idFor: node.
-    compiler toTokenRememberStrategy.	
-    
-    compiler codeAssign: 'context position + 1.' to: startVar.
-    compiler codeStoreValueOf: [ self visit: node child ] intoVariable: #whatever.
-    compiler add: 'error ifFalse: [ '.
-    compiler indent.	
-        compiler codeAssign: 'context position.' to: endVar.
-    
-        compiler codeTranscriptShow: 'current token type: ', id storeString.
-        compiler codeAssign: id storeString, '.' to: 'currentTokenType'.
-        compiler codeAssign: node tokenClass asString, ' on: (context collection) 
-                                                                    start: ', startVar, '  
-                                                                    stop: ', endVar, '
-                                                                    value: nil.'
-                    to: 'currentTokenValue := ', self retvalVar.
-        compiler codeReturn.
-    compiler dedent.
-    compiler add: '].'.		
-    compiler toNormalRememberStrategy.
+    self error: 'shoudl not happend!!'
 !
 
 visitTokenizingParserNode: node
     self visit: node tokenizer.
+    self visit: node whitespace.
     
 "	compiler codeNextToken."
     compiler codeHaltIfShiftPressed.
@@ -133,41 +134,6 @@
 !
 
 visitTrimmingTokenNode: node
-    |  id  startVar endVar |
-    
-    startVar := compiler allocateTemporaryVariableNamed: 'start'.
-    endVar := compiler allocateTemporaryVariableNamed:  'end'.
-    
-    id := compiler idFor: node.
-    compiler toTokenRememberStrategy.
-    
-    
-    compiler addComment: 'Consume Whitespace:'.
-    compiler codeStoreValueOf: [ self visit: node whitespace ] intoVariable: #whatever.
-    compiler nl.
-
-    compiler codeAssign: 'context position + 1.' to: startVar.
-    compiler codeStoreValueOf: [ self visit: node child ] intoVariable: #whatever.
-
-    compiler add: 'error ifFalse: [ '.
-    compiler indent.	
-        compiler codeAssign: 'context position.' to: endVar.
-    
-        compiler addComment: 'Consume Whitespace:'.
-        compiler codeStoreValueOf: [ self visit: node whitespace ] intoVariable: #whatever.
-        compiler nl.
-    
-    
-        compiler codeTranscriptShow: 'current token type: ', id storeString.
-        compiler codeAssign: id storeString, '.' to: 'currentTokenType'.
-        compiler codeAssign: node tokenClass asString, ' on: (context collection) 
-                                                                start: ', startVar, ' 
-                                                                stop: ', endVar, '
-                                                                value: nil.'
-                   to: 'currentTokenValue := ', self retvalVar.
-        compiler codeReturn.
-    compiler dedent.																
-    compiler add: '].'	.
-    compiler toNormalRememberStrategy.
+    self error: 'shoudl not happend!!'
 ! !
 
--- a/compiler/PPCTokenizingCompiler.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCTokenizingCompiler.st	Tue May 12 01:33:33 2015 +0100
@@ -9,12 +9,6 @@
 	category:'PetitCompiler-Core'
 !
 
-!PPCTokenizingCompiler methodsFor:'accessing'!
-
-compiledParserSuperclass
-    ^ compiledParserSuperclass ifNil: [ PPTokenizingCompiledParser ]
-! !
-
 !PPCTokenizingCompiler methodsFor:'code generation'!
 
 smartRemember: parser to: variableName 
@@ -25,6 +19,20 @@
     rememberStrategy smartRestore: parser from: mementoName
 ! !
 
+!PPCTokenizingCompiler methodsFor:'hooks'!
+
+compiledParserSuperclass
+    ^ compiledParserSuperclass ifNil: [ PPTokenizingCompiledParser ]
+!
+
+rememberStrategy
+    ^ rememberStrategy ifNil: [ PPCCompilerTokenizingRememberStrategy on: self  ]
+!
+
+rememberStrategy: whatever
+    rememberStrategy := whatever 
+! !
+
 !PPCTokenizingCompiler methodsFor:'initialization'!
 
 initialize
--- a/compiler/PPCTokenizingParserNode.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCTokenizingParserNode.st	Tue May 12 01:33:33 2015 +0100
@@ -13,7 +13,7 @@
 
 initialize
     super initialize.
-    children := Array new: 2
+    children := Array new: 3
 !
 
 parser
@@ -34,6 +34,14 @@
 
 tokenizer: node
     ^ children at: 2 put: node
+!
+
+whitespace
+    ^ children at: 3
+!
+
+whitespace: node
+    children at: 3 put: node
 ! !
 
 !PPCTokenizingParserNode methodsFor:'visiting'!
--- a/compiler/PPCTokenizingVisitor.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPCTokenizingVisitor.st	Tue May 12 01:33:33 2015 +0100
@@ -11,25 +11,37 @@
 
 !PPCTokenizingVisitor methodsFor:'hooks'!
 
-afterAccept: node retval: retval
+afterAccept: node retval: parserNode
     self isRoot ifTrue: [ 
-        | tokenizerNode |
+        | tokenizerNode whitespaceNode |
         self change.
         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
+            ].
+        
         tokenizerNode := PPCTokenChoiceNode new
             children: tokens asArray;
             name: 'nextToken';
             yourself.
     
         ^ PPCTokenizingParserNode new
-            parser: retval;
+            parser: parserNode;
             tokenizer: tokenizerNode;
+            whitespace: whitespaceNode;
             name: #'mainParser';
             yourself
     ].
-    ^ retval
+    ^ parserNode
 
     "Modified: / 10-05-2015 / 07:27:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
--- a/compiler/PPTokenizingCompiledParser.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/PPTokenizingCompiledParser.st	Tue May 12 01:33:33 2015 +0100
@@ -23,6 +23,10 @@
     ]
 !
 
+consumeWhitespace
+    self shouldBeImplemented 
+!
+
 currentTokenType
     currentTokenType isNil ifTrue: [ self nextToken ].
     ^ currentTokenType
@@ -49,8 +53,24 @@
     self shouldBeImplemented 
 !
 
-parseOn: input
+parseOn: aPPContext
+    | retval |
+
+    context := aPPContext.
+    context compiledParser: self.
+    failure := PPFailure new message: nil; context: context; position: -1.
+    context noteFailure: failure.
+    error := false.
     currentTokenType := nil.
-    ^ super parseOn: input.
+
+    self consumeWhitespace.
+    retval := self perform: startSymbol.
+    self consumeWhitespace.
+
+    (retval isPetitFailure) ifTrue: [ aPPContext noteFailure: failure ].
+    error ifTrue: [ aPPContext noteFailure: failure. retval := failure ].
+    
+"	aPPContext position: context position."
+    ^ retval
 ! !
 
--- a/compiler/abbrev.stc	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/abbrev.stc	Tue May 12 01:33:33 2015 +0100
@@ -63,6 +63,7 @@
 PPCSequenceNode PPCSequenceNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCSpecializingVisitor PPCSpecializingVisitor stx:goodies/petitparser/compiler 'PetitCompiler-Visitors' 0
 PPCStarNode PPCStarNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCTokenCodeGenerator PPCTokenCodeGenerator stx:goodies/petitparser/compiler 'PetitCompiler-Visitors' 0
 PPCTokenConsumeNode PPCTokenConsumeNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCTokenDetector PPCTokenDetector stx:goodies/petitparser/compiler 'PetitCompiler-Visitors' 0
 PPCTokenNode PPCTokenNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
--- a/compiler/bc.mak	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/bc.mak	Tue May 12 01:33:33 2015 +0100
@@ -140,6 +140,7 @@
 $(OUTDIR)PPCSequenceNode.$(O) PPCSequenceNode.$(H): PPCSequenceNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCListNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCSpecializingVisitor.$(O) PPCSpecializingVisitor.$(H): PPCSpecializingVisitor.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNodeVisitor.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCRewritingVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCStarNode.$(O) PPCStarNode.$(H): PPCStarNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenCodeGenerator.$(O) PPCTokenCodeGenerator.$(H): PPCTokenCodeGenerator.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCCodeGenerator.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNodeVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenConsumeNode.$(O) PPCTokenConsumeNode.$(H): PPCTokenConsumeNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenDetector.$(O) PPCTokenDetector.$(H): PPCTokenDetector.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNodeVisitor.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCRewritingVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenNode.$(O) PPCTokenNode.$(H): PPCTokenNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/compiler/benchmarks/Make.proto	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/benchmarks/Make.proto	Tue May 12 01:33:33 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/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/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
--- a/compiler/benchmarks/PPCBenchmark.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/benchmarks/PPCBenchmark.st	Tue May 12 01:33:33 2015 +0100
@@ -30,7 +30,7 @@
     ].
     ^ (benchmarkSuiteClass  class:self) run
 
-  	"
+  		"
     PPCBenchmark run.
     "
 !
@@ -217,6 +217,68 @@
         self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
 ! !
 
+!PPCBenchmark methodsFor:'benchmarks - expression grammar'!
+
+benchmarkExpressionGrammar
+    | time |
+
+    self setupExpressionGrammar.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Expression Grammar'.
+!
+
+benchmarkExpressionGrammarCompiled
+    | time |
+
+    self setupExpressionGrammarCompiled.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Compiled Expression Grammar'.
+!
+
+benchmarkExpressionGrammarTokenized
+    | time |
+
+    self setupExpressionGrammarTokenized.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Tokenized Expression Grammar'.
+!
+
+benchmarkLL1ExpressionGrammar
+    | time |
+
+    self setupLL1ExpressionGrammar.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'LL1 Expression Grammar'.
+!
+
+benchmarkLL1ExpressionGrammarCompiled
+    | time |
+
+    self setupLL1ExpressionGrammarCompiled.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Compiled LL1 Expression Grammar'.
+!
+
+benchmarkLL1ExpressionGrammarTokenized
+    | time |
+
+    self setupLL1ExpressionGrammarTokenized.
+
+    time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+    
+    self reportInput: input time: time name: 'Tokenized LL1 Expression Grammar'.
+! !
+
 !PPCBenchmark methodsFor:'benchmarks - micro'!
 
 benchmarkAnyStar
@@ -243,6 +305,22 @@
 
 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
 
+benchmarkExpressionGrammarC
+    <setup: #setupExpressionGrammar>
+    <benchmark: 'Petit Expression Grammar - Standard'>
+    
+    input do: [ :source | parser parse: source withContext: context ]
+!
+
+benchmarkExpressionGrammarTokenizedC
+    <setup: #setupExpressionGrammarTokenized>
+    <teardown: #teardownExpressionGrammarTokenized>
+    <benchmark: 'Petit Expression Grammar - Tokenized'>
+    
+    
+    input do: [ :source | parser parse: source withContext: context ]
+!
+
 benchmarkJavaSyntaxC
     <setup: #setupJavaSyntax>
     <benchmark: 'Petit Java Parser - Standard'>
@@ -354,6 +432,34 @@
 
 !PPCBenchmark methodsFor:'setup & teardown'!
 
+setupExpressionGrammar
+    
+    parser := PPExpressionGrammar new.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources expressionSourcesMedium.
+!
+
+setupExpressionGrammarCompiled
+    
+    configuration := PPCConfiguration universal.
+    configuration arguments name: #PPCompiledExpressionGrammar.
+    parser := PPExpressionGrammar new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources expressionSourcesMedium.
+!
+
+setupExpressionGrammarTokenized
+    
+    configuration := PPCConfiguration LL1.
+    configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
+    parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources expressionSourcesMedium.
+!
+
 setupJavaSyntax
     
     parser := PPJavaSyntax new.
@@ -375,6 +481,34 @@
 "
 !
 
+setupLL1ExpressionGrammar
+    
+    parser := PPLL1ExpressionGrammar new.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources expressionSourcesBig.
+!
+
+setupLL1ExpressionGrammarCompiled
+    
+    configuration := PPCConfiguration universal.
+    configuration arguments name: #PPCompiledLL1ExpressionGrammar.
+    parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources expressionSourcesBig.
+!
+
+setupLL1ExpressionGrammarTokenized
+    
+    configuration := PPCConfiguration universal.
+    configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
+    parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
+    context := PPCContext new.
+    context initializeFor: parser.
+    input := sources expressionSourcesBig.
+!
+
 setupRBParser
     
     input := sources smalltalkSourcesBig.
@@ -434,6 +568,10 @@
     input := sources smalltalkSourcesBig.
 !
 
+teardownExpressionGrammarTokenized
+    parser class removeFromSystem.
+!
+
 teardownJavaSyntaxCompiled
     parser class removeFromSystem.
 "	
--- a/compiler/benchmarks/bc.mak	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/benchmarks/bc.mak	Tue May 12 01:33:33 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\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\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\libbasic
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
--- a/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Tue May 12 01:33:33 2015 +0100
@@ -16,15 +16,15 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitCompiler-Benchmarks-JanKurs.2
+    Name: PetitCompiler-Benchmarks-JanKurs.20150510144201
     Author: JanKurs
-    Time: 17-11-2014, 05:51:07.887 PM
-    UUID: d5e3a980-7871-487a-a232-e3ca93fc2483            
+    Time: 10-05-2015, 05:04:54.561 PM
+    UUID: d8e764fd-016b-46e2-9fc1-17c38c18f0e5    
     Repository: http://smalltalkhub.com/mc/JanKurs/PetitParser/main
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 24-11-2014 / 00:09:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-05-2015 / 01:19:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
@@ -73,6 +73,8 @@
     ^ #(
         #'stx:goodies/petitparser'    "PPContext - referenced by PPCBenchmark>>benchmarkSmalltalkParser"
         #'stx:goodies/petitparser/compiler'    "PPCConfiguration - referenced by PPCBenchmark>>benchmarkSmalltalkParserCompiled"
+        #'stx:goodies/petitparser/compiler/tests'    "PPExpressionGrammar - referenced by PPCBenchmark>>setupExpressionGrammar"
+        #'stx:goodies/petitparser/compiler/tests/extras'    "PPCResources - referenced by PPCBenchmark>>initialize"
         #'stx:goodies/petitparser/parsers/java'    "PPJavaSyntax - referenced by PPCBenchmark>>benchmarkJavaSyntax"
         #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCBenchmark>>setupSmalltalkGrammar"
         #'stx:goodies/refactoryBrowser/parser'    "RBParser - referenced by PPCBenchmark>>benchmarkRBParserC"
--- a/compiler/extensions.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/extensions.st	Tue May 12 01:33:33 2015 +0100
@@ -399,6 +399,14 @@
 
 !PPParser methodsFor:'*petitcompiler'!
 
+compileLL1
+    | configuration |
+    configuration := PPCConfiguration LL1.
+    ^ self compileWithConfiguration: configuration
+! !
+
+!PPParser methodsFor:'*petitcompiler'!
+
 compileWithConfiguration: configuration
     ^ configuration compile: self
 ! !
--- a/compiler/libInit.cc	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/libInit.cc	Tue May 12 01:33:33 2015 +0100
@@ -89,6 +89,7 @@
 _PPCSequenceNode_Init(pass,__pRT__,snd);
 _PPCSpecializingVisitor_Init(pass,__pRT__,snd);
 _PPCStarNode_Init(pass,__pRT__,snd);
+_PPCTokenCodeGenerator_Init(pass,__pRT__,snd);
 _PPCTokenConsumeNode_Init(pass,__pRT__,snd);
 _PPCTokenDetector_Init(pass,__pRT__,snd);
 _PPCTokenNode_Init(pass,__pRT__,snd);
--- a/compiler/stx_goodies_petitparser_compiler.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/stx_goodies_petitparser_compiler.st	Tue May 12 01:33:33 2015 +0100
@@ -16,15 +16,15 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitCompiler-JanKurs.111
+    Name: PetitCompiler-JanKurs.20150510144201
     Author: JanKurs
-    Time: 08-05-2015, 05:56:05.327 PM
-    UUID: 8805e696-9933-49b8-a5c8-a963b931b996                        
+    Time: 10-05-2015, 04:42:29.192 PM
+    UUID: 58a4786b-1182-4904-8b44-a13d3918f244
     Repository: http://smalltalkhub.com/mc/JanKurs/PetitParser/main
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 10-05-2015 / 06:20:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-05-2015 / 01:19:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
@@ -169,6 +169,7 @@
         PPCSequenceNode
         PPCSpecializingVisitor
         PPCStarNode
+        PPCTokenCodeGenerator
         PPCTokenConsumeNode
         PPCTokenDetector
         PPCTokenNode
@@ -302,6 +303,7 @@
         PPEndOfInputParser asCompilerNode
         PPParser allNodesDo:seen:
         PPSmalltalkWhitespaceParser hash
+        PPParser compileLL1
     )
 ! !
 
--- a/compiler/tests/Make.proto	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/Make.proto	Tue May 12 01:33:33 2015 +0100
@@ -155,6 +155,12 @@
 $(OUTDIR)PPCompiledExpressionGrammarTest.$(O) PPCompiledExpressionGrammarTest.$(H): PPCompiledExpressionGrammarTest.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)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)PPExpressionGrammarTest.$(O) PPExpressionGrammarTest.$(H): PPExpressionGrammarTest.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)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)PPLL1ExpressionGrammarTest.$(O) PPLL1ExpressionGrammarTest.$(H): PPLL1ExpressionGrammarTest.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)PPTokenizedExpressionGrammarResource.$(O) PPTokenizedExpressionGrammarResource.$(H): PPTokenizedExpressionGrammarResource.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestResource.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedExpressionGrammarTest.$(O) PPTokenizedExpressionGrammarTest.$(H): PPTokenizedExpressionGrammarTest.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)PPTokenizedLL1ExpressionGrammarResource.$(O) PPTokenizedLL1ExpressionGrammarResource.$(H): PPTokenizedLL1ExpressionGrammarResource.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestResource.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedLL1ExpressionGrammarTest.$(O) PPTokenizedLL1ExpressionGrammarTest.$(H): PPTokenizedLL1ExpressionGrammarTest.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.$(O) stx_goodies_petitparser_compiler_tests.$(H): stx_goodies_petitparser_compiler_tests.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/tests/Make.spec	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/Make.spec	Tue May 12 01:33:33 2015 +0100
@@ -78,6 +78,12 @@
 	PPCompiledExpressionGrammarTest \
 	PPExpressionGrammar \
 	PPExpressionGrammarTest \
+	PPLL1ExpressionGrammar \
+	PPLL1ExpressionGrammarTest \
+	PPTokenizedExpressionGrammarResource \
+	PPTokenizedExpressionGrammarTest \
+	PPTokenizedLL1ExpressionGrammarResource \
+	PPTokenizedLL1ExpressionGrammarTest \
 	stx_goodies_petitparser_compiler_tests \
 
 
@@ -111,6 +117,12 @@
     $(OUTDIR_SLASH)PPCompiledExpressionGrammarTest.$(O) \
     $(OUTDIR_SLASH)PPExpressionGrammar.$(O) \
     $(OUTDIR_SLASH)PPExpressionGrammarTest.$(O) \
+    $(OUTDIR_SLASH)PPLL1ExpressionGrammar.$(O) \
+    $(OUTDIR_SLASH)PPLL1ExpressionGrammarTest.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedExpressionGrammarResource.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedExpressionGrammarTest.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedLL1ExpressionGrammarResource.$(O) \
+    $(OUTDIR_SLASH)PPTokenizedLL1ExpressionGrammarTest.$(O) \
     $(OUTDIR_SLASH)stx_goodies_petitparser_compiler_tests.$(O) \
 
 
--- a/compiler/tests/PPCCodeGeneratorTest.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/PPCCodeGeneratorTest.st	Tue May 12 01:33:33 2015 +0100
@@ -365,21 +365,21 @@
 
 testInlinePluggableNode
    "Sadly, on Smalltalk/X blocks cannot be inlined because
-	 the VM does not provide enough information to map
-	 it back to source code. Very bad indeed!!"          
-	((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
-	    self skipIf: true description: 'Blocks cannot be inlined due to a lack of proper VM support'.
-	].
+		 the VM does not provide enough information to map
+		 it back to source code. Very bad indeed!!"          
+		((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
+			self skipIf: true description: 'Blocks cannot be inlined due to a lack of proper VM support'.
+		].
 
-	node := PPCSequenceNode new
-		children: { 
-			PPCPluggableNode new block: [ :ctx | ctx next ]; markForInline; yourself. 
-			$a asParser asCompilerNode }.
-	
-	self compileTree: node.
-	
-	self assert: parser class methodDictionary size = 2.
-	self assert: parser parse: 'ba' to: #($b $a).
+		node := PPCSequenceNode new
+				children: { 
+						PPCPluggableNode new block: [ :ctx | ctx next ]; markForInline; yourself. 
+						$a asParser asCompilerNode }.
+		
+		self compileTree: node.
+		
+		self assert: parser class methodDictionary size = 2.
+		self assert: parser parse: 'ba' to: #($b $a).
 !
 
 testLiteralNode
--- a/compiler/tests/PPCLL1Test.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/PPCLL1Test.st	Tue May 12 01:33:33 2015 +0100
@@ -36,7 +36,6 @@
 setUp
     arguments := PPCArguments default
         profile: true;
-        guards: false;
         yourself.
         
     configuration := PPCLL1Configuration new
--- a/compiler/tests/PPCTokenizingCodeGeneratorTest.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/PPCTokenizingCodeGeneratorTest.st	Tue May 12 01:33:33 2015 +0100
@@ -3,7 +3,8 @@
 "{ NameSpace: Smalltalk }"
 
 PPAbstractParserTest subclass:#PPCTokenizingCodeGeneratorTest
-	instanceVariableNames:'visitor node result compiler parser context arguments tokenizer'
+	instanceVariableNames:'visitor node result compiler parser context arguments tokenizer
+		whitespace'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Tests-Visitors'
@@ -30,6 +31,10 @@
     
 !
 
+compileWs: aNode
+    whitespace := visitor visit: aNode	
+!
+
 context	
     ^ context := PPCProfilingContext new
 !
@@ -133,7 +138,7 @@
 !PPCTokenizingCodeGeneratorTest methodsFor:'testing'!
 
 testSimpleChoice1
-    | token1 token2 token1Consume token2Consume  tokenizerNode eof choiceNode |
+    | token1 token2 token1Consume token2Consume  tokenizerNode eof choiceNode wsNode |
 
     token1 := (self tokenNodeForLiteral: 'foo') yourself.
     token2 := (self tokenNodeForLiteral: 'bar') yourself.
@@ -154,14 +159,15 @@
         children: { token1 . token2 . eof };
         name: 'nextToken';
         yourself.
+        
+    wsNode := PPCTokenStarSeparatorNode new
+        name: 'consumeWhitespace';
+        yourself.
     
+    self compileWs: wsNode.
     self compileTokenizer: tokenizerNode.
     self compileTree: choiceNode.
     
-    self assert: parser recognizesToken: 'foo'.
-    self assert: parser recognizesToken: 'bar'.
-    self assert: parser recognizesToken: ''.
-    
     parser := compiler compiledParser new.
     self assert: parser parse: 'foo'.
     self assert: result inputValue = 'foo'.
@@ -175,7 +181,7 @@
 !
 
 testTokenizingParserNode
-    |  tokenNode tokenizerNode consumeNode eof |
+    |  tokenNode tokenizerNode consumeNode eof wsNode |
     tokenNode := (self tokenNodeForLiteral: 'bar') yourself.
     eof := (self tokenNodeForEOF) yourself.	
         
@@ -186,18 +192,19 @@
     consumeNode := PPCTokenConsumeNode new
                             child: tokenNode;
                             yourself.
+    wsNode := PPCTokenStarSeparatorNode new
+        name: 'consumeWhitespace';
+        yourself.
+    
     node := PPCTokenizingParserNode new
         parser: consumeNode;
         tokenizer: tokenizerNode;
+        whitespace: wsNode;
         yourself.
 
     
     self compileTree: node.
     
-    self assert: parser recognizesToken: 'bar'.
-    self assert: parser recognizesToken: ''.
-    self assert: parser rejectsToken: 'foo'.
-    
     parser := compiler compiledParser new.
     self assert: parser parse: 'bar'.
     self assert: result inputValue = 'bar'.
@@ -207,7 +214,7 @@
 !
 
 testTrimmingToken1
-    | token tokenConsume tokenizerNode eof  |
+    | token tokenConsume tokenizerNode eof  wsNode |
 
     token := self trimmingTokenNode: (self literalNode: 'foo').
     eof := (self tokenNodeForEOF) yourself.
@@ -221,18 +228,25 @@
         name: 'nextToken';
         yourself.
     
+    wsNode := PPCTokenStarSeparatorNode new
+        name: 'consumeWhitespace';
+        yourself.
+    
+    self compileWs: wsNode.
     self compileTokenizer: tokenizerNode.
     self compileTree: tokenConsume.
-    
-    self assert: parser recognizesToken: 'foo'.
-    self assert: parser recognizesToken: ' foo'.
-    self assert: parser recognizesToken: ' '.
-    self assert: parser recognizesToken: ''.
+
     
     parser := compiler compiledParser new.
     self assert: parser parse: ' foo'.
     self assert: result inputValue = 'foo'.
 
+    
+    parser := compiler compiledParser new.
+    self assert: parser parse: ' foo  '.
+    self assert: result inputValue = 'foo'.
+
+
     parser := compiler compiledParser new.
     self assert: parser fail: 'baz'.	
 ! !
--- a/compiler/tests/PPCompiledExpressionGrammarResource.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/PPCompiledExpressionGrammarResource.st	Tue May 12 01:33:33 2015 +0100
@@ -14,8 +14,8 @@
 
 setUp
     | time configuration |
-    configuration := PPCLL1Configuration new.
-    configuration arguments name:#PPCompiledExpressionGrammar.
+    configuration := PPCConfiguration universal.
+    configuration arguments name: #PPCompiledExpressionGrammar.
     
     
     time := Time millisecondsToRun: [
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPLL1ExpressionGrammar.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,74 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCompositeParser subclass:#PPLL1ExpressionGrammar
+	instanceVariableNames:'add prod term mul prim parens number mulPrime addPrime termPrime'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-ExpressionGrammar'
+!
+
+!PPLL1ExpressionGrammar methodsFor:'as yet unclassified'!
+
+add
+   ^ prod, addPrime optional
+ 	map: [ :_prod :_addPrime |
+		_addPrime isNil 
+			ifTrue: [ _prod  ]
+			ifFalse: [ Array with: _prod withAll: _addPrime ]
+		
+	]
+!
+
+addPrime
+    ^ $+ asParser trimmingToken , term
+!
+
+mul
+   ^ prim, mulPrime optional
+ 	map: [ :_prim :_mulPrime |
+		_mulPrime isNil 
+			ifTrue: [ _prim  ]
+			ifFalse: [ Array with: _prim withAll: _mulPrime ]
+		
+	]
+!
+
+mulPrime
+   ^ $* asParser trimmingToken, prod
+!
+
+number
+   ^ #digit asParser plus trimmingToken ==> [ :token | token inputValue asNumber ]
+!
+
+parens
+   ^ ($( asParser token trim), term , ($) asParser token trim)
+!
+
+prim
+   ^ parens / number
+!
+
+prod
+   ^ mul
+!
+
+start
+   ^ term end
+!
+
+term
+    ^ prod, termPrime optional
+ 	map: [ :_prod :_termPrime |
+        _termPrime isNil 
+            ifTrue: [ _prod  ]
+            ifFalse: [ Array with: _prod withAll: _termPrime ]
+    ]	
+!
+
+termPrime
+    ^ $+ asParser trimmingToken, term
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPLL1ExpressionGrammarTest.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,100 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCompositeParserTest subclass:#PPLL1ExpressionGrammarTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-ExpressionGrammar'
+!
+
+!PPLL1ExpressionGrammarTest methodsFor:'as yet unclassified'!
+
+parserClass
+    ^ PPLL1ExpressionGrammar
+!
+
+testAdd
+    result := self parse: '1+2' rule: #add.
+    self assert: result isArray.
+    self assert: result first = 1.
+    self assert: result second inputValue = '+'.
+    self assert: result third = 2.
+!
+
+testMul
+    result := self parse: '1 * 2' rule: #mul.
+    self assert: result isArray.
+    self assert: result first = 1.
+    self assert: result second inputValue = '*'.
+    self assert: result third = 2.
+!
+
+testNumber
+    result := self parse: '1' rule: #number.
+    self assert: result = 1.
+!
+
+testParens
+    result := self parse: '(1)' rule: #parens.
+    self assert: result size = 3.
+    self assert: result first inputValue = '('.
+    self assert: result second = 1.
+    self assert: result third inputValue = ')'.
+    
+!
+
+testPrim
+    result := self parse: '1' rule: #prim.
+    self assert: result = 1.
+!
+
+testPrim2
+    result := self parse: '(1)' rule: #prim.
+    self assert: result size = 3.
+    self assert: result second = 1.
+!
+
+testProd
+    result := self parse: '1' rule: #prod.
+    self assert: result = 1.
+!
+
+testTerm
+    result := self parse: '1' rule: #term.
+    self assert: result = 1.
+    
+!
+
+testTerm11
+    result := self parse: '1 + 2' rule: #term.
+    self assert: result size = 3.
+    self assert: result first = 1.
+    self assert: result second inputValue = '+'.
+    self assert: result third = 2.
+    
+!
+
+testTerm12
+    result := self parse: '1 + 2 * 3' rule: #term.
+    self assert: result size = 3.
+    self assert: result second inputValue = '+'.
+    self assert: result first = 1.
+    self assert: result third isArray.
+    self assert: result third first = 2.
+    self assert: result third second inputValue = '*'.
+    self assert: result third third = 3.
+!
+
+testTerm13
+    result := self parse: '1 * 2 + 3' rule: #term.
+    self assert: result size = 3.
+    self assert: result first isArray.
+    self assert: result first first = 1.
+    self assert: result first second inputValue = '*'.
+    self assert: result first third = 2.	
+    self assert: result second inputValue = '+'.
+    self assert: result third = 3.
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPTokenizedExpressionGrammarResource.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,26 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+"{ NameSpace: Smalltalk }"
+
+TestResource subclass:#PPTokenizedExpressionGrammarResource
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-ExpressionGrammar'
+!
+
+!PPTokenizedExpressionGrammarResource methodsFor:'as yet unclassified'!
+
+setUp
+    | time configuration |
+    configuration := PPCLL1Configuration new.
+    configuration arguments name:#PPTokenizedExpressionGrammar.
+    
+    
+    time := Time millisecondsToRun: [
+        PPExpressionGrammar new compileWithConfiguration: configuration.
+    ].
+    Transcript crShow: 'Expression grammar tokenized in: ', time asString, 'ms'.
+    
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPTokenizedExpressionGrammarTest.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,130 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCompositeParserTest subclass:#PPTokenizedExpressionGrammarTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-ExpressionGrammar'
+!
+
+
+!PPTokenizedExpressionGrammarTest class methodsFor:'as yet unclassified'!
+
+resources
+    ^ (OrderedCollection with: PPTokenizedExpressionGrammarResource)
+        addAll: super resources;
+        yourself
+! !
+
+!PPTokenizedExpressionGrammarTest methodsFor:'as yet unclassified'!
+
+compilerArguments
+    ^ PPCArguments default
+        profile: true;
+        yourself
+!
+
+context
+    ^ PPCContext new
+!
+
+parserClass
+    ^ Smalltalk at: #PPTokenizedExpressionGrammar
+!
+
+parserInstanceFor: aSymbol
+    ^ (Smalltalk at: #PPTokenizedExpressionGrammar) new startSymbol: aSymbol
+!
+
+testAdd
+    result := self parse: '1+2' rule: #add.
+    self assert: result isArray.
+    self assert: result first = 1.
+    self assert: result second inputValue = '+'.
+    self assert: result third = 2.
+!
+
+testMul
+    result := self parse: '1 * 2' rule: #mul.
+    self assert: result isArray.
+    self assert: result first = 1.
+    self assert: result second inputValue = '*'.
+    self assert: result third = 2.
+!
+
+testNumber
+    result := self parse: '1' rule: #number.
+    self assert: result = 1.
+!
+
+testParens
+    result := self parse: '(1)' rule: #parens.
+    self assert: result size = 3.
+    self assert: result first inputValue = '('.
+    self assert: result second = 1.
+    self assert: result third inputValue = ')'.
+    
+!
+
+testPrim
+    result := self parse: '1' rule: #prim.
+    self assert: result = 1.
+!
+
+testPrim2
+    result := self parse: '(1)' rule: #prim.
+    self assert: result size = 3.
+    self assert: result second = 1.
+!
+
+testProd
+    result := self parse: '1' rule: #prod.
+    self assert: result = 1.
+!
+
+testTerm
+    result := self parse: '1' rule: #term.
+    self assert: result = 1.
+    
+!
+
+testTerm11
+    result := self parse: '1 + 2' rule: #term.
+    self assert: result size = 3.
+    self assert: result first = 1.
+    self assert: result second inputValue = '+'.
+    self assert: result third = 2.
+    
+!
+
+testTerm12
+    result := self parse: '1 + 2 * 3' rule: #term.
+    self assert: result size = 3.
+    self assert: result second inputValue = '+'.
+    self assert: result first = 1.
+    self assert: result third isArray.
+    self assert: result third first = 2.
+    self assert: result third second inputValue = '*'.
+    self assert: result third third = 3.	
+!
+
+testTerm13
+    result := self parse: '1 * 2 + 3' rule: #term.
+    self assert: result size = 3.
+    self assert: result first isArray.
+    self assert: result first first = 1.
+    self assert: result first second inputValue = '*'.
+    self assert: result first third = 2.	
+    self assert: result second inputValue = '+'.
+    self assert: result third = 3.
+! !
+
+!PPTokenizedExpressionGrammarTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPTokenizedLL1ExpressionGrammarResource.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,26 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+"{ NameSpace: Smalltalk }"
+
+TestResource subclass:#PPTokenizedLL1ExpressionGrammarResource
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-ExpressionGrammar'
+!
+
+!PPTokenizedLL1ExpressionGrammarResource methodsFor:'as yet unclassified'!
+
+setUp
+    | time configuration |
+    configuration := PPCLL1Configuration new.
+    configuration arguments name:#PPTokenizedLL1ExpressionGrammar.
+    
+    
+    time := Time millisecondsToRun: [
+        PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
+    ].
+    Transcript crShow: 'Expression grammar compiled in: ', time asString, 'ms'.
+    
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPTokenizedLL1ExpressionGrammarTest.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,123 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCompositeParserTest subclass:#PPTokenizedLL1ExpressionGrammarTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-ExpressionGrammar'
+!
+
+!PPTokenizedLL1ExpressionGrammarTest class methodsFor:'as yet unclassified'!
+
+resources
+    ^ (OrderedCollection with: PPTokenizedLL1ExpressionGrammarResource)
+        addAll: super resources;
+        yourself
+! !
+
+!PPTokenizedLL1ExpressionGrammarTest methodsFor:'as yet unclassified'!
+
+compilerArguments
+    ^ PPCArguments default
+        profile: true;
+        ll: true;
+        yourself
+!
+
+context
+    ^ PPCContext new
+!
+
+parserClass
+    ^ Smalltalk at: #PPTokenizedLL1ExpressionGrammar
+!
+
+parserInstanceFor: aSymbol
+    ^ (Smalltalk at: #PPCompiledExpressionGrammar) new startSymbol: aSymbol
+!
+
+testAdd
+    result := self parse: '1+2' rule: #add.
+    self assert: result isArray.
+    self assert: result first = 1.
+    self assert: result second inputValue = '+'.
+    self assert: result third = 2.
+!
+
+testMul
+    result := self parse: '1 * 2' rule: #mul.
+    self assert: result isArray.
+    self assert: result first = 1.
+    self assert: result second inputValue = '*'.
+    self assert: result third = 2.
+!
+
+testNumber
+    result := self parse: '1' rule: #number.
+    self assert: result = 1.
+!
+
+testParens
+    result := self parse: '(1)' rule: #parens.
+    self assert: result size = 3.
+    self assert: result first inputValue = '('.
+    self assert: result second = 1.
+    self assert: result third inputValue = ')'.
+    
+!
+
+testPrim
+    result := self parse: '1' rule: #prim.
+    self assert: result = 1.
+!
+
+testPrim2
+    result := self parse: '(1)' rule: #prim.
+    self assert: result size = 3.
+    self assert: result second = 1.
+!
+
+testProd
+    result := self parse: '1' rule: #prod.
+    self assert: result = 1.
+!
+
+testTerm
+    result := self parse: '1' rule: #term.
+    self assert: result = 1.
+    
+!
+
+testTerm11
+    result := self parse: '1 + 2' rule: #term.
+    self assert: result size = 3.
+    self assert: result first = 1.
+    self assert: result second inputValue = '+'.
+    self assert: result third = 2.
+    
+!
+
+testTerm12
+    result := self parse: '1 + 2 * 3' rule: #term.
+    self assert: result size = 3.
+    self assert: result second inputValue = '+'.
+    self assert: result first = 1.
+    self assert: result third isArray.
+    self assert: result third first = 2.
+    self assert: result third second inputValue = '*'.
+    self assert: result third third = 3.	
+!
+
+testTerm13
+    result := self parse: '1 * 2 + 3' rule: #term.
+    self assert: result size = 3.
+    self assert: result first isArray.
+    self assert: result first first = 1.
+    self assert: result first second inputValue = '*'.
+    self assert: result first third = 2.	
+    self assert: result second inputValue = '+'.
+    self assert: result third = 3.
+! !
+
--- a/compiler/tests/abbrev.stc	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/abbrev.stc	Tue May 12 01:33:33 2015 +0100
@@ -28,4 +28,10 @@
 PPCompiledExpressionGrammarTest PPCompiledExpressionGrammarTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
 PPExpressionGrammar PPExpressionGrammar stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 0
 PPExpressionGrammarTest PPExpressionGrammarTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
+PPLL1ExpressionGrammar PPLL1ExpressionGrammar stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 0
+PPLL1ExpressionGrammarTest PPLL1ExpressionGrammarTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
+PPTokenizedExpressionGrammarResource PPTokenizedExpressionGrammarResource stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
+PPTokenizedExpressionGrammarTest PPTokenizedExpressionGrammarTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
+PPTokenizedLL1ExpressionGrammarResource PPTokenizedLL1ExpressionGrammarResource stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
+PPTokenizedLL1ExpressionGrammarTest PPTokenizedLL1ExpressionGrammarTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-ExpressionGrammar' 1
 stx_goodies_petitparser_compiler_tests stx_goodies_petitparser_compiler_tests stx:goodies/petitparser/compiler/tests '* Projects & Packages *' 3
--- a/compiler/tests/bc.mak	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/bc.mak	Tue May 12 01:33:33 2015 +0100
@@ -102,6 +102,12 @@
 $(OUTDIR)PPCompiledExpressionGrammarTest.$(O) PPCompiledExpressionGrammarTest.$(H): PPCompiledExpressionGrammarTest.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)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)PPExpressionGrammarTest.$(O) PPExpressionGrammarTest.$(H): PPExpressionGrammarTest.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)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)PPLL1ExpressionGrammarTest.$(O) PPLL1ExpressionGrammarTest.$(H): PPLL1ExpressionGrammarTest.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)PPTokenizedExpressionGrammarResource.$(O) PPTokenizedExpressionGrammarResource.$(H): PPTokenizedExpressionGrammarResource.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestResource.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedExpressionGrammarTest.$(O) PPTokenizedExpressionGrammarTest.$(H): PPTokenizedExpressionGrammarTest.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)PPTokenizedLL1ExpressionGrammarResource.$(O) PPTokenizedLL1ExpressionGrammarResource.$(H): PPTokenizedLL1ExpressionGrammarResource.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestResource.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPTokenizedLL1ExpressionGrammarTest.$(O) PPTokenizedLL1ExpressionGrammarTest.$(H): PPTokenizedLL1ExpressionGrammarTest.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.$(O) stx_goodies_petitparser_compiler_tests.$(H): stx_goodies_petitparser_compiler_tests.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/tests/extras/Make.proto	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/Make.proto	Tue May 12 01:33:33 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/parsers/java -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk -I$(INCLUDE_TOP)/stx/goodies/petitparser/tests -I$(INCLUDE_TOP)/stx/goodies/sunit -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/parsers/java -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk -I$(INCLUDE_TOP)/stx/goodies/petitparser/tests -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic2
 
 
 # if you need any additional defines for embedded C code,
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/extras/PPCExpressionsVerificationTest.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,81 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests/extras' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPAbstractParserTest subclass:#PPCExpressionsVerificationTest
+	instanceVariableNames:'parser result context resource fileResources'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Extras-Tests-Expressions'
+!
+
+!PPCExpressionsVerificationTest class methodsFor:'as yet unclassified'!
+
+isAbstract
+    ^ self name = #PPCExpressionsVerificationTest
+!
+
+resources
+    ^ (OrderedCollection with: PPCResources)
+        addAll: super resources;
+        yourself
+! !
+
+!PPCExpressionsVerificationTest methodsFor:'accessing'!
+
+compiledGrammar
+    ^ self compiledGrammarClass new
+!
+
+compiledGrammarClass
+    self subclassResponsibility 
+!
+
+grammar
+    ^ PPExpressionGrammar new
+! !
+
+!PPCExpressionsVerificationTest methodsFor:'setup'!
+
+setUp
+    super setUp.
+    fileResources := (self resources detect: [:e | e = PPCResources ]) current.
+!
+
+tearDown
+    super tearDown.
+    "
+    self compiledSmalltalkGrammarClass isNil ifFalse:[ 
+        self compiledSmalltalkGrammarClass removeFromSystem
+    ].
+    "
+! !
+
+!PPCExpressionsVerificationTest methodsFor:'tests'!
+
+testExpressions
+    | compiledParser normalParser expected actual |
+    normalParser := self grammar.
+    compiledParser := self compiledGrammar.
+    
+    fileResources expressionSourcesBig do: [ :source |
+        expected := normalParser parse: source.
+        expected isPetitFailure ifFalse: [ 
+     		actual := (compiledParser parse: source withContext: self context). 
+            self assert: expected equals: actual.
+        ]
+    ].
+!
+
+testSanity
+    | compiledParser normalParser source |
+    normalParser := self grammar.
+    compiledParser := self compiledGrammar.
+    
+    source := fileResources expressionOfSize: 100. 
+    result := normalParser parse: source.
+    
+    self assert: ((result deepFlatten select: [ :e | e isNumber ]) size) = 100.
+    self assert: ((result deepFlatten select: [ :e | e isNumber ]) size) = 100.
+! !
+
--- a/compiler/tests/extras/PPCResources.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/PPCResources.st	Tue May 12 01:33:33 2015 +0100
@@ -3,12 +3,84 @@
 "{ NameSpace: Smalltalk }"
 
 TestResource subclass:#PPCResources
-	instanceVariableNames:''
+	instanceVariableNames:'cache'
 	classVariableNames:'javaCache'
 	poolDictionaries:''
 	category:'PetitCompiler-Extras-Tests-Support'
 !
 
+!PPCResources methodsFor:'expressions'!
+
+expressionOfSize: size
+    | stream |
+    stream := WriteStream on: (String new: size * 5).
+    self expressionOfSize: size stream: stream.
+    ^ stream contents
+!
+
+expressionOfSize: size stream: stream
+    | index rand |
+    index := 0.
+    rand := Random new.
+    
+    [index < size] whileTrue: [ 
+ 		(rand next < 0.1) ifTrue: [  
+            | subSize |
+            subSize := rand nextInt: (size - index - 1) + 1.
+            stream nextPutAll: ' ('.
+            self expressionOfSize: subSize stream: stream.
+            stream nextPutAll: ') '.
+            index := index + subSize.
+        ] ifFalse: [ 
+            stream nextPutAll: (rand nextInt: 10) asString.
+            index := index + 1.
+        ].
+    
+        (index < size) ifTrue: [ 
+ 			(rand next < 0.5) 
+                ifTrue: [  stream nextPutAll: ' + ' ] 
+                ifFalse: [ stream nextPutAll: ' * ' ]
+        ]
+    ]
+!
+
+expressionSourcesBig
+    | sources |
+    
+    cache at: #expressionSourcesBig ifAbsentPut: [ 
+        sources := OrderedCollection new.
+        
+        2000 timesRepeat: [ 
+            sources add: (self expressionOfSize: 200).
+        ].
+        sources	
+    ].
+
+    ^ cache at: #expressionSourcesBig
+    
+
+expressionSourcesMedium
+    | sources |
+    
+    cache at: #expressionSourcesMedium ifAbsentPut: [ 
+        sources := OrderedCollection new.
+        
+        1000 timesRepeat: [ 
+            sources add: (self expressionOfSize: 100).
+        ].
+        sources	
+    ].
+
+    ^ cache at: #expressionSourcesMedium
+    
+! !
+
+!PPCResources methodsFor:'initialization'!
+
+initialize
+    super initialize.
+    cache := IdentityDictionary new
+! !
 
 !PPCResources methodsFor:'java'!
 
--- a/compiler/tests/extras/PPCSmalltalkTests.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkTests.st	Tue May 12 01:33:33 2015 +0100
@@ -14,7 +14,6 @@
 setUp
     arguments := PPCArguments default
         profile: true;
-        guards: false;
         yourself.
         
     configuration := PPCLL1Configuration new
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/extras/PPCompiledExpressionsVerificationTest.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,35 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests/extras' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCExpressionsVerificationTest subclass:#PPCompiledExpressionsVerificationTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Extras-Tests-Expressions'
+!
+
+!PPCompiledExpressionsVerificationTest class methodsFor:'as yet unclassified'!
+
+resources
+    ^ (OrderedCollection with: PPCompiledExpressionGrammarResource)
+        addAll: super resources;
+        yourself
+! !
+
+!PPCompiledExpressionsVerificationTest methodsFor:'as yet unclassified'!
+
+compiledGrammarClass
+    ^ (Smalltalk at: #PPCompiledExpressionGrammar)
+! !
+
+!PPCompiledExpressionsVerificationTest methodsFor:'testing'!
+
+testExpressions
+    ^ super testExpressions
+!
+
+testSanity
+    ^ super testSanity
+! !
+
--- a/compiler/tests/extras/PPCompiledJavaSyntaxTest.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/PPCompiledJavaSyntaxTest.st	Tue May 12 01:33:33 2015 +0100
@@ -9,7 +9,6 @@
 	category:'PetitCompiler-Extras-Tests-Java'
 !
 
-
 !PPCompiledJavaSyntaxTest class methodsFor:'as yet unclassified'!
 
 resources
@@ -70,7 +69,7 @@
         parse:
         '{
             System.out.println("Hello World!!");
- 	       	System.out.println("Hello World!!");
+ 			   		System.out.println("Hello World!!");
         }'
         rule: #block
 !
@@ -107,9 +106,9 @@
 
     self parse: '
                     public class OddEven {
- 						private int input;
- 					  public static void main(String[] args) {
-     					OddEven number = new OddEven();
+ 												private int input;
+ 										  public static void main(String[] args) {
+     										OddEven number = new OddEven();
                             number.showDialog(); }
                     public void showDialog() {
        
--- a/compiler/tests/extras/PPCompiledSmalltalkVerificationTest.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/PPCompiledSmalltalkVerificationTest.st	Tue May 12 01:33:33 2015 +0100
@@ -9,7 +9,6 @@
 	category:'PetitCompiler-Extras-Tests-Smalltalk'
 !
 
-
 !PPCompiledSmalltalkVerificationTest class methodsFor:'as yet unclassified'!
 
 resources
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/extras/PPTokenizedExpressionsVerificationTest.st	Tue May 12 01:33:33 2015 +0100
@@ -0,0 +1,35 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests/extras' }"
+
+"{ NameSpace: Smalltalk }"
+
+PPCExpressionsVerificationTest subclass:#PPTokenizedExpressionsVerificationTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Extras-Tests-Expressions'
+!
+
+!PPTokenizedExpressionsVerificationTest class methodsFor:'as yet unclassified'!
+
+resources
+    ^ (OrderedCollection with: PPTokenizedExpressionGrammarResource)
+        addAll: super resources;
+        yourself
+! !
+
+!PPTokenizedExpressionsVerificationTest methodsFor:'as yet unclassified'!
+
+compiledGrammarClass
+    ^ (Smalltalk at: #PPTokenizedExpressionGrammar)
+! !
+
+!PPTokenizedExpressionsVerificationTest methodsFor:'testing'!
+
+testExpressions
+    ^ super testExpressions
+!
+
+testSanity
+    ^ super testSanity
+! !
+
--- a/compiler/tests/extras/PPTokenizedSmalltalkGrammarResource.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/PPTokenizedSmalltalkGrammarResource.st	Tue May 12 01:33:33 2015 +0100
@@ -37,3 +37,10 @@
 "
 ! !
 
+!PPTokenizedSmalltalkGrammarResource class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/abbrev.stc	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/abbrev.stc	Tue May 12 01:33:33 2015 +0100
@@ -2,6 +2,7 @@
 # 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
+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
@@ -12,5 +13,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
+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
+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	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/bc.mak	Tue May 12 01:33:33 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\parsers\java -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk -I$(INCLUDE_TOP)\stx\goodies\petitparser\tests -I$(INCLUDE_TOP)\stx\goodies\sunit -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\parsers\java -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk -I$(INCLUDE_TOP)\stx\goodies\petitparser\tests -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic2
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
--- a/compiler/tests/extras/stx_goodies_petitparser_compiler_tests_extras.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/extras/stx_goodies_petitparser_compiler_tests_extras.st	Tue May 12 01:33:33 2015 +0100
@@ -42,16 +42,16 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitCompiler-Extras-Tests-JanKurs.4
+    Name: PetitCompiler-Extras-Tests-JanKurs.20150510144201
     Author: JanKurs
-    Time: 08-05-2015, 05:56:46.180 PM
-    UUID: 4d4d4d23-c5bc-41ef-ad41-8a56528ddb42                    
+    Time: 10-05-2015, 04:59:25.308 PM
+    UUID: ef43bd1a-be60-4e88-b749-8b635622c969
     Repository: http://smalltalkhub.com/mc/JanKurs/PetitParser/main
 
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 10-05-2015 / 06:28:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-05-2015 / 01:20:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
@@ -103,7 +103,9 @@
     ^ #(
         #'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:"
     )
 !
 
@@ -129,6 +131,7 @@
         "<className> or (<className> attributes...) in load order"
         PPCCompiledJavaVerificationTest
         PPCResources
+        PPCExpressionsVerificationTest
         PPCSmalltalkTests
         PPCSmalltalkVerificationTest
         PPCompiledJavaResource
@@ -139,7 +142,9 @@
         PPTokenizedSmalltalkGrammarTests
         #'stx_goodies_petitparser_compiler_tests_extras'
         PPCompiledSmalltalkVerificationTest
+        PPCompiledExpressionsVerificationTest
         PPTokenizedSmalltalkVerificationTest
+        PPTokenizedExpressionsVerificationTest
     )
 !
 
--- a/compiler/tests/libInit.cc	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/libInit.cc	Tue May 12 01:33:33 2015 +0100
@@ -54,6 +54,12 @@
 _PPCompiledExpressionGrammarTest_Init(pass,__pRT__,snd);
 _PPExpressionGrammar_Init(pass,__pRT__,snd);
 _PPExpressionGrammarTest_Init(pass,__pRT__,snd);
+_PPLL1ExpressionGrammar_Init(pass,__pRT__,snd);
+_PPLL1ExpressionGrammarTest_Init(pass,__pRT__,snd);
+_PPTokenizedExpressionGrammarResource_Init(pass,__pRT__,snd);
+_PPTokenizedExpressionGrammarTest_Init(pass,__pRT__,snd);
+_PPTokenizedLL1ExpressionGrammarResource_Init(pass,__pRT__,snd);
+_PPTokenizedLL1ExpressionGrammarTest_Init(pass,__pRT__,snd);
 _stx_137goodies_137petitparser_137compiler_137tests_Init(pass,__pRT__,snd);
 
 
--- a/compiler/tests/stx_goodies_petitparser_compiler_tests.st	Mon May 11 18:31:26 2015 +0100
+++ b/compiler/tests/stx_goodies_petitparser_compiler_tests.st	Tue May 12 01:33:33 2015 +0100
@@ -16,16 +16,15 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitCompiler-Tests-JanKurs.21
+    Name: PetitCompiler-Tests-JanKurs.20150510144201
     Author: JanKurs
-    Time: 17-11-2014, 05:51:53.134 PM
-    UUID: 8d6c0799-14e7-4871-8d91-8b0f9886db83           
+    Time: 10-05-2015, 04:32:12.870 PM
+    UUID: 2a8fd41a-331b-4dcf-a7a3-752a50ce86e7   
     Repository: http://smalltalkhub.com/mc/JanKurs/PetitParser/main
-
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 21-11-2014 / 12:40:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-05-2015 / 01:20:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
@@ -135,6 +134,12 @@
         PPCompiledExpressionGrammarTest
         PPExpressionGrammar
         PPExpressionGrammarTest
+        PPLL1ExpressionGrammar
+        PPLL1ExpressionGrammarTest
+        PPTokenizedExpressionGrammarResource
+        PPTokenizedExpressionGrammarTest
+        PPTokenizedLL1ExpressionGrammarResource
+        PPTokenizedLL1ExpressionGrammarTest
         #'stx_goodies_petitparser_compiler_tests'
     )
 !
--- a/islands/PPWater.st	Mon May 11 18:31:26 2015 +0100
+++ b/islands/PPWater.st	Tue May 12 01:33:33 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitIslands-Parsers'
 !
 
+
 !PPWater class methodsFor:'as yet unclassified'!
 
 on: parser
@@ -80,3 +81,10 @@
 	^ waterToken := aPPParser
 ! !
 
+!PPWater class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/islands/stx_goodies_petitparser_islands.st	Mon May 11 18:31:26 2015 +0100
+++ b/islands/stx_goodies_petitparser_islands.st	Tue May 12 01:33:33 2015 +0100
@@ -75,7 +75,10 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
--- a/islands/tests/stx_goodies_petitparser_islands_tests.st	Mon May 11 18:31:26 2015 +0100
+++ b/islands/tests/stx_goodies_petitparser_islands_tests.st	Tue May 12 01:33:33 2015 +0100
@@ -63,7 +63,10 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
--- a/tests/PPConditionalParserTests.st	Mon May 11 18:31:26 2015 +0100
+++ b/tests/PPConditionalParserTests.st	Tue May 12 01:33:33 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitTests-Tests'
 !
 
+
 !PPConditionalParserTests methodsFor:'as yet unclassified'!
 
 context
@@ -49,3 +50,10 @@
 	self assert: parser fail: 'b'.
 ! !
 
+!PPConditionalParserTests class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+