Merged JK's version from Monticello
authorJan Vrany <jan.vrany@fit.cvut.cz>
Mon, 24 Nov 2014 00:09:23 +0000
changeset 421 7e08b31e0dae
parent 420 b2f2f15cef26
child 422 116d2b2af905
Merged JK's version from Monticello Name: PetitParser-JanKurs.260 Author: JanKurs Time: 17-11-2014, 12:09:05.490 PM UUID: 07411cef-ef69-40db-9d93-d4018a9b34ef Name: PetitTests-JanKurs.65 Author: JanKurs Time: 17-11-2014, 12:09:04.530 PM UUID: f98d613f-f4ce-4e0e-a7e9-310ee7c7e7a6 Name: PetitSmalltalk-JanKurs.78 Author: JanKurs Time: 14-11-2014, 05:05:07.765 PM UUID: 3d68330d-44d5-46c3-9705-97f627b3edbc Name: PetitCompiler-JanKurs.71 Author: JanKurs Time: 18-11-2014, 09:48:35.425 AM UUID: 06352c33-3c76-4382-8536-0cc48e225117 Name: PetitCompiler-Tests-JanKurs.21 Author: JanKurs Time: 17-11-2014, 05:51:53.134 PM UUID: 8d6c0799-14e7-4871-8d91-8b0f9886db83 Name: PetitCompiler-Benchmarks-JanKurs.2 Author: JanKurs Time: 17-11-2014, 05:51:07.887 PM UUID: d5e3a980-7871-487a-a232-e3ca93fc2483
Make.proto
Make.spec
PPContext.st
PPContextMemento.st
PPEndOfLineParser.st
PPLimitedChoiceParser.st
PPListParser.st
PPParser.st
PPPluggableParser.st
PPSequenceParser.st
PPStartOfLineParser.st
PPStream.st
PPToken.st
abbrev.stc
analyzer/Make.spec
analyzer/analyzer.rc
analyzer/bc.mak
bc.mak
compiler/Make.proto
compiler/Make.spec
compiler/PPCAbstractActionNode.st
compiler/PPCAbstractCharacterNode.st
compiler/PPCAbstractLiteralNode.st
compiler/PPCAbstractPredicateNode.st
compiler/PPCActionNode.st
compiler/PPCChoiceNode.st
compiler/PPCCompiler.st
compiler/PPCContext.st
compiler/PPCForwardNode.st
compiler/PPCInlineLiteralNode.st
compiler/PPCInlineNotLiteralNode.st
compiler/PPCInlinePluggableNode.st
compiler/PPCInlineTokenStarMessagePredicateNode.st
compiler/PPCInlineTokenStarSeparatorNode.st
compiler/PPCListNode.st
compiler/PPCMessagePredicateNode.st
compiler/PPCNilNode.st
compiler/PPCNode.st
compiler/PPCNotLiteralNode.st
compiler/PPCNotMessagePredicateNode.st
compiler/PPCOptionalNode.st
compiler/PPCPluggableNode.st
compiler/PPCPlusNode.st
compiler/PPCSentinelNode.st
compiler/PPCSequenceNode.st
compiler/PPCStarAnyNode.st
compiler/PPCStarCharSetPredicateNode.st
compiler/PPCStarMessagePredicateNode.st
compiler/PPCStarNode.st
compiler/PPCTokenActionNode.st
compiler/PPCTokenNode.st
compiler/PPCTokenStarMessagePredicateNode.st
compiler/PPCTokenStarSeparatorNode.st
compiler/PPCTrimNode.st
compiler/PPCTrimmingTokenNode.st
compiler/PPCUnknownNode.st
compiler/PPCompiledParser.st
compiler/abbrev.stc
compiler/bc.mak
compiler/benchmarks/PPCBenchmark.st
compiler/benchmarks/PPCBenchmarkResources.st
compiler/benchmarks/abbrev.stc
compiler/benchmarks/benchmarks.rc
compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st
compiler/compiler.rc
compiler/extensions.st
compiler/libInit.cc
compiler/stx_goodies_petitparser_compiler.st
compiler/tests/Make.proto
compiler/tests/Make.spec
compiler/tests/PPCCompilerTest.st
compiler/tests/PPCGuardTest.st
compiler/tests/PPCNodeCompilingTest.st
compiler/tests/PPCNodeFirstFollowNextTests.st
compiler/tests/PPCNodeTest.st
compiler/tests/PPCOptimizingTest.st
compiler/tests/PPCompiledSmalltalkGrammarResource.st
compiler/tests/abbrev.stc
compiler/tests/bc.mak
compiler/tests/libInit.cc
compiler/tests/stx_goodies_petitparser_compiler_tests.st
compiler/tests/tests.rc
extensions.st
libInit.cc
parsers/smalltalk/Make.spec
parsers/smalltalk/PPSmalltalkWhitespaceParser.st
parsers/smalltalk/bc.mak
parsers/smalltalk/smalltalk.rc
parsers/smalltalk/stx_goodies_petitparser_parsers_smalltalk.st
parsers/smalltalk/tests/Make.spec
parsers/smalltalk/tests/PPSmalltalkGrammarTests.st
parsers/smalltalk/tests/PPSmalltalkParserTests.st
parsers/smalltalk/tests/bc.mak
parsers/smalltalk/tests/stx_goodies_petitparser_parsers_smalltalk_tests.st
parsers/smalltalk/tests/tests.rc
petitparser.rc
stx_goodies_petitparser.st
tests/Make.spec
tests/PPContextMementoTest.st
tests/PPContextTest.st
tests/PPPredicateTest.st
tests/bc.mak
tests/tests.rc
--- a/Make.proto	Wed Nov 19 10:52:37 2014 +0000
+++ b/Make.proto	Mon Nov 24 00:09:23 2014 +0000
@@ -63,7 +63,7 @@
 
 all:: preMake classLibRule postMake
 
-pre_objs::
+pre_objs::  
 
 
 mc:
@@ -71,7 +71,7 @@
 
 mcz: mc
 	$(TOP)/projects/smalltalk/smalltalk --eval "                            \
-	        Class tryLocalSourceFirst: true.				\
+		Class tryLocalSourceFirst: true.				\
 		Smalltalk packagePath add:'$(TOP)/..' .                       \
 		Smalltalk loadPackage:'stx:goodies/petitparser'.              \
 		(Smalltalk at: #'stx_goodies_petitparser') exportAsMczTo: 'mc'."
@@ -165,6 +165,7 @@
 $(OUTDIR)PPToken.$(O) PPToken.$(H): PPToken.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)stx_goodies_petitparser.$(O) stx_goodies_petitparser.$(H): stx_goodies_petitparser.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
 $(OUTDIR)PPDelegateParser.$(O) PPDelegateParser.$(H): PPDelegateParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPEndOfLineParser.$(O) PPEndOfLineParser.$(H): PPEndOfLineParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPEpsilonParser.$(O) PPEpsilonParser.$(H): PPEpsilonParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPFailingParser.$(O) PPFailingParser.$(H): PPFailingParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPListParser.$(O) PPListParser.$(H): PPListParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -172,6 +173,7 @@
 $(OUTDIR)PPPluggableParser.$(O) PPPluggableParser.$(H): PPPluggableParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPPredicateParser.$(O) PPPredicateParser.$(H): PPPredicateParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPStartOfLine.$(O) PPStartOfLine.$(H): PPStartOfLine.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPStartOfLineParser.$(O) PPStartOfLineParser.$(H): PPStartOfLineParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPUnresolvedParser.$(O) PPUnresolvedParser.$(H): PPUnresolvedParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPActionParser.$(O) PPActionParser.$(H): PPActionParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPAndParser.$(O) PPAndParser.$(H): PPAndParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -190,6 +192,7 @@
 $(OUTDIR)PPRepeatingParser.$(O) PPRepeatingParser.$(H): PPRepeatingParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPSequenceParser.$(O) PPSequenceParser.$(H): PPSequenceParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPListParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPTrimmingParser.$(O) PPTrimmingParser.$(H): PPTrimmingParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPLimitedChoiceParser.$(O) PPLimitedChoiceParser.$(H): PPLimitedChoiceParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPChoiceParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPListParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPLimitedRepeatingParser.$(O) PPLimitedRepeatingParser.$(H): PPLimitedRepeatingParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPRepeatingParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPPossessiveRepeatingParser.$(O) PPPossessiveRepeatingParser.$(H): PPPossessiveRepeatingParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPRepeatingParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPTokenParser.$(O) PPTokenParser.$(H): PPTokenParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPFlattenParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -42,6 +42,7 @@
 #  -warnNonStandard : no warnings about ST/X extensions
 #  -warnEOLComments : no warnings about EOL comment extension
 #  -warnPrivacy     : no warnings about privateClass extension
+#  -warnUnused      : no warnings about unused variables
 #
 # ********** OPTIONAL: MODIFY the next line(s) ***
 # STCWARNINGS=-warn
@@ -60,6 +61,7 @@
 	PPToken \
 	stx_goodies_petitparser \
 	PPDelegateParser \
+	PPEndOfLineParser \
 	PPEpsilonParser \
 	PPFailingParser \
 	PPListParser \
@@ -67,6 +69,7 @@
 	PPPluggableParser \
 	PPPredicateParser \
 	PPStartOfLine \
+	PPStartOfLineParser \
 	PPUnresolvedParser \
 	PPActionParser \
 	PPAndParser \
@@ -85,6 +88,7 @@
 	PPRepeatingParser \
 	PPSequenceParser \
 	PPTrimmingParser \
+	PPLimitedChoiceParser \
 	PPLimitedRepeatingParser \
 	PPPossessiveRepeatingParser \
 	PPTokenParser \
@@ -106,6 +110,7 @@
     $(OUTDIR_SLASH)PPToken.$(O) \
     $(OUTDIR_SLASH)stx_goodies_petitparser.$(O) \
     $(OUTDIR_SLASH)PPDelegateParser.$(O) \
+    $(OUTDIR_SLASH)PPEndOfLineParser.$(O) \
     $(OUTDIR_SLASH)PPEpsilonParser.$(O) \
     $(OUTDIR_SLASH)PPFailingParser.$(O) \
     $(OUTDIR_SLASH)PPListParser.$(O) \
@@ -113,6 +118,7 @@
     $(OUTDIR_SLASH)PPPluggableParser.$(O) \
     $(OUTDIR_SLASH)PPPredicateParser.$(O) \
     $(OUTDIR_SLASH)PPStartOfLine.$(O) \
+    $(OUTDIR_SLASH)PPStartOfLineParser.$(O) \
     $(OUTDIR_SLASH)PPUnresolvedParser.$(O) \
     $(OUTDIR_SLASH)PPActionParser.$(O) \
     $(OUTDIR_SLASH)PPAndParser.$(O) \
@@ -131,6 +137,7 @@
     $(OUTDIR_SLASH)PPRepeatingParser.$(O) \
     $(OUTDIR_SLASH)PPSequenceParser.$(O) \
     $(OUTDIR_SLASH)PPTrimmingParser.$(O) \
+    $(OUTDIR_SLASH)PPLimitedChoiceParser.$(O) \
     $(OUTDIR_SLASH)PPLimitedRepeatingParser.$(O) \
     $(OUTDIR_SLASH)PPPossessiveRepeatingParser.$(O) \
     $(OUTDIR_SLASH)PPTokenParser.$(O) \
--- a/PPContext.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPContext.st	Mon Nov 24 00:09:23 2014 +0000
@@ -198,9 +198,17 @@
 restoreProperties: aPPContextMemento
 	aPPContextMemento stream == stream ifFalse: [ self error: 'Oops!!' ].
 	
+	properties ifNil: [ ^ self ].
+	
+	properties keysDo: [ :key |
+		(aPPContextMemento hasProperty: key)
+			ifTrue: [ properties at: key put: (aPPContextMemento propertyAt: key) ]
+			ifFalse: [ properties removeKey: key  ]. 
+	].
+
 	aPPContextMemento keysAndValuesDo: [ :key :value |
-		self propertyAt: key put: value
-	].
+		properties at: key put: value
+	]
 ! !
 
 !PPContext methodsFor:'stream mimicry'!
@@ -257,6 +265,36 @@
 	^ stream skip: anInteger 
 !
 
+skipTo: anObject 
+	^ stream skipTo: anObject 
+!
+
+skipToAll: aString
+	"Set the access position of the receiver to be past the next occurrence of the subCollection. Answer whether subCollection is found.  No wildcards, and case does matter."
+	| pattern startMatch |
+	pattern := aString readStream.
+	startMatch := nil.
+	[ pattern atEnd ] whileFalse: 
+		[ stream atEnd ifTrue: [ ^ false ].
+		stream next = pattern next 
+			ifTrue: [ pattern position = 1 ifTrue: [ startMatch := stream position ] ]
+			ifFalse: 
+				[ pattern position: 0.
+				startMatch ifNotNil: 
+					[ stream position: startMatch.
+					startMatch := nil ] ] ].
+	^ true
+!
+
+skipToAnyOf: aCharacterSet 
+	"Set the access position of the receiver to be past the next occurrence of
+	a character in the character set. Answer whether a fitting character is found."
+
+	[stream atEnd]
+		whileFalse: [ (aCharacterSet includes: stream next) ifTrue: [^true]].
+	^false
+!
+
 uncheckedPeek
 	^ stream uncheckedPeek
 !
--- a/PPContextMemento.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPContextMemento.st	Mon Nov 24 00:09:23 2014 +0000
@@ -50,18 +50,16 @@
 !
 
 propertyAt: aKey ifAbsent: aBlock
-        "Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
-
-        properties isNil
-                ifTrue: [ ^  aBlock value ]
-                ifFalse: [ 
-                        (properties includesKey: aKey) ifTrue: [ 
-                                ^ (properties at: aKey) copy
-                        ].
-                        ^ aBlock value
-                ]
-
-    "Created: / 03-10-2014 / 02:17:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	"Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
+	
+	properties isNil
+		ifTrue: [ ^ aBlock value ]
+		ifFalse: [ 
+			(properties includesKey: aKey) ifTrue: [ 
+				^ (properties at: aKey) copy
+			].
+			^ aBlock value
+		]
 !
 
 propertyAt: aKey ifAbsentPut: aBlock
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PPEndOfLineParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,18 @@
+"{ Package: 'stx:goodies/petitparser' }"
+
+PPParser subclass:#PPEndOfLineParser
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitParser-Parsers'
+!
+
+!PPEndOfLineParser methodsFor:'parsing'!
+
+parseOn: aPPContext
+	(aPPContext isEndOfLine) ifTrue: [ 
+		^ #endOfLine
+	].
+	^ PPFailure message: 'End of line expected' context: aPPContext at: aPPContext position
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PPLimitedChoiceParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,54 @@
+"{ Package: 'stx:goodies/petitparser' }"
+
+PPChoiceParser subclass:#PPLimitedChoiceParser
+	instanceVariableNames:'limit'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitParser-Parsers'
+!
+
+!PPLimitedChoiceParser methodsFor:'accessing'!
+
+limit
+	
+	^ limit
+!
+
+limit: anObject
+	
+	limit := anObject
+! !
+
+!PPLimitedChoiceParser methodsFor:'as yet unclassified'!
+
+// aRule 
+	^ self copyWith: aRule
+!
+
+initialize
+	limit := nil asParser
+!
+
+parseOn: aPPContext
+	"This is optimized code that avoids unnecessary block activations, do not change. When all choices fail, the last failure is answered."
+
+	| element limitResult memento |
+	"self halt."
+	1 to: parsers size do: [ :index |
+		memento := aPPContext remember.
+		
+		element := (parsers at: index)
+			parseOn: aPPContext.
+		
+		(element isPetitFailure not) ifTrue: [ 
+			"check limit"
+			limitResult := limit parseOn: aPPContext.
+			limitResult isPetitFailure ifTrue: [ 
+				element := PPFailure message: 'limit failed' at: aPPContext position .
+				aPPContext restore: memento.
+			] ifFalse: [ ^ element ].
+		].
+	].	
+	^ element
+! !
+
--- a/PPListParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPListParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -19,37 +19,12 @@
 !
 
 withAll: aCollection
-	^ self basicNew setParsers: aCollection
+	^ self basicNew initialize;
+		setParsers: aCollection
 ! !
 
-!PPListParser methodsFor:'*petitanalyzer-matching'!
 
-copyInContext: aDictionary seen: aSeenDictionary
-	| copy copies |
-	aSeenDictionary at: self ifPresent: [ :value | ^ value ].
-	copy := aSeenDictionary at: self put: self copy.
-	copies := OrderedCollection new.
-	parsers do: [ :each |
-		| result |
-		result := each 
-			copyInContext: aDictionary
-			seen: aSeenDictionary.
-		result isCollection
-			ifTrue: [ copies addAll: result ]
-			ifFalse: [ copies add: result ] ].
-	^ copy
-		setParsers: copies;
-		yourself
-! !
 
-!PPListParser methodsFor:'*petitanalyzer-transforming'!
-
-replace: aParser with: anotherParser
-	super replace: aParser with: anotherParser.
-	parsers keysAndValuesDo: [ :index :parser |
-		parser == aParser
-			ifTrue: [ parsers at: index put: anotherParser ] ]
-! !
 
 !PPListParser methodsFor:'accessing'!
 
--- a/PPParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -26,6 +26,7 @@
 
 
 
+
 !PPParser methodsFor:'accessing'!
 
 children
@@ -302,6 +303,17 @@
 	^ self trimSpaces
 ! !
 
+!PPParser methodsFor:'operators'!
+
+// aParser 
+	"
+		Answer a new parser that parses the receiver, if the receiver fails try with aParser (ordered-choice).
+		If the receiver passes, limit must pass as well.
+	"
+	
+	^ PPLimitedChoiceParser with: self with: aParser
+! !
+
 !PPParser methodsFor:'operators-convenience'!
 
 withoutSeparators
--- a/PPPluggableParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPPluggableParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -15,6 +15,7 @@
 ! !
 
 
+
 !PPPluggableParser methodsFor:'accessing'!
 
 block
@@ -31,6 +32,10 @@
 
 !PPPluggableParser methodsFor:'parsing'!
 
+acceptsEpsilon
+	^ false
+!
+
 parseOn: aPPContext
 	| memento result |
 	memento := aPPContext remember.
--- a/PPSequenceParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPSequenceParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -9,6 +9,8 @@
 
 
 
+
+
 !PPSequenceParser methodsFor:'operations'!
 
 , aRule
@@ -60,6 +62,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPSequenceParser.st,v 1.4 2014-03-04 14:33:25 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: PPSequenceParser.st,v 1.4 2014-03-04 14:33:25 cg Exp $'
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PPStartOfLineParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,18 @@
+"{ Package: 'stx:goodies/petitparser' }"
+
+PPParser subclass:#PPStartOfLineParser
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitParser-Parsers'
+!
+
+!PPStartOfLineParser methodsFor:'parsing'!
+
+parseOn: aPPContext
+	(aPPContext isStartOfLine) ifTrue: [ 
+		^ #startOfLine
+	].
+	^ PPFailure message: 'Start of line expected' context: aPPContext at: aPPContext position
+! !
+
--- a/PPStream.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPStream.st	Mon Nov 24 00:09:23 2014 +0000
@@ -72,6 +72,32 @@
 
 !PPStream methodsFor:'queries'!
 
+column
+	^ self column: position.
+!
+
+column: pos
+	| column clear tmp |
+	
+	pos > readLimit ifTrue: [ ^ Error signal: 'Oot of bounds' ].	
+
+	tmp := position.
+	column := 0.	
+	clear := true.
+
+	(0 to: pos) do: 
+	[:index |
+		position := index.
+		self isStartOfLine ifTrue: [ clear := true ].
+
+		clear ifTrue: [ column := 0. clear := false ].
+		column := column + 1.
+		(position > readLimit) ifTrue: [ position := tmp. ^ column ].
+	].
+	position := tmp.
+	^ column
+!
+
 insideCRLF
 	(position < 1) ifTrue: [ ^ false ].
 	
@@ -90,6 +116,27 @@
 	self insideCRLF ifTrue: [ ^ false ].
 	
 	^ (self peekBack = (Character codePoint: 13)) or: [ self peekBack = (Character codePoint: 10)].
+!
+
+line
+	^ self line: position
+!
+
+line: pos
+	| tmp line |
+	(pos = -1) ifTrue: [  ^ 0 ].
+	(pos > readLimit) ifTrue: [ ^ self error: 'Out of limit' ].
+	
+	tmp := position.
+	line := 0.
+	
+	(0 to: pos) do: 
+	[:index |
+		position := index.
+		self isStartOfLine ifTrue: [ line := line + 1 ]
+	].
+	position := tmp.
+	^ line
 ! !
 
 !PPStream class methodsFor:'documentation'!
--- a/PPToken.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/PPToken.st	Mon Nov 24 00:09:23 2014 +0000
@@ -35,15 +35,6 @@
 		value: anObject
 ! !
 
-!PPToken methodsFor:'*petitcompiler'!
-
-= anObject
-	^ self class = anObject class and: [ self inputValue = anObject inputValue ]
-!
-
-hash
-	^ self inputValue hash
-! !
 
 !PPToken methodsFor:'accessing'!
 
@@ -90,6 +81,16 @@
 	^ self inputValue
 ! !
 
+!PPToken methodsFor:'comparing'!
+
+= anObject
+	^ self class = anObject class and: [ self parsedValue = anObject parsedValue ]
+!
+
+hash
+	^ self parsedValue hash
+! !
+
 !PPToken methodsFor:'copying'!
 
 copyFrom: aStartInteger to: aStopInteger
--- a/abbrev.stc	Wed Nov 19 10:52:37 2014 +0000
+++ b/abbrev.stc	Mon Nov 24 00:09:23 2014 +0000
@@ -11,6 +11,7 @@
 PPToken PPToken stx:goodies/petitparser 'PetitParser-Core' 0
 stx_goodies_petitparser stx_goodies_petitparser stx:goodies/petitparser '* Projects & Packages *' 3
 PPDelegateParser PPDelegateParser stx:goodies/petitparser 'PetitParser-Parsers' 0
+PPEndOfLineParser PPEndOfLineParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPEpsilonParser PPEpsilonParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPFailingParser PPFailingParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPListParser PPListParser stx:goodies/petitparser 'PetitParser-Parsers' 0
@@ -18,6 +19,7 @@
 PPPluggableParser PPPluggableParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPPredicateParser PPPredicateParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPStartOfLine PPStartOfLine stx:goodies/petitparser 'PetitParser-Parsers' 0
+PPStartOfLineParser PPStartOfLineParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPUnresolvedParser PPUnresolvedParser stx:goodies/petitparser 'PetitParser-Tools' 0
 PPActionParser PPActionParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPAndParser PPAndParser stx:goodies/petitparser 'PetitParser-Parsers' 0
@@ -36,6 +38,7 @@
 PPRepeatingParser PPRepeatingParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPSequenceParser PPSequenceParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPTrimmingParser PPTrimmingParser stx:goodies/petitparser 'PetitParser-Parsers' 0
+PPLimitedChoiceParser PPLimitedChoiceParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPLimitedRepeatingParser PPLimitedRepeatingParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPPossessiveRepeatingParser PPPossessiveRepeatingParser stx:goodies/petitparser 'PetitParser-Parsers' 0
 PPTokenParser PPTokenParser stx:goodies/petitparser 'PetitParser-Parsers' 0
--- a/analyzer/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/analyzer/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -42,6 +42,7 @@
 #  -warnNonStandard : no warnings about ST/X extensions
 #  -warnEOLComments : no warnings about EOL comment extension
 #  -warnPrivacy     : no warnings about privateClass extension
+#  -warnUnused      : no warnings about unused variables
 #
 # ********** OPTIONAL: MODIFY the next line(s) ***
 # STCWARNINGS=-warn
--- a/analyzer/analyzer.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/analyzer/analyzer.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -4,7 +4,7 @@
 //
 VS_VERSION_INFO VERSIONINFO
   FILEVERSION     6,2,32767,32767
-  PRODUCTVERSION  6,2,4,0
+  PRODUCTVERSION  6,2,5,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -24,8 +24,8 @@
       VALUE "InternalName", "stx:goodies/petitparser/analyzer\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
-      VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Mon, 03 Nov 2014 09:07:04 GMT\0"
+      VALUE "ProductVersion", "6.2.5.0\0"
+      VALUE "ProductDate", "Wed, 19 Nov 2014 11:10:22 GMT\0"
     END
 
   END
--- a/analyzer/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/analyzer/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -30,6 +30,7 @@
 !INCLUDE Make.spec
 
 LIBNAME=libstx_goodies_petitparser_analyzer
+MODULE_PATH=goodies\petitparser\analyzer
 RESFILES=analyzer.$(RES)
 
 
--- a/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -30,6 +30,7 @@
 !INCLUDE Make.spec
 
 LIBNAME=libstx_goodies_petitparser
+MODULE_PATH=goodies\petitparser
 RESFILES=petitparser.$(RES)
 
 
@@ -78,6 +79,7 @@
 $(OUTDIR)PPToken.$(O) PPToken.$(H): PPToken.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)stx_goodies_petitparser.$(O) stx_goodies_petitparser.$(H): stx_goodies_petitparser.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
 $(OUTDIR)PPDelegateParser.$(O) PPDelegateParser.$(H): PPDelegateParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPEndOfLineParser.$(O) PPEndOfLineParser.$(H): PPEndOfLineParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPEpsilonParser.$(O) PPEpsilonParser.$(H): PPEpsilonParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPFailingParser.$(O) PPFailingParser.$(H): PPFailingParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPListParser.$(O) PPListParser.$(H): PPListParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -85,6 +87,7 @@
 $(OUTDIR)PPPluggableParser.$(O) PPPluggableParser.$(H): PPPluggableParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPPredicateParser.$(O) PPPredicateParser.$(H): PPPredicateParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPStartOfLine.$(O) PPStartOfLine.$(H): PPStartOfLine.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPStartOfLineParser.$(O) PPStartOfLineParser.$(H): PPStartOfLineParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPUnresolvedParser.$(O) PPUnresolvedParser.$(H): PPUnresolvedParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPActionParser.$(O) PPActionParser.$(H): PPActionParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPAndParser.$(O) PPAndParser.$(H): PPAndParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -103,6 +106,7 @@
 $(OUTDIR)PPRepeatingParser.$(O) PPRepeatingParser.$(H): PPRepeatingParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPSequenceParser.$(O) PPSequenceParser.$(H): PPSequenceParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPListParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPTrimmingParser.$(O) PPTrimmingParser.$(H): PPTrimmingParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPLimitedChoiceParser.$(O) PPLimitedChoiceParser.$(H): PPLimitedChoiceParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPChoiceParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPListParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPLimitedRepeatingParser.$(O) PPLimitedRepeatingParser.$(H): PPLimitedRepeatingParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPRepeatingParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPPossessiveRepeatingParser.$(O) PPPossessiveRepeatingParser.$(H): PPPossessiveRepeatingParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPRepeatingParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPTokenParser.$(O) PPTokenParser.$(H): PPTokenParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPFlattenParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/compiler/Make.proto	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/Make.proto	Mon Nov 24 00:09:23 2014 +0000
@@ -148,9 +148,6 @@
 $(OUTDIR)PPCNilNode.$(O) PPCNilNode.$(H): PPCNilNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCPluggableNode.$(O) PPCPluggableNode.$(H): PPCPluggableNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCProfilingContext.$(O) PPCProfilingContext.$(H): PPCProfilingContext.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPStream.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCContext.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
-$(OUTDIR)PPCStarAnyNode.$(O) PPCStarAnyNode.$(H): PPCStarAnyNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)PPCStarCharSetPredicateNode.$(O) PPCStarCharSetPredicateNode.$(H): PPCStarCharSetPredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)PPCStarMessagePredicateNode.$(O) PPCStarMessagePredicateNode.$(H): PPCStarMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCUnknownNode.$(O) PPCUnknownNode.$(H): PPCUnknownNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCAbstractActionNode.$(O) PPCAbstractActionNode.$(H): PPCAbstractActionNode.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)PPCAndNode.$(O) PPCAndNode.$(H): PPCAndNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -160,9 +157,7 @@
 $(OUTDIR)PPCForwardNode.$(O) PPCForwardNode.$(H): PPCForwardNode.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)PPCInlineAnyNode.$(O) PPCInlineAnyNode.$(H): PPCInlineAnyNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAnyNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineCharacterNode.$(O) PPCInlineCharacterNode.$(H): PPCInlineCharacterNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractCharacterNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)PPCInlineLiteralNode.$(O) PPCInlineLiteralNode.$(H): PPCInlineLiteralNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineNilNode.$(O) PPCInlineNilNode.$(H): PPCInlineNilNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNilNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)PPCInlineNotLiteralNode.$(O) PPCInlineNotLiteralNode.$(H): PPCInlineNotLiteralNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlinePluggableNode.$(O) PPCInlinePluggableNode.$(H): PPCInlinePluggableNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCPluggableNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCLiteralNode.$(O) PPCLiteralNode.$(H): PPCLiteralNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMessagePredicateNode.$(O) PPCMessagePredicateNode.$(H): PPCMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -174,19 +169,29 @@
 $(OUTDIR)PPCOptionalNode.$(O) PPCOptionalNode.$(H): PPCOptionalNode.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)PPCPlusNode.$(O) PPCPlusNode.$(H): PPCPlusNode.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)PPCPredicateNode.$(O) PPCPredicateNode.$(H): PPCPredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSentinelNode.$(O) PPCSentinelNode.$(H): PPCSentinelNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNilNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(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)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)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)
-$(OUTDIR)PPCTokenStarMessagePredicateNode.$(O) PPCTokenStarMessagePredicateNode.$(H): PPCTokenStarMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTrimNode.$(O) PPCTrimNode.$(H): PPCTrimNode.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)PPCTrimmingTokenNode.$(O) PPCTrimmingTokenNode.$(H): PPCTrimmingTokenNode.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)PPCActionNode.$(O) PPCActionNode.$(H): PPCActionNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractActionNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineCharSetPredicateNode.$(O) PPCInlineCharSetPredicateNode.$(H): PPCInlineCharSetPredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCCharSetPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineLiteralNode.$(O) PPCInlineLiteralNode.$(H): PPCInlineLiteralNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCLiteralNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineMessagePredicateNode.$(O) PPCInlineMessagePredicateNode.$(H): PPCInlineMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineNotCharSetPredicateNode.$(O) PPCInlineNotCharSetPredicateNode.$(H): PPCInlineNotCharSetPredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNotCharSetPredicateNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineNotLiteralNode.$(O) PPCInlineNotLiteralNode.$(H): PPCInlineNotLiteralNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNotLiteralNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineNotMessagePredicateNode.$(O) PPCInlineNotMessagePredicateNode.$(H): PPCInlineNotMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNotMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCStarAnyNode.$(O) PPCStarAnyNode.$(H): PPCStarAnyNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCStarCharSetPredicateNode.$(O) PPCStarCharSetPredicateNode.$(H): PPCStarCharSetPredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCStarMessagePredicateNode.$(O) PPCStarMessagePredicateNode.$(H): PPCStarMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCSymbolActionNode.$(O) PPCSymbolActionNode.$(H): PPCSymbolActionNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractActionNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenSequenceNode.$(O) PPCTokenSequenceNode.$(H): PPCTokenSequenceNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCListNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCSequenceNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenActionNode.$(O) PPCTokenActionNode.$(H): PPCTokenActionNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCAbstractActionNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCActionNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenStarMessagePredicateNode.$(O) PPCTokenStarMessagePredicateNode.$(H): PPCTokenStarMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineTokenStarMessagePredicateNode.$(O) PPCInlineTokenStarMessagePredicateNode.$(H): PPCInlineTokenStarMessagePredicateNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCTokenStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenStarSeparatorNode.$(O) PPCTokenStarSeparatorNode.$(H): PPCTokenStarSeparatorNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCTokenStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineTokenStarSeparatorNode.$(O) PPCInlineTokenStarSeparatorNode.$(H): PPCInlineTokenStarSeparatorNode.st $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCDelegateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCStarNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCTokenStarMessagePredicateNode.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/compiler/PPCTokenStarSeparatorNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPActionParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPAndParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPCharSetPredicate.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPChoiceParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPCompositeParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPContext.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPEpsilonParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPFailure.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPFlattenParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPListParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPLiteralObjectParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPLiteralParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPLiteralSequenceParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPNotParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPOptionalParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPPluggableParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPPossessiveRepeatingParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPPredicateObjectParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPPredicateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPRepeatingParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPSequenceParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPStream.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPToken.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPTokenParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPTrimmingParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk/PPSmalltalkGrammar.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk/PPSmalltalkTokenParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk/PPSmalltalkWhitespaceParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Character.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/UndefinedObject.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/compiler/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -74,9 +74,6 @@
 	PPCNilNode \
 	PPCPluggableNode \
 	PPCProfilingContext \
-	PPCStarAnyNode \
-	PPCStarCharSetPredicateNode \
-	PPCStarMessagePredicateNode \
 	PPCUnknownNode \
 	PPCAbstractActionNode \
 	PPCAndNode \
@@ -86,9 +83,7 @@
 	PPCForwardNode \
 	PPCInlineAnyNode \
 	PPCInlineCharacterNode \
-	PPCInlineLiteralNode \
 	PPCInlineNilNode \
-	PPCInlineNotLiteralNode \
 	PPCInlinePluggableNode \
 	PPCLiteralNode \
 	PPCMessagePredicateNode \
@@ -100,19 +95,29 @@
 	PPCOptionalNode \
 	PPCPlusNode \
 	PPCPredicateNode \
+	PPCSentinelNode \
 	PPCSequenceNode \
 	PPCStarNode \
 	PPCTokenNode \
-	PPCTokenStarMessagePredicateNode \
 	PPCTrimNode \
 	PPCTrimmingTokenNode \
 	PPCActionNode \
 	PPCInlineCharSetPredicateNode \
+	PPCInlineLiteralNode \
 	PPCInlineMessagePredicateNode \
 	PPCInlineNotCharSetPredicateNode \
+	PPCInlineNotLiteralNode \
 	PPCInlineNotMessagePredicateNode \
+	PPCStarAnyNode \
+	PPCStarCharSetPredicateNode \
+	PPCStarMessagePredicateNode \
 	PPCSymbolActionNode \
 	PPCTokenSequenceNode \
+	PPCTokenActionNode \
+	PPCTokenStarMessagePredicateNode \
+	PPCInlineTokenStarMessagePredicateNode \
+	PPCTokenStarSeparatorNode \
+	PPCInlineTokenStarSeparatorNode \
 
 
 
@@ -141,9 +146,6 @@
     $(OUTDIR_SLASH)PPCNilNode.$(O) \
     $(OUTDIR_SLASH)PPCPluggableNode.$(O) \
     $(OUTDIR_SLASH)PPCProfilingContext.$(O) \
-    $(OUTDIR_SLASH)PPCStarAnyNode.$(O) \
-    $(OUTDIR_SLASH)PPCStarCharSetPredicateNode.$(O) \
-    $(OUTDIR_SLASH)PPCStarMessagePredicateNode.$(O) \
     $(OUTDIR_SLASH)PPCUnknownNode.$(O) \
     $(OUTDIR_SLASH)PPCAbstractActionNode.$(O) \
     $(OUTDIR_SLASH)PPCAndNode.$(O) \
@@ -153,9 +155,7 @@
     $(OUTDIR_SLASH)PPCForwardNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineAnyNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineCharacterNode.$(O) \
-    $(OUTDIR_SLASH)PPCInlineLiteralNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineNilNode.$(O) \
-    $(OUTDIR_SLASH)PPCInlineNotLiteralNode.$(O) \
     $(OUTDIR_SLASH)PPCInlinePluggableNode.$(O) \
     $(OUTDIR_SLASH)PPCLiteralNode.$(O) \
     $(OUTDIR_SLASH)PPCMessagePredicateNode.$(O) \
@@ -167,19 +167,29 @@
     $(OUTDIR_SLASH)PPCOptionalNode.$(O) \
     $(OUTDIR_SLASH)PPCPlusNode.$(O) \
     $(OUTDIR_SLASH)PPCPredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCSentinelNode.$(O) \
     $(OUTDIR_SLASH)PPCSequenceNode.$(O) \
     $(OUTDIR_SLASH)PPCStarNode.$(O) \
     $(OUTDIR_SLASH)PPCTokenNode.$(O) \
-    $(OUTDIR_SLASH)PPCTokenStarMessagePredicateNode.$(O) \
     $(OUTDIR_SLASH)PPCTrimNode.$(O) \
     $(OUTDIR_SLASH)PPCTrimmingTokenNode.$(O) \
     $(OUTDIR_SLASH)PPCActionNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineCharSetPredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCInlineLiteralNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineMessagePredicateNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineNotCharSetPredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCInlineNotLiteralNode.$(O) \
     $(OUTDIR_SLASH)PPCInlineNotMessagePredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCStarAnyNode.$(O) \
+    $(OUTDIR_SLASH)PPCStarCharSetPredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCStarMessagePredicateNode.$(O) \
     $(OUTDIR_SLASH)PPCSymbolActionNode.$(O) \
     $(OUTDIR_SLASH)PPCTokenSequenceNode.$(O) \
+    $(OUTDIR_SLASH)PPCTokenActionNode.$(O) \
+    $(OUTDIR_SLASH)PPCTokenStarMessagePredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCInlineTokenStarMessagePredicateNode.$(O) \
+    $(OUTDIR_SLASH)PPCTokenStarSeparatorNode.$(O) \
+    $(OUTDIR_SLASH)PPCInlineTokenStarSeparatorNode.$(O) \
     $(OUTDIR_SLASH)extensions.$(O) \
 
 
--- a/compiler/PPCAbstractActionNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCAbstractActionNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -25,3 +25,14 @@
 	^ #action
 ! !
 
+!PPCAbstractActionNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ block = anotherNode block.
+!
+
+hash
+	^ super hash bitXor: block hash
+! !
+
--- a/compiler/PPCAbstractCharacterNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCAbstractCharacterNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -36,6 +36,17 @@
 	^ PPCharSetPredicate on: [:e | e = character ]
 ! !
 
+!PPCAbstractCharacterNode methodsFor:'comparison'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ character = anotherNode character.
+!
+
+hash
+	^ super hash bitXor: character hash
+! !
+
 !PPCAbstractCharacterNode methodsFor:'compiling'!
 
 body: compiler
--- a/compiler/PPCAbstractLiteralNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCAbstractLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -37,6 +37,17 @@
 	^ #lit
 ! !
 
+!PPCAbstractLiteralNode methodsFor:'comparison'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ literal = anotherNode literal.
+!
+
+hash
+	^ super hash bitXor: literal hash
+! !
+
 !PPCAbstractLiteralNode methodsFor:'compiling'!
 
 encodeQuotes: string
--- a/compiler/PPCAbstractPredicateNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCAbstractPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,7 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
 PPCNode subclass:#PPCAbstractPredicateNode
-	instanceVariableNames:'predicate methodStrategy'
+	instanceVariableNames:'predicate'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Nodes'
@@ -17,16 +17,6 @@
 
 !PPCAbstractPredicateNode methodsFor:'accessing'!
 
-methodStrategy
-	
-	^ methodStrategy
-!
-
-methodStrategy: anObject
-	
-	methodStrategy := anObject
-!
-
 predicate
 	
 	^ predicate
@@ -43,15 +33,6 @@
 
 !PPCAbstractPredicateNode methodsFor:'analysis'!
 
-= anotherNode
-	(self == anotherNode) ifTrue: [ ^ true ].
-	(anotherNode class = self class) ifFalse: [ ^ false ].
-	
-	(anotherNode name = name) ifFalse: [ ^ false ].
-	(anotherNode methodStrategy = methodStrategy) ifFalse: [ ^ false ].
-	^ anotherNode children = self children.
-!
-
 acceptsEpsilon
 	^ false
 !
@@ -64,6 +45,17 @@
 	^ PPCharSetPredicate on: predicate
 ! !
 
+!PPCAbstractPredicateNode methodsFor:'comparison'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ predicate = anotherNode predicate.
+!
+
+hash
+	^ super hash bitXor: predicate hash
+! !
+
 !PPCAbstractPredicateNode methodsFor:'compiling'!
 
 bodyOfPredicate: compiler
@@ -85,19 +77,12 @@
 
 initialize
 	super initialize.
-	methodStrategy := PPCMethodStrategy new
 ! !
 
 !PPCAbstractPredicateNode methodsFor:'optimizing'!
 
 asInlined
 	^ super asInlined
-"	(methodStrategy == (PPCInlineStrategy instance)) ifFalse: [ 
-		^ self copy 
-			methodStrategy: PPCInlineStrategy instance;
-			yourself
-	].
-	^ self"
 !
 
 optimize: params status: changeStatus
--- a/compiler/PPCActionNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCActionNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -12,6 +12,7 @@
 asFast
 	^ PPCTokenActionNode new
 		child: child;
+		properties: properties;
 		name: self name;
 		yourself
 !
@@ -30,13 +31,11 @@
 !
 
 rewrite: changeStatus
-	"TODO JK: Find another way how to recognize the trimming token!!"
-	(name = 'trimmingToken') ifTrue: [ 
+	(self hasProperty: #trimmingToken) ifTrue: [ 
 		changeStatus change.
 		^ PPCTrimmingTokenNode new
-			"name: name"
-			"JK: I am sorry"
-			child: child children second child;
+			name: name;
+			child: child children second child; 				"Oups, what a chain"
 			tokenClass: child children second tokenClass;
 			whitespace: child children first;
 			yourself
--- a/compiler/PPCChoiceNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCChoiceNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -19,8 +19,9 @@
 !
 
 compileWith: compiler effect: effect id: id
-	| firsts guard  |
+	| firsts guard whitespaceConsumed |
 
+	whitespaceConsumed := false.
 	firsts := (self firstSetSuchThat: [ :e | (e isKindOf: PPCTrimmingTokenNode) or: [ e isTerminal ] ]).
 	
 	compiler startMethod: id.
@@ -29,12 +30,16 @@
 	"If we start with trimming token, we should invoke the whitespace parser"
 	(firsts allSatisfy: [ :e | e isKindOf: PPCTrimmingTokenNode ]) ifTrue: [  
 		firsts anyOne compileWhitespace: compiler.
+		whitespaceConsumed := true.
 	].
 	
-	(1 to: children size) do: [ :idx  | |child|
+	(1 to: children size) do: [ :idx  | |child allowGuard |
 		child := children at: idx.
-		
-		(compiler guards and: [ (guard := PPCGuard on: child) makesSense ]) ifTrue: [ 	
+"		allowGuard := ((child isKindOf: PPCTrimmingTokenNode) and: [ whitespaceConsumed not ]) not.
+"	
+		allowGuard := whitespaceConsumed.
+				
+ 		(allowGuard and: [compiler 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	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCCompiler.st	Mon Nov 24 00:09:23 2014 +0000
@@ -2,7 +2,7 @@
 
 Object subclass:#PPCCompiler
 	instanceVariableNames:'compilerStack compiledParser cache inlining debug profile
-		currentMethod lastMethod guards ids updateContextMethod tokenMode'
+		currentMethod guards ids tokenMode rootNode'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Core'
@@ -31,10 +31,6 @@
 	inlining := value
 !
 
-lastMethod
-	^ lastMethod 
-!
-
 parameters: associations
 	| key value |
 	associations do: [ :ass |
@@ -55,12 +51,8 @@
 	profile := aBoolean 
 !
 
-startInline: id
-	self push.
-	
-	currentMethod := PPCInlinedMethod new.
-	currentMethod id: id.	
-	currentMethod profile: self profile.
+rootNode
+	^ rootNode
 ! !
 
 !PPCCompiler methodsFor:'cleaning'!
@@ -106,6 +98,10 @@
 	currentMethod add: string.
 !
 
+addComment: string
+	currentMethod add: '"', string, '"'.
+!
+
 addConstant: value as: name
 	compiledParser addConstant: value as: name.
 !
@@ -138,15 +134,6 @@
 	currentMethod addOnLine: anotherMethod call.
 !
 
-checkCache: id
-	| method value |
-	"Check if method is already compiled/hand written"
-	method := compiledParser compiledMethodAt: id ifAbsent: [ nil ].
-	method ifNotNil: [ ^ lastMethod := PPCCompiledMethod new id: id; yourself ].
-	
-	^ (value := self cachedValue: id) ifNotNil: [ lastMethod := value ].
-!
-
 dedent
 	currentMethod dedent
 !
@@ -159,19 +146,6 @@
 	currentMethod nl
 !
 
-pop
-	| array |
-	array := compilerStack pop.
-	currentMethod := array first	
-!
-
-push
-	| array |
-	array := { currentMethod }.
-	compilerStack push: array.
-	(compilerStack size > 500 )ifTrue: [ self error: 'unless it is very complex grammar, there is an error somewhere' ]
-!
-
 smartRemember: parser
 	^ self smartRemember: parser to: #memento 
 !
@@ -194,41 +168,10 @@
 	^ 'context restore: ', mementoName, '.'.
 !
 
-startMethod: id
-	|  sender |
-	(cache includesKey: id) ifTrue: [ self error: 'OOOUPS!!' ].
-	self push.
-	
-	
-	currentMethod := PPCMethod new.
-	currentMethod id: id.
-	currentMethod profile: self profile.	
-	self cache: id as: currentMethod.
-	
-	sender := thisContext sender receiver.
-	self add: '"Method generated from ', sender asString, '"'.
-!
-
 startTokenMode
 	tokenMode := true
 !
 
-stopInline
-	| sender |
-	sender := thisContext sender receiver.
-	self add: '"Inlined by ', sender asString, '"'.
-	lastMethod := currentMethod.
-	currentMethod := nil.
-	self pop.
-!
-
-stopMethod
-	self cache: currentMethod methodName as: currentMethod.
-	lastMethod := currentMethod.
-	currentMethod := nil.
-	self pop.
-!
-
 stopTokenMode
 	tokenMode := false
 ! !
@@ -244,10 +187,24 @@
 !
 
 idFor: object prefixed: prefix suffixed: suffix effect: effect
-	| body |
+	| body id |
+	
+	"Halt if: [ (object isKindOf: PPCNode) and: [object name = #smalltalk_ws ] ]."
+	
+"	((object isKindOf: PPCNode) and: [object name = #smalltalk_ws ])  ifTrue: [ Transcript crShow: 'st_ws' ].
+"	
 	^ ids at: object ifAbsentPut: [ 
 		((object isKindOf: PPCNode) and: [object name isNotNil]) ifTrue: [ 
-			 (object name, suffix) asSymbol
+			"Halt if: [ object name = #smalltalk_ws ]."
+"			(object name = #smalltalk_ws) ifTrue: [Transcript crShow: 'NEW st_ws'].
+"			
+			id := (object name, suffix) asSymbol.
+			"Make sure, that the generated ID is uniqe!!"
+			((ids values select: [ :e | e = id ]) isEmpty) ifTrue: [ id ]
+			ifFalse: [ 
+				body := ids size asString.
+				(id, '_', body) asSymbol 
+			]
 		] ifFalse: [ 
 			body := ids size asString.
 			(prefix asString, '_', body, suffix) asSymbol
@@ -255,6 +212,81 @@
 	]
 ! !
 
+!PPCCompiler methodsFor:'code generation - support'!
+
+checkCache: id
+	| method  |
+	"Check if method is hand written"
+	method := compiledParser compiledMethodAt: id ifAbsent: [ nil ].
+	method ifNotNil: [ ^ PPCCompiledMethod new id: id; yourself ].
+	
+	^ self cachedValue: id
+!
+
+pop
+        | retval |
+        retval := compilerStack pop.
+        compilerStack isEmpty ifFalse: [ currentMethod := compilerStack top ].
+        ^ retval
+
+    "Modified: / 21-11-2014 / 12:27:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+push
+        compilerStack push: currentMethod.
+        (compilerStack size > 500 )ifTrue: [ self error: 'unless it is very complex grammar, there is an error somewhere' ]
+
+    "Modified: / 21-11-2014 / 12:27:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+startInline: id
+	| sender |	
+	
+	currentMethod := PPCInlinedMethod new.
+	currentMethod id: id.	
+	currentMethod profile: self profile.
+	self push.
+	
+	
+	sender := thisContext sender receiver.
+	self addComment: 'START inlining by ', sender asString.
+!
+
+startMethod: id
+	|  sender |
+	(cache includesKey: id) ifTrue: [ self error: 'OOOUPS!!' ].
+	
+	currentMethod := PPCMethod new.
+	currentMethod id: id.
+	currentMethod profile: self profile.	
+	self push.	
+		
+	self cache: id as: currentMethod.
+	
+	sender := thisContext sender receiver.
+	self addComment: 'START of method generated by ', sender asString.
+!
+
+stopInline
+	| sender |
+	sender := thisContext sender receiver.
+	self addComment: 'STOP inlining by ', sender asString.
+	^ self pop.
+!
+
+stopMethod
+	| sender |
+	sender := thisContext sender receiver.
+	self addComment: 'END of method generated by ', sender asString.
+
+	self cache: currentMethod methodName as: currentMethod.
+	^ self pop.
+!
+
+top
+	^ compilerStack top
+! !
+
 !PPCCompiler methodsFor:'compiling'!
 
 compile: aPPParser as: name
@@ -272,18 +304,18 @@
 !
 
 compileTree: compilerTree as: name parser: parser params: params
-        |  |
-        params do: [ :p | 
-                (p key = #guards) ifTrue: [ self guards: p value ].
-        ].      
+	|  |
+	params do: [ :p | 
+		(p key = #guards) ifTrue: [ self guards: p value ].
+	].	
 
 
-        ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
-                | rPackageOrganizer |
-                rPackageOrganizer := Smalltalk at: #RPackageOrganizer.
-                rPackageOrganizer notNil ifTrue:[
-                        rPackageOrganizer default registerPackageNamed: 'PetitCompiler-Generated'.
-                ].
+	((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
+		| rPackageOrganizer |
+		rPackageOrganizer := Smalltalk at: #RPackageOrganizer.
+		rPackageOrganizer notNil ifTrue:[
+			rPackageOrganizer default registerPackageNamed: 'PetitCompiler-Generated'.
+		].
 
       compiledParser := (Smalltalk at: name ifAbsent: [ nil ]).
       compiledParser ifNil: [ 
@@ -295,32 +327,34 @@
                 compiledParser := Smalltalk at: name.
       ] ifNotNil: [ 
                 self clean: compiledParser 
-      ].                
-        ] ifFalse: [ 
-                RPackageOrganizer default registerPackageNamed: 'PetitCompiler-Generated'.
-                compiledParser := (Smalltalk at: name ifAbsent: [ nil ]).
-                compiledParser ifNil: [ 
-                                                        PPCompiledParser subclass: name.
-                                                        compiledParser := Smalltalk at: name.
-                                                        compiledParser category: 'PetitCompiler-Generated'                                                      
-                                                        ] ifNotNil: [ 
-                                                                self clean: compiledParser 
-                                                        ].      
-        ].
-        compiledParser constants removeAll.
-        
+      ].      		
+	] ifFalse: [ 
+		RPackageOrganizer default registerPackageNamed: 'PetitCompiler-Generated'.
+		compiledParser := (Smalltalk at: name ifAbsent: [ nil ]).
+		compiledParser ifNil: [ 
+							PPCompiledParser subclass: name.
+							compiledParser := Smalltalk at: name.
+							compiledParser category: 'PetitCompiler-Generated'							
+							] ifNotNil: [ 
+								self clean: compiledParser 
+							].	
+	].
+	compiledParser constants removeAll.
+	
+	rootNode := compilerTree.
+	self precomputeFirstSets: rootNode.
+	self precomputeFollowSets: rootNode.
+	self precomputeFollowSetsWithTokens: rootNode.
+	
+	self startMethod: #start.
+	self add: '^ '.
+	self callOnLine: (compilerTree compileWith: self).
+	self stopMethod.
 
-        self startMethod: #start.
-        self add: '^ '.
-        self callOnLine: (compilerTree compileWith: self).
-        self stopMethod.
+	self installVariablesAndMethods.
 
-        self installVariablesAndMethods.
-
-        compiledParser referringParser: parser.
-        ^ compiledParser
-
-    "Modified: / 05-11-2014 / 23:17:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	compiledParser referringParser: parser.
+	^ compiledParser
 !
 
 copy: parser
@@ -334,11 +368,9 @@
 !
 
 installVariables: class
-        | string |
-        string := class constants keys inject: '' into: [:r :e | r, ' ', e  ].
-        PPCompiledParser subclass: class name instanceVariableNames: string classVariableNames: '' poolDictionaries:'' category: 'PetitCompiler-Generated'.
-
-    "Modified: / 26-10-2014 / 22:01:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	| string |
+	string := class constants keys inject: '' into: [:r :e | r, ' ', e  ].
+	PPCompiledParser subclass: class name instanceVariableNames: string classVariableNames: '' poolDictionaries: '' category: 'PetitCompiler-Generated'.
 !
 
 installVariablesAndMethods
@@ -356,8 +388,6 @@
     compiledParser := Smalltalk at: compiledParserClassName.
 
     self installMethods: compiledParser.
-
-    "Created: / 30-10-2014 / 23:15:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 optimize: parser params: params
@@ -367,6 +397,36 @@
 	^ retval
 !
 
+precomputeFirstSets: root
+	| firstSets |
+	firstSets := root firstSets.
+	
+	root allNodesDo: [ :node |
+		node firstSet: (firstSets at: node).
+	]
+	
+!
+
+precomputeFollowSets: root
+	| followSets |
+	followSets := root followSets.
+	
+	root allNodesDo: [ :node |
+		node followSet: (followSets at: node).
+	]
+	
+!
+
+precomputeFollowSetsWithTokens: root
+	| followSets |
+	followSets := root followSetsSuchThat: [:e | e isTerminal or: [ e isKindOf: PPCTrimmingTokenNode ]].
+	
+	root allNodesDo: [ :node |
+		node followSetWithTokens: (followSets at: node).
+	]
+	
+!
+
 toCompilerTree: parser
 	^ parser asCompilerTree
 ! !
@@ -429,7 +489,7 @@
 	super initialize.
 	compilerStack := Stack new.
 	cache := IdentityDictionary new.
-	ids := IdentityDictionary new.
+	ids := Dictionary new.
 	
 	tokenMode := false.
 	inlining := true.
@@ -437,20 +497,6 @@
 	guards := true.
 ! !
 
-!PPCCompiler methodsFor:'ppcmethod protocol'!
-
-bridge
-	^ PPCBridge on: lastMethod methodName.
-!
-
-call
-	^ lastMethod call
-!
-
-canInline
-	^ lastMethod canInline
-! !
-
 !PPCCompiler class methodsFor:'documentation'!
 
 version_HG
--- a/compiler/PPCContext.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCContext.st	Mon Nov 24 00:09:23 2014 +0000
@@ -235,23 +235,19 @@
 !
 
 remember
-        | memento |
+	| memento |
 "
-        ^ position
+	^ position
 "
-        memento := PPCContextMemento new
-                position: position;
-                yourself.
-                
-        self rememberProperties: memento.
-        "JK: Just while developing"
-        "
-        rc := rc + 1.
-        (rc > ((self size + 1)* 1000*1000)) ifTrue: [ self error: 'Hey, this is not normal, is it?' ].
-        "
-        ^ memento
-
-    "Modified (comment): / 08-11-2014 / 02:08:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	memento := PPCContextMemento new
+		position: position;
+		yourself.
+		
+	self rememberProperties: memento.
+	"JK: Just while developing"
+	rc := rc + 1.
+	(rc > ((self size + 1)* 1000*1000)) ifTrue: [ self error: 'Hey, this is not normal, is it?' ].
+	^ memento
 !
 
 rememberProperties: aPPContextMemento
--- a/compiler/PPCForwardNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCForwardNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,7 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
 PPCDelegateNode subclass:#PPCForwardNode
-	instanceVariableNames:'block'
+	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Nodes'
--- a/compiler/PPCInlineLiteralNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCInlineLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,6 +1,6 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
-PPCAbstractLiteralNode subclass:#PPCInlineLiteralNode
+PPCLiteralNode subclass:#PPCInlineLiteralNode
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -37,6 +37,10 @@
 
 !PPCInlineLiteralNode methodsFor:'printing'!
 
+asInlined
+	^ self
+!
+
 printOn: aStream
 	aStream nextPutAll: '#inline'.
 	super printOn: aStream
--- a/compiler/PPCInlineNotLiteralNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCInlineNotLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,6 +1,6 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
-PPCAbstractLiteralNode subclass:#PPCInlineNotLiteralNode
+PPCNotLiteralNode subclass:#PPCInlineNotLiteralNode
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -41,6 +41,10 @@
 
 !PPCInlineNotLiteralNode methodsFor:'printing'!
 
+asInlined
+	^ self
+!
+
 firstCharParser
 	^ literal first asParser not
 !
--- a/compiler/PPCInlinePluggableNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCInlinePluggableNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -14,10 +14,8 @@
 !
 
 compileWith: compiler effect: effect id: id
-        compiler startInline: id.
-        compiler add: block asString, ' value: context.'.
-        ^ compiler stopInline.
-
-    "Modified (format): / 06-11-2014 / 01:13:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	compiler startInline: id.
+	compiler add: block asString, ' value: context.'.
+ ^ compiler stopInline.
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/PPCInlineTokenStarMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,26 @@
+"{ Package: 'stx:goodies/petitparser/compiler' }"
+
+PPCTokenStarMessagePredicateNode subclass:#PPCInlineTokenStarMessagePredicateNode
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Nodes'
+!
+
+!PPCInlineTokenStarMessagePredicateNode methodsFor:'as yet unclassified'!
+
+asInlined
+	^ self
+!
+
+compileWith: compiler effect: effect id: id
+	compiler startInline: id.
+	compiler add: '[ context peek ', message,' ] whileTrue: ['.
+	compiler indent.
+	compiler add: 'context next'.
+	compiler indent.
+	compiler dedent.
+	compiler add: '].'.
+ ^ compiler stopInline.
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/PPCInlineTokenStarSeparatorNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,21 @@
+"{ Package: 'stx:goodies/petitparser/compiler' }"
+
+PPCTokenStarSeparatorNode subclass:#PPCInlineTokenStarSeparatorNode
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Nodes'
+!
+
+!PPCInlineTokenStarSeparatorNode methodsFor:'as yet unclassified'!
+
+asInlined
+	^ self
+!
+
+compileWith: compiler effect: effect id: id
+	compiler startInline: id.
+	compiler add: 'context skipSeparators.'.
+ ^ compiler stopInline.
+! !
+
--- a/compiler/PPCListNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCListNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -8,6 +8,12 @@
 !
 
 
+!PPCListNode class methodsFor:'as yet unclassified'!
+
+withAll: aCollection
+	^ self basicNew children: aCollection
+! !
+
 !PPCListNode methodsFor:'accessing'!
 
 children
--- a/compiler/PPCMessagePredicateNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -37,3 +37,14 @@
 	compiler dedent.
 ! !
 
+!PPCMessagePredicateNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ message = anotherNode message.
+!
+
+hash
+	^ super hash bitXor: message hash
+! !
+
--- a/compiler/PPCNilNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCNilNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -7,6 +7,12 @@
 	category:'PetitCompiler-Nodes'
 !
 
+!PPCNilNode methodsFor:'analyzing'!
+
+isNullable
+	^ true
+! !
+
 !PPCNilNode methodsFor:'as yet unclassified'!
 
 acceptsEpsilon
--- a/compiler/PPCNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,7 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
 Object subclass:#PPCNode
-	instanceVariableNames:'contextFree name firstSet firstCharSet'
+	instanceVariableNames:'contextFree name firstFollowCache firstCharSet properties'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Nodes'
@@ -32,6 +32,26 @@
 	^ ''
 ! !
 
+!PPCNode methodsFor:'accessing-properties'!
+
+hasProperty: aKey
+	"Test if the property aKey is present."
+	
+	^ properties notNil and: [ properties includesKey: aKey ]
+!
+
+properties: aDictionary
+	properties := aDictionary 
+!
+
+propertyAt: aKey ifAbsent: aBlock
+	"Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
+	
+	^ properties isNil
+		ifTrue: [ aBlock value ]
+		ifFalse: [ properties at: aKey ifAbsent: aBlock ]
+! !
+
 !PPCNode methodsFor:'analysis'!
 
 acceptsEpsilon
@@ -125,13 +145,6 @@
 
 !PPCNode methodsFor:'as yet unclassified'!
 
-firstSet
-	firstSet ifNil: [ 
-		firstSet := self firstSetSuchThat: [ :e | e isFirstSetTerminal ].
-	].
-	^ firstSet
-!
-
 name
 	^ name
 ! !
@@ -144,6 +157,13 @@
 	
 	(anotherNode name = name) ifFalse: [ ^ false ].
 	^ anotherNode children = self children.
+!
+
+hash
+	"TODO JK: IMO not a good hashing function bacause of children size, 
+		but at least it is not recursive, which would be worse :)
+	"
+	^ self class hash bitXor: (name hash bitXor: self children size hash)
 ! !
 
 !PPCNode methodsFor:'compiling'!
@@ -154,15 +174,162 @@
 !
 
 compileWith: compiler effect: effect
-	| id |
+	| id method |
 	id := (compiler idFor: self prefixed: (self prefix) suffixed: (self suffix) effect: effect).
-	(compiler checkCache: id) ifNotNil: [ ^ compiler ].
+	(method := compiler checkCache: id) ifNotNil: [ ^ method ].
 
 	^ self compileWith: compiler effect: effect id: id.
 !
 
 compileWith: compiler effect: effect id: id
 	self subclassResponsibility 
+!
+
+initialize
+	super initialize.
+	firstFollowCache := IdentityDictionary new.
+! !
+
+!PPCNode methodsFor:'first follow next'!
+
+firstSet
+	^ firstFollowCache at: #firstSet ifAbsentPut: [
+		self firstSets at: self
+	]
+!
+
+firstSet: set
+	firstFollowCache at: #firstSet put: set
+!
+
+firstSets
+	^ self firstSetsSuchThat: [ :e | e isFirstSetTerminal ]
+!
+
+firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	"PRIVATE: Try to add additional elements to the first-set aSet of the receiver, use the incomplete aFirstDictionary."
+
+	(aBlock value: self) ifFalse: [ 
+		self children do: [ :node | aSet addAll: (aFirstDictionary at: node) ]
+	]
+!
+
+firstSetsSuchThat: block
+
+	| firstSets |
+	firstSets := IdentityDictionary new.
+	self allParsersDo: [ :each |
+		firstSets at: each put: ((block value: each)
+			ifTrue: [ IdentitySet with: each ]
+			ifFalse: [ IdentitySet new ]).
+		each isNullable
+			ifTrue: [ (firstSets at: each) add: PPCSentinelNode instance ] ].
+		
+		
+	[	| changed tally |
+		changed := false.
+		firstSets keysAndValuesDo: [ :node :first |
+			tally := first size.
+			node firstSets: firstSets into: first suchThat: block.
+			changed := changed or: [ tally ~= first size ] ].
+		changed ] whileTrue.
+	^ firstSets
+!
+
+followSet
+	^ firstFollowCache at: #followSet ifAbsent: [ self error: 'no follow set cached' ]
+!
+
+followSet: aSet
+	^ firstFollowCache at: #followSet put: aSet
+!
+
+followSetIn: rootNode
+	^ rootNode followSets at: self
+!
+
+followSetWithTokens
+	^ firstFollowCache at: #followSetWithTokens ifAbsent: [ self error: 'no follow with tokens cached' ]
+!
+
+followSetWithTokens: aSet
+	^ firstFollowCache at: #followSetWithTokens put: aSet
+!
+
+followSets
+	^ self followSetsSuchThat: [ :e | e isFirstSetTerminal ]
+!
+
+followSets: aFollowDictionary firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	"PRIVATE: Try to add additional elements to the follow-set aSet of the receiver, use the incomplete aFollowDictionary and the complete aFirstDictionary."
+	
+	self children do: [ :node | (aFollowDictionary at: node) addAll: aSet ]
+!
+
+followSetsSuchThat: aBlock
+	"Answer a dictionary with all the parsers reachable from the receiver as key and their follow-set as value. The follow-set of a parser is the list of terminal parsers that can appear immediately to the right of that parser."
+	
+	| current previous continue firstSets followSets |
+	current := previous := 0.
+	firstSets := self firstSetsSuchThat: aBlock.
+	followSets := IdentityDictionary new.
+	self allNodesDo: [ :each | followSets at: each put: IdentitySet new ].
+	(followSets at: self) add: PPCSentinelNode instance.
+	[	followSets keysAndValuesDo: [ :node :follow |
+			node 
+				followSets: followSets
+				firstSets: firstSets
+				into: follow
+				suchThat: aBlock ].
+		current := followSets
+			inject: 0
+			into: [ :result :each | result + each size ].
+		continue := previous < current.
+		previous := current.
+		continue ] whileTrue.
+	^ followSets
+!
+
+nextSetIn: rootNode
+	^ rootNode nextSets at: self
+!
+
+nextSets
+		| nextSets |
+	
+	nextSets := IdentityDictionary new.
+	self allNodesDo: [ :each | nextSets at: each put: IdentitySet new ].
+	
+	(nextSets at: self) add: PPCSentinelNode instance.
+	
+	[ 	| changed |
+		changed := false.
+	
+		nextSets keysAndValuesDo: [:node :next |
+			changed := (node 
+				nextSets: nextSets
+				into: next) or: [ changed ].
+		].
+		changed ] whileTrue.
+	
+	^ nextSets
+!
+
+nextSets: aNextDictionary into: aSet
+	"return true/false, if something has changed or not...."
+	| childSet change tally |
+	
+	change := false.
+	
+	self children do: [:each | 
+		childSet := aNextDictionary at: each.
+		tally := childSet size.
+		childSet addAll: aSet.
+		change := change or: [ tally ~= childSet size ].
+	].
+
+	^ change
+	
 ! !
 
 !PPCNode methodsFor:'gt'!
@@ -239,7 +406,13 @@
 !
 
 optimize: params status: changeStatus
-	" nothing to do "
+	| retval |
+	retval := self.
+	
+	retval := retval rewrite: params status: changeStatus.
+	retval := retval inline: params status: changeStatus.
+	
+	^ retval
 !
 
 optimizeTree
--- a/compiler/PPCNotLiteralNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCNotLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -21,7 +21,7 @@
 !
 
 firstCharSet
-	^ PPCharSetPredicate on: [:e | e ~= literal first ]
+	^ PPCharSetPredicate on: [:e | true ]
 !
 
 literal
--- a/compiler/PPCNotMessagePredicateNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCNotMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -45,3 +45,14 @@
 	compiler dedent.
 ! !
 
+!PPCNotMessagePredicateNode methodsFor:'comparison'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ message = anotherNode message.
+!
+
+hash
+	^ super hash bitXor: message hash
+! !
+
--- a/compiler/PPCOptionalNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCOptionalNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -7,6 +7,12 @@
 	category:'PetitCompiler-Nodes'
 !
 
+!PPCOptionalNode methodsFor:'analyzing'!
+
+isNullable
+	^ true
+! !
+
 !PPCOptionalNode methodsFor:'as yet unclassified'!
 
 acceptsEpsilon
--- a/compiler/PPCPluggableNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCPluggableNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -35,15 +35,14 @@
      it back to source code. Very bad indeed!!"
 
     ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
-        ^ super asInlined
+		^ super asInlined
     ] ifFalse:[
-        ^ PPCInlinePluggableNode new
-                name: name;
-                block: block;
-                yourself
+		^ PPCInlinePluggableNode new
+			name: name;
+			block: block;
+			yourself
     ]
 
-    "Modified: / 06-11-2014 / 01:46:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 compileWith: compiler effect: effect id: id
@@ -68,3 +67,14 @@
 	^ #plug
 ! !
 
+!PPCPluggableNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ block = anotherNode block.
+!
+
+hash
+	^ super hash bitXor: block hash
+! !
+
--- a/compiler/PPCPlusNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCPlusNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -35,6 +35,14 @@
  ^ compiler stopMethod.
 !
 
+followSets: aFollowDictionary firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	| first |
+	super followSets: aFollowDictionary firstSets:  aFirstDictionary into: aSet suchThat: aBlock.
+	
+	first := aFirstDictionary at: self.
+	(aFollowDictionary at: child) addAll: (first reject: [:each | each isNullable])
+!
+
 prefix
 	^ #plus
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/PPCSentinelNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,15 @@
+"{ Package: 'stx:goodies/petitparser/compiler' }"
+
+PPCNilNode subclass:#PPCSentinelNode
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Nodes'
+!
+
+!PPCSentinelNode class methodsFor:'as yet unclassified'!
+
+instance
+	^ Instance ifNil: [ Instance := self basicNew ]
+! !
+
--- a/compiler/PPCSequenceNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCSequenceNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -35,6 +35,21 @@
 		child acceptsEpsilon ifFalse: [ ^ aCollection ]
 	].
 	^ aCollection
+!
+
+firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	| nullable |
+	
+	"TODO JK: aBlock is ignored by now"
+	children do: [ :node |
+		nullable := false.
+		(aFirstDictionary at: node) do: [ :each |
+			each isNullable
+				ifTrue: [ nullable := true ]
+				ifFalse: [ aSet add: each ] ].
+		nullable
+			ifFalse: [ ^ self ] ].
+	aSet add: PPCSentinelNode instance
 ! !
 
 !PPCSequenceNode methodsFor:'compiling'!
@@ -73,6 +88,8 @@
 	compiler add: 'retval := Array new: ', children size asString, '.'.
 	self addGuard: compiler id: id.
 
+"	Halt if: [ self name = #qualifiedName ]."
+
 	(1 to: children size) do: [ :idx  | |child|
 		child := children at: idx.
 		compiler add: 'element := '.
@@ -85,12 +102,33 @@
  ^ compiler stopMethod.
 ! !
 
+!PPCSequenceNode methodsFor:'first follow next'!
+
+followSets: aFollowDictionary firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	children keysAndValuesDo: [ :index :node |
+		| follow first |
+		follow := aFollowDictionary at: node.
+		index = children size
+			ifTrue: [ follow addAll: aSet ]
+			ifFalse: [
+				(self class withAll: (children 
+					copyFrom: index + 1 to: children size))
+						firstSets: aFirstDictionary
+						into: (first := IdentitySet new)
+						suchThat: aBlock.
+				(first anySatisfy: [ :each | each isNullable ])
+					ifTrue: [ follow addAll: aSet ].
+				follow addAll: (first 
+					reject: [ :each | each isNullable ]) ] ]
+! !
+
 !PPCSequenceNode methodsFor:'optimizing'!
 
 asFast
 	^ PPCTokenSequenceNode new
 		children: children;
 		name: self name;
+		properties: properties;
 		yourself
 ! !
 
--- a/compiler/PPCStarAnyNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCStarAnyNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,6 +1,6 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
-PPCNode subclass:#PPCStarAnyNode
+PPCStarNode subclass:#PPCStarAnyNode
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -29,5 +29,9 @@
 
 prefix
 	^ #starAny
+!
+
+rewrite: changeStatus
+	"Nothing TODO"
 ! !
 
--- a/compiler/PPCStarCharSetPredicateNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCStarCharSetPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,6 +1,6 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
-PPCNode subclass:#PPCStarCharSetPredicateNode
+PPCStarNode subclass:#PPCStarCharSetPredicateNode
 	instanceVariableNames:'predicate'
 	classVariableNames:''
 	poolDictionaries:''
@@ -56,5 +56,20 @@
 
 prefix
 	^ #starPredicate
+!
+
+rewrite: changeStatus
+	"Nothing TODO"
 ! !
 
+!PPCStarCharSetPredicateNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ predicate = anotherNode predicate.
+!
+
+hash
+	^ super hash bitXor: predicate hash
+! !
+
--- a/compiler/PPCStarMessagePredicateNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCStarMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,6 +1,6 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
-PPCNode subclass:#PPCStarMessagePredicateNode
+PPCStarNode subclass:#PPCStarMessagePredicateNode
 	instanceVariableNames:'message'
 	classVariableNames:''
 	poolDictionaries:''
@@ -13,6 +13,10 @@
 	^ true
 !
 
+firstCharSet
+	^ PPCharSetPredicate on: [:char | char perform: message ] 	
+!
+
 message
 	
 	^ message
@@ -25,6 +29,10 @@
 
 prefix
 	^ #starPredicate
+!
+
+rewrite: changeStatus
+	"Nothing TODO"
 ! !
 
 !PPCStarMessagePredicateNode methodsFor:'as yet unclassified'!
@@ -59,12 +67,24 @@
  ^ compiler stopMethod.
 ! !
 
+!PPCStarMessagePredicateNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ message = anotherNode message.
+!
+
+hash
+	^ super hash bitXor: message hash
+! !
+
 !PPCStarMessagePredicateNode methodsFor:'optimizing'!
 
 asFast
 	^ PPCTokenStarMessagePredicateNode new
 		name: name;
 		message: message;
+		child: child;
 		yourself
 ! !
 
--- a/compiler/PPCStarNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCStarNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -26,6 +26,7 @@
 		changeStatus change.
 		^ PPCStarMessagePredicateNode new
 			name: name;
+			child: child;
 			message: child message;
 			yourself
 	]. 
@@ -34,6 +35,7 @@
 		changeStatus change.
 		^ PPCStarAnyNode new
 			name: name;
+			child: child;
 			yourself
 	]. 
 
@@ -42,10 +44,17 @@
 		^ PPCStarCharSetPredicateNode new
 			name: name;
 			predicate: child predicate;
+			child: child;
 			yourself
 	] 
 ! !
 
+!PPCStarNode methodsFor:'analyzing'!
+
+isNullable
+	^ true
+! !
+
 !PPCStarNode methodsFor:'as yet unclassified'!
 
 compileWith: compiler effect: effect id: id
@@ -68,3 +77,13 @@
  ^ compiler stopMethod.
 ! !
 
+!PPCStarNode methodsFor:'first follow next'!
+
+followSets: aFollowDictionary firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	| first |
+	super followSets: aFollowDictionary firstSets:  aFirstDictionary into: aSet suchThat: aBlock.
+	
+	first := aFirstDictionary at: self.
+	(aFollowDictionary at: child) addAll: (first reject: [:each | each isNullable])
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/PPCTokenActionNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,56 @@
+"{ Package: 'stx:goodies/petitparser/compiler' }"
+
+PPCActionNode subclass:#PPCTokenActionNode
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Nodes'
+!
+
+!PPCTokenActionNode methodsFor:'as yet unclassified'!
+
+asFast
+	^ self
+!
+
+compileWith: compiler effect: effect id: id
+	|  |
+	compiler addConstant: block as: id.
+
+	"
+		Actually, do nothing, we are in Token mode and the 
+		child does not return any result and token takes only
+		the input value.
+	"	
+	compiler startMethod: id.
+	compiler add: '^ '.
+	compiler callOnLine: (child compileWith: compiler).
+ ^ compiler stopMethod.
+!
+
+rewrite: changeStatus
+	(self hasProperty: #trimmingToken) ifTrue: [ 
+		| retval |
+		changeStatus change.
+		"Get rid of action and sequence with whitespace"
+		retval := child children second child. 	"JK: oups, what a chain!!"
+		retval name ifNil: [ retval name: self name ].
+		^ retval
+	].
+
+	child name ifNil: [  
+		changeStatus change.
+		child name: self name.
+		^ child
+	].
+
+	(child name = self name) ifTrue: [ 
+		changeStatus change.
+		^ child
+	]
+!
+
+suffix
+	^ '_fast'
+! !
+
--- a/compiler/PPCTokenNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCTokenNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -66,3 +66,14 @@
 	^ #token
 ! !
 
+!PPCTokenNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ tokenClass = anotherNode tokenClass.
+!
+
+hash
+	^ super hash bitXor: tokenClass hash
+! !
+
--- a/compiler/PPCTokenStarMessagePredicateNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCTokenStarMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -13,6 +13,14 @@
 	^ self
 !
 
+asInlined
+	^ PPCInlineTokenStarMessagePredicateNode new
+		name: name;
+		message: message;
+		child: child;
+		yourself
+!
+
 compileWith: compiler effect: effect id: id
 	compiler startMethod: id.
 	compiler add: '[ context peek ', message,' ] whileTrue: ['.
@@ -22,5 +30,17 @@
 	compiler dedent.
 	compiler add: '].'.
  ^ compiler stopMethod.
+!
+
+rewrite: changeStatus
+
+	(message = #isSeparator) ifTrue: [ 
+		changeStatus change.
+		^ PPCTokenStarSeparatorNode new
+			name: name;
+			child: child;
+			message: message;
+			yourself.
+	]
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/PPCTokenStarSeparatorNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,29 @@
+"{ Package: 'stx:goodies/petitparser/compiler' }"
+
+PPCTokenStarMessagePredicateNode subclass:#PPCTokenStarSeparatorNode
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Nodes'
+!
+
+!PPCTokenStarSeparatorNode methodsFor:'as yet unclassified'!
+
+asInlined
+	^ PPCInlineTokenStarSeparatorNode new
+		message: message;
+		name: name;
+		child: child;
+		yourself
+!
+
+compileWith: compiler effect: effect id: id
+	compiler startMethod: id.
+	compiler add: 'context skipSeparators.'.
+ ^ compiler stopMethod.
+!
+
+rewrite: changeStatus
+	"Nothing to do"
+! !
+
--- a/compiler/PPCTrimNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCTrimNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -36,7 +36,6 @@
 	compiler add: '].'.
 
 	compiler add: '^ result'.
-	compiler stopMethod.
- ^ compiler lastMethod
+ ^ compiler stopMethod.
 ! !
 
--- a/compiler/PPCTrimmingTokenNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCTrimmingTokenNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -27,6 +27,24 @@
 	children at: 2 put: anObject
 !
 
+compileFirstWhitespace: compiler
+	compiler call: (self whitespace compileWith: compiler).
+!
+
+compileSecondWhitespace: compiler
+	| root follow |
+	root := compiler rootNode.
+	
+	follow := self followSetWithTokens.
+	
+	(follow allSatisfy: [ :e | e isKindOf: PPCTrimmingTokenNode ]) ifTrue: [  
+		compiler add: '"second water skipped because there are only trimming tokens in the follow"'
+	] ifFalse: [  
+		compiler add: '"second water compiled because some of the follow parsers are not trimming toknes"'.
+		compiler call: (self whitespace compileWith: compiler).
+	]
+!
+
 compileWhitespace: compiler
 	compiler add: 'context atWs ifFalse: ['.
 	compiler indent.
@@ -95,6 +113,14 @@
 	(block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
 	
 	^ self child firstSetSuchThat: block into: aCollection openSet: aSet.
+!
+
+firstSets: aFirstDictionary into: aSet suchThat: aBlock
+	"PRIVATE: Try to add additional elements to the first-set aSet of the receiver, use the incomplete aFirstDictionary."
+
+	(aBlock value: self) ifFalse: [ 
+		aSet addAll: (aFirstDictionary at: self child)
+	]
 ! !
 
 !PPCTrimmingTokenNode methodsFor:'as yet unclassified'!
@@ -106,6 +132,7 @@
 	compiler addVariable: 'start'.
 	compiler addVariable: 'end'.
 	
+	"self compileFirstWhitespace: compiler."
 	self compileWhitespace: compiler.
 
 	(compiler guards and: [(guard := PPCGuard on: self) makesSense]) ifTrue: [ 
@@ -120,6 +147,7 @@
 	compiler add: 'error ifTrue: [ ^ self ].'.	
 	compiler add: 'end := context position.'.
 	
+"	self compileSecondWhitespace: compiler."
 	self compileWhitespace: compiler.
 
 	compiler add: '^ ', tokenClass asString, ' on: (context collection) 
@@ -133,3 +161,14 @@
 	^ #token
 ! !
 
+!PPCTrimmingTokenNode methodsFor:'comparing'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ tokenClass = anotherNode tokenClass.
+!
+
+hash
+	^ super hash bitXor: tokenClass hash
+! !
+
--- a/compiler/PPCUnknownNode.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCUnknownNode.st	Mon Nov 24 00:09:23 2014 +0000
@@ -7,6 +7,13 @@
 	category:'PetitCompiler-Nodes'
 !
 
+
+!PPCUnknownNode class methodsFor:'as yet unclassified'!
+
+new
+	^ self basicNew initialize
+! !
+
 !PPCUnknownNode methodsFor:'accessing'!
 
 acceptsEpsilon
@@ -29,6 +36,10 @@
 	^ parser isContextFreePrim
 !
 
+isNullable
+	^ parser isNullable
+!
+
 parser
 	
 	^ parser
@@ -49,6 +60,17 @@
 	^ parser firstCharSet
 ! !
 
+!PPCUnknownNode methodsFor:'comparison'!
+
+= anotherNode
+	super = anotherNode ifFalse: [ ^ false ].
+	^ parser = anotherNode parser.
+!
+
+hash
+	^ super hash bitXor: parser hash
+! !
+
 !PPCUnknownNode methodsFor:'compiling'!
 
 compileWith: compiler effect: effect id: id
@@ -81,3 +103,10 @@
 	parser replace: node with: anotherNode
 ! !
 
+!PPCUnknownNode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCompiledParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/PPCompiledParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -17,10 +17,12 @@
 !PPCompiledParser class methodsFor:'as yet unclassified'!
 
 addConstant: value as: id
-	self constants at: id ifPresent: [ 
-		((self constants at: id) = value) ifFalse: [self error: 'ooups']].	
-	
-	self constants at: id put: value.
+        self constants at: id ifPresent: [ :ignored | 
+                ((self constants at: id) = value) ifFalse: [self error: 'ooups']].      
+        
+        self constants at: id put: value.
+
+    "Modified: / 21-11-2014 / 12:32:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 addParser: aPPParser as: id
--- a/compiler/abbrev.stc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/abbrev.stc	Mon Nov 24 00:09:23 2014 +0000
@@ -24,9 +24,6 @@
 PPCNilNode PPCNilNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCPluggableNode PPCPluggableNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCProfilingContext PPCProfilingContext stx:goodies/petitparser/compiler 'PetitCompiler-Context' 0
-PPCStarAnyNode PPCStarAnyNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
-PPCStarCharSetPredicateNode PPCStarCharSetPredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
-PPCStarMessagePredicateNode PPCStarMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCUnknownNode PPCUnknownNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCAbstractActionNode PPCAbstractActionNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCAndNode PPCAndNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
@@ -36,9 +33,7 @@
 PPCForwardNode PPCForwardNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineAnyNode PPCInlineAnyNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineCharacterNode PPCInlineCharacterNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
-PPCInlineLiteralNode PPCInlineLiteralNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineNilNode PPCInlineNilNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
-PPCInlineNotLiteralNode PPCInlineNotLiteralNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlinePluggableNode PPCInlinePluggableNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCLiteralNode PPCLiteralNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCMessagePredicateNode PPCMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
@@ -50,16 +45,26 @@
 PPCOptionalNode PPCOptionalNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCPlusNode PPCPlusNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCPredicateNode PPCPredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCSentinelNode PPCSentinelNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCSequenceNode PPCSequenceNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCStarNode PPCStarNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCTokenNode PPCTokenNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
-PPCTokenStarMessagePredicateNode PPCTokenStarMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCTrimNode PPCTrimNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCTrimmingTokenNode PPCTrimmingTokenNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCActionNode PPCActionNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineCharSetPredicateNode PPCInlineCharSetPredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCInlineLiteralNode PPCInlineLiteralNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineMessagePredicateNode PPCInlineMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineNotCharSetPredicateNode PPCInlineNotCharSetPredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCInlineNotLiteralNode PPCInlineNotLiteralNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCInlineNotMessagePredicateNode PPCInlineNotMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCStarAnyNode PPCStarAnyNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCStarCharSetPredicateNode PPCStarCharSetPredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCStarMessagePredicateNode PPCStarMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCSymbolActionNode PPCSymbolActionNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
 PPCTokenSequenceNode PPCTokenSequenceNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCTokenActionNode PPCTokenActionNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCTokenStarMessagePredicateNode PPCTokenStarMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCInlineTokenStarMessagePredicateNode PPCInlineTokenStarMessagePredicateNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCTokenStarSeparatorNode PPCTokenStarSeparatorNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
+PPCInlineTokenStarSeparatorNode PPCInlineTokenStarSeparatorNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
--- a/compiler/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -95,9 +95,6 @@
 $(OUTDIR)PPCNilNode.$(O) PPCNilNode.$(H): PPCNilNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCPluggableNode.$(O) PPCPluggableNode.$(H): PPCPluggableNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCProfilingContext.$(O) PPCProfilingContext.$(H): PPCProfilingContext.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPStream.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCContext.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
-$(OUTDIR)PPCStarAnyNode.$(O) PPCStarAnyNode.$(H): PPCStarAnyNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)PPCStarCharSetPredicateNode.$(O) PPCStarCharSetPredicateNode.$(H): PPCStarCharSetPredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)PPCStarMessagePredicateNode.$(O) PPCStarMessagePredicateNode.$(H): PPCStarMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCUnknownNode.$(O) PPCUnknownNode.$(H): PPCUnknownNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCAbstractActionNode.$(O) PPCAbstractActionNode.$(H): PPCAbstractActionNode.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)PPCAndNode.$(O) PPCAndNode.$(H): PPCAndNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -107,9 +104,7 @@
 $(OUTDIR)PPCForwardNode.$(O) PPCForwardNode.$(H): PPCForwardNode.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)PPCInlineAnyNode.$(O) PPCInlineAnyNode.$(H): PPCInlineAnyNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAnyNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineCharacterNode.$(O) PPCInlineCharacterNode.$(H): PPCInlineCharacterNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractCharacterNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)PPCInlineLiteralNode.$(O) PPCInlineLiteralNode.$(H): PPCInlineLiteralNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineNilNode.$(O) PPCInlineNilNode.$(H): PPCInlineNilNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNilNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)PPCInlineNotLiteralNode.$(O) PPCInlineNotLiteralNode.$(H): PPCInlineNotLiteralNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlinePluggableNode.$(O) PPCInlinePluggableNode.$(H): PPCInlinePluggableNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCPluggableNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCLiteralNode.$(O) PPCLiteralNode.$(H): PPCLiteralNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMessagePredicateNode.$(O) PPCMessagePredicateNode.$(H): PPCMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -121,19 +116,29 @@
 $(OUTDIR)PPCOptionalNode.$(O) PPCOptionalNode.$(H): PPCOptionalNode.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)PPCPlusNode.$(O) PPCPlusNode.$(H): PPCPlusNode.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)PPCPredicateNode.$(O) PPCPredicateNode.$(H): PPCPredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCSentinelNode.$(O) PPCSentinelNode.$(H): PPCSentinelNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNilNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(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)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)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)
-$(OUTDIR)PPCTokenStarMessagePredicateNode.$(O) PPCTokenStarMessagePredicateNode.$(H): PPCTokenStarMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTrimNode.$(O) PPCTrimNode.$(H): PPCTrimNode.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)PPCTrimmingTokenNode.$(O) PPCTrimmingTokenNode.$(H): PPCTrimmingTokenNode.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)PPCActionNode.$(O) PPCActionNode.$(H): PPCActionNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractActionNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineCharSetPredicateNode.$(O) PPCInlineCharSetPredicateNode.$(H): PPCInlineCharSetPredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCCharSetPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineLiteralNode.$(O) PPCInlineLiteralNode.$(H): PPCInlineLiteralNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCLiteralNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineMessagePredicateNode.$(O) PPCInlineMessagePredicateNode.$(H): PPCInlineMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineNotCharSetPredicateNode.$(O) PPCInlineNotCharSetPredicateNode.$(H): PPCInlineNotCharSetPredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNotCharSetPredicateNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineNotLiteralNode.$(O) PPCInlineNotLiteralNode.$(H): PPCInlineNotLiteralNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractLiteralNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNotLiteralNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCInlineNotMessagePredicateNode.$(O) PPCInlineNotMessagePredicateNode.$(H): PPCInlineNotMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractPredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNotMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCStarAnyNode.$(O) PPCStarAnyNode.$(H): PPCStarAnyNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCStarCharSetPredicateNode.$(O) PPCStarCharSetPredicateNode.$(H): PPCStarCharSetPredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCStarMessagePredicateNode.$(O) PPCStarMessagePredicateNode.$(H): PPCStarMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCSymbolActionNode.$(O) PPCSymbolActionNode.$(H): PPCSymbolActionNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractActionNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCTokenSequenceNode.$(O) PPCTokenSequenceNode.$(H): PPCTokenSequenceNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCListNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCSequenceNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenActionNode.$(O) PPCTokenActionNode.$(H): PPCTokenActionNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCAbstractActionNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCActionNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenStarMessagePredicateNode.$(O) PPCTokenStarMessagePredicateNode.$(H): PPCTokenStarMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineTokenStarMessagePredicateNode.$(O) PPCInlineTokenStarMessagePredicateNode.$(H): PPCInlineTokenStarMessagePredicateNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCTokenStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCTokenStarSeparatorNode.$(O) PPCTokenStarSeparatorNode.$(H): PPCTokenStarSeparatorNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCTokenStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCInlineTokenStarSeparatorNode.$(O) PPCInlineTokenStarSeparatorNode.$(H): PPCInlineTokenStarSeparatorNode.st $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCDelegateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCStarNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCTokenStarMessagePredicateNode.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\compiler\PPCTokenStarSeparatorNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPActionParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPAndParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPCharSetPredicate.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPChoiceParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPCompositeParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPContext.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPEpsilonParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPFailure.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPFlattenParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPListParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPLiteralObjectParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPLiteralParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPLiteralSequenceParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPNotParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPOptionalParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPPluggableParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPPossessiveRepeatingParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPPredicateObjectParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPPredicateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPRepeatingParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPSequenceParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPStream.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPToken.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPTokenParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPTrimmingParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk\PPSmalltalkGrammar.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk\PPSmalltalkTokenParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk\PPSmalltalkWhitespaceParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Character.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\UndefinedObject.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/compiler/benchmarks/PPCBenchmark.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/benchmarks/PPCBenchmark.st	Mon Nov 24 00:09:23 2014 +0000
@@ -4,9 +4,10 @@
 	instanceVariableNames:'sources report contextClass compile parser context input'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Benchmarks'
+	category:'PetitCompiler-Benchmarks-Core'
 !
 
+
 !PPCBenchmark class methodsFor:'instance creation'!
 
 new
@@ -188,6 +189,36 @@
 	self measure: parser on: sources javaLangMath name: #java.
 !
 
+benchmarkJavaSyntax
+	| time |
+	
+	self assert: '../java-src' asFileReference exists description: '../java-src directory with java sources expected'.
+
+	parser := PPJavaSyntax new.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources javaSourcesBig.
+
+	time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+	
+	self reportInput: input time: time name: 'Java Syntax'.
+!
+
+benchmarkJavaSyntaxCompiled
+	| time |
+	
+	self assert: '../java-src' asFileReference exists description: '../java-src directory with java sources expected'.
+
+	parser := PPJavaSyntax new compile.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources javaSourcesBig.
+
+	time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
+	
+	self reportInput: input time: time name: 'Java Syntax Compiled'.
+!
+
 benchmarkNegate
 "
 	self measure: self anyStar on: sources petitParserPackage.
@@ -286,6 +317,22 @@
 
 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
 
+benchmarkJavaSyntaxC
+	<setup: #setupJavaSyntaxC>
+	<benchmark: 'Petit Java Parser - Standard'>
+	
+	input do: [ :source | parser parse: source withContext: context ]
+!
+
+benchmarkJavaSyntaxCompiledC
+	<setup: #setupJavaSyntaxCompiledC>
+	<teardown: #teardownJavaSyntaxCompiledC>
+	<benchmark: 'Petit Java Parser - Compiled'>
+	
+	input do: [ :source | parser parse: source withContext: context ]
+	
+!
+
 benchmarkRBParserC
 	<setup: #setupRBParserC>
 	<benchmark: 'RB Smalltalk Parser'>
@@ -293,6 +340,22 @@
 	input do: [ :source | RBParser parseMethod: source ]
 !
 
+benchmarkSmalltalkGrammarC
+	<setup: #setupSmalltalkGrammarC>
+	<benchmark: 'Petit Smalltalk Grammar - Standard'>
+	
+	input do: [ :source | parser parse: source withContext: context ]
+!
+
+benchmarkSmalltalkGrammarCompiledC
+	<setup: #setupSmalltalkGrammarCompiledC>
+	<teardown: #teardownSmalltalkGrammarCompiledC>
+	<benchmark: 'Petit Smalltalk Grammar - Compiled'>
+	
+	
+	input do: [ :source | parser parse: source withContext: context ]
+!
+
 benchmarkSmalltalkParserC
 	<setup: #setupSmalltalkParserC>
 	<benchmark: 'Petit Smalltalk Parser - Standard'>
@@ -302,7 +365,7 @@
 
 benchmarkSmalltalkParserCompiledC
 	<setup: #setupSmalltalkParserCompiledC>
-	<teaddown: #teardownSmalltalkParserCompiledC>
+	<teardown: #teardownSmalltalkParserCompiledC>
 	<benchmark: 'Petit Smalltalk Parser - Compiled'>
 	
 	input do: [ :source | parser parse: source withContext: context ]
@@ -352,6 +415,14 @@
 
 !PPCBenchmark methodsFor:'setup & teardown-CalipeL'!
 
+setupJavaSyntaxC
+	
+	parser := PPJavaSyntax new.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources javaSourcesBig.
+!
+
 setupJavaSyntaxCompiledC
 	parser := PPJavaSyntax new compile.
 	context := PPCContext new.
@@ -370,6 +441,27 @@
 	input := sources smalltalkSourcesBig.
 !
 
+setupSmalltalkGrammarC
+	
+	parser := PPSmalltalkGrammar new.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources smalltalkSourcesBig.
+!
+
+setupSmalltalkGrammarCompiledC
+	parser := PPSmalltalkGrammar new compile.
+	context := PPCContext new.
+	context initializeFor: parser.
+	input := sources smalltalkSourcesBig.
+
+"	
+	size := input inject: 0 into: [:r :e | r + e size  ].
+	Transcript crShow: 'Compiled Grammar time: ', time asString.
+	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
+"
+!
+
 setupSmalltalkParserC
 	
 	parser := PPSmalltalkParser new.
@@ -400,6 +492,15 @@
 "
 !
 
+teardownSmalltalkGrammarCompiledC
+	parser class removeFromSystem.
+"	
+	size := input inject: 0 into: [:r :e | r + e size  ].
+	Transcript crShow: 'Compiled Grammar time: ', time asString.
+	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
+"
+!
+
 teardownSmalltalkParserCompiledC
 	parser class removeFromSystem.
 "	
@@ -433,3 +534,10 @@
 	self endSuite.
 ! !
 
+!PPCBenchmark class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/benchmarks/PPCBenchmarkResources.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/benchmarks/PPCBenchmarkResources.st	Mon Nov 24 00:09:23 2014 +0000
@@ -4,7 +4,7 @@
 	instanceVariableNames:''
 	classVariableNames:'javaCache'
 	poolDictionaries:''
-	category:'PetitCompiler-Benchmarks'
+	category:'PetitCompiler-Benchmarks-Core'
 !
 
 !PPCBenchmarkResources methodsFor:'as yet unclassified'!
@@ -29,1231 +29,12 @@
 !
 
 javaLangMath
-	^ '/*
- * @(#)Math.java	1.69 04/06/14
- *
- * Copyright 2004 Sun Microsystems, Inc. All rights reserved.
- * SUN PROPRIETARY/CONFIDENTIAL. Use is subject to license terms.
- */
-
-package java.lang;
-import java.util.Random;
-
-
-/**
- * The class <code>Math</code> contains methods for performing basic
- * numeric operations such as the elementary exponential, logarithm,
- * square root, and trigonometric functions.
- * 
- * <p>Unlike some of the numeric methods of class
- * <code>StrictMath</code>, all implementations of the equivalent
- * functions of class <code>Math</code> are not defined to return the
- * bit-for-bit same results.  This relaxation permits
- * better-performing implementations where strict reproducibility is
- * not required.
- * 
- * <p>By default many of the <code>Math</code> methods simply call
- * the equivalent method in <code>StrictMath</code> for their
- * implementation.  Code generators are encouraged to use
- * platform-specific native libraries or microprocessor instructions,
- * where available, to provide higher-performance implementations of
- * <code>Math</code> methods.  Such higher-performance
- * implementations still must conform to the specification for
- * <code>Math</code>.
- * 
- * <p>The quality of implementation specifications concern two
- * properties, accuracy of the returned result and monotonicity of the
- * method.  Accuracy of the floating-point <code>Math</code> methods
- * is measured in terms of <i>ulps</i>, units in the last place.  For
- * a given floating-point format, an ulp of a specific real number
- * value is the distance between the two floating-point values
- * bracketing that numerical value.  When discussing the accuracy of a
- * method as a whole rather than at a specific argument, the number of
- * ulps cited is for the worst-case error at any argument.  If a
- * method always has an error less than 0.5 ulps, the method always
- * returns the floating-point number nearest the exact result; such a
- * method is <i>correctly rounded</i>.  A correctly rounded method is
- * generally the best a floating-point approximation can be; however,
- * it is impractical for many floating-point methods to be correctly
- * rounded.  Instead, for the <code>Math</code> class, a larger error
- * bound of 1 or 2 ulps is allowed for certain methods.  Informally,
- * with a 1 ulp error bound, when the exact result is a representable
- * number, the exact result should be returned as the computed result;
- * otherwise, either of the two floating-point values which bracket
- * the exact result may be returned.  For exact results large in
- * magnitude, one of the endpoints of the bracket may be infinite.
- * Besides accuracy at individual arguments, maintaining proper
- * relations between the method at different arguments is also
- * important.  Therefore, most methods with more than 0.5 ulp errors
- * are required to be <i>semi-monotonic</i>: whenever the mathematical
- * function is non-decreasing, so is the floating-point approximation,
- * likewise, whenever the mathematical function is non-increasing, so
- * is the floating-point approximation.  Not all approximations that
- * have 1 ulp accuracy will automatically meet the monotonicity
- * requirements.
- * 
- * @author  unascribed
- * @author  Joseph D. Darcy
- * @version 1.69, 06/14/04
- * @since   JDK1.0
- */
-
-public final class Math {
-
-    /**
-     * Don''t let anyone instantiate this class.
-     */
-    private Math() {}
-
-    /**
-     * The <code>double</code> value that is closer than any other to
-     * <i>e</i>, the base of the natural logarithms.
-     */
-    public static final double E = 2.7182818284590452354;
-
-    /**
-     * The <code>double</code> value that is closer than any other to
-     * <i>pi</i>, the ratio of the circumference of a circle to its
-     * diameter.
-     */
-    public static final double PI = 3.14159265358979323846;
-
-    /**
-     * Returns the trigonometric sine of an angle.  Special cases:
-     * <ul><li>If the argument is NaN or an infinity, then the 
-     * result is NaN.
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   an angle, in radians.
-     * @return  the sine of the argument.
-     */
-    public static double sin(double a) {
-	return StrictMath.sin(a); // default impl. delegates to StrictMath
-    }
-    
-    /**
-     * Returns the trigonometric cosine of an angle. Special cases:
-     * <ul><li>If the argument is NaN or an infinity, then the 
-     * result is NaN.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   an angle, in radians.
-     * @return  the cosine of the argument.
-     */
-    public static double cos(double a) {
-	return StrictMath.cos(a); // default impl. delegates to StrictMath
-    }
-   
-    /**
-     * Returns the trigonometric tangent of an angle.  Special cases:
-     * <ul><li>If the argument is NaN or an infinity, then the result 
-     * is NaN.
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   an angle, in radians.
-     * @return  the tangent of the argument.
-     */
-    public static double tan(double a) {
-	return StrictMath.tan(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the arc sine of an angle, in the range of -<i>pi</i>/2 through
-     * <i>pi</i>/2. Special cases: 
-     * <ul><li>If the argument is NaN or its absolute value is greater 
-     * than 1, then the result is NaN.
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   the value whose arc sine is to be returned.
-     * @return  the arc sine of the argument.
-     */
-    public static double asin(double a) {
-	return StrictMath.asin(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the arc cosine of an angle, in the range of 0.0 through
-     * <i>pi</i>.  Special case:
-     * <ul><li>If the argument is NaN or its absolute value is greater 
-     * than 1, then the result is NaN.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   the value whose arc cosine is to be returned.
-     * @return  the arc cosine of the argument.
-     */
-    public static double acos(double a) {
-	return StrictMath.acos(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the arc tangent of an angle, in the range of -<i>pi</i>/2
-     * through <i>pi</i>/2.  Special cases: 
-     * <ul><li>If the argument is NaN, then the result is NaN.
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   the value whose arc tangent is to be returned.
-     * @return  the arc tangent of the argument.
-     */
-    public static double atan(double a) {
-	return StrictMath.atan(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Converts an angle measured in degrees to an approximately
-     * equivalent angle measured in radians.  The conversion from
-     * degrees to radians is generally inexact.
-     *
-     * @param   angdeg   an angle, in degrees
-     * @return  the measurement of the angle <code>angdeg</code>
-     *          in radians.
-     * @since   1.2
-     */
-    public static double toRadians(double angdeg) {
-	return angdeg / 180.0 * PI;
-    }
-
-    /**
-     * Converts an angle measured in radians to an approximately
-     * equivalent angle measured in degrees.  The conversion from
-     * radians to degrees is generally inexact; users should
-     * <i>not</i> expect <code>cos(toRadians(90.0))</code> to exactly
-     * equal <code>0.0</code>.
-     *
-     * @param   angrad   an angle, in radians
-     * @return  the measurement of the angle <code>angrad</code>
-     *          in degrees.
-     * @since   1.2
-     */
-    public static double toDegrees(double angrad) {
-	return angrad * 180.0 / PI;
-    }
-
-    /**
-     * Returns Euler''s number <i>e</i> raised to the power of a
-     * <code>double</code> value.  Special cases:
-     * <ul><li>If the argument is NaN, the result is NaN.
-     * <li>If the argument is positive infinity, then the result is 
-     * positive infinity.
-     * <li>If the argument is negative infinity, then the result is 
-     * positive zero.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   the exponent to raise <i>e</i> to.
-     * @return  the value <i>e</i><sup><code>a</code></sup>, 
-     *          where <i>e</i> is the base of the natural logarithms.
-     */
-    public static double exp(double a) {
-	return StrictMath.exp(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the natural logarithm (base <i>e</i>) of a <code>double</code>
-     * value.  Special cases:
-     * <ul><li>If the argument is NaN or less than zero, then the result 
-     * is NaN.
-     * <li>If the argument is positive infinity, then the result is 
-     * positive infinity.
-     * <li>If the argument is positive zero or negative zero, then the 
-     * result is negative infinity.</ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   a value
-     * @return  the value ln&nbsp;<code>a</code>, the natural logarithm of
-     *          <code>a</code>.
-     */
-    public static double log(double a) {
-	return StrictMath.log(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the base 10 logarithm of a <code>double</code> value.
-     * Special cases:
-     *
-     * <ul><li>If the argument is NaN or less than zero, then the result 
-     * is NaN.
-     * <li>If the argument is positive infinity, then the result is 
-     * positive infinity.
-     * <li>If the argument is positive zero or negative zero, then the 
-     * result is negative infinity.
-     * <li> If the argument is equal to 10<sup><i>n</i></sup> for
-     * integer <i>n</i>, then the result is <i>n</i>.
-     * </ul>
-     * 
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   a value
-     * @return  the base 10 logarithm of  <code>a</code>.
-     * @since 1.5
-     */
-    public static double log10(double a) {
-	return StrictMath.log10(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the correctly rounded positive square root of a 
-     * <code>double</code> value.
-     * Special cases:
-     * <ul><li>If the argument is NaN or less than zero, then the result 
-     * is NaN. 
-     * <li>If the argument is positive infinity, then the result is positive 
-     * infinity. 
-     * <li>If the argument is positive zero or negative zero, then the 
-     * result is the same as the argument.</ul>
-     * Otherwise, the result is the <code>double</code> value closest to 
-     * the true mathematical square root of the argument value.
-     * 
-     * @param   a   a value.
-     * @return  the positive square root of <code>a</code>.
-     *          If the argument is NaN or less than zero, the result is NaN.
-     */
-    public static double sqrt(double a) {
-	return StrictMath.sqrt(a); // default impl. delegates to StrictMath
-				   // Note that hardware sqrt instructions
-				   // frequently can be directly used by JITs
-				   // and should be much faster than doing
-				   // Math.sqrt in software.
-    }
-
-
-    /**
-     * Returns the cube root of a <code>double</code> value.  For
-     * positive finite <code>x</code>, <code>cbrt(-x) ==
-     * -cbrt(x)</code>; that is, the cube root of a negative value is
-     * the negative of the cube root of that value''s magnitude.
-     * 
-     * Special cases: 
-     *
-     * <ul>
-     * 
-     * <li>If the argument is NaN, then the result is NaN.
-     *
-     * <li>If the argument is infinite, then the result is an infinity
-     * with the same sign as the argument.
-     *
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.
-     * 
-     * </ul>
-     *
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * 
-     * @param   a   a value.
-     * @return  the cube root of <code>a</code>.
-     * @since 1.5
-     */
-    public static double cbrt(double a) {
-	return StrictMath.cbrt(a);
-    }
-
-    /**
-     * Computes the remainder operation on two arguments as prescribed 
-     * by the IEEE 754 standard.
-     * The remainder value is mathematically equal to 
-     * <code>f1&nbsp;-&nbsp;f2</code>&nbsp;&times;&nbsp;<i>n</i>,
-     * where <i>n</i> is the mathematical integer closest to the exact 
-     * mathematical value of the quotient <code>f1/f2</code>, and if two 
-     * mathematical integers are equally close to <code>f1/f2</code>, 
-     * then <i>n</i> is the integer that is even. If the remainder is 
-     * zero, its sign is the same as the sign of the first argument. 
-     * Special cases:
-     * <ul><li>If either argument is NaN, or the first argument is infinite, 
-     * or the second argument is positive zero or negative zero, then the 
-     * result is NaN.
-     * <li>If the first argument is finite and the second argument is 
-     * infinite, then the result is the same as the first argument.</ul>
-     *
-     * @param   f1   the dividend.
-     * @param   f2   the divisor.
-     * @return  the remainder when <code>f1</code> is divided by
-     *          <code>f2</code>.
-     */
-    public static double IEEEremainder(double f1, double f2) {
-        return StrictMath.IEEEremainder(f1, f2); // delegate to StrictMath
-    }
-
-    /**
-     * Returns the smallest (closest to negative infinity)
-     * <code>double</code> value that is greater than or equal to the
-     * argument and is equal to a mathematical integer. Special cases:
-     * <ul><li>If the argument value is already equal to a
-     * mathematical integer, then the result is the same as the
-     * argument.  <li>If the argument is NaN or an infinity or
-     * positive zero or negative zero, then the result is the same as
-     * the argument.  <li>If the argument value is less than zero but
-     * greater than -1.0, then the result is negative zero.</ul> Note
-     * that the value of <code>Math.ceil(x)</code> is exactly the
-     * value of <code>-Math.floor(-x)</code>.
-     *
-     *
-     * @param   a   a value.
-     * @return  the smallest (closest to negative infinity) 
-     *          floating-point value that is greater than or equal to 
-     *          the argument and is equal to a mathematical integer. 
-     */
-    public static double ceil(double a) {
-	return StrictMath.ceil(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the largest (closest to positive infinity)
-     * <code>double</code> value that is less than or equal to the
-     * argument and is equal to a mathematical integer. Special cases:
-     * <ul><li>If the argument value is already equal to a
-     * mathematical integer, then the result is the same as the
-     * argument.  <li>If the argument is NaN or an infinity or
-     * positive zero or negative zero, then the result is the same as
-     * the argument.</ul>
-     *
-     * @param   a   a value.
-     * @return  the largest (closest to positive infinity) 
-     *          floating-point value that less than or equal to the argument
-     *          and is equal to a mathematical integer. 
-     */
-    public static double floor(double a) {
-	return StrictMath.floor(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the <code>double</code> value that is closest in value
-     * to the argument and is equal to a mathematical integer. If two
-     * <code>double</code> values that are mathematical integers are
-     * equally close, the result is the integer value that is
-     * even. Special cases:
-     * <ul><li>If the argument value is already equal to a mathematical 
-     * integer, then the result is the same as the argument. 
-     * <li>If the argument is NaN or an infinity or positive zero or negative 
-     * zero, then the result is the same as the argument.</ul>
-     *
-     * @param   a   a <code>double</code> value.
-     * @return  the closest floating-point value to <code>a</code> that is
-     *          equal to a mathematical integer.
-     */
-    public static double rint(double a) {
-	return StrictMath.rint(a); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Converts rectangular coordinates (<code>x</code>,&nbsp;<code>y</code>)
-     * to polar (r,&nbsp;<i>theta</i>).
-     * This method computes the phase <i>theta</i> by computing an arc tangent
-     * of <code>y/x</code> in the range of -<i>pi</i> to <i>pi</i>. Special 
-     * cases:
-     * <ul><li>If either argument is NaN, then the result is NaN. 
-     * <li>If the first argument is positive zero and the second argument 
-     * is positive, or the first argument is positive and finite and the 
-     * second argument is positive infinity, then the result is positive 
-     * zero. 
-     * <li>If the first argument is negative zero and the second argument 
-     * is positive, or the first argument is negative and finite and the 
-     * second argument is positive infinity, then the result is negative zero. 
-     * <li>If the first argument is positive zero and the second argument 
-     * is negative, or the first argument is positive and finite and the 
-     * second argument is negative infinity, then the result is the 
-     * <code>double</code> value closest to <i>pi</i>. 
-     * <li>If the first argument is negative zero and the second argument 
-     * is negative, or the first argument is negative and finite and the 
-     * second argument is negative infinity, then the result is the 
-     * <code>double</code> value closest to -<i>pi</i>. 
-     * <li>If the first argument is positive and the second argument is 
-     * positive zero or negative zero, or the first argument is positive 
-     * infinity and the second argument is finite, then the result is the 
-     * <code>double</code> value closest to <i>pi</i>/2. 
-     * <li>If the first argument is negative and the second argument is 
-     * positive zero or negative zero, or the first argument is negative 
-     * infinity and the second argument is finite, then the result is the 
-     * <code>double</code> value closest to -<i>pi</i>/2. 
-     * <li>If both arguments are positive infinity, then the result is the 
-     * <code>double</code> value closest to <i>pi</i>/4. 
-     * <li>If the first argument is positive infinity and the second argument 
-     * is negative infinity, then the result is the <code>double</code> 
-     * value closest to 3*<i>pi</i>/4. 
-     * <li>If the first argument is negative infinity and the second argument 
-     * is positive infinity, then the result is the <code>double</code> value 
-     * closest to -<i>pi</i>/4. 
-     * <li>If both arguments are negative infinity, then the result is the 
-     * <code>double</code> value closest to -3*<i>pi</i>/4.</ul>
-     * 
-     * <p>The computed result must be within 2 ulps of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   y   the ordinate coordinate
-     * @param   x   the abscissa coordinate
-     * @return  the <i>theta</i> component of the point
-     *          (<i>r</i>,&nbsp;<i>theta</i>)
-     *          in polar coordinates that corresponds to the point
-     *          (<i>x</i>,&nbsp;<i>y</i>) in Cartesian coordinates.
-     */
-    public static double atan2(double y, double x) {
-	return StrictMath.atan2(y, x); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the value of the first argument raised to the power of the
-     * second argument. Special cases:
-     *
-     * <ul><li>If the second argument is positive or negative zero, then the 
-     * result is 1.0. 
-     * <li>If the second argument is 1.0, then the result is the same as the 
-     * first argument.
-     * <li>If the second argument is NaN, then the result is NaN. 
-     * <li>If the first argument is NaN and the second argument is nonzero, 
-     * then the result is NaN. 
-     *
-     * <li>If
-     * <ul>
-     * <li>the absolute value of the first argument is greater than 1
-     * and the second argument is positive infinity, or
-     * <li>the absolute value of the first argument is less than 1 and
-     * the second argument is negative infinity,
-     * </ul>
-     * then the result is positive infinity. 
-     *
-     * <li>If 
-     * <ul>
-     * <li>the absolute value of the first argument is greater than 1 and 
-     * the second argument is negative infinity, or 
-     * <li>the absolute value of the 
-     * first argument is less than 1 and the second argument is positive 
-     * infinity,
-     * </ul>
-     * then the result is positive zero. 
-     *
-     * <li>If the absolute value of the first argument equals 1 and the 
-     * second argument is infinite, then the result is NaN. 
-     *
-     * <li>If 
-     * <ul>
-     * <li>the first argument is positive zero and the second argument
-     * is greater than zero, or
-     * <li>the first argument is positive infinity and the second
-     * argument is less than zero,
-     * </ul>
-     * then the result is positive zero. 
-     *
-     * <li>If 
-     * <ul>
-     * <li>the first argument is positive zero and the second argument
-     * is less than zero, or
-     * <li>the first argument is positive infinity and the second
-     * argument is greater than zero,
-     * </ul>
-     * then the result is positive infinity.
-     *
-     * <li>If 
-     * <ul>
-     * <li>the first argument is negative zero and the second argument
-     * is greater than zero but not a finite odd integer, or
-     * <li>the first argument is negative infinity and the second
-     * argument is less than zero but not a finite odd integer,
-     * </ul>
-     * then the result is positive zero. 
-     *
-     * <li>If 
-     * <ul>
-     * <li>the first argument is negative zero and the second argument
-     * is a positive finite odd integer, or
-     * <li>the first argument is negative infinity and the second
-     * argument is a negative finite odd integer,
-     * </ul>
-     * then the result is negative zero. 
-     *
-     * <li>If
-     * <ul>
-     * <li>the first argument is negative zero and the second argument
-     * is less than zero but not a finite odd integer, or
-     * <li>the first argument is negative infinity and the second
-     * argument is greater than zero but not a finite odd integer,
-     * </ul>
-     * then the result is positive infinity. 
-     *
-     * <li>If 
-     * <ul>
-     * <li>the first argument is negative zero and the second argument
-     * is a negative finite odd integer, or
-     * <li>the first argument is negative infinity and the second
-     * argument is a positive finite odd integer,
-     * </ul>
-     * then the result is negative infinity. 
-     *
-     * <li>If the first argument is finite and less than zero
-     * <ul>
-     * <li> if the second argument is a finite even integer, the
-     * result is equal to the result of raising the absolute value of
-     * the first argument to the power of the second argument
-     *
-     * <li>if the second argument is a finite odd integer, the result
-     * is equal to the negative of the result of raising the absolute
-     * value of the first argument to the power of the second
-     * argument
-     *
-     * <li>if the second argument is finite and not an integer, then
-     * the result is NaN.
-     * </ul>
-     *
-     * <li>If both arguments are integers, then the result is exactly equal 
-     * to the mathematical result of raising the first argument to the power 
-     * of the second argument if that result can in fact be represented 
-     * exactly as a <code>double</code> value.</ul>
-     * 
-     * <p>(In the foregoing descriptions, a floating-point value is
-     * considered to be an integer if and only if it is finite and a
-     * fixed point of the method {@link #ceil <tt>ceil</tt>} or,
-     * equivalently, a fixed point of the method {@link #floor
-     * <tt>floor</tt>}. A value is a fixed point of a one-argument
-     * method if and only if the result of applying the method to the
-     * value is equal to the value.)
-     *
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   a   the base.
-     * @param   b   the exponent.
-     * @return  the value <code>a<sup>b</sup></code>.
-     */
-    public static double pow(double a, double b) {
-	return StrictMath.pow(a, b); // default impl. delegates to StrictMath
-    }
-
-    /**
-     * Returns the closest <code>int</code> to the argument. The 
-     * result is rounded to an integer by adding 1/2, taking the 
-     * floor of the result, and casting the result to type <code>int</code>. 
-     * In other words, the result is equal to the value of the expression:
-     * <p><pre>(int)Math.floor(a + 0.5f)</pre>
-     * <p>
-     * Special cases:
-     * <ul><li>If the argument is NaN, the result is 0.
-     * <li>If the argument is negative infinity or any value less than or 
-     * equal to the value of <code>Integer.MIN_VALUE</code>, the result is 
-     * equal to the value of <code>Integer.MIN_VALUE</code>. 
-     * <li>If the argument is positive infinity or any value greater than or 
-     * equal to the value of <code>Integer.MAX_VALUE</code>, the result is 
-     * equal to the value of <code>Integer.MAX_VALUE</code>.</ul> 
-     *
-     * @param   a   a floating-point value to be rounded to an integer.
-     * @return  the value of the argument rounded to the nearest
-     *          <code>int</code> value.
-     * @see     java.lang.Integer#MAX_VALUE
-     * @see     java.lang.Integer#MIN_VALUE
-     */
-    public static int round(float a) {
-	return (int)floor(a + 0.5f);
-    }
-
-    /**
-     * Returns the closest <code>long</code> to the argument. The result 
-     * is rounded to an integer by adding 1/2, taking the floor of the 
-     * result, and casting the result to type <code>long</code>. In other 
-     * words, the result is equal to the value of the expression:
-     * <p><pre>(long)Math.floor(a + 0.5d)</pre>
-     * <p>
-     * Special cases:
-     * <ul><li>If the argument is NaN, the result is 0.
-     * <li>If the argument is negative infinity or any value less than or 
-     * equal to the value of <code>Long.MIN_VALUE</code>, the result is 
-     * equal to the value of <code>Long.MIN_VALUE</code>. 
-     * <li>If the argument is positive infinity or any value greater than or 
-     * equal to the value of <code>Long.MAX_VALUE</code>, the result is 
-     * equal to the value of <code>Long.MAX_VALUE</code>.</ul> 
-     *
-     * @param   a   a floating-point value to be rounded to a 
-     *		<code>long</code>.
-     * @return  the value of the argument rounded to the nearest
-     *          <code>long</code> value.
-     * @see     java.lang.Long#MAX_VALUE
-     * @see     java.lang.Long#MIN_VALUE
-     */
-    public static long round(double a) {
-	return (long)floor(a + 0.5d);
-    }
-
-    private static Random randomNumberGenerator;
-
-    private static synchronized void initRNG() {
-        if (randomNumberGenerator == null) 
-            randomNumberGenerator = new Random();
-    }
-
-    /**
-     * Returns a <code>double</code> value with a positive sign, greater 
-     * than or equal to <code>0.0</code> and less than <code>1.0</code>. 
-     * Returned values are chosen pseudorandomly with (approximately) 
-     * uniform distribution from that range. 
-     * 
-     * <p>When this method is first called, it creates a single new
-     * pseudorandom-number generator, exactly as if by the expression
-     * <blockquote><pre>new java.util.Random</pre></blockquote> This
-     * new pseudorandom-number generator is used thereafter for all
-     * calls to this method and is used nowhere else.
-     * 
-     * <p>This method is properly synchronized to allow correct use by
-     * more than one thread. However, if many threads need to generate
-     * pseudorandom numbers at a great rate, it may reduce contention
-     * for each thread to have its own pseudorandom-number generator.
-     *  
-     * @return  a pseudorandom <code>double</code> greater than or equal 
-     * to <code>0.0</code> and less than <code>1.0</code>.
-     * @see     java.util.Random#nextDouble()
-     */
-    public static double random() {
-        if (randomNumberGenerator == null) initRNG();
-        return randomNumberGenerator.nextDouble();
-    }
-
-    /**
-     * Returns the absolute value of an <code>int</code> value.
-     * If the argument is not negative, the argument is returned.
-     * If the argument is negative, the negation of the argument is returned. 
-     * 
-     * <p>Note that if the argument is equal to the value of
-     * <code>Integer.MIN_VALUE</code>, the most negative representable
-     * <code>int</code> value, the result is that same value, which is
-     * negative.
-     *
-     * @param   a   the argument whose absolute value is to be determined
-     * @return  the absolute value of the argument.
-     * @see     java.lang.Integer#MIN_VALUE
-     */
-    public static int abs(int a) {
-	return (a < 0) ? -a : a;
-    }
-
-    /**
-     * Returns the absolute value of a <code>long</code> value.
-     * If the argument is not negative, the argument is returned.
-     * If the argument is negative, the negation of the argument is returned. 
-     * 
-     * <p>Note that if the argument is equal to the value of
-     * <code>Long.MIN_VALUE</code>, the most negative representable
-     * <code>long</code> value, the result is that same value, which
-     * is negative.
-     *
-     * @param   a   the argument whose absolute value is to be determined
-     * @return  the absolute value of the argument.
-     * @see     java.lang.Long#MIN_VALUE
-     */
-    public static long abs(long a) {
-	return (a < 0) ? -a : a;
-    }
-
-    /**
-     * Returns the absolute value of a <code>float</code> value.
-     * If the argument is not negative, the argument is returned.
-     * If the argument is negative, the negation of the argument is returned.
-     * Special cases:
-     * <ul><li>If the argument is positive zero or negative zero, the 
-     * result is positive zero. 
-     * <li>If the argument is infinite, the result is positive infinity. 
-     * <li>If the argument is NaN, the result is NaN.</ul>
-     * In other words, the result is the same as the value of the expression: 
-     * <p><pre>Float.intBitsToFloat(0x7fffffff & Float.floatToIntBits(a))</pre>
-     *
-     * @param   a   the argument whose absolute value is to be determined
-     * @return  the absolute value of the argument.
-     */
-    public static float abs(float a) {
-        return (a <= 0.0F) ? 0.0F - a : a;
-    }
-  
-    /**
-     * Returns the absolute value of a <code>double</code> value.
-     * If the argument is not negative, the argument is returned.
-     * If the argument is negative, the negation of the argument is returned.
-     * Special cases:
-     * <ul><li>If the argument is positive zero or negative zero, the result 
-     * is positive zero. 
-     * <li>If the argument is infinite, the result is positive infinity. 
-     * <li>If the argument is NaN, the result is NaN.</ul>
-     * In other words, the result is the same as the value of the expression: 
-     * <p><code>Double.longBitsToDouble((Double.doubleToLongBits(a)&lt;&lt;1)&gt;&gt;&gt;1)</code> 
-     *
-     * @param   a   the argument whose absolute value is to be determined
-     * @return  the absolute value of the argument.
-     */
-    public static double abs(double a) {
-        return (a <= 0.0D) ? 0.0D - a : a;
-    }
-
-    /**
-     * Returns the greater of two <code>int</code> values. That is, the 
-     * result is the argument closer to the value of 
-     * <code>Integer.MAX_VALUE</code>. If the arguments have the same value, 
-     * the result is that same value.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the larger of <code>a</code> and <code>b</code>.
-     * @see     java.lang.Long#MAX_VALUE
-     */
-    public static int max(int a, int b) {
-	return (a >= b) ? a : b;
-    }
-
-    /**
-     * Returns the greater of two <code>long</code> values. That is, the 
-     * result is the argument closer to the value of 
-     * <code>Long.MAX_VALUE</code>. If the arguments have the same value, 
-     * the result is that same value. 
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the larger of <code>a</code> and <code>b</code>.
-     * @see     java.lang.Long#MAX_VALUE
-     */
-    public static long max(long a, long b) {
-	return (a >= b) ? a : b;
-    }
-
-    private static long negativeZeroFloatBits = Float.floatToIntBits(-0.0f);
-    private static long negativeZeroDoubleBits = Double.doubleToLongBits(-0.0d);
-
-    /**
-     * Returns the greater of two <code>float</code> values.  That is,
-     * the result is the argument closer to positive infinity. If the
-     * arguments have the same value, the result is that same
-     * value. If either value is NaN, then the result is NaN.  Unlike
-     * the numerical comparison operators, this method considers
-     * negative zero to be strictly smaller than positive zero. If one
-     * argument is positive zero and the other negative zero, the
-     * result is positive zero.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the larger of <code>a</code> and <code>b</code>.
-     */
-    public static float max(float a, float b) {
-        if (a !!= a) return a;	// a is NaN
-	if ((a == 0.0f) && (b == 0.0f)
-	    && (Float.floatToIntBits(a) == negativeZeroFloatBits)) {
-	    return b;
-	}
-	return (a >= b) ? a : b;
-    }
-
-    /**
-     * Returns the greater of two <code>double</code> values.  That
-     * is, the result is the argument closer to positive infinity. If
-     * the arguments have the same value, the result is that same
-     * value. If either value is NaN, then the result is NaN.  Unlike
-     * the numerical comparison operators, this method considers
-     * negative zero to be strictly smaller than positive zero. If one
-     * argument is positive zero and the other negative zero, the
-     * result is positive zero.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the larger of <code>a</code> and <code>b</code>.
-     */
-    public static double max(double a, double b) {
-        if (a !!= a) return a;	// a is NaN
-	if ((a == 0.0d) && (b == 0.0d)
-	    && (Double.doubleToLongBits(a) == negativeZeroDoubleBits)) {
-	    return b;
-	}
-	return (a >= b) ? a : b;
-    }
-
-    /**
-     * Returns the smaller of two <code>int</code> values. That is,
-     * the result the argument closer to the value of
-     * <code>Integer.MIN_VALUE</code>.  If the arguments have the same
-     * value, the result is that same value.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the smaller of <code>a</code> and <code>b</code>.
-     * @see     java.lang.Long#MIN_VALUE
-     */
-    public static int min(int a, int b) {
-	return (a <= b) ? a : b;
-    }
-
-    /**
-     * Returns the smaller of two <code>long</code> values. That is,
-     * the result is the argument closer to the value of
-     * <code>Long.MIN_VALUE</code>. If the arguments have the same
-     * value, the result is that same value.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the smaller of <code>a</code> and <code>b</code>.
-     * @see     java.lang.Long#MIN_VALUE
-     */
-    public static long min(long a, long b) {
-	return (a <= b) ? a : b;
-    }
-
-    /**
-     * Returns the smaller of two <code>float</code> values.  That is,
-     * the result is the value closer to negative infinity. If the
-     * arguments have the same value, the result is that same
-     * value. If either value is NaN, then the result is NaN.  Unlike
-     * the numerical comparison operators, this method considers
-     * negative zero to be strictly smaller than positive zero.  If
-     * one argument is positive zero and the other is negative zero,
-     * the result is negative zero.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the smaller of <code>a</code> and <code>b.</code>
-     */
-    public static float min(float a, float b) {
-        if (a !!= a) return a;	// a is NaN
-	if ((a == 0.0f) && (b == 0.0f)
-	    && (Float.floatToIntBits(b) == negativeZeroFloatBits)) {
-	    return b;
-	}
-	return (a <= b) ? a : b;
-    }
-
-    /**
-     * Returns the smaller of two <code>double</code> values.  That
-     * is, the result is the value closer to negative infinity. If the
-     * arguments have the same value, the result is that same
-     * value. If either value is NaN, then the result is NaN.  Unlike
-     * the numerical comparison operators, this method considers
-     * negative zero to be strictly smaller than positive zero. If one
-     * argument is positive zero and the other is negative zero, the
-     * result is negative zero.
-     *
-     * @param   a   an argument.
-     * @param   b   another argument.
-     * @return  the smaller of <code>a</code> and <code>b</code>.
-     */
-    public static double min(double a, double b) {
-        if (a !!= a) return a;	// a is NaN
-	if ((a == 0.0d) && (b == 0.0d)
-	    && (Double.doubleToLongBits(b) == negativeZeroDoubleBits)) {
-	    return b;
-	}
-	return (a <= b) ? a : b;
-    }
-
-    /**
-     * Returns the size of an ulp of the argument.  An ulp of a
-     * <code>double</code> value is the positive distance between this
-     * floating-point value and the <code>double</code> value next
-     * larger in magnitude.  Note that for non-NaN <i>x</i>,
-     * <code>ulp(-<i>x</i>) == ulp(<i>x</i>)</code>.
-     * 
-     * <p>Special Cases:
-     * <ul>
-     * <li> If the argument is NaN, then the result is NaN.
-     * <li> If the argument is positive or negative infinity, then the
-     * result is positive infinity.
-     * <li> If the argument is positive or negative zero, then the result is
-     * <code>Double.MIN_VALUE</code>.
-     * <li> If the argument is &plusmn;<code>Double.MAX_VALUE</code>, then
-     * the result is equal to 2<sup>971</sup>.
-     * </ul>
-     *
-     * @param d the floating-point value whose ulp is to be returned
-     * @return the size of an ulp of the argument
-     * @author Joseph D. Darcy
-     * @since 1.5
-     */
-    public static double ulp(double d) {
-	return sun.misc.FpUtils.ulp(d);
-    }
-
-    /**
-     * Returns the size of an ulp of the argument.  An ulp of a
-     * <code>float</code> value is the positive distance between this
-     * floating-point value and the <code>float</code> value next
-     * larger in magnitude.  Note that for non-NaN <i>x</i>,
-     * <code>ulp(-<i>x</i>) == ulp(<i>x</i>)</code>.
-     * 
-     * <p>Special Cases:
-     * <ul>
-     * <li> If the argument is NaN, then the result is NaN.
-     * <li> If the argument is positive or negative infinity, then the
-     * result is positive infinity.
-     * <li> If the argument is positive or negative zero, then the result is
-     * <code>Float.MIN_VALUE</code>.
-     * <li> If the argument is &plusmn;<code>Float.MAX_VALUE</code>, then
-     * the result is equal to 2<sup>104</sup>.
-     * </ul>
-     *
-     * @param f the floating-point value whose ulp is to be returned
-     * @return the size of an ulp of the argument
-     * @author Joseph D. Darcy
-     * @since 1.5
-     */
-    public static float ulp(float f) {
-	return sun.misc.FpUtils.ulp(f);
-    }
-
-    /**
-     * Returns the signum function of the argument; zero if the argument
-     * is zero, 1.0 if the argument is greater than zero, -1.0 if the
-     * argument is less than zero.
-     *
-     * <p>Special Cases:
-     * <ul>
-     * <li> If the argument is NaN, then the result is NaN.
-     * <li> If the argument is positive zero or negative zero, then the
-     *      result is the same as the argument.
-     * </ul>
-     *
-     * @param d the floating-point value whose signum is to be returned
-     * @return the signum function of the argument
-     * @author Joseph D. Darcy
-     * @since 1.5
-     */
-    public static double signum(double d) {
-	return sun.misc.FpUtils.signum(d);
-    }
-
-    /**
-     * Returns the signum function of the argument; zero if the argument
-     * is zero, 1.0f if the argument is greater than zero, -1.0f if the
-     * argument is less than zero.
-     *
-     * <p>Special Cases:
-     * <ul>
-     * <li> If the argument is NaN, then the result is NaN.
-     * <li> If the argument is positive zero or negative zero, then the
-     *      result is the same as the argument.
-     * </ul>
-     *
-     * @param f the floating-point value whose signum is to be returned
-     * @return the signum function of the argument
-     * @author Joseph D. Darcy
-     * @since 1.5
-     */
-    public static float signum(float f) {
-	return sun.misc.FpUtils.signum(f);
-    }
-
-    /**
-     * Returns the hyperbolic sine of a <code>double</code> value.
-     * The hyperbolic sine of <i>x</i> is defined to be
-     * (<i>e<sup>x</sup>&nbsp;-&nbsp;e<sup>-x</sup></i>)/2
-     * where <i>e</i> is {@linkplain Math#E Euler''s number}.
-     *
-     * <p>Special cases:
-     * <ul>
-     *
-     * <li>If the argument is NaN, then the result is NaN.
-     *
-     * <li>If the argument is infinite, then the result is an infinity
-     * with the same sign as the argument.
-     *
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.
-     *
-     * </ul>
-     *
-     * <p>The computed result must be within 2.5 ulps of the exact result.
-     *
-     * @param   x The number whose hyperbolic sine is to be returned.
-     * @return  The hyperbolic sine of <code>x</code>.
-     * @since 1.5
-     */
-    public static double sinh(double x) {
-	return StrictMath.sinh(x);
-    }
-
-    /**
-     * Returns the hyperbolic cosine of a <code>double</code> value.
-     * The hyperbolic cosine of <i>x</i> is defined to be
-     * (<i>e<sup>x</sup>&nbsp;+&nbsp;e<sup>-x</sup></i>)/2
-     * where <i>e</i> is {@linkplain Math#E Euler''s number}.
-     *
-     * <p>Special cases:
-     * <ul>
-     *
-     * <li>If the argument is NaN, then the result is NaN.
-     *
-     * <li>If the argument is infinite, then the result is positive
-     * infinity.
-     *
-     * <li>If the argument is zero, then the result is <code>1.0</code>.
-     *
-     * </ul>
-     *
-     * <p>The computed result must be within 2.5 ulps of the exact result.
-     *
-     * @param   x The number whose hyperbolic cosine is to be returned.
-     * @return  The hyperbolic cosine of <code>x</code>.
-     * @since 1.5
-     */
-    public static double cosh(double x) {
-	return StrictMath.cosh(x);
-    }
-
-    /**
-     * Returns the hyperbolic tangent of a <code>double</code> value.
-     * The hyperbolic tangent of <i>x</i> is defined to be
-     * (<i>e<sup>x</sup>&nbsp;-&nbsp;e<sup>-x</sup></i>)/(<i>e<sup>x</sup>&nbsp;+&nbsp;e<sup>-x</sup></i>),
-     * in other words, {@linkplain Math#sinh
-     * sinh(<i>x</i>)}/{@linkplain Math#cosh cosh(<i>x</i>)}.  Note
-     * that the absolute value of the exact tanh is always less than
-     * 1.
-     *
-     * <p>Special cases:
-     * <ul>
-     *
-     * <li>If the argument is NaN, then the result is NaN.
-     *
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.
-     *
-     * <li>If the argument is positive infinity, then the result is
-     * <code>+1.0</code>.
-     *
-     * <li>If the argument is negative infinity, then the result is
-     * <code>-1.0</code>.
-     *  
-     * </ul>
-     *
-     * <p>The computed result must be within 2.5 ulps of the exact result.
-     * The result of <code>tanh</code> for any finite input must have
-     * an absolute value less than or equal to 1.  Note that once the
-     * exact result of tanh is within 1/2 of an ulp of the limit value
-     * of &plusmn;1, correctly signed &plusmn;<code>1.0</code> should
-     * be returned.
-     *
-     * @param   x The number whose hyperbolic tangent is to be returned.
-     * @return  The hyperbolic tangent of <code>x</code>.
-     * @since 1.5
-     */
-    public static double tanh(double x) {
-	return StrictMath.tanh(x);
-    }
-
-    /**
-     * Returns sqrt(<i>x</i><sup>2</sup>&nbsp;+<i>y</i><sup>2</sup>)
-     * without intermediate overflow or underflow.
-     *
-     * <p>Special cases:
-     * <ul>
-     *
-     * <li> If either argument is infinite, then the result
-     * is positive infinity.
-     *
-     * <li> If either argument is NaN and neither argument is infinite,
-     * then the result is NaN.
-     *
-     * </ul>
-     *
-     * <p>The computed result must be within 1 ulp of the exact
-     * result.  If one parameter is held constant, the results must be
-     * semi-monotonic in the other parameter.
-     *
-     * @param x a value
-     * @param y a value
-     * @return sqrt(<i>x</i><sup>2</sup>&nbsp;+<i>y</i><sup>2</sup>)
-     * without intermediate overflow or underflow
-     * @since 1.5
-     */
-    public static double hypot(double x, double y) {
-	return StrictMath.hypot(x, y);
-    }
-
-    /**
-     * Returns <i>e</i><sup>x</sup>&nbsp;-1.  Note that for values of
-     * <i>x</i> near 0, the exact sum of
-     * <code>expm1(x)</code>&nbsp;+&nbsp;1 is much closer to the true
-     * result of <i>e</i><sup>x</sup> than <code>exp(x)</code>.
-     *
-     * <p>Special cases:
-     * <ul>
-     * <li>If the argument is NaN, the result is NaN.
-     *
-     * <li>If the argument is positive infinity, then the result is
-     * positive infinity.
-     *
-     * <li>If the argument is negative infinity, then the result is
-     * -1.0.
-     *
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.
-     *
-     * </ul>
-     *
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.  The result of
-     * <code>expm1</code> for any finite input must be greater than or
-     * equal to <code>-1.0</code>.  Note that once the exact result of
-     * <i>e</i><sup><code>x</code></sup>&nbsp;-&nbsp;1 is within 1/2
-     * ulp of the limit value -1, <code>-1.0</code> should be
-     * returned.
-     *
-     * @param   x   the exponent to raise <i>e</i> to in the computation of
-     *              <i>e</i><sup><code>x</code></sup>&nbsp;-1.
-     * @return  the value <i>e</i><sup><code>x</code></sup>&nbsp;-&nbsp;1.
-     */
-    public static double expm1(double x) {
-	return StrictMath.expm1(x);
-    }
-
-    /**
-     * Returns the natural logarithm of the sum of the argument and 1.
-     * Note that for small values <code>x</code>, the result of
-     * <code>log1p(x)</code> is much closer to the true result of ln(1
-     * + <code>x</code>) than the floating-point evaluation of
-     * <code>log(1.0+x)</code>.
-     *
-     * <p>Special cases:
-     *
-     * <ul>
-     *
-     * <li>If the argument is NaN or less than -1, then the result is
-     * NaN.
-     *
-     * <li>If the argument is positive infinity, then the result is
-     * positive infinity.
-     *
-     * <li>If the argument is negative one, then the result is
-     * negative infinity.
-     *
-     * <li>If the argument is zero, then the result is a zero with the
-     * same sign as the argument.
-     *
-     * </ul>
-     *
-     * <p>The computed result must be within 1 ulp of the exact result.
-     * Results must be semi-monotonic.
-     *
-     * @param   x   a value
-     * @return the value ln(<code>x</code>&nbsp;+&nbsp;1), the natural
-     * log of <code>x</code>&nbsp;+&nbsp;1
-     */
-    public static double log1p(double x) {
-	return StrictMath.log1p(x);
-    }
-}
-'
+	^ (FileStream fileNamed: '../java-src/java/lang/Math.java') contents
 !
 
 javaSourcesBig
-	^ self workingJavaInDirectory: '../java-src/java/util'
+	^ self javaInDirectory: '../java-src/java/util'.
+	"^ self workingJavaInDirectory: '../java-src/java/util'"
 !
 
 petitParserPackage
@@ -5175,11 +3956,23 @@
 '
 !
 
+smalltalkInDirectory: directory
+	| files |
+	files := self readDirectory: directory.
+	files := self files: files withExtension: 'st'.
+	
+	^ files collect: [ :f | (FileStream fileNamed: f) contents ]
+!
+
 smalltalkObjectMethods
 	^ Object allMethods collect: [ :m | m sourceCode ].
 !
 
 smalltalkSourcesBig
+	^ self smalltalkInDirectory: '../smalltalk-src/'
+!
+
+smalltalkSourcesBig_old
 	^ ((Smalltalk allClasses copyFrom: 1 to: 30) collect: [ :c |
 			c allMethods collect: [ :m | m sourceCode ]
 	  ]) gather: [:each | each ].
--- a/compiler/benchmarks/abbrev.stc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/benchmarks/abbrev.stc	Mon Nov 24 00:09:23 2014 +0000
@@ -1,6 +1,6 @@
 # automagically generated by the project definition
 # 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' 0
-PPCBenchmarkResources PPCBenchmarkResources stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks' 0
+PPCBenchmark PPCBenchmark stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Core' 0
+PPCBenchmarkResources PPCBenchmarkResources stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Core' 0
 stx_goodies_petitparser_compiler_benchmarks stx_goodies_petitparser_compiler_benchmarks stx:goodies/petitparser/compiler/benchmarks '* Projects & Packages *' 3
--- a/compiler/benchmarks/benchmarks.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/benchmarks/benchmarks.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.5.0\0"
-      VALUE "ProductDate", "Wed, 19 Nov 2014 10:47:33 GMT\0"
+      VALUE "ProductDate", "Mon, 24 Nov 2014 00:09:16 GMT\0"
     END
 
   END
--- a/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Mon Nov 24 00:09:23 2014 +0000
@@ -8,6 +8,32 @@
 !
 
 
+!stx_goodies_petitparser_compiler_benchmarks class methodsFor:'accessing - monticello'!
+
+monticelloLastMergedVersionInfo
+    "The last merged version is: "
+
+    ^ '
+    Name: PetitCompiler-Benchmarks-JanKurs.2
+    Author: JanKurs
+    Time: 17-11-2014, 05:51:07.887 PM
+    UUID: d5e3a980-7871-487a-a232-e3ca93fc2483            
+    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>"
+!
+
+monticelloName
+    "Return name of the package for Monticello. This is used when package is exported"
+
+    ^ 'PetitCompiler-Benchmarks'
+
+    "Created: / 03-10-2014 / 01:47:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 24-11-2014 / 00:08:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !stx_goodies_petitparser_compiler_benchmarks class methodsFor:'description'!
 
 excludedFromPreRequisites
--- a/compiler/compiler.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/compiler.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.5.0\0"
-      VALUE "ProductDate", "Wed, 19 Nov 2014 10:47:27 GMT\0"
+      VALUE "ProductDate", "Fri, 21 Nov 2014 15:17:53 GMT\0"
     END
 
   END
--- a/compiler/extensions.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/extensions.st	Mon Nov 24 00:09:23 2014 +0000
@@ -19,6 +19,7 @@
 		name: self name;
 		block: block;
 		child: parser;
+		properties: properties;
 		yourself
 ! !
 
@@ -468,7 +469,7 @@
 	| ws |
 	ws := #space asParser star.
 	^ ((ws, (PPTokenParser on: self), ws) ==> #second)
-		name: 'trimmingToken';
+		propertyAt: #trimmingToken put: true;
 		yourself
 ! !
 
@@ -570,6 +571,7 @@
 	^ PPCSequenceNode new
 		children: parsers;
 		name: self name;
+		properties: properties;
 		yourself
 ! !
 
@@ -688,6 +690,14 @@
 
 !PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
 
+= anotherParser
+	anotherParser == self ifTrue: [ ^ true ].
+	anotherParser class = self class ifFalse: [ ^ false ].
+ ^ anotherParser name = self name
+! !
+
+!PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
+
 acceptsEpsilon
 	^ true
 ! !
--- a/compiler/libInit.cc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/libInit.cc	Mon Nov 24 00:09:23 2014 +0000
@@ -50,9 +50,6 @@
 _PPCNilNode_Init(pass,__pRT__,snd);
 _PPCPluggableNode_Init(pass,__pRT__,snd);
 _PPCProfilingContext_Init(pass,__pRT__,snd);
-_PPCStarAnyNode_Init(pass,__pRT__,snd);
-_PPCStarCharSetPredicateNode_Init(pass,__pRT__,snd);
-_PPCStarMessagePredicateNode_Init(pass,__pRT__,snd);
 _PPCUnknownNode_Init(pass,__pRT__,snd);
 _PPCAbstractActionNode_Init(pass,__pRT__,snd);
 _PPCAndNode_Init(pass,__pRT__,snd);
@@ -62,9 +59,7 @@
 _PPCForwardNode_Init(pass,__pRT__,snd);
 _PPCInlineAnyNode_Init(pass,__pRT__,snd);
 _PPCInlineCharacterNode_Init(pass,__pRT__,snd);
-_PPCInlineLiteralNode_Init(pass,__pRT__,snd);
 _PPCInlineNilNode_Init(pass,__pRT__,snd);
-_PPCInlineNotLiteralNode_Init(pass,__pRT__,snd);
 _PPCInlinePluggableNode_Init(pass,__pRT__,snd);
 _PPCLiteralNode_Init(pass,__pRT__,snd);
 _PPCMessagePredicateNode_Init(pass,__pRT__,snd);
@@ -76,19 +71,29 @@
 _PPCOptionalNode_Init(pass,__pRT__,snd);
 _PPCPlusNode_Init(pass,__pRT__,snd);
 _PPCPredicateNode_Init(pass,__pRT__,snd);
+_PPCSentinelNode_Init(pass,__pRT__,snd);
 _PPCSequenceNode_Init(pass,__pRT__,snd);
 _PPCStarNode_Init(pass,__pRT__,snd);
 _PPCTokenNode_Init(pass,__pRT__,snd);
-_PPCTokenStarMessagePredicateNode_Init(pass,__pRT__,snd);
 _PPCTrimNode_Init(pass,__pRT__,snd);
 _PPCTrimmingTokenNode_Init(pass,__pRT__,snd);
 _PPCActionNode_Init(pass,__pRT__,snd);
 _PPCInlineCharSetPredicateNode_Init(pass,__pRT__,snd);
+_PPCInlineLiteralNode_Init(pass,__pRT__,snd);
 _PPCInlineMessagePredicateNode_Init(pass,__pRT__,snd);
 _PPCInlineNotCharSetPredicateNode_Init(pass,__pRT__,snd);
+_PPCInlineNotLiteralNode_Init(pass,__pRT__,snd);
 _PPCInlineNotMessagePredicateNode_Init(pass,__pRT__,snd);
+_PPCStarAnyNode_Init(pass,__pRT__,snd);
+_PPCStarCharSetPredicateNode_Init(pass,__pRT__,snd);
+_PPCStarMessagePredicateNode_Init(pass,__pRT__,snd);
 _PPCSymbolActionNode_Init(pass,__pRT__,snd);
 _PPCTokenSequenceNode_Init(pass,__pRT__,snd);
+_PPCTokenActionNode_Init(pass,__pRT__,snd);
+_PPCTokenStarMessagePredicateNode_Init(pass,__pRT__,snd);
+_PPCInlineTokenStarMessagePredicateNode_Init(pass,__pRT__,snd);
+_PPCTokenStarSeparatorNode_Init(pass,__pRT__,snd);
+_PPCInlineTokenStarSeparatorNode_Init(pass,__pRT__,snd);
 
 _stx_137goodies_137petitparser_137compiler_extensions_Init(pass,__pRT__,snd);
 __END_PACKAGE__();
--- a/compiler/stx_goodies_petitparser_compiler.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/stx_goodies_petitparser_compiler.st	Mon Nov 24 00:09:23 2014 +0000
@@ -20,16 +20,16 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitCompiler-JanKurs.57
+    Name: PetitCompiler-JanKurs.71
     Author: JanKurs
-    Time: 05-11-2014, 05:10:47 AM
-    UUID: 4c625efe-77fd-465d-bd63-72ead0b5d3ba        
+    Time: 18-11-2014, 09:48:35.425 AM
+    UUID: 06352c33-3c76-4382-8536-0cc48e225117                   
     Repository: http://smalltalkhub.com/mc/JanKurs/PetitParser/main
 
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 05-11-2014 / 22:58:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 12:40:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
@@ -122,9 +122,6 @@
         PPCNilNode
         PPCPluggableNode
         PPCProfilingContext
-        PPCStarAnyNode
-        PPCStarCharSetPredicateNode
-        PPCStarMessagePredicateNode
         PPCUnknownNode
         PPCAbstractActionNode
         PPCAndNode
@@ -134,9 +131,7 @@
         PPCForwardNode
         PPCInlineAnyNode
         PPCInlineCharacterNode
-        PPCInlineLiteralNode
         PPCInlineNilNode
-        PPCInlineNotLiteralNode
         PPCInlinePluggableNode
         PPCLiteralNode
         PPCMessagePredicateNode
@@ -148,19 +143,29 @@
         PPCOptionalNode
         PPCPlusNode
         PPCPredicateNode
+        PPCSentinelNode
         PPCSequenceNode
         PPCStarNode
         PPCTokenNode
-        PPCTokenStarMessagePredicateNode
         PPCTrimNode
         PPCTrimmingTokenNode
         PPCActionNode
         PPCInlineCharSetPredicateNode
+        PPCInlineLiteralNode
         PPCInlineMessagePredicateNode
         PPCInlineNotCharSetPredicateNode
+        PPCInlineNotLiteralNode
         PPCInlineNotMessagePredicateNode
+        PPCStarAnyNode
+        PPCStarCharSetPredicateNode
+        PPCStarMessagePredicateNode
         PPCSymbolActionNode
         PPCTokenSequenceNode
+        PPCTokenActionNode
+        PPCTokenStarMessagePredicateNode
+        PPCInlineTokenStarMessagePredicateNode
+        PPCTokenStarSeparatorNode
+        PPCInlineTokenStarSeparatorNode
     )
 !
 
@@ -287,6 +292,7 @@
         PPPredicateObjectParser firstCharSetCached
         PPSmalltalkWhitespaceParser firstCharSet
         UndefinedObject isSeparator
+        PPSmalltalkWhitespaceParser #'='
     )
 ! !
 
--- a/compiler/tests/Make.proto	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/Make.proto	Mon Nov 24 00:09:23 2014 +0000
@@ -133,6 +133,7 @@
 $(OUTDIR)PPCContextTest.$(O) PPCContextTest.$(H): PPCContextTest.st $(INCLUDE_TOP)/stx/goodies/petitparser/tests/PPContextTest.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCGuardTest.$(O) PPCGuardTest.$(H): PPCGuardTest.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMockCompiler.$(O) PPCMockCompiler.$(H): PPCMockCompiler.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PPCNodeFirstFollowNextTests.$(O) PPCNodeFirstFollowNextTests.$(H): PPCNodeFirstFollowNextTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCNodeTest.$(O) PPCNodeTest.$(H): PPCNodeTest.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCOptimizingTest.$(O) PPCOptimizingTest.$(H): PPCOptimizingTest.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(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)
--- a/compiler/tests/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -56,6 +56,7 @@
 	PPCContextTest \
 	PPCGuardTest \
 	PPCMockCompiler \
+	PPCNodeFirstFollowNextTests \
 	PPCNodeTest \
 	PPCOptimizingTest \
 	PPCompiledSmalltalkGrammarResource \
@@ -70,6 +71,7 @@
     $(OUTDIR_SLASH)PPCContextTest.$(O) \
     $(OUTDIR_SLASH)PPCGuardTest.$(O) \
     $(OUTDIR_SLASH)PPCMockCompiler.$(O) \
+    $(OUTDIR_SLASH)PPCNodeFirstFollowNextTests.$(O) \
     $(OUTDIR_SLASH)PPCNodeTest.$(O) \
     $(OUTDIR_SLASH)PPCOptimizingTest.$(O) \
     $(OUTDIR_SLASH)PPCompiledSmalltalkGrammarResource.$(O) \
--- a/compiler/tests/PPCCompilerTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/PPCCompilerTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -14,19 +14,6 @@
 	^ context := PPCProfilingContext new
 ! !
 
-!PPCCompilerTest methodsFor:'running'!
-
-tearDown
-    | parserClass |
-
-    parserClass := (Smalltalk at: #PPGeneratedParser).
-    parserClass notNil ifTrue:[ 
-        parserClass removeFromSystem
-    ].
-
-    "Created: / 30-10-2014 / 22:56:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
 !PPCCompilerTest methodsFor:'test support'!
 
 assert: p parse: whatever
@@ -65,6 +52,15 @@
 
 parse: whatever
 	^ result := super parse: whatever.
+!
+
+tearDown
+	| parserClass |
+
+	parserClass := (Smalltalk at: #PPGeneratedParser ifAbsent: [nil]).
+	parserClass notNil ifTrue:[ 
+		parserClass removeFromSystem
+	].
 ! !
 
 !PPCCompilerTest methodsFor:'tests - compiling'!
@@ -195,30 +191,28 @@
 !
 
 testCompileNotLiteral
-        parser := 'foo' asParser not compile.
-        self assert: parser class methodDictionary size = 2.
+	parser := 'foo' asParser not compile.
+	self assert: parser class methodDictionary size = 2.
 
-        self assert: parser parse: 'bar' to: nil end: 0.
-                
-        self assert: parser fail: 'foo'.
-        self assert: parser parse: '' to: nil end: 0.
+	self assert: parser parse: 'bar' to: nil end: 0.
+		
+	self assert: parser fail: 'foo'.
+	self assert: parser parse: '' to: nil end: 0.
 
-        parser := '''' asParser not compile.
-        self assert: parser class methodDictionary size = 2.
+	parser := '''' asParser not compile.
+	self assert: parser class methodDictionary size = 2.
 
-        self assert: parser parse: 'a' to: nil end: 0.
-        self assert: parser fail: ''''.
-        self assert: parser parse: '' to: nil end: 0.
+	self assert: parser parse: 'a' to: nil end: 0.
+	self assert: parser fail: ''''.
+	self assert: parser parse: '' to: nil end: 0.
 
 
-        parser := ('foo' asParser, 'bar' asParser not) compile.
-        self assert: parser parse: 'foofoo' to: { 'foo'. nil } end: 3.
-        
-        parser := ('foo' asParser, 'foo' asParser not, #any asParser star) compile.
-        self assert: parser parse: 'foobar' to: { 'foo'. nil . #($b $a $r) } end: 6.
-        self assert: parser fail: 'foofoo'.
-
-    "Modified: / 05-11-2014 / 23:18:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	parser := ('foo' asParser, 'bar' asParser not) compile.
+	self assert: parser parse: 'foofoo' to: { 'foo'. nil } end: 3.
+	
+	parser := ('foo' asParser, 'foo' asParser not, #any asParser star) compile.
+	self assert: parser parse: 'foobar' to: { 'foo'. nil . #($b $a $r) } end: 6.
+	self assert: parser fail: 'foofoo'.
 !
 
 testCompileOptional
@@ -313,7 +307,7 @@
 
 testCompileSymbolBlock
 	parser := (#letter asParser) plus ==> #second.
-	parser := parser compile: #PPCompilerTest.
+	parser := parser compile.
 	
 	self assert: parser parse: 'foo' to: $o.
 	self assert: parser parse: 'bar' to: $a.
@@ -321,6 +315,28 @@
 	self should: [ parser parse: 'f' ] raise: Error.
 !
 
+testCompileTrimmingToken
+	| token1 token2 |
+	token1 := (#letter asParser) plus trimmingToken.
+	token2 := (#letter asParser) plus trimmingToken.
+	
+	parser := (token1, token2) compile.
+	
+	self assert: parser parse: 'foo bar'.
+	self assert: parser parse: ' foo bar '.
+!
+
+testCompileTrimmingToken2
+	| token1 token2 |
+	token1 := (#letter asParser) plus trimmingToken.
+	token2 := (#letter asParser) plus trimmingToken / 'foo' asParser trimmingToken.
+	
+	parser := (token1, token2) compile.
+	
+	self assert: parser parse: 'foo bar'.
+	self assert: parser parse: ' foo bar '.
+!
+
 testTrim
 	parser := self compile: $a asParser trim.
 	
@@ -369,37 +385,22 @@
 	block := ${ asParser, p1, $} asParser / nil asParser.
 	p1 setParser: block.
 	
-	parser := block compile: #PPCompilerTest.
+	parser := block compile.
 	self assert: parser parse: '{}' to: { ${. nil . $} }.
 	self assert: parser parse: '{{}}' to: { ${. { ${ . nil . $} } . $} }.
 	
 !
 
-testGuardSmalltlakToken
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: 'foo' asParser smalltalkToken.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char = $f ])).
-	
-	parser := (#letter asParser, #word asParser star) smalltalkToken compileWithParameters: { #profile -> true }.
-	self assert: parser parse: 'bar'.
-	self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'seq' ]).
+testSmalltalkToken
+	parser := (#letter asParser, (#digit asParser / #letter asParser) star) smalltalkToken compileWithParameters: {#profile -> true}.
 	
-	self assert: parser fail: '123'.
-	self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'seq' ]).
-!
-
-testSmalltalkToken
-        parser := (#letter asParser, (#digit asParser / #letter asParser) star) smalltalkToken compileWithParameters: {#profile -> true}.
-        
-        self assert: parser class methodDictionary size = 6.
-        self assert: parser parse: 'foo'.
-        self assert: result inputValue = 'foo'.
-        self assert: context invocationCount = 9.
-        self assert: context rememberCount = 0.
-        self assert: context lwRememberCount = 1.
-        self assert: context lwRestoreCount = 0.
-
-    "Modified: / 05-11-2014 / 23:17:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	self assert: parser class methodDictionary size = 6.
+	self assert: parser parse: 'foo'.
+	self assert: result inputValue = 'foo'.
+	self assert: context invocationCount = 9.
+	self assert: context rememberCount = 0.
+	self assert: context lwRememberCount = 1.
+	self assert: context lwRestoreCount = 0.	
 !
 
 testSmalltalkToken2
@@ -408,7 +409,7 @@
 		name: 'identifier';
 		yourself.
 		
-	parser := (id, $: asParser) smalltalkToken 
+	parser := (id wrapped, $: asParser) smalltalkToken 
 		name: 'kw';
 		yourself.
 	
@@ -428,48 +429,94 @@
 !
 
 testToken2
-        parser := (#letter asParser, (#digit asParser / #letter asParser) star) token compileWithParameters: {#profile -> true}.
-        
-        self assert: parser class methodDictionary size = 5.
-        self assert: parser parse: 'foo'.
-        self assert: result inputValue = 'foo'.
-        self assert: context invocationCount = 7.
-        self assert: context rememberCount = 0.
-        self assert: context lwRememberCount = 1.
-        self assert: context lwRestoreCount = 0.
-
-    "Modified: / 05-11-2014 / 23:17:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	parser := (#letter asParser, (#digit asParser / #letter asParser) star) token compileWithParameters: {#profile -> true}.
+	
+	self assert: parser class methodDictionary size = 5.
+	self assert: parser parse: 'foo'.
+	self assert: result inputValue = 'foo'.
+	self assert: context invocationCount = 7.
+	self assert: context rememberCount = 0.
+	self assert: context lwRememberCount = 1.
+	self assert: context lwRestoreCount = 0.	
 !
 
 testTrimmingToken
-        parser := (#letter asParser, (#digit asParser / #letter asParser) star) trimmingToken compileWithParameters: { #profile -> true }.
+	parser := (#letter asParser, (#digit asParser / #letter asParser) star) trimmingToken compileWithParameters: { #profile -> true }.
 
-        self assert: parser class methodDictionary size = 6.
+	self assert: parser class methodDictionary size = 5.
 
-        self assert: parser parse: 'foo'.
-        self assert: result inputValue = 'foo'.
+	self assert: parser parse: 'foo'.
+	self assert: result inputValue = 'foo'.
 
-        self assert: context invocationCount = 9.
-        self assert: context rememberCount = 0.
-        self assert: context lwRememberCount = 1.
-        self assert: context lwRestoreCount = 0.        
+	self assert: context invocationCount = 7.
+	self assert: context rememberCount = 0.
+	self assert: context lwRememberCount = 1.
+	self assert: context lwRestoreCount = 0.	
 
-        self assert: parser parse: ' foo '.
-        self assert: result inputValue = 'foo'.
+	self assert: parser parse: ' foo '.
+	self assert: result inputValue = 'foo'.
 
 
 
-        self assert: parser fail: '123'.
+	self assert: parser fail: '123'.
 
-        self assert: context invocationCount = 3.
-        self assert: context rememberCount = 0.
-        self assert: context lwRememberCount = 0.
-        self assert: context lwRestoreCount = 0.        
+	self assert: context invocationCount = 2.
+	self assert: context rememberCount = 0.
+	self assert: context lwRememberCount = 0.
+	self assert: context lwRestoreCount = 0.	
 
 
-        self assert: parser fail: ''.
+	self assert: parser fail: ''.
+!
+
+testTrimmingTokenNested
+	| identifier kw |
+	kw := 'false' asParser trimmingToken name: #kw.
+	identifier := (kw not, (#letter asParser, #word asParser star)) trimmingToken name: #identifier.
+	
+	parser := identifier / kw.
+	parser := parser compileWithParameters: { #profile -> true }.
+	self assert: parser class methodDictionary size = 6.
+
+	self assert: parser parse: 'foo'.
+	self assert: result inputValue = 'foo'.
+
+	self assert: parser parse: 'false'.
+	self assert: result inputValue = 'false'.
+!
 
-    "Modified: / 06-11-2014 / 00:46:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+testTrimmingTokenNested2
+	| identifier kw |
+	kw := 'false' asParser trimmingToken name: #kw.
+	identifier := (kw not, (#letter asParser, #word asParser star)) trimmingToken name: #identifier.
+	
+	parser := identifier / kw.
+	parser := parser compileWithParameters: { #profile -> true }.
+	self assert: parser class methodDictionary size = 6.
+
+	self assert: parser parse: 'foo'.
+	self assert: result inputValue = 'foo'.
+
+	self assert: parser parse: 'false'.
+	self assert: result inputValue = 'false'.
+!
+
+testTrimmingTokenNested3
+	| identifier kw |
+	kw := ('false' asParser, #word asParser not) trimmingToken name: #kw.
+	identifier := (kw not, (#letter asParser, #word asParser star)) trimmingToken name: #identifier.
+	
+	parser := identifier / kw.
+	parser := parser compileWithParameters: { #profile -> true }.
+	self assert: parser class methodDictionary size = 9.
+	self assert: (parser class methods anySatisfy: [ :m | m selector = #kw ]).
+	self assert: (parser class methods anySatisfy: [ :m | m selector = #kw_fast ]).
+
+	self assert: parser parse: 'foo'.
+	self assert: result inputValue = 'foo'.
+
+	self assert: parser parse: 'false'.
+	self assert: result inputValue = 'false'.
 ! !
 
 !PPCCompilerTest methodsFor:'tests - first set'!
@@ -606,6 +653,15 @@
 	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | (char = $f) or: [ char = $b ]] )).
 !
 
+testGuardSmalltlakToken
+	parser := (#letter asParser, #word asParser star) smalltalkToken compileWithParameters: { #profile -> true }.
+	self assert: parser parse: 'bar'.
+	self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'seq' ]).
+	
+	self assert: parser fail: '123'.
+	self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'seq' ]).
+!
+
 testSequenceGuard
 	parser := ((#any asParser, #any asParser) wrapped, (#any asParser, #any asParser)) compile.
 	
--- a/compiler/tests/PPCGuardTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/PPCGuardTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -34,25 +34,35 @@
 !
 
 testCompiling3
-        guard := PPCGuard new initializeFor: ($a asParser, (#letter asParser / #digit asParser)) asCompilerTree.
-        guard id: #foo.
-        guard compileGuard: compiler.
-        
-        self assert: compiler lines size = 1.
-        self assert: compiler lines first = ('(context peek = ', $a storeString ,')').
-
-    "Modified: / 06-11-2014 / 00:47:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	guard := PPCGuard new initializeFor: ($a asParser, (#letter asParser / #digit asParser)) asCompilerTree.
+	guard id: #foo.
+	guard compileGuard: compiler.
+	
+	self assert: compiler lines size = 1.
+	self assert: compiler lines first = ('(context peek = ', $a storeString ,')').
 !
 
 testCompiling4
-        guard := PPCGuard new initializeFor: ('foo' asParser / 'foobar' asParser) asCompilerTree.
-        guard id: #foo.
-        guard compileGuard: compiler.
-        
-        self assert: compiler lines size = 1.
-        self assert: compiler lines first = ('(context peek = ', $f storeString ,')').
+	guard := PPCGuard new initializeFor: ('foo' asParser / 'foobar' asParser) asCompilerTree.
+	guard id: #foo.
+	guard compileGuard: compiler.
+	
+	self assert: compiler lines size = 1.
+	self assert: compiler lines first = ('(context peek = ', $f storeString ,')').
+!
 
-    "Modified: / 06-11-2014 / 00:47:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+testIdentifierToken
+	| id parser |
+	id := (#letter asParser plus)
+		name: 'identifier';
+		yourself.
+		
+	parser := id smalltalkToken.
+	parser name: 'kw'.
+
+	guard := PPCGuard new initializeFor: parser asCompilerTree optimizeTree.
+	self assert: (guard classification at: $a asInteger).
+	self assert: (guard classification at: $z asInteger).
 !
 
 testMakesSense
@@ -106,6 +116,11 @@
 	self assert: (guard classification at: $f asInteger).
 !
 
+testNot3
+	guard := PPCGuard new initializeFor: (#letter asParser negate star, #letter asParser) asCompilerTree optimizeTree.
+	self assert: (guard classification allSatisfy: [ :e | e]).
+!
+
 testTestMessage
 	guard := PPCGuard new initializeFor: #letter asParser asCompilerTree.
 	self assert: (guard testMessage: #isLetter).
--- a/compiler/tests/PPCNodeCompilingTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/PPCNodeCompilingTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -92,33 +92,29 @@
 !
 
 testCompileChoice
-        tree := PPCChoiceNode new
-                children: { #digit asParser asCompilerNode. #letter asParser asCompilerNode };
-                yourself.
-                
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 4.
-        
-        self assert: parser parse: '1' to: $1.
-        self assert: parser parse: 'a' to: $a.
-        self assert: parser fail: '_'.
-
-    "Modified: / 06-11-2014 / 00:48:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCChoiceNode new
+		children: { #digit asParser asCompilerNode. #letter asParser asCompilerNode };
+		yourself.
+		
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 4.
+	
+	self assert: parser parse: '1' to: $1.
+	self assert: parser parse: 'a' to: $a.
+	self assert: parser fail: '_'.
 !
 
 testCompileLiteral
-        tree := PPCLiteralNode new
-                literal: 'foo';
-                yourself.
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'foo'  to: 'foo'.
-        self assert: parser parse: 'foobar'  to: 'foo' end: 3.
-        self assert: parser fail: 'boo'.
-
-    "Modified: / 06-11-2014 / 00:48:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCLiteralNode new
+		literal: 'foo';
+		yourself.
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'foo'  to: 'foo'.
+	self assert: parser parse: 'foobar'  to: 'foo' end: 3.
+	self assert: parser fail: 'boo'.
 !
 
 testCompileLiteral2
@@ -153,51 +149,45 @@
 !
 
 testCompileNotCharSetPredicate
-        tree := PPCNotCharSetPredicateNode new
-                predicate: (PPCharSetPredicate on: [ :e | e = $a ]);
-                yourself.
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'b' to: nil end: 0.
-        self assert: context invocationCount = 2.
-                
-        self assert: parser fail: 'a'.
-        self assert: parser parse: '' to: nil end: 0.
-
-    "Modified: / 06-11-2014 / 00:48:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCNotCharSetPredicateNode new
+		predicate: (PPCharSetPredicate on: [ :e | e = $a ]);
+		yourself.
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'b' to: nil end: 0.
+	self assert: context invocationCount = 2.
+		
+	self assert: parser fail: 'a'.
+	self assert: parser parse: '' to: nil end: 0.
 !
 
 testCompileNotLiteral
-        tree := PPCNotLiteralNode new
-                literal: 'foo';
-                yourself.
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'bar' to: nil end: 0.
-        self assert: context invocationCount = 2.
-                
-        self assert: parser fail: 'foo'.
-        self assert: parser parse: '' to: nil end: 0.
-
-    "Modified: / 06-11-2014 / 00:48:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCNotLiteralNode new
+		literal: 'foo';
+		yourself.
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'bar' to: nil end: 0.
+	self assert: context invocationCount = 2.
+		
+	self assert: parser fail: 'foo'.
+	self assert: parser parse: '' to: nil end: 0.
 !
 
 testCompileNotMessagePredicate
-        tree := PPCNotMessagePredicateNode new
-                message: #isDigit;
-                yourself.
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'a' to: nil end: 0.
-        self assert: context invocationCount = 2.
-                
-        self assert: parser fail: '1'.
-        self assert: parser parse: '' to: nil end: 0.
-
-    "Modified: / 06-11-2014 / 00:48:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCNotMessagePredicateNode new
+		message: #isDigit;
+		yourself.
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'a' to: nil end: 0.
+	self assert: context invocationCount = 2.
+		
+	self assert: parser fail: '1'.
+	self assert: parser parse: '' to: nil end: 0.
 !
 
 testCompileOptional
@@ -256,7 +246,7 @@
 !
 
 testCompileStarAny
-	tree := PPCStarAnyNode new.
+	tree := PPCStarAnyNode new child: PPCNilNode new; yourself.
 	parser := self compileTree: tree.
 	
 	self assert: parser parse: 'abc' to: #($a $b $c).
@@ -265,34 +255,36 @@
 !
 
 testCompileStarCharSetPredicate
-        tree := PPCStarCharSetPredicateNode new
-                predicate: (PPCharSetPredicate on: [:e | e = $a ]);
-                yourself.
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'aaa1' to: #( $a $a $a) end: 3.
-        self assert: context invocationCount = 2.
-        self assert: parser parse: 'bba' to: #() end: 0.
-        self assert: context invocationCount = 2.
-
-    "Modified: / 06-11-2014 / 00:48:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCStarCharSetPredicateNode new
+		predicate: (PPCharSetPredicate on: [:e | e = $a ]);
+		"I have to put something here"
+		child: PPCNilNode new;
+		yourself.
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'aaa1' to: #( $a $a $a) end: 3.
+	self assert: context invocationCount = 2.
+	self assert: parser parse: 'bba' to: #() end: 0.
+	self assert: context invocationCount = 2.
+	
 !
 
 testCompileStarMessagePredicate
-        tree := PPCStarMessagePredicateNode new
-                message: #isLetter;
-                yourself.
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'abc1' to: #( $a $b $c) end: 3.
-        self assert: context invocationCount = 2.
-        
-        self assert: parser parse: '123a' to: #() end: 0.
-        self assert: context invocationCount = 2.
-
-    "Modified: / 06-11-2014 / 00:48:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCStarMessagePredicateNode new
+		message: #isLetter;
+		"I have to add something here"
+		child: PPCNilNode new;
+		yourself.
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'abc1' to: #( $a $b $c) end: 3.
+	self assert: context invocationCount = 2.
+	
+	self assert: parser parse: '123a' to: #() end: 0.
+	self assert: context invocationCount = 2.
+	
 !
 
 testCompileSymbolAction
@@ -353,21 +345,19 @@
 !
 
 testCompileTokenStarMessagePredicate
-        
-        tree := PPCTokenStarMessagePredicateNode new message: #isLetter.
-        parser := self compileTree: tree params: {#guards -> false}.
-        
-        self assert: parser class methodDictionary size = 2.
-        
-        self assert: parser parse: 'foo' to: parser.
-        self assert: context invocationCount = 2.
-        self assert: context lwRememberCount  = 0.
-        self assert: context lwRestoreCount  = 0.
-        self assert: context rememberCount = 0.
-        
-        self assert: parser parse: 'foo123' to: parser end: 3.
-
-    "Modified: / 06-11-2014 / 00:49:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	
+	tree := PPCTokenStarMessagePredicateNode new message: #isLetter; child: PPCNilNode new; yourself.
+	parser := self compileTree: tree params: {#guards -> false}.
+	
+	self assert: parser class methodDictionary size = 2.
+	
+	self assert: parser parse: 'foo' to: parser.
+	self assert: context invocationCount = 2.
+	self assert: context lwRememberCount  = 0.
+	self assert: context lwRestoreCount  = 0.
+	self assert: context rememberCount = 0.
+	
+	self assert: parser parse: 'foo123' to: parser end: 3.
 ! !
 
 !PPCNodeCompilingTest methodsFor:'tests - guard'!
@@ -422,98 +412,84 @@
 !PPCNodeCompilingTest methodsFor:'tests - inlining'!
 
 testInlineAny
-        tree := PPCSequenceNode new
-                children: { PPCInlineAnyNode new. $a asParser asCompilerNode }.
-        
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 3.
-        self assert: parser parse: '.a' to: #($. $a).
-
-    "Modified: / 06-11-2014 / 01:12:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCSequenceNode new
+		children: { PPCInlineAnyNode new. $a asParser asCompilerNode }.
+	
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 3.
+	self assert: parser parse: '.a' to: #($. $a).
 !
 
 testInlineCharSetPredicate
-        tree := PPCPlusNode new
-                child: (PPCInlineCharSetPredicateNode new 
-                        predicate: (PPCharSetPredicate on: [ :e | e = $a ]);
-                        yourself);
-                yourself.
-        
-        parser := self compileTree: tree.
+	tree := PPCPlusNode new
+		child: (PPCInlineCharSetPredicateNode new 
+			predicate: (PPCharSetPredicate on: [ :e | e = $a ]);
+			yourself);
+		yourself.
+	
+	parser := self compileTree: tree.
 
-        self assert: parser class methodDictionary size = 2.
-        self assert: parser parse: 'a'  to: #($a).
-        self assert: parser fail: 'b'.
-
-    "Modified: / 06-11-2014 / 01:12:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	self assert: parser class methodDictionary size = 2.
+	self assert: parser parse: 'a'  to: #($a).
+	self assert: parser fail: 'b'.
 !
 
 testInlineCharacter
-        tree := PPCSequenceNode new
-                children: { PPCInlineCharacterNode new character: $b . $a asParser asCompilerNode }.
-        
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 3.
-        self assert: parser parse: 'ba' to: #($b $a).
-
-    "Modified: / 06-11-2014 / 01:12:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCSequenceNode new
+		children: { PPCInlineCharacterNode new character: $b . $a asParser asCompilerNode }.
+	
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 3.
+	self assert: parser parse: 'ba' to: #($b $a).
 !
 
 testInlineLiteral
-        tree := PPCSequenceNode new
-                children: { PPCInlineLiteralNode new literal: 'foo'. $a asParser asCompilerNode }.
-        
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 3.
-        self assert: parser parse: 'fooa' to: #('foo' $a).
-
-    "Modified: / 06-11-2014 / 01:12:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCSequenceNode new
+		children: { PPCInlineLiteralNode new literal: 'foo'. $a asParser asCompilerNode }.
+	
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 3.
+	self assert: parser parse: 'fooa' to: #('foo' $a).
 !
 
 testInlineNil
-        tree := PPCSequenceNode new
-                children: { PPCInlineNilNode new . $a asParser asCompilerNode }.
-        
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 3.
-        self assert: parser parse: 'a' to: #(nil $a).
-
-    "Modified: / 06-11-2014 / 01:12:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCSequenceNode new
+		children: { PPCInlineNilNode new . $a asParser asCompilerNode }.
+	
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 3.
+	self assert: parser parse: 'a' to: #(nil $a).
 !
 
 testInlineNotLiteral
-        tree := PPCSequenceNode new
-                children: { PPCInlineNotLiteralNode new literal: 'foo'. $a asParser asCompilerNode }.
-        
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 3.
-        self assert: parser parse: 'a' to: #(nil $a).
-
-    "Modified: / 06-11-2014 / 01:12:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCSequenceNode new
+		children: { PPCInlineNotLiteralNode new literal: 'foo'. $a asParser asCompilerNode }.
+	
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 3.
+	self assert: parser parse: 'a' to: #(nil $a).
 !
 
 testInlinePluggable
-       "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'.
-        ].
+   "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'.
+	].
 
-        tree := PPCSequenceNode new
-                children: { PPCInlinePluggableNode new block: [ :ctx | ctx next ]. $a asParser asCompilerNode }.
-        
-        parser := self compileTree: tree.
-        
-        self assert: parser class methodDictionary size = 3.
-        self assert: parser parse: 'ba' to: #($b $a).
-
-    "Modified: / 06-11-2014 / 01:48:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	tree := PPCSequenceNode new
+		children: { PPCInlinePluggableNode new block: [ :ctx | ctx next ]. $a asParser asCompilerNode }.
+	
+	parser := self compileTree: tree.
+	
+	self assert: parser class methodDictionary size = 3.
+	self assert: parser parse: 'ba' to: #($b $a).
 ! !
 
 !PPCNodeCompilingTest class methodsFor:'documentation'!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPCNodeFirstFollowNextTests.st	Mon Nov 24 00:09:23 2014 +0000
@@ -0,0 +1,559 @@
+"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
+
+TestCase subclass:#PPCNodeFirstFollowNextTests
+	instanceVariableNames:'tree first node followSet'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'PetitCompiler-Tests-Nodes'
+!
+
+!PPCNodeFirstFollowNextTests methodsFor:'as yet unclassified'!
+
+assert: set anyMatchesType: whatever
+	self assert: (set anySatisfy: [:e | e isKindOf: whatever ])
+!
+
+assert: set anySatisfy: whateverBlock
+	self assert: (set anySatisfy: [:e |  [whateverBlock value: e]  on: Error do: [ false ] ])
+!
+
+assert: set noneMatchesType: whatever
+	self assert: (set noneSatisfy: [:e | e isKindOf: whatever ])
+!
+
+assert: set noneSatisfy: whateverBlock
+	self assert: (set noneSatisfy: [:e |  [whateverBlock value: e]  on: Error do: [ false ] ])
+!
+
+assert: set size: anInteger
+	self assert: (set size = anInteger )
+!
+
+first: aNode 
+	^ aNode firstSet
+!
+
+first: aNode suchThat: aBlock
+	^ (aNode firstSetsSuchThat: aBlock) at: aNode
+!
+
+followOf: name in: rootNode
+	node := (rootNode allNodes select: [ :n | n name = name ] )anyOne.
+	^ rootNode followSets at: node
+!
+
+followOf: name in: rootNode suchThat: aBlock
+	node := (rootNode allNodes select: [ :n | n name = name ] )anyOne.
+	^ (rootNode followSetsSuchThat: aBlock) at: node
+!
+
+followOfNodeIn: rootNode
+	^ self followOf: 'node' in: rootNode
+!
+
+testFirst1
+	tree := self treeFrom: nil asParser / 'a' asParser.
+	
+	self assert: (self first: tree) anyMatchesType: PPCNilNode.
+	self assert: (self first: tree) anyMatchesType: PPCAbstractLiteralNode.
+!
+
+testFirst2
+	tree := self treeFrom: 'a' asParser optional, 'b' asParser.
+	
+	self assert: (self first: tree) anySatisfy: [ :e | e literal = 'a' ].
+	self assert: (self first: tree) anySatisfy: [ :e | e literal = 'b' ].
+!
+
+testFirst3
+	tree := ('a' asParser optional, 'b' asParser asParser optional), 'c' asParser.
+	
+	self assert: (self first: tree) anySatisfy: [ :e | e literal = 'a' ].
+	self assert: (self first: tree) anySatisfy: [ :e | e literal = 'b' ].
+	self assert: (self first: tree) anySatisfy: [ :e | e literal = 'c' ].
+!
+
+testFirstChoice1
+	tree := self treeFrom: nil asParser / '' asParser.
+	
+	self assert: (self first: tree) anySatisfy: [:e | e literal = ''].
+	self assert: (self first: tree) anyMatchesType: PPCNilNode.
+!
+
+testFirstChoice2
+	tree := self treeFrom: 'a' asParser / nil asParser / 'b' asParser.
+	
+	first := (self first: tree).
+	
+	self assert: first anySatisfy: [:e | e literal =  'a'].
+	self assert: first anySatisfy: [:e | e literal = 'b'].
+	self assert: first anyMatchesType: PPCNilNode.
+!
+
+testFirstComplex1
+	tree := self treeFrom: ('a' asParser / nil asParser), 'c' asParser.
+	
+	first := (self first: tree).
+	
+	self assert: first size: 2.
+	self assert: first anySatisfy: [:e | e literal = 'a'].
+	self assert: first anySatisfy: [:e | e literal = 'c'].
+	self assert: first noneMatchesType: PPCNilNode.
+!
+
+testFirstComplex2
+	tree := self treeFrom: ('a' asParser / nil asParser / 'b' asParser), 'c' asParser.
+	
+	
+	first := (self first: tree).
+	
+	self assert: first size: 3.
+	self assert: first anySatisfy: [:e | e literal = 'a'].
+	self assert: first anySatisfy: [:e | e literal = 'b'].
+	self assert: first anySatisfy: [:e | e literal = 'c'].
+!
+
+testFirstComplex3
+	tree := self treeFrom: ('a' asParser / nil asParser / 'b' asParser), 'c' asParser not.
+	
+	first := (self first: tree).
+	
+	self assert: first anySatisfy: [:e | e literal = 'a'].
+	self assert: first anySatisfy: [:e | e literal = 'b'].
+	self assert: first anySatisfy: [:e | (e isKindOf: PPCNotLiteralNode) and: [e literal = 'c']].
+!
+
+testFirstComplex4
+	tree := (('a' asParser / nil asParser / 'b' asParser), 'c' asParser not) wrapped asCompilerTree.
+	
+	first := (self first: tree).
+	
+	self assert: first anySatisfy: [:e | e literal = 'a'].
+	self assert: first anySatisfy: [:e | e literal = 'b'].
+	self assert: first anySatisfy: [:e | (e isKindOf: PPCNotNode) and: [ e child literal = 'c' ]].
+	self assert: first noneMatchesType: PPCNilNode.
+!
+
+testFirstNegate1
+	tree := ('a' asParser negate, 'b' asParser) asCompilerTree.
+	
+	first := self first: tree.
+
+	self assert: first size: 1.
+	self assert: first anyMatchesType: PPCNotNode
+!
+
+testFirstNot
+	tree := ('a' asParser not star, 'b' asParser) asCompilerTree.
+	
+	first := self first: tree.
+		
+	self assert: first size: 2.
+	self assert: first anyMatchesType: PPCNotNode.
+!
+
+testFirstNot2
+	tree := ('a' asParser not star, 'b' asParser) asCompilerTree optimizeTree.
+	
+	first := self first: tree.
+		
+	self assert: first size: 2.
+	self assert: first anyMatchesType: PPCNotLiteralNode.
+	self assert: first anyMatchesType: PPCLiteralNode.
+!
+
+testFirstNot3
+	tree := (#letter asParser not star, #letter asParser) asCompilerTree optimizeTree.
+	
+	first := self first: tree.
+		
+	self assert: first size: 2.
+	self assert: first anyMatchesType: PPCNotMessagePredicateNode.
+	self assert: first anyMatchesType: PPCMessagePredicateNode.
+!
+
+testFirstNot4
+	tree := (#letter asParser negate plus, #letter asParser) asCompilerTree optimizeTree.
+	
+	first := self first: tree.
+		
+	self assert: first size: 1.
+	self assert: (first anyOne predicate value: $a) not.
+	self assert: (first anyOne predicate value: $1).
+!
+
+testFirstNot5
+	tree := (#letter asParser negate star, #letter asParser) asCompilerTree optimizeTree.
+	
+	first := self first: tree.
+		
+	self assert: first size: 2.
+	self assert: first anySatisfy: [ :e |	(e predicate value: $a) not ].
+	self assert: first anySatisfy: [ :e |	(e predicate value: $1) ].
+
+
+	self assert: first anySatisfy: [ :e |	(e predicate value: $a) ].
+	self assert: first anySatisfy: [ :e |	(e predicate value: $1) not ].
+!
+
+testFirstOptional
+	tree := 'a' asParser optional asCompilerTree.
+	
+	first := (self first: tree).
+	
+	self assert: first anyMatchesType: PPCNilNode.
+	self assert: first anyMatchesType: PPCLiteralNode.
+!
+
+testFirstOptional2
+	tree := ('a' asParser optional, 'b' asParser) asCompilerTree.
+	
+	first := (self first: tree).
+	
+	self assert: first size: 2.
+	self assert: first anySatisfy: [ :e | e literal = 'a' ].
+	self assert: first anySatisfy: [ :e | e literal = 'b' ].
+!
+
+testFirstRepeat1
+	tree := ('a' asParser / nil asParser) plus asCompilerTree.
+	
+	first := self first: tree.
+
+	self assert: first anySatisfy: [:e | e literal = 'a' ].
+	self assert: first anyMatchesType: PPCNilNode.	
+!
+
+testFirstRepeat2
+	tree := ('a' asParser star, 'b' asParser) asCompilerTree.
+	
+	first := self first: tree.
+
+	self assert: first anySatisfy: [:e | e literal = 'a' ].
+	self assert: first anySatisfy: [:e | e literal = 'b' ].
+!
+
+testFirstRepeat3
+	tree := ('a' asParser negate plus, 'b' asParser) asCompilerTree.
+	
+	first := self first: tree.
+
+	self assert: first size: 1.
+	self assert: first anyMatchesType: PPCNotNode.
+!
+
+testFirstRepeat4
+	tree := ('a' asParser negate star, 'b' asParser) asCompilerTree.
+	
+	first := self first: tree.
+
+	self assert: first size: 2.
+	self assert: first anySatisfy: [:e | (e isKindOf: PPCNotNode) and: [e child literal = 'a']].
+	self assert: first anySatisfy: [ :e | e literal = 'b' ]
+!
+
+testFirstSequence1
+	tree := self treeFrom: 'a' asParser, 'b' asParser .
+	
+	first := self first: tree.
+	
+	self assert: first size: 1.
+	self assert: first anySatisfy: [ :e | e literal = 'a' ].
+!
+
+testFirstSequence2
+	tree := nil asParser, 'a' asParser, 'b' asParser .
+	
+	first := self first: tree.
+	
+	self assert: first size: 1.
+	self assert: first anySatisfy: [ :e | e literal = 'a' ].
+!
+
+testFirstSequence3
+	tree := self treeFrom: nil asParser, nil asParser.
+	
+	first := self first: tree.
+	
+	self assert: first size: 1.
+	self assert: first anyMatchesType: PPCNilNode.
+!
+
+testFirstSequence4
+	tree := self treeFrom: ((nil asParser / 'a' asParser) plus), 'b' asParser.
+	
+	first := self first: tree.
+	
+	self assert: first size: 2.
+	self assert: first anySatisfy: [ :e | e literal = 'a' ].
+	self assert: first anySatisfy: [ :e | e literal = 'b' ].
+	self assert: first noneMatchesType: PPCNilNode.
+!
+
+testFirstSequence5
+	tree := ((nil asParser / 'a' asParser) star), 'b' asParser.
+	
+	first := self first: tree.
+	
+	self assert: first size: 2.
+	self assert: first anySatisfy: [ :e | e literal = 'a' ].
+	self assert: first anySatisfy: [ :e | e literal = 'b' ].
+	self assert: first noneMatchesType: PPCNilNode.
+!
+
+testFirstTerminal
+	tree := self treeFrom: 'a' asParser not.
+
+	first := self first: tree.
+	
+	self assert: first size: 1.
+	self assert: (self first: tree) anyMatchesType: PPCNotLiteralNode.
+!
+
+testFirstTerminal2
+	tree := self treeFrom: 'a' asParser and.
+	
+	first := self first: tree.
+	
+	self assert: first size: 1.
+	self assert: first anySatisfy: [: e | e literal = 'a' ]
+!
+
+testFirstTrimmingToken
+	tree := self treeFrom: 'a' asParser trimmingToken.
+	
+	first := self first: tree 
+					  suchThat: [:e | (e isKindOf: PPCTrimmingTokenNode) or: [e isFirstSetTerminal]].
+	
+	self assert: first size: 1.
+	self assert: first anyMatchesType: PPCTrimmingTokenNode
+!
+
+testFollowSet1
+	node := 'a' asParser name: 'node'; yourself.
+	tree := self treeFrom: (node star, 'b' asParser).
+	
+	followSet := self followOfNodeIn: tree.
+	
+	self assert: followSet size: 2.
+	self assert: followSet anySatisfy: [:e | e literal = 'a'].
+	self assert: followSet anySatisfy: [:e | e literal = 'b'].
+!
+
+testFollowSet10
+	| a b c |
+	
+	a := 'a' asParser name: 'a'; yourself.
+	b := 'b' asParser optional name: 'b'; yourself.
+	c := 'c' asParser name: 'c'; yourself.
+	
+	
+		
+	tree := self treeFrom: a plus, b, c.
+
+	followSet := self followOf: 'a' in: tree.
+
+	self assert: followSet size: 3.
+	self assert: followSet anySatisfy: [:e | e literal = 'a' ].	
+	self assert: followSet anySatisfy: [:e | e literal =  'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'c' ].
+!
+
+testFollowSet2
+	| follow |
+	node := 'a' asParser name: 'node'; yourself.
+	follow := 'b' asParser, 'c' asParser.
+	
+	tree := self treeFrom: (node, follow).
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet size: 1.
+	self assert: followSet anySatisfy: [:e | e literal = 'b'].
+	self assert: followSet noneSatisfy: [:e | e literal = 'c'].	
+!
+
+testFollowSet3
+	| follow |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow := ('b' asParser, 'c' asParser) / ('d' asParser).
+	
+	
+	tree := self treeFrom: (node, follow).
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet size: 2.
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'd' ].
+!
+
+testFollowSet4
+	| follow |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow := ('b' asParser, 'c' asParser).
+	
+	
+	tree := self treeFrom: (node star, follow).
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'a' ].
+!
+
+testFollowSet5
+	| follow1 follow2 |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow1 := ('b' asParser, 'c' asParser) / nil asParser.
+	follow2 := 'd' asParser.
+	
+	
+	tree := self treeFrom: (node, follow1, follow2).
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'd' ].
+!
+
+testFollowSet6
+	| follow follow1 follow2 |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow1 := ('b' asParser, 'c' asParser) / nil asParser.
+	follow2 := 'd' asParser.
+	
+	follow := (follow1, follow2).
+	
+	tree  := self treeFrom: (node, follow).
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'd' ].
+!
+
+testFollowSet7
+	|  r1 r2 follow1 follow2 |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow1 := ('b' asParser, 'c' asParser) / nil asParser.
+	follow2 := 'd' asParser / nil asParser .
+	
+	r1 := (node, follow1).
+	r2 := (r1, follow2).
+	
+	tree  := self treeFrom: r2.
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'd' ].
+!
+
+testFollowSet8
+	node := 'a' asParser name: 'node'; yourself.
+	tree := self treeFrom: node.
+	
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet anyMatchesType: PPCNilNode.
+!
+
+testFollowSet9
+	| a b c |
+	
+	a := 'a' asParser name: 'a'; yourself.
+	b := 'b' asParser optional name: 'b'; yourself.
+	c := 'c' asParser name: 'c'; yourself.
+	
+	
+	tree := self treeFrom: a, b, c.
+	followSet := self followOf: 'c' in: tree.
+	self assert: followSet anyMatchesType: PPCNilNode.
+	
+	followSet := self followOf: 'b' in: tree.
+	self assert: followSet anySatisfy: [:e | e literal = 'c' ].
+
+	followSet := self followOf: 'a' in: tree.
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'c' ].
+!
+
+testFollowSetChoice1
+	| follow |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow := 'b' asParser / 'c' asParser .
+	
+	tree := self treeFrom: node, follow.
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet size: 2.	
+	self assert: followSet anySatisfy: [:e | e literal = 'b' ].
+	self assert: followSet anySatisfy: [:e | e literal = 'c' ].
+!
+
+testFollowSetOptional1
+	|  follow1 follow2 |
+
+	node := 'a' asParser name: 'node'; yourself.
+	follow1 := 'b' asParser optional.
+	follow2 := 'c' asParser.
+	
+	tree := self treeFrom: node, follow1, follow2.
+
+	followSet := self followOfNodeIn: tree.
+
+	self assert: followSet size: 2.
+	self assert: followSet anySatisfy: [:e | e literal = 'b'].
+	self assert: followSet anySatisfy: [:e | e literal = 'c'].
+!
+
+testFollowSetRepeat1
+
+	node := 'a' asParser name: 'node'; yourself.
+	tree := self treeFrom: node plus.
+	
+	followSet := self followOfNodeIn: tree.
+	
+	self assert: followSet anySatisfy: [:e | e literal = 'a' ].
+	self assert: followSet anyMatchesType: PPCNilNode
+!
+
+testFollowSetRepeat2
+
+	node := 'a' asParser.
+	tree := self treeFrom: (node plus name: 'node'; yourself).
+	
+	followSet := self followOfNodeIn: tree.
+	
+	self assert: followSet size: 1.
+	self assert: followSet anyMatchesType: PPCNilNode
+!
+
+testFollowTrimmingToken
+	| token1 token2 |
+	
+	token1 := #letter asParser plus trimmingToken name: 'token1'; yourself.
+	token2 := #letter asParser plus trimmingToken name: 'token2'; yourself.
+	
+	
+	tree := self treeFrom: token1, token2.
+	followSet := self 	followOf: 'token1' 
+							in: tree 
+							suchThat: [:e | e isFirstSetTerminal or: [e isKindOf: PPCTrimmingTokenNode ]].
+
+	self assert: followSet size: 1.
+	self assert: followSet anyMatchesType: PPCTrimmingTokenNode. 
+!
+
+treeFrom: parser
+	^ parser asCompilerTree optimizeTree
+! !
+
--- a/compiler/tests/PPCNodeTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/PPCNodeTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -137,7 +137,7 @@
 	
 	self assert: tree type: PPCTrimmingTokenNode.
 	self assert: tree child type: PPCTokenSequenceNode.
-	self assert: tree whitespace type: PPCTokenStarMessagePredicateNode.
+	self assert: tree whitespace type: PPCInlineTokenStarSeparatorNode.
 	
 	parser := $d asParser trimmingToken star.
 	tree := parser asCompilerTree optimizeTree.
--- a/compiler/tests/PPCOptimizingTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/PPCOptimizingTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -15,7 +15,11 @@
 !
 
 optimize: p
-	^ p asCompilerTree optimizeTree 
+	^ self optimize: p parameters: #()
+!
+
+optimize: p parameters: parameters
+	^ p asCompilerTree optimizeTree: parameters 
 ! !
 
 !PPCOptimizingTest methodsFor:'tests'!
@@ -116,20 +120,11 @@
 !
 
 testInlinePluggable
-        | tree |
-        tree := self optimize: [:ctx | nil] asParser star.
+	| tree |
+	tree := self optimize: [:ctx | nil] asParser star.
 
-        self assert: tree type: PPCStarNode.
-        "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 assert: tree child type: PPCPluggableNode.
-        ] ifFalse:[ 
-                self assert: tree child type: PPCInlinePluggableNode.
-        ]
-
-    "Modified: / 08-11-2014 / 00:57:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	self assert: tree type: PPCStarNode.
+	self assert: tree child type: PPCInlinePluggableNode.
 !
 
 testInlinePredicate
@@ -149,6 +144,14 @@
 	self assert: tree message = #isLetter.
 !
 
+testNotAction
+	| tree |
+	tree := self optimize: (($f asParser, $o asParser) ==> #second) not.
+
+	self assert: tree type: PPCNotNode.
+	self assert: tree child type: PPCTokenSequenceNode.
+!
+
 testNotCharSetPredicate
 	| tree |
 	tree := self optimize: (PPPredicateObjectParser on: [:each | each = $b or: [each = $c] ] message: #foo) asParser not.
@@ -171,6 +174,14 @@
 	self assert: tree type: PPCNotMessagePredicateNode.
 !
 
+testNotSequence
+	| tree |
+	tree := self optimize: ($f asParser, $o asParser) not.
+
+	self assert: tree type: PPCNotNode.
+	self assert: tree child type: PPCTokenSequenceNode.
+!
+
 testStarAny
 	| tree |
 	tree := self optimize: #any asParser star.
@@ -192,6 +203,23 @@
 	self assert: tree type: PPCStarMessagePredicateNode.
 !
 
+testStarSeparator
+	| tree |
+	tree := self optimize: #space asParser star trimmingToken parameters: { #inline -> false }.
+
+	self assert: tree type: PPCTrimmingTokenNode.
+	self assert: tree child type: PPCTokenStarSeparatorNode.
+!
+
+testStarSeparator2
+	| tree |
+	tree := self optimize: (#space asParser star, 'whatever' asParser) trimmingToken.
+
+	self assert: tree type: PPCTrimmingTokenNode.
+	self assert: tree child type: PPCTokenSequenceNode.
+	self assert: tree child children first type: PPCInlineTokenStarSeparatorNode.
+!
+
 testSymbolAction
 	| tree |
 	tree := self optimize: (#letter asParser) ==> #second.
@@ -210,7 +238,7 @@
 	self assert: tree child type: PPCTokenSequenceNode.
 	self assert: tree child children size = 2.
 	self assert: tree child children first type: PPCInlineMessagePredicateNode.
-	self assert: tree child children second type: PPCTokenStarMessagePredicateNode.	
+	self assert: tree child children second type: PPCInlineTokenStarMessagePredicateNode.	
 !
 
 testTokenSequence
@@ -231,11 +259,11 @@
 	tree := self optimize: ((#letter asParser, #word asParser star) trimmingToken).
 
 	self assert: tree type: PPCTrimmingTokenNode.
-	self assert: tree whitespace type: PPCTokenStarMessagePredicateNode.
+	self assert: tree whitespace type: PPCInlineTokenStarSeparatorNode.
 	self assert: tree child type: PPCTokenSequenceNode.
 	self assert: tree child children size = 2.
 	self assert: tree child children first type: PPCInlineMessagePredicateNode.
-	self assert: tree child children second type: PPCTokenStarMessagePredicateNode.	
+	self assert: tree child children second type: PPCInlineTokenStarMessagePredicateNode.	
 !
 
 testTrimmingToken2
@@ -252,7 +280,7 @@
 	
 	self assert: tree type: PPCTrimmingTokenNode.
 	self assert: tree child type: PPCTokenSequenceNode.
-	self assert: tree whitespace type: PPCTokenStarMessagePredicateNode.
+	self assert: tree whitespace type: PPCInlineTokenStarSeparatorNode.
 	
 	parser := $d asParser trimmingToken star.
 	tree := parser asCompilerTree optimizeTree.
@@ -260,6 +288,27 @@
 	self assert: tree type: PPCStarNode.
 	self assert: tree child type: PPCTrimmingTokenNode.
 	self assert: tree child child type: PPCInlineCharacterNode.
+!
+
+testTrimmingToken3
+	| parser tree |
+	parser := ('foo' asParser trimmingToken name: 'foo'), ('bar' asParser trimmingToken name: 'bar').
+	tree := parser asCompilerTree optimizeTree.
+	
+	self assert: tree type: PPCSequenceNode.
+	self assert: tree children first type: PPCTrimmingTokenNode.
+	self assert: tree children second type: PPCTrimmingTokenNode.
+!
+
+testTrimmingTokenNested
+	| parser tree foo|
+	foo := 'foo' asParser trimmingToken name: 'foo'.
+	parser := (foo not, 'bar' asParser) trimmingToken name: 'token'.
+	tree := self optimize: parser.
+	
+	self assert: tree type: PPCTrimmingTokenNode.
+	self assert: tree children second type: PPCTokenSequenceNode.
+	self assert: tree children second children first type: PPCInlineNotLiteralNode.
 ! !
 
 !PPCOptimizingTest class methodsFor:'documentation'!
--- a/compiler/tests/PPCompiledSmalltalkGrammarResource.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/PPCompiledSmalltalkGrammarResource.st	Mon Nov 24 00:09:23 2014 +0000
@@ -12,10 +12,10 @@
 setUp
         | time |
         time := Time millisecondsToRun: [
-        PPSmalltalkGrammar new compile: #PPCompiledSmalltalkGrammar
+                PPSmalltalkGrammar new compile: #PPCompiledSmalltalkGrammar
         ].
         Transcript show: 'Grammar compiled in: ', time asString, 'ms'; cr.
 
-    "Modified: / 08-11-2014 / 00:54:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 12:33:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/abbrev.stc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/abbrev.stc	Mon Nov 24 00:09:23 2014 +0000
@@ -6,9 +6,10 @@
 PPCContextTest PPCContextTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Context' 1
 PPCGuardTest PPCGuardTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Core' 1
 PPCMockCompiler PPCMockCompiler stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Core' 0
+PPCNodeCompilingTest PPCNodeCompilingTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Nodes' 1
+PPCNodeFirstFollowNextTests PPCNodeFirstFollowNextTests stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Nodes' 1
 PPCNodeTest PPCNodeTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Nodes' 1
 PPCOptimizingTest PPCOptimizingTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Nodes' 1
 PPCompiledSmalltalkGrammarResource PPCompiledSmalltalkGrammarResource stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Smalltalk' 1
+PPCompiledSmalltalkGrammarTests PPCompiledSmalltalkGrammarTests stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Smalltalk' 1
 stx_goodies_petitparser_compiler_tests stx_goodies_petitparser_compiler_tests stx:goodies/petitparser/compiler/tests '* Projects & Packages *' 3
-PPCNodeCompilingTest PPCNodeCompilingTest stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Nodes' 1
-PPCompiledSmalltalkGrammarTests PPCompiledSmalltalkGrammarTests stx:goodies/petitparser/compiler/tests 'PetitCompiler-Tests-Smalltalk' 1
--- a/compiler/tests/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -80,6 +80,7 @@
 $(OUTDIR)PPCContextTest.$(O) PPCContextTest.$(H): PPCContextTest.st $(INCLUDE_TOP)\stx\goodies\petitparser\tests\PPContextTest.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCGuardTest.$(O) PPCGuardTest.$(H): PPCGuardTest.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMockCompiler.$(O) PPCMockCompiler.$(H): PPCMockCompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PPCNodeFirstFollowNextTests.$(O) PPCNodeFirstFollowNextTests.$(H): PPCNodeFirstFollowNextTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCNodeTest.$(O) PPCNodeTest.$(H): PPCNodeTest.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCOptimizingTest.$(O) PPCOptimizingTest.$(H): PPCOptimizingTest.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(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)
--- a/compiler/tests/libInit.cc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/libInit.cc	Mon Nov 24 00:09:23 2014 +0000
@@ -32,6 +32,7 @@
 _PPCContextTest_Init(pass,__pRT__,snd);
 _PPCGuardTest_Init(pass,__pRT__,snd);
 _PPCMockCompiler_Init(pass,__pRT__,snd);
+_PPCNodeFirstFollowNextTests_Init(pass,__pRT__,snd);
 _PPCNodeTest_Init(pass,__pRT__,snd);
 _PPCOptimizingTest_Init(pass,__pRT__,snd);
 _PPCompiledSmalltalkGrammarResource_Init(pass,__pRT__,snd);
--- a/compiler/tests/stx_goodies_petitparser_compiler_tests.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/stx_goodies_petitparser_compiler_tests.st	Mon Nov 24 00:09:23 2014 +0000
@@ -14,16 +14,16 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitCompiler-Tests-JanVrany.13
-    Author: JanVrany
-    Time: 05-11-2014, 09:31:07 AM
-    UUID: 189ae287-6bc1-40ba-8458-b8392c4260a0        
+    Name: PetitCompiler-Tests-JanKurs.21
+    Author: JanKurs
+    Time: 17-11-2014, 05:51:53.134 PM
+    UUID: 8d6c0799-14e7-4871-8d91-8b0f9886db83           
     Repository: http://smalltalkhub.com/mc/JanKurs/PetitParser/main
 
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 05-11-2014 / 22:59:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 12:40:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
@@ -57,7 +57,7 @@
     ^ #(
         #'stx:goodies/petitparser/tests'    "PPAbstractParserTest - superclass of PPCCompilerTest"
         #'stx:goodies/sunit'    "TestAsserter - superclass of PPCCompilerTest"
-        #'stx:libbasic'    "Autoload - superclass of PPCNodeCompilingTest"
+        #'stx:libbasic'    "LibraryDefinition - superclass of stx_goodies_petitparser_compiler_tests"
     )
 !
 
@@ -70,7 +70,7 @@
 
     ^ #(
         #'stx:goodies/petitparser'    "PPCharSetPredicate - referenced by PPCCompilerTest>>testGuard1"
-        #'stx:goodies/petitparser/compiler'    "PPCActionNode - referenced by PPCOptimizingTest>>testSymbolAction"
+        #'stx:goodies/petitparser/compiler'    "PPCAbstractLiteralNode - referenced by PPCNodeFirstFollowNextTests>>testFirst1"
         #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCCompilerTest>>testClass"
     )
 !
@@ -100,12 +100,13 @@
         PPCContextTest
         PPCGuardTest
         PPCMockCompiler
+        (PPCNodeCompilingTest autoload)
+        PPCNodeFirstFollowNextTests
         PPCNodeTest
         PPCOptimizingTest
         PPCompiledSmalltalkGrammarResource
+        (PPCompiledSmalltalkGrammarTests autoload)
         #'stx_goodies_petitparser_compiler_tests'
-        (PPCNodeCompilingTest autoload)
-        (PPCompiledSmalltalkGrammarTests autoload)
     )
 !
 
--- a/compiler/tests/tests.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/compiler/tests/tests.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.5.0\0"
-      VALUE "ProductDate", "Wed, 19 Nov 2014 10:47:30 GMT\0"
+      VALUE "ProductDate", "Fri, 21 Nov 2014 15:17:55 GMT\0"
     END
 
   END
--- a/extensions.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/extensions.st	Mon Nov 24 00:09:23 2014 +0000
@@ -56,7 +56,7 @@
 !Interval methodsFor:'*petitparser-core-converting'!
 
 asParser    
-        "Create a range of characters between start and stop."
+	"Create a range of characters between start and stop."
 
     self assert:start isCharacter.
     self assert:stop isCharacter.
@@ -64,11 +64,9 @@
     ^ PPPredicateObjectParser between: start and: stop
 
     "
-                ($a to: $f) asParser parse: 'a'
-                ($a to: $f) asParser parse: 'g'
+		($a to: $f) asParser parse: 'a'
+		($a to: $f) asParser parse: 'g'
     "
-
-    "Modified (comment): / 01-11-2014 / 13:13:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Object methodsFor:'*petitparser-core-converting'!
@@ -96,9 +94,14 @@
 asPetitStream
 	"Some of my subclasses do not use the instance-variables collection, position and readLimit but instead have a completely different internal representation. In these cases just use the super implementation that is inefficient but should work in all cases."
 
+"
+	Disabled until we agree on some way how to optimize this
+
 	^ (collection isNil or: [ position isNil or: [ readLimit isNil ] ])
 		ifFalse: [ PPStream on: collection from: ( position + 1 ) to: readLimit ]
       ifTrue: [ super asPetitStream ]
+"
+	^ super asPetitStream
 ! !
 
 !PositionableStream methodsFor:'*petitparser-core'!
--- a/libInit.cc	Wed Nov 19 10:52:37 2014 +0000
+++ b/libInit.cc	Mon Nov 24 00:09:23 2014 +0000
@@ -37,6 +37,7 @@
 _PPToken_Init(pass,__pRT__,snd);
 _stx_137goodies_137petitparser_Init(pass,__pRT__,snd);
 _PPDelegateParser_Init(pass,__pRT__,snd);
+_PPEndOfLineParser_Init(pass,__pRT__,snd);
 _PPEpsilonParser_Init(pass,__pRT__,snd);
 _PPFailingParser_Init(pass,__pRT__,snd);
 _PPListParser_Init(pass,__pRT__,snd);
@@ -44,6 +45,7 @@
 _PPPluggableParser_Init(pass,__pRT__,snd);
 _PPPredicateParser_Init(pass,__pRT__,snd);
 _PPStartOfLine_Init(pass,__pRT__,snd);
+_PPStartOfLineParser_Init(pass,__pRT__,snd);
 _PPUnresolvedParser_Init(pass,__pRT__,snd);
 _PPActionParser_Init(pass,__pRT__,snd);
 _PPAndParser_Init(pass,__pRT__,snd);
@@ -62,6 +64,7 @@
 _PPRepeatingParser_Init(pass,__pRT__,snd);
 _PPSequenceParser_Init(pass,__pRT__,snd);
 _PPTrimmingParser_Init(pass,__pRT__,snd);
+_PPLimitedChoiceParser_Init(pass,__pRT__,snd);
 _PPLimitedRepeatingParser_Init(pass,__pRT__,snd);
 _PPPossessiveRepeatingParser_Init(pass,__pRT__,snd);
 _PPTokenParser_Init(pass,__pRT__,snd);
--- a/parsers/smalltalk/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -42,6 +42,7 @@
 #  -warnNonStandard : no warnings about ST/X extensions
 #  -warnEOLComments : no warnings about EOL comment extension
 #  -warnPrivacy     : no warnings about privateClass extension
+#  -warnUnused      : no warnings about unused variables
 #
 # ********** OPTIONAL: MODIFY the next line(s) ***
 # STCWARNINGS=-warn
--- a/parsers/smalltalk/PPSmalltalkWhitespaceParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/PPSmalltalkWhitespaceParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,7 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"
 
 PPParser subclass:#PPSmalltalkWhitespaceParser
-	instanceVariableNames:'separator'
+	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitSmalltalk-Core'
@@ -19,14 +19,17 @@
 
 initialize
 	super initialize.
-	separator := PPCharSetPredicate on: [ :char | char isSeparator ].
 ! !
 
 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
 
+name
+	^ 'smalltalk_ws'
+!
+
 parseOn: aPPContext
         "Skip any leading whitespace"
-        [ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
+        [ [aPPContext atEnd not and: [  aPPContext uncheckedPeek isSeparator ] ]
                 whileTrue: [ aPPContext next ].
 
         "Check for comment"
@@ -49,7 +52,7 @@
                 ]
         ].
 
-    "Modified: / 07-11-2014 / 01:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 10:10:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!
--- a/parsers/smalltalk/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -30,6 +30,7 @@
 !INCLUDE Make.spec
 
 LIBNAME=libstx_goodies_petitparser_parsers_smalltalk
+MODULE_PATH=goodies\petitparser\parsers\smalltalk
 RESFILES=smalltalk.$(RES)
 
 
--- a/parsers/smalltalk/smalltalk.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/smalltalk.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -4,7 +4,7 @@
 //
 VS_VERSION_INFO VERSIONINFO
   FILEVERSION     6,2,32767,32767
-  PRODUCTVERSION  6,2,4,0
+  PRODUCTVERSION  6,2,5,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -24,8 +24,8 @@
       VALUE "InternalName", "stx:goodies/petitparser/parsers/smalltalk\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
-      VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Fri, 07 Nov 2014 02:08:51 GMT\0"
+      VALUE "ProductVersion", "6.2.5.0\0"
+      VALUE "ProductDate", "Fri, 21 Nov 2014 10:47:23 GMT\0"
     END
 
   END
--- a/parsers/smalltalk/stx_goodies_petitparser_parsers_smalltalk.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/stx_goodies_petitparser_parsers_smalltalk.st	Mon Nov 24 00:09:23 2014 +0000
@@ -20,15 +20,15 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitSmalltalk-JanKurs.71
+    Name: PetitSmalltalk-JanKurs.78
     Author: JanKurs
-    Time: 19-08-2014, 02:18:05 AM
-    UUID: d1d11836-f3e2-4709-abd3-e2ff3b72d7c4          
+    Time: 14-11-2014, 05:05:07.765 PM
+    UUID: 3d68330d-44d5-46c3-9705-97f627b3edbc              
     Repository: http://smalltalkhub.com/mc/Moose/PetitParser/main
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 07-10-2014 / 09:14:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 10:46:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
--- a/parsers/smalltalk/tests/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/tests/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -42,6 +42,7 @@
 #  -warnNonStandard : no warnings about ST/X extensions
 #  -warnEOLComments : no warnings about EOL comment extension
 #  -warnPrivacy     : no warnings about privateClass extension
+#  -warnUnused      : no warnings about unused variables
 #
 # ********** OPTIONAL: MODIFY the next line(s) ***
 # STCWARNINGS=-warn
--- a/parsers/smalltalk/tests/PPSmalltalkGrammarTests.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/tests/PPSmalltalkGrammarTests.st	Mon Nov 24 00:09:23 2014 +0000
@@ -82,6 +82,12 @@
 		rule: #expression
 !
 
+testBlock1
+	self 
+		parse: '[]'
+		rule: #block
+!
+
 testComment1
 	self 
 		parse: '1"one"+2'
@@ -242,6 +248,12 @@
 		rule: #sequence
 !
 
+testStatements9
+	self 
+		parse: ''
+		rule: #statements
+!
+
 testTemporaries1
 	self 
 		parse: '| a |'
--- a/parsers/smalltalk/tests/PPSmalltalkParserTests.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/tests/PPSmalltalkParserTests.st	Mon Nov 24 00:09:23 2014 +0000
@@ -390,6 +390,11 @@
 	self assert: result statements first value isInteger
 !
 
+testStatements9
+	super testStatements9.
+	self assert: result isEmpty.
+!
+
 testTemporaries1
 	super testTemporaries1.
 	self assert: result isSequence.
@@ -507,6 +512,14 @@
 	self assert: result body statements isEmpty
 !
 
+testBlock1
+	super testBlock1.
+	self assert: result isBlock.
+	self assert: result arguments size equals: 0.
+	self assert: result body temporaries isEmpty.
+	self assert: result body statements isEmpty
+!
+
 testComplexBlock1
 	super testComplexBlock1.
 	self assert: result isBlock.
--- a/parsers/smalltalk/tests/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/tests/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -30,6 +30,7 @@
 !INCLUDE Make.spec
 
 LIBNAME=libstx_goodies_petitparser_parsers_smalltalk_tests
+MODULE_PATH=goodies\petitparser\parsers\smalltalk\tests
 RESFILES=tests.$(RES)
 
 
--- a/parsers/smalltalk/tests/stx_goodies_petitparser_parsers_smalltalk_tests.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/tests/stx_goodies_petitparser_parsers_smalltalk_tests.st	Mon Nov 24 00:09:23 2014 +0000
@@ -14,15 +14,15 @@
     "The last merged version is: "
 
     ^ '
-    Name: PetitSmalltalk-JanKurs.71
+    Name: PetitSmalltalk-JanKurs.78
     Author: JanKurs
-    Time: 19-08-2014, 02:18:05 AM
-    UUID: d1d11836-f3e2-4709-abd3-e2ff3b72d7c4
+    Time: 14-11-2014, 05:05:07.765 PM
+    UUID: 3d68330d-44d5-46c3-9705-97f627b3edbc              
     Repository: http://smalltalkhub.com/mc/Moose/PetitParser/main
     '
 
     "Created: / 03-10-2014 / 02:27:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 07-10-2014 / 09:14:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 10:47:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 monticelloName
--- a/parsers/smalltalk/tests/tests.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/tests/tests.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -4,7 +4,7 @@
 //
 VS_VERSION_INFO VERSIONINFO
   FILEVERSION     6,2,32767,32767
-  PRODUCTVERSION  6,2,4,0
+  PRODUCTVERSION  6,2,5,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -24,8 +24,8 @@
       VALUE "InternalName", "stx:goodies/petitparser/parsers/smalltalk/tests\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
-      VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Fri, 07 Nov 2014 02:08:52 GMT\0"
+      VALUE "ProductVersion", "6.2.5.0\0"
+      VALUE "ProductDate", "Fri, 21 Nov 2014 10:47:25 GMT\0"
     END
 
   END
--- a/petitparser.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/petitparser.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -4,7 +4,7 @@
 //
 VS_VERSION_INFO VERSIONINFO
   FILEVERSION     6,2,32767,32767
-  PRODUCTVERSION  6,2,4,0
+  PRODUCTVERSION  6,2,5,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -24,8 +24,8 @@
       VALUE "InternalName", "stx:goodies/petitparser\0"
       VALUE "LegalCopyright", "(C) Lukas Renggli\0"
       VALUE "ProductName", "Petit Parser\0"
-      VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Mon, 03 Nov 2014 09:06:53 GMT\0"
+      VALUE "ProductVersion", "6.2.5.0\0"
+      VALUE "ProductDate", "Wed, 19 Nov 2014 11:10:17 GMT\0"
     END
 
   END
--- a/stx_goodies_petitparser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/stx_goodies_petitparser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -157,6 +157,7 @@
         PPToken
         #'stx_goodies_petitparser'
         PPDelegateParser
+        PPEndOfLineParser
         PPEpsilonParser
         PPFailingParser
         PPListParser
@@ -164,6 +165,7 @@
         PPPluggableParser
         PPPredicateParser
         PPStartOfLine
+        PPStartOfLineParser
         PPUnresolvedParser
         PPActionParser
         PPAndParser
@@ -182,6 +184,7 @@
         PPRepeatingParser
         PPSequenceParser
         PPTrimmingParser
+        PPLimitedChoiceParser
         PPLimitedRepeatingParser
         PPPossessiveRepeatingParser
         PPTokenParser
--- a/tests/Make.spec	Wed Nov 19 10:52:37 2014 +0000
+++ b/tests/Make.spec	Mon Nov 24 00:09:23 2014 +0000
@@ -42,6 +42,7 @@
 #  -warnNonStandard : no warnings about ST/X extensions
 #  -warnEOLComments : no warnings about EOL comment extension
 #  -warnPrivacy     : no warnings about privateClass extension
+#  -warnUnused      : no warnings about unused variables
 #
 # ********** OPTIONAL: MODIFY the next line(s) ***
 # STCWARNINGS=-warn
--- a/tests/PPContextMementoTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/tests/PPContextMementoTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -7,6 +7,7 @@
 	category:'PetitTests-Tests'
 !
 
+
 !PPContextMementoTest methodsFor:'accessing'!
 
 memento
@@ -115,3 +116,10 @@
 	self assert: (memento hasProperty: #foo).	
 ! !
 
+!PPContextMementoTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/tests/PPContextTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/tests/PPContextTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -72,6 +72,23 @@
 	self assert: context position = 0.
 !
 
+testMemoization3
+	| stream memento memento2 collection |
+	stream := 'abc' asPetitStream.
+	context := context stream: stream.
+	collection := OrderedCollection new.
+
+	memento := context remember.
+	context propertyAt: #foo put: collection.
+	memento2 := context remember.
+	
+	context restore: memento.
+	self assert: (context hasProperty: #foo) not.
+	
+	context restore: memento2.
+	self assert: (context hasProperty: #foo).
+!
+
 testPutGlobals
 	self assert: (context hasGlobal: #foo) not.
 	self assert: (context hasGlobal: #bar) not.	
--- a/tests/PPPredicateTest.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/tests/PPPredicateTest.st	Mon Nov 24 00:09:23 2014 +0000
@@ -11,9 +11,7 @@
 !PPPredicateTest methodsFor:'private'!
 
 charactersDo: aBlock
-        0 to: 255 do: [ :index | aBlock value: (Character codePoint: index) ]
-
-    "Modified: / 03-11-2014 / 09:11:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	1 to: 256 do: [ :index | aBlock value: (Character codePoint: index) ]
 ! !
 
 !PPPredicateTest methodsFor:'testing'!
@@ -324,14 +322,12 @@
 !
 
 parsedCharacterSet: aParser
-        | result |
-        result := String new writeStream.
-        self charactersDo: [ :char |
-                (aParser matches: char asString)
-                        ifTrue: [ result nextPut: char ] ].
-        ^ result contents
-
-    "Modified: / 03-11-2014 / 09:16:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	| result |
+	result := String new writeStream.
+	self charactersDo: [ :char |
+		(aParser matches: (char asString))
+			ifTrue: [ result nextPut: char ] ].
+	^ result contents
 ! !
 
 !PPPredicateTest class methodsFor:'documentation'!
--- a/tests/bc.mak	Wed Nov 19 10:52:37 2014 +0000
+++ b/tests/bc.mak	Mon Nov 24 00:09:23 2014 +0000
@@ -30,6 +30,7 @@
 !INCLUDE Make.spec
 
 LIBNAME=libstx_goodies_petitparser_tests
+MODULE_PATH=goodies\petitparser\tests
 RESFILES=tests.$(RES)
 
 
--- a/tests/tests.rc	Wed Nov 19 10:52:37 2014 +0000
+++ b/tests/tests.rc	Mon Nov 24 00:09:23 2014 +0000
@@ -4,7 +4,7 @@
 //
 VS_VERSION_INFO VERSIONINFO
   FILEVERSION     6,2,32767,32767
-  PRODUCTVERSION  6,2,4,0
+  PRODUCTVERSION  6,2,5,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -24,8 +24,8 @@
       VALUE "InternalName", "stx:goodies/petitparser/tests\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2014\nCopyright eXept Software AG 1998-2014\0"
       VALUE "ProductName", "Smalltalk/X\0"
-      VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Mon, 03 Nov 2014 11:25:50 GMT\0"
+      VALUE "ProductVersion", "6.2.5.0\0"
+      VALUE "ProductDate", "Wed, 19 Nov 2014 11:10:19 GMT\0"
     END
 
   END