To fold
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 15 Apr 2015 11:28:09 +0100
changeset 422 116d2b2af905
parent 421 7e08b31e0dae
child 423 f3b99c7c1b20
To fold
compiler/Make.proto
compiler/Make.spec
compiler/PPCAbstractActionNode.st
compiler/PPCAbstractCharacterNode.st
compiler/PPCAbstractLiteralNode.st
compiler/PPCAbstractPredicateNode.st
compiler/PPCActionNode.st
compiler/PPCAndNode.st
compiler/PPCAnyNode.st
compiler/PPCBridge.st
compiler/PPCCharSetPredicateNode.st
compiler/PPCCharacterNode.st
compiler/PPCChoiceNode.st
compiler/PPCCompiledMethod.st
compiler/PPCCompiler.st
compiler/PPCContext.st
compiler/PPCContextMemento.st
compiler/PPCDelegateNode.st
compiler/PPCForwardNode.st
compiler/PPCGuard.st
compiler/PPCInlineAnyNode.st
compiler/PPCInlineCharSetPredicateNode.st
compiler/PPCInlineCharacterNode.st
compiler/PPCInlineLiteralNode.st
compiler/PPCInlineMessagePredicateNode.st
compiler/PPCInlineNilNode.st
compiler/PPCInlineNotCharSetPredicateNode.st
compiler/PPCInlineNotLiteralNode.st
compiler/PPCInlineNotMessagePredicateNode.st
compiler/PPCInlinePluggableNode.st
compiler/PPCInlineStrategy.st
compiler/PPCInlineTokenStarMessagePredicateNode.st
compiler/PPCInlineTokenStarSeparatorNode.st
compiler/PPCInlinedMethod.st
compiler/PPCListNode.st
compiler/PPCLiteralNode.st
compiler/PPCMessagePredicateNode.st
compiler/PPCMethod.st
compiler/PPCMethodStrategy.st
compiler/PPCNegateNode.st
compiler/PPCNilNode.st
compiler/PPCNode.st
compiler/PPCNotCharSetPredicateNode.st
compiler/PPCNotLiteralNode.st
compiler/PPCNotMessagePredicateNode.st
compiler/PPCNotNode.st
compiler/PPCOptimizationResult.st
compiler/PPCOptionalNode.st
compiler/PPCPluggableNode.st
compiler/PPCPlusNode.st
compiler/PPCPredicateNode.st
compiler/PPCProfilingContext.st
compiler/PPCSentinelNode.st
compiler/PPCSequenceNode.st
compiler/PPCStarAnyNode.st
compiler/PPCStarCharSetPredicateNode.st
compiler/PPCStarMessagePredicateNode.st
compiler/PPCStarNode.st
compiler/PPCSymbolActionNode.st
compiler/PPCTokenActionNode.st
compiler/PPCTokenNode.st
compiler/PPCTokenSequenceNode.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/Make.proto
compiler/benchmarks/PPCBenchmark.st
compiler/benchmarks/PPCBenchmarkResources.st
compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st
compiler/extensions.st
compiler/libInit.cc
compiler/stx_goodies_petitparser_compiler.st
compiler/tests/Make.proto
compiler/tests/PPCCompilerTest.st
compiler/tests/PPCContextMementoTest.st
compiler/tests/PPCContextTest.st
compiler/tests/PPCGuardTest.st
compiler/tests/PPCMockCompiler.st
compiler/tests/PPCNodeCompilingTest.st
compiler/tests/PPCNodeFirstFollowNextTests.st
compiler/tests/PPCNodeTest.st
compiler/tests/PPCOptimizingTest.st
compiler/tests/PPCompiledSmalltalkGrammarResource.st
compiler/tests/PPCompiledSmalltalkGrammarTests.st
compiler/tests/stx_goodies_petitparser_compiler_tests.st
--- a/compiler/Make.proto	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/Make.proto	Wed Apr 15 11:28:09 2015 +0100
@@ -110,7 +110,7 @@
 
 
 # build all packages containing referenced classes for this package
-# they are nor needed to compile the package
+# they are not needed to compile the package (but later, to load it)
 references:
 
 
@@ -131,7 +131,6 @@
 $(OUTDIR)PPCContext.$(O) PPCContext.$(H): PPCContext.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPStream.$(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)PPCContextMemento.$(O) PPCContextMemento.$(H): PPCContextMemento.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCGuard.$(O) PPCGuard.$(H): PPCGuard.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)PPCInlineStrategy.$(O) PPCInlineStrategy.$(H): PPCInlineStrategy.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMethod.$(O) PPCMethod.$(H): PPCMethod.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMethodStrategy.$(O) PPCMethodStrategy.$(H): PPCMethodStrategy.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PPCNode.$(O) PPCNode.$(H): PPCNode.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/compiler/Make.spec	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/Make.spec	Wed Apr 15 11:28:09 2015 +0100
@@ -57,7 +57,6 @@
 	PPCContext \
 	PPCContextMemento \
 	PPCGuard \
-	PPCInlineStrategy \
 	PPCMethod \
 	PPCMethodStrategy \
 	PPCNode \
@@ -129,7 +128,6 @@
     $(OUTDIR_SLASH)PPCContext.$(O) \
     $(OUTDIR_SLASH)PPCContextMemento.$(O) \
     $(OUTDIR_SLASH)PPCGuard.$(O) \
-    $(OUTDIR_SLASH)PPCInlineStrategy.$(O) \
     $(OUTDIR_SLASH)PPCMethod.$(O) \
     $(OUTDIR_SLASH)PPCMethodStrategy.$(O) \
     $(OUTDIR_SLASH)PPCNode.$(O) \
--- a/compiler/PPCAbstractActionNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCAbstractActionNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCAbstractActionNode
 	instanceVariableNames:'block'
 	classVariableNames:''
--- a/compiler/PPCAbstractCharacterNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCAbstractCharacterNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCAbstractCharacterNode
 	instanceVariableNames:'character'
 	classVariableNames:''
@@ -28,10 +30,6 @@
 
 !PPCAbstractCharacterNode methodsFor:'analysis'!
 
-firstCharParser
-	^ character asParser
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:e | e = character ]
 ! !
--- a/compiler/PPCAbstractLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCAbstractLiteralNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCAbstractLiteralNode
 	instanceVariableNames:'literal'
 	classVariableNames:''
@@ -13,10 +15,6 @@
 	^ literal size = 0
 !
 
-firstCharParser
-	^ literal first asParser
-!
-
 firstCharSet
 	| letter |
 	letter := literal first.
--- a/compiler/PPCAbstractPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCAbstractPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCAbstractPredicateNode
 	instanceVariableNames:'predicate'
 	classVariableNames:''
@@ -7,14 +9,6 @@
 	category:'PetitCompiler-Nodes'
 !
 
-!PPCAbstractPredicateNode class methodsFor:'instance creation'!
-
-new
-    "return an initialized instance"
-
-    ^ self basicNew initialize.
-! !
-
 !PPCAbstractPredicateNode methodsFor:'accessing'!
 
 predicate
@@ -37,10 +31,6 @@
 	^ false
 !
 
-firstCharParser
-	^ PPPredicateObjectParser on: predicate message: 'predicate expected'.
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: predicate
 ! !
@@ -83,14 +73,5 @@
 
 asInlined
 	^ super asInlined
-!
-
-optimize: params status: changeStatus
-	| retval |
-	retval := self.
-	retval := retval rewrite: params status: changeStatus.
-	retval := retval inline: params status: changeStatus.
-	
-	^ retval
 ! !
 
--- a/compiler/PPCActionNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCActionNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractActionNode subclass:#PPCActionNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCAndNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCAndNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCAndNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCAnyNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCAnyNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCAnyNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -26,11 +28,6 @@
  ^ compiler stopMethod.	
 !
 
-firstCharParser
-	^ #any asParser
-	
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:e | true ] 
 !
--- a/compiler/PPCBridge.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCBridge.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPParser subclass:#PPCBridge
 	instanceVariableNames:'selector'
 	classVariableNames:''
--- a/compiler/PPCCharSetPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCCharSetPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractPredicateNode subclass:#PPCCharSetPredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCCharacterNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCCharacterNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractCharacterNode subclass:#PPCCharacterNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCChoiceNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCChoiceNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCListNode subclass:#PPCChoiceNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -65,14 +67,3 @@
 	^ #ch
 ! !
 
-!PPCChoiceNode methodsFor:'optimizing'!
-
-optimize: params status: changeStatus
-	| retval |
-	retval := self.
-	retval := retval rewrite: params status: changeStatus.
-	retval := retval inline: params status: changeStatus.
-	
-	^ retval
-! !
-
--- a/compiler/PPCCompiledMethod.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCCompiledMethod.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCCompiledMethod
 	instanceVariableNames:'code id'
 	classVariableNames:''
--- a/compiler/PPCCompiler.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCCompiler.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCCompiler
 	instanceVariableNames:'compilerStack compiledParser cache inlining debug profile
 		currentMethod guards ids tokenMode rootNode'
@@ -19,10 +21,6 @@
 
 !PPCCompiler methodsFor:'accessing'!
 
-fastMode
-	^ tokenMode
-!
-
 inlining
 	^ inlining
 !
@@ -114,18 +112,6 @@
 	currentMethod addVariable: name.
 !
 
-allowInline
-	currentMethod allowInline
-!
-
-cache: id as: value
-	cache at: id put: value.
-!
-
-cachedValue: id
-	^ cache at: id ifAbsent: [ nil ]
-!
-
 call: anotherMethod
 	currentMethod add: anotherMethod call.
 !
@@ -166,14 +152,6 @@
 		^ 'context lwRestore: ', mementoName, '.'.
 	].
 	^ 'context restore: ', mementoName, '.'.
-!
-
-startTokenMode
-	tokenMode := true
-!
-
-stopTokenMode
-	tokenMode := false
 ! !
 
 !PPCCompiler methodsFor:'code generation - ids'!
@@ -214,6 +192,14 @@
 
 !PPCCompiler methodsFor:'code generation - support'!
 
+cache: id as: value
+	cache at: id put: value.
+!
+
+cachedValue: id
+	^ cache at: id ifAbsent: [ nil ]
+!
+
 checkCache: id
 	| method  |
 	"Check if method is hand written"
@@ -433,48 +419,6 @@
 
 !PPCCompiler methodsFor:'guard'!
 
-addSequenceGuard: parser
-
-	| firsts  guardSet guardSetId |
-	(self guards not or: [(guardSet := self guardCharSet: parser) isNil]) ifTrue: [ ^ self].
-
-	firsts := (parser firstSetSuchThat: [ :e | (e isKindOf: PPTokenParser) or: [ e isTerminal ] ]).
-	
-	"If we start with PPTokenParser, we should invoke the whitespace parser"
-	(firsts allSatisfy: [ :e | e isKindOf: PPTokenParser ]) ifTrue: [  
-		guardSetId := (self idFor: guardSet prefixed: #guard).
-		self addConstant: guardSet as: guardSetId.
-		self add: 'wsParser parseOn: context.'.
-		self add: 'context atEnd ifTrue: [ ^ self error ].'.
-		self add: '(', guardSetId, ' value: context peek) ifFalse: [ ^ self error ].'.
-	].
-
-	(firsts allSatisfy: [ :e | e isTerminal ]) ifTrue: [  
-		guardSetId := (self idFor: guardSet prefixed: #guard).
-		self addConstant: guardSet as: guardSetId.
-		self add: 'context atEnd ifTrue: [ ^ self error ].'.
-		self add: '(', guardSetId, ' value: context peek) ifFalse: [ ^ self error ].'.
-	].
-!
-
-guardCharSet: parser
-	| fs charSet   |
-	"No Guards fro trimming parser so far"
-	(parser firstSetSuchThat: [ :e | e isKindOf: PPCTrimNode ]) isEmpty ifFalse: [ ^ nil ].
-
-	"Makes no sense to do guard for epsilon parse"
-	(parser acceptsEpsilon) ifTrue: [ ^ nil ].
-
-	fs := parser firstSet.
-	fs do: [ :p |
-		"If we can accept epsilon guard does not make sense"
-		p isNullable ifTrue: [ ^ nil ].
-	].
-	
-	charSet := PPCharSetPredicate on: [:char | fs anySatisfy: [:e | (e firstCharParser parse: char asString) isPetitFailure not ]].
-	^ charSet
-!
-
 guards
 	^ guards
 !
--- a/compiler/PPCContext.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCContext.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPStream subclass:#PPCContext
 	instanceVariableNames:'root properties globals furthestFailure compiledParser rc ws'
 	classVariableNames:''
--- a/compiler/PPCContextMemento.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCContextMemento.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCContextMemento
 	instanceVariableNames:'position properties'
 	classVariableNames:''
@@ -43,7 +45,7 @@
 
 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: [ 
@@ -53,7 +55,7 @@
                         ^ aBlock value
                 ]
 
-    "Created: / 26-10-2014 / 01:23:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-04-2015 / 11:19:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 propertyAt: aKey ifAbsentPut: aBlock
--- a/compiler/PPCDelegateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCDelegateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCDelegateNode
 	instanceVariableNames:'child'
 	classVariableNames:''
@@ -45,16 +47,6 @@
 		changeStatus change.
 		self replace: child with: inlinedNode.
 	]
-!
-
-optimize: params status: changeStatus
-	| retval |
-	retval := self.
-	
-	retval := retval rewrite: params status: changeStatus.
-	retval := retval inline: params status: changeStatus.
-	
-	^ retval
 ! !
 
 !PPCDelegateNode methodsFor:'transformation'!
--- a/compiler/PPCForwardNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCForwardNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCForwardNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCGuard.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCGuard.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCGuard
 	instanceVariableNames:'node classification id message'
 	classVariableNames:''
--- a/compiler/PPCInlineAnyNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineAnyNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAnyNode subclass:#PPCInlineAnyNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineCharSetPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineCharSetPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCCharSetPredicateNode subclass:#PPCInlineCharSetPredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineCharacterNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineCharacterNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractCharacterNode subclass:#PPCInlineCharacterNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineLiteralNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCLiteralNode subclass:#PPCInlineLiteralNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -20,19 +22,6 @@
 	compiler add: ' ifFalse: [ self error: ''', encodedLiteral,  ' expected'' ].'.
 	compiler dedent.
  ^ compiler stopInline.
-!
-
-inlineWith: compiler id: id
-	| encodedLiteral |
-	
-	encodedLiteral := self encodeQuotes: literal.
-	compiler startInline: id.
-	compiler add: '((context peek: ', literal size asString, ') = #''', encodedLiteral, ''')'.
-	compiler indent.
-	compiler add: ' ifTrue: [ context skip: ', literal size asString, '. #''', encodedLiteral, ''']'.
-	compiler add: ' ifFalse: [ self error: ''', encodedLiteral,  ' expected'' ].'.
-	compiler dedent.
- ^ compiler stopInline.
 ! !
 
 !PPCInlineLiteralNode methodsFor:'printing'!
--- a/compiler/PPCInlineMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCMessagePredicateNode subclass:#PPCInlineMessagePredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineNilNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineNilNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNilNode subclass:#PPCInlineNilNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineNotCharSetPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineNotCharSetPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNotCharSetPredicateNode subclass:#PPCInlineNotCharSetPredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineNotLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineNotLiteralNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNotLiteralNode subclass:#PPCInlineNotLiteralNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,22 +9,6 @@
 	category:'PetitCompiler-Nodes'
 !
 
-!PPCInlineNotLiteralNode methodsFor:'accessing'!
-
-literal
-	
-	^ literal
-!
-
-literal: anObject
-	
-	literal := anObject
-!
-
-prefix
-	^ #notLit
-! !
-
 !PPCInlineNotLiteralNode methodsFor:'as yet unclassified'!
 
 compileWith: compiler effect: effect id: id
@@ -45,14 +31,6 @@
 	^ self
 !
 
-firstCharParser
-	^ literal first asParser not
-!
-
-firstCharSet
-	^ PPCharSetPredicate on: [:e | true ]
-!
-
 printOn: aStream
 	aStream nextPutAll: #inlined.
 	super printOn: aStream.
--- a/compiler/PPCInlineNotMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineNotMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNotMessagePredicateNode subclass:#PPCInlineNotMessagePredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlinePluggableNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlinePluggableNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCPluggableNode subclass:#PPCInlinePluggableNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineStrategy.st	Mon Nov 24 00:09:23 2014 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,42 +0,0 @@
-"{ Package: 'stx:goodies/petitparser/compiler' }"
-
-Object subclass:#PPCInlineStrategy
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'PetitCompiler-Nodes'
-!
-
-PPCInlineStrategy class instanceVariableNames:'Instance'
-
-"
- No other class instance variables are inherited by this class.
-"
-!
-
-!PPCInlineStrategy class methodsFor:'as yet unclassified'!
-
-instance
-	^ Instance ifNil: [ 
-		Instance := self basicNew initialize.
-	]
-!
-
-new
-	^ self instance
-! !
-
-!PPCInlineStrategy methodsFor:'as yet unclassified'!
-
-return: compiler
-	compiler add: ''.
-!
-
-start: compiler id: id
-	^ compiler startInline: id
-!
-
-stop: compiler
- ^ compiler stopInline
-! !
-
--- a/compiler/PPCInlineTokenStarMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineTokenStarMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCTokenStarMessagePredicateNode subclass:#PPCInlineTokenStarMessagePredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlineTokenStarSeparatorNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlineTokenStarSeparatorNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCTokenStarSeparatorNode subclass:#PPCInlineTokenStarSeparatorNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCInlinedMethod.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCInlinedMethod.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCMethod subclass:#PPCInlinedMethod
 	instanceVariableNames:'code'
 	classVariableNames:''
--- a/compiler/PPCListNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCListNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCListNode
 	instanceVariableNames:'children'
 	classVariableNames:''
@@ -59,15 +61,6 @@
 			^ self replace: child with: inlinedNode.
 		]
 	]
-!
-
-optimize: params status: changeStatus
-	| retval |
-	retval := self.
-	retval := retval rewrite: params status: changeStatus.
-	retval := retval inline: params status: changeStatus.
-	
-	^ retval
 ! !
 
 !PPCListNode class methodsFor:'documentation'!
--- a/compiler/PPCLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCLiteralNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractLiteralNode subclass:#PPCLiteralNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractPredicateNode subclass:#PPCMessagePredicateNode
 	instanceVariableNames:'message'
 	classVariableNames:''
--- a/compiler/PPCMethod.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCMethod.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCMethod
 	instanceVariableNames:'buffer variables indentation id profile canInline'
 	classVariableNames:''
@@ -8,7 +10,7 @@
 !
 
 
-!PPCMethod class methodsFor:'instance creation'!
+!PPCMethod class methodsFor:'as yet unclassified'!
 
 new
     "return an initialized instance"
--- a/compiler/PPCMethodStrategy.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCMethodStrategy.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCMethodStrategy
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCNegateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNegateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCNegateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCNilNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNilNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCNilNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -29,10 +31,6 @@
  ^ compiler stopMethod.
 !
 
-firstCharParser
-	^ PPFailingParser new
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:e | false ] 
 !
--- a/compiler/PPCNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCNode
 	instanceVariableNames:'contextFree name firstFollowCache firstCharSet properties'
 	classVariableNames:''
@@ -369,30 +371,27 @@
 !
 
 doOptimizationLoop: params status: changeStatus
-        | mapping optimized root |
-        mapping := IdentityDictionary new.
-        self allNodes do: [ :node |
-                optimized := (node optimize: params status: changeStatus).
-                (optimized ~= node) ifTrue: [  
-                        mapping at: node put: optimized.
-                ].
-        ].
-        
-        root := mapping at: self ifAbsent: [ self ].
-        [  | changed |
-                changed := false.
-                root allNodes do: [ :node |
-                        node children do: [ :child | 
-                                mapping at: child ifPresent: [:newChild | 
-                                        node replace: child with: newChild.
-                                        changed := true.
-                                        changeStatus change]
-                ]].
-                changed 
-        ] whileTrue.
-        ^ root
-
-    "Modified: / 26-10-2014 / 01:14:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	| mapping optimized root |
+	mapping := IdentityDictionary new.
+	self allNodes do: [ :node |
+		optimized := (node optimize: params status: changeStatus).
+		(optimized ~= node) ifTrue: [  
+			mapping at: node put: optimized.
+		].
+	].
+	
+	root := mapping at: self ifAbsent: [ self ].
+	[  | changed |
+		changed := false.
+		root allNodes do: [ :node |
+			node children do: [ :child | 
+				mapping at: child ifPresent: [:newChild | 
+					node replace: child with: newChild.
+					changed := true ]
+		]].
+		changed 
+	] whileTrue.
+	^ root
 !
 
 inline: changeStatus
@@ -477,10 +476,6 @@
 	aBlock value: self.
 	self children
 		do: [ :each | each allParsersDo: aBlock seen: aSet ]
-!
-
-firstSets: aFirstDictionary into: aSet
-	self children do: [ :child | aSet addAll: (aFirstDictionary at: child) ]
 ! !
 
 !PPCNode methodsFor:'transformation'!
--- a/compiler/PPCNotCharSetPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNotCharSetPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractPredicateNode subclass:#PPCNotCharSetPredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -30,10 +32,6 @@
 	compiler dedent.
 !
 
-firstCharParser
-	^ (PPPredicateObjectParser on: predicate message: 'predicate not expected') not.
-!
-
 firstCharSet
 	^ firstCharSet := PPCharSetPredicate on: [:e | (predicate value:e)  not ] 
 	
--- a/compiler/PPCNotLiteralNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNotLiteralNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractLiteralNode subclass:#PPCNotLiteralNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -16,10 +18,6 @@
 		yourself
 !
 
-firstCharParser
-	^ literal first asParser
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:e | true ]
 !
--- a/compiler/PPCNotMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNotMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractPredicateNode subclass:#PPCNotMessagePredicateNode
 	instanceVariableNames:'message'
 	classVariableNames:''
@@ -17,10 +19,6 @@
 		yourself
 !
 
-firstCharParser
-	^ (PPPredicateObjectParser on: predicate message: 'predicate not expected') not.
-!
-
 firstCharSet
 	PPCharSetPredicate on: [:e | (predicate value:e)  not ] 
 !
--- a/compiler/PPCNotNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCNotNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCNotNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCOptimizationResult.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCOptimizationResult.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCOptimizationResult
 	instanceVariableNames:'change'
 	classVariableNames:''
@@ -7,15 +9,13 @@
 	category:'PetitCompiler-Nodes'
 !
 
-!PPCOptimizationResult class methodsFor:'instance creation'!
+!PPCOptimizationResult class methodsFor:'as yet unclassified'!
 
 new
     "return an initialized instance"
 
     ^ self basicNew initialize.
-! !
-
-!PPCOptimizationResult class methodsFor:'as yet unclassified'!
+!
 
 nothing
 	^ PPCOptimizationResult new
--- a/compiler/PPCOptionalNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCOptionalNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCOptionalNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCPluggableNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCPluggableNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCPluggableNode
 	instanceVariableNames:'block'
 	classVariableNames:''
@@ -55,10 +57,6 @@
  ^ compiler stopMethod.
 !
 
-firstCharParser
-	^  block asParser
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:char | (block asParser parse: char asString) isPetitFailure not ]
 !
--- a/compiler/PPCPlusNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCPlusNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCPlusNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,6 +9,7 @@
 	category:'PetitCompiler-Nodes'
 !
 
+
 !PPCPlusNode methodsFor:'as yet unclassified'!
 
 compileWith: compiler effect: effect id: id
@@ -47,3 +50,10 @@
 	^ #plus
 ! !
 
+!PPCPlusNode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractPredicateNode subclass:#PPCPredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCProfilingContext.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCProfilingContext.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCContext subclass:#PPCProfilingContext
 	instanceVariableNames:'invocations remembers restores lwRemembers lwRestores totalSize'
 	classVariableNames:''
--- a/compiler/PPCSentinelNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCSentinelNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNilNode subclass:#PPCSentinelNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,6 +9,13 @@
 	category:'PetitCompiler-Nodes'
 !
 
+PPCSentinelNode class instanceVariableNames:'Instance'
+
+"
+ No other class instance variables are inherited by this class.
+"
+!
+
 !PPCSentinelNode class methodsFor:'as yet unclassified'!
 
 instance
--- a/compiler/PPCSequenceNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCSequenceNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCListNode subclass:#PPCSequenceNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCStarAnyNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCStarAnyNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCStarNode subclass:#PPCStarAnyNode
 	instanceVariableNames:''
 	classVariableNames:''
@@ -9,14 +11,6 @@
 
 !PPCStarAnyNode methodsFor:'as yet unclassified'!
 
-acceptsEpsilon
-	^ true
-!
-
-acceptsEpsilonOpenSet: set
-	^ true
-!
-
 compileWith: compiler effect: effect id: id
 	compiler startMethod: id.
 	compiler addVariable: 'retval size'.
--- a/compiler/PPCStarCharSetPredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCStarCharSetPredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCStarNode subclass:#PPCStarCharSetPredicateNode
 	instanceVariableNames:'predicate'
 	classVariableNames:''
@@ -9,10 +11,6 @@
 
 !PPCStarCharSetPredicateNode methodsFor:'accessing'!
 
-acceptsEpsilon
-	^ true
-!
-
 compileWith: compiler effect: effect id: id
 	| classification classificationId |
 	
@@ -36,10 +34,6 @@
 	^ (classification asOrderedCollection addLast: false; yourself) asArray
 !
 
-firstCharParser
-	^ PPPredicateObjectParser on: predicate message: 'predicate expected'.
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: predicate 	
 !
--- a/compiler/PPCStarMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCStarMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCStarNode subclass:#PPCStarMessagePredicateNode
 	instanceVariableNames:'message'
 	classVariableNames:''
@@ -9,10 +11,6 @@
 
 !PPCStarMessagePredicateNode methodsFor:'accessing'!
 
-acceptsEpsilon
-	^ true
-!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:char | char perform: message ] 	
 !
@@ -48,23 +46,6 @@
 	compiler add: '].'.
 	compiler add: '^ retval asArray'.
  ^ compiler stopMethod.
-!
-
-compileWith_old: compiler effect: effect id: id
-	compiler startMethod: id.
-	compiler addVariable: 'retval'.
-	compiler add: 'retval := OrderedCollection new.'.	
-	compiler add: '[ context atEnd ] whileFalse: ['.
-	compiler indent.
-	compiler add: '(context uncheckedPeek ', message,')'.
-	compiler indent.
-	compiler add: ' ifFalse: [ ^ retval asArray ].'.
-	compiler dedent.
-	compiler add: ' retval add: context next'.
-	compiler dedent.
-	compiler add: '].'.
-	compiler add: '^ retval asArray'.
- ^ compiler stopMethod.
 ! !
 
 !PPCStarMessagePredicateNode methodsFor:'comparing'!
--- a/compiler/PPCStarNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCStarNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCStarNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCSymbolActionNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCSymbolActionNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCAbstractActionNode subclass:#PPCSymbolActionNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCTokenActionNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTokenActionNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCActionNode subclass:#PPCTokenActionNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCTokenNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTokenNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCTokenNode
 	instanceVariableNames:'tokenClass'
 	classVariableNames:''
@@ -7,14 +9,6 @@
 	category:'PetitCompiler-Nodes'
 !
 
-!PPCTokenNode class methodsFor:'instance creation'!
-
-new
-    "return an initialized instance"
-
-    ^ self basicNew initialize.
-! !
-
 !PPCTokenNode methodsFor:'accessing'!
 
 initialize
--- a/compiler/PPCTokenSequenceNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTokenSequenceNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCSequenceNode subclass:#PPCTokenSequenceNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCTokenStarMessagePredicateNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTokenStarMessagePredicateNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCStarMessagePredicateNode subclass:#PPCTokenStarMessagePredicateNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCTokenStarSeparatorNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTokenStarSeparatorNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCTokenStarMessagePredicateNode subclass:#PPCTokenStarSeparatorNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCTrimNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTrimNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCDelegateNode subclass:#PPCTrimNode
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/PPCTrimmingTokenNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCTrimmingTokenNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCListNode subclass:#PPCTrimmingTokenNode
 	instanceVariableNames:'tokenClass'
 	classVariableNames:''
@@ -7,14 +9,6 @@
 	category:'PetitCompiler-Nodes'
 !
 
-!PPCTrimmingTokenNode class methodsFor:'instance creation'!
-
-new
-    "return an initialized instance"
-
-    ^ self basicNew initialize.
-! !
-
 !PPCTrimmingTokenNode methodsFor:'accessing'!
 
 child
--- a/compiler/PPCUnknownNode.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCUnknownNode.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCNode subclass:#PPCUnknownNode
 	instanceVariableNames:'parser'
 	classVariableNames:''
@@ -28,10 +30,6 @@
 	^ parser children
 !
 
-firstCharParser
-	^ parser firstCharParser
-!
-
 isContextFreePrim
 	^ parser isContextFreePrim
 !
--- a/compiler/PPCompiledParser.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCompiledParser.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPParser subclass:#PPCompiledParser
 	instanceVariableNames:'startSymbol context failure error'
 	classVariableNames:''
--- a/compiler/abbrev.stc	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/abbrev.stc	Wed Apr 15 11:28:09 2015 +0100
@@ -7,7 +7,6 @@
 PPCContext PPCContext stx:goodies/petitparser/compiler 'PetitCompiler-Context' 0
 PPCContextMemento PPCContextMemento stx:goodies/petitparser/compiler 'PetitCompiler-Context' 0
 PPCGuard PPCGuard stx:goodies/petitparser/compiler 'PetitCompiler-Core' 0
-PPCInlineStrategy PPCInlineStrategy stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 1
 PPCMethod PPCMethod stx:goodies/petitparser/compiler 'PetitCompiler-Core' 0
 PPCMethodStrategy PPCMethodStrategy stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 1
 PPCNode PPCNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 0
@@ -45,7 +44,7 @@
 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
+PPCSentinelNode PPCSentinelNode stx:goodies/petitparser/compiler 'PetitCompiler-Nodes' 1
 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
--- a/compiler/bc.mak	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/bc.mak	Wed Apr 15 11:28:09 2015 +0100
@@ -78,7 +78,6 @@
 $(OUTDIR)PPCContext.$(O) PPCContext.$(H): PPCContext.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPStream.$(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)PPCContextMemento.$(O) PPCContextMemento.$(H): PPCContextMemento.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCGuard.$(O) PPCGuard.$(H): PPCGuard.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)PPCInlineStrategy.$(O) PPCInlineStrategy.$(H): PPCInlineStrategy.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMethod.$(O) PPCMethod.$(H): PPCMethod.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCMethodStrategy.$(O) PPCMethodStrategy.$(H): PPCMethodStrategy.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PPCNode.$(O) PPCNode.$(H): PPCNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/compiler/benchmarks/Make.proto	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/benchmarks/Make.proto	Wed Apr 15 11:28:09 2015 +0100
@@ -106,7 +106,7 @@
 
 
 # build all packages containing referenced classes for this package
-# they are nor needed to compile the package
+# they are not needed to compile the package (but later, to load it)
 references:
 
 
--- a/compiler/benchmarks/PPCBenchmark.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/benchmarks/PPCBenchmark.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCBenchmark
 	instanceVariableNames:'sources report contextClass compile parser context input'
 	classVariableNames:''
--- a/compiler/benchmarks/PPCBenchmarkResources.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/benchmarks/PPCBenchmarkResources.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCBenchmarkResources
 	instanceVariableNames:''
 	classVariableNames:'javaCache'
--- a/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
 
+"{ NameSpace: Smalltalk }"
+
 LibraryDefinition subclass:#stx_goodies_petitparser_compiler_benchmarks
 	instanceVariableNames:''
 	classVariableNames:''
@@ -61,13 +63,16 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
         #'stx:goodies/petitparser'    "PPContext - referenced by PPCBenchmark>>benchmarkSmalltalkGrammar"
-        #'stx:goodies/petitparser/compiler'    "PPCContext - referenced by PPCBenchmark>>benchmarkSmalltalkGrammarCompiled"
+        #'stx:goodies/petitparser/compiler'    "PPCContext - referenced by PPCBenchmark>>benchmarkJavaSyntax"
         #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCBenchmark>>benchmarkSmalltalkGrammar"
         #'stx:goodies/refactoryBrowser/parser'    "RBParser - referenced by PPCBenchmark>>benchmarkRBParserC"
     )
--- a/compiler/extensions.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/extensions.st	Wed Apr 15 11:28:09 2015 +0100
@@ -112,12 +112,6 @@
 
 !PPContext methodsFor:'*petitcompiler'!
 
-lastTokenResult
-	^ scanner lastResult
-! !
-
-!PPContext methodsFor:'*petitcompiler'!
-
 lwRemember
 	^ self position
 ! !
@@ -130,24 +124,6 @@
 
 !PPContext methodsFor:'*petitcompiler'!
 
-matchToken: id
-	^ scanner matchToken: id
-! !
-
-!PPContext methodsFor:'*petitcompiler'!
-
-nextToken
-	scanner next
-! !
-
-!PPContext methodsFor:'*petitcompiler'!
-
-nextToken: id
-	^ scanner next: id
-! !
-
-!PPContext methodsFor:'*petitcompiler'!
-
 peek: anInteger
 	^ stream peek: anInteger
 ! !
@@ -237,12 +213,6 @@
 	^ aPetitCompiler compileCharacter: literal.
 ! !
 
-!PPLiteralObjectParser methodsFor:'*petitcompiler'!
-
-firstCharParser
-	^ self
-! !
-
 !PPLiteralParser methodsFor:'*petitcompiler'!
 
 id
@@ -264,12 +234,6 @@
 	^ aPetitCompiler compileLiteral: literal.
 ! !
 
-!PPLiteralSequenceParser methodsFor:'*petitcompiler'!
-
-firstCharParser
-	^ literal first asParser
-! !
-
 !PPNotParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
@@ -285,12 +249,6 @@
 	^ aPetitCompiler compileNot: self
 ! !
 
-!PPNotParser methodsFor:'*petitcompiler'!
-
-firstCharParser
-	^ parser firstCharParser not
-! !
-
 !PPOptionalParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
@@ -331,14 +289,6 @@
 
 !PPParser methodsFor:'*petitcompiler'!
 
-cached
-	"Faster way of memoizing --- it ignores context information, therefore it is not suitable for context-sensitive rules"
-	
-	^ PPCachingParser on: self
-! !
-
-!PPParser methodsFor:'*petitcompiler'!
-
 compile
 	^ self compile: #PPGeneratedParser
 ! !
@@ -380,21 +330,6 @@
 
 !PPParser methodsFor:'*petitcompiler'!
 
-first
-	first ifNil: [  
-		first := self firstSet
-	].
-	^ first
-! !
-
-!PPParser methodsFor:'*petitcompiler'!
-
-first: firstSet
-	first := firstSet
-! !
-
-!PPParser methodsFor:'*petitcompiler'!
-
 firstSetSuchThat: block
 	^ self firstSetSuchThat: block into: (OrderedCollection new) openSet: IdentitySet new.
 ! !
@@ -520,15 +455,6 @@
 	^ super compileWith: aPetitCompiler.
 ! !
 
-!PPPossessiveRepeatingParser methodsFor:'*petitcompiler'!
-
-optimized
-	^ (PPFastPossessiveRepeatingParser on: parser)
-		setMin: min;
-		setMax: max;
-		yourself
-! !
-
 !PPPredicateObjectParser methodsFor:'*petitcompiler'!
 
 asCompilerNode
@@ -549,12 +475,6 @@
 
 !PPPredicateObjectParser methodsFor:'*petitcompiler'!
 
-firstCharParser
-	^ self
-! !
-
-!PPPredicateObjectParser methodsFor:'*petitcompiler'!
-
 firstCharSet
 	^ predicate
 ! !
@@ -577,17 +497,6 @@
 
 !PPSequenceParser methodsFor:'*petitcompiler'!
 
-checkFirst: context
-	first isEmpty ifTrue: [ ^ true ].
-
-	first do: [ :elem | 
-		(context matchToken: elem id) ifTrue: [ ^ true ].
-	].
-	^ false
-! !
-
-!PPSequenceParser methodsFor:'*petitcompiler'!
-
 compileWith: aPetitCompiler
 	^ aPetitCompiler compileSequence: self.
 ! !
@@ -607,12 +516,6 @@
 	^ aCollection
 ! !
 
-!PPSequenceParser methodsFor:'*petitcompiler'!
-
-optimized
-	^ PPFastSequenceParser withAll: parsers
-! !
-
 !PPSmalltalkGrammar methodsFor:'*petitcompiler'!
 
 comment
@@ -635,21 +538,6 @@
 	^ #space asParser plus
 ! !
 
-!PPSmalltalkGrammar methodsFor:'*petitcompiler'!
-
-whitespaceOld
-	^ #space asParser plus
-! !
-
-!PPSmalltalkGrammar methodsFor:'*petitcompiler'!
-
-whitespaceX
-	whitespace ifNil: [
-		whitespace := PPSmalltalkWhitespaceParser new
-	].
-	^ whitespace
-! !
-
 !PPSmalltalkTokenParser methodsFor:'*petitcompiler'!
 
 compileWith: aPetitCompiler
@@ -710,12 +598,6 @@
 
 !PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
 
-firstCharParser
-	^ PPFailingParser new
-! !
-
-!PPSmalltalkWhitespaceParser methodsFor:'*petitcompiler'!
-
 firstCharSet
 	^ PPCharSetPredicate on: [:e | false ] 
 ! !
@@ -771,15 +653,6 @@
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
-id
-	id ifNil: [ 
-		id := ('TOK[', parser id, ']') asSymbol
-	].
-	^ id
-! !
-
-!PPTokenParser methodsFor:'*petitcompiler'!
-
 isFirstSetTerminal
 	^ false
 ! !
@@ -792,30 +665,12 @@
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
-isUnique
-	unique ifNil: [  
-		unique := parser firstSet size = 1 and: [ (parser firstSet anyOne isKindOf: PPLiteralParser) ]
-	].
-	^ unique
-! !
-
-!PPTokenParser methodsFor:'*petitcompiler'!
-
 optimize
 	^ self transform: [ :each | each optimized ]
 ! !
 
 !PPTokenParser methodsFor:'*petitcompiler'!
 
-parseOnX: aPPContext
-	(aPPContext matchToken: self id) ifTrue: [ 
-		^ aPPContext nextToken: self id.
-	].
-	^ PPFailure message: self id, ' not found' context: aPPContext.
-! !
-
-!PPTokenParser methodsFor:'*petitcompiler'!
-
 parser
 	^ parser
 ! !
--- a/compiler/libInit.cc	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/libInit.cc	Wed Apr 15 11:28:09 2015 +0100
@@ -33,7 +33,6 @@
 _PPCContext_Init(pass,__pRT__,snd);
 _PPCContextMemento_Init(pass,__pRT__,snd);
 _PPCGuard_Init(pass,__pRT__,snd);
-_PPCInlineStrategy_Init(pass,__pRT__,snd);
 _PPCMethod_Init(pass,__pRT__,snd);
 _PPCMethodStrategy_Init(pass,__pRT__,snd);
 _PPCNode_Init(pass,__pRT__,snd);
--- a/compiler/stx_goodies_petitparser_compiler.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/stx_goodies_petitparser_compiler.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 LibraryDefinition subclass:#stx_goodies_petitparser_compiler
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,12 +9,6 @@
 	category:'* Projects & Packages *'
 !
 
-!stx_goodies_petitparser_compiler class methodsFor:'documentation'!
-
-extensionsVersion_HG
-
-    ^ '$Changeset: <not expanded> $'
-! !
 
 !stx_goodies_petitparser_compiler class methodsFor:'accessing - monticello'!
 
@@ -70,7 +66,10 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
@@ -105,7 +104,6 @@
         PPCContext
         PPCContextMemento
         PPCGuard
-        PPCInlineStrategy
         PPCMethod
         PPCMethodStrategy
         PPCNode
@@ -189,12 +187,8 @@
         PPContext comment:
         PPContext compiledParser
         PPContext compiledParser:
-        PPContext lastTokenResult
         PPContext lwRemember
         PPContext lwRestore:
-        PPContext matchToken:
-        PPContext nextToken
-        PPContext nextToken:
         PPContext peek:
         PPContext whitespace
         PPContext whitespace:
@@ -207,28 +201,22 @@
         PPFailure position:
         PPLiteralObjectParser asCompilerNode
         PPLiteralObjectParser compileWith:
-        PPLiteralObjectParser firstCharParser
         PPLiteralParser id
         PPLiteralSequenceParser asCompilerNode
         PPLiteralSequenceParser compileWith:
-        PPLiteralSequenceParser firstCharParser
         PPNotParser asCompilerNode
         PPNotParser compileWith:
-        PPNotParser firstCharParser
         PPOptionalParser asCompilerNode
         PPOptionalParser compileWith:
         PPParser asCompilerNode
         PPParser asCompilerTree
         PPParser bridge
-        PPParser cached
         PPParser compile
         PPParser compile:
         PPParser compile:andParse:
         PPParser compile:parameters:
         PPParser compileWith:
         PPParser compileWithParameters:
-        PPParser first
-        PPParser first:
         PPParser firstSetSuchThat:
         PPParser firstSetSuchThat:into:openSet:
         PPParser id
@@ -244,27 +232,24 @@
         PPPluggableParser asCompilerNode
         PPPossessiveRepeatingParser asCompilerNode
         PPPossessiveRepeatingParser compileWith:
-        PPPossessiveRepeatingParser optimized
         PPPredicateObjectParser asCompilerNode
         PPPredicateObjectParser compileWith:
-        PPPredicateObjectParser firstCharParser
+        PPPredicateObjectParser firstCharSet
+        PPPredicateObjectParser firstCharSetCached
         PPSequenceParser asCompilerNode
-        PPSequenceParser checkFirst:
         PPSequenceParser compileWith:
         PPSequenceParser firstSetSuchThat:into:openSet:
-        PPSequenceParser optimized
         PPSmalltalkGrammar comment
         PPSmalltalkGrammar updateContext:
         PPSmalltalkGrammar whitespace
-        PPSmalltalkGrammar whitespaceOld
-        PPSmalltalkGrammar whitespaceX
         PPSmalltalkTokenParser compileWith:
         PPSmalltalkTokenParser parseOnX:
         PPSmalltalkTokenParser updateContext:
         PPSmalltalkTokenParser whitespace
+        PPSmalltalkWhitespaceParser #'='
         PPSmalltalkWhitespaceParser acceptsEpsilon
         PPSmalltalkWhitespaceParser acceptsEpsilonOpenSet:
-        PPSmalltalkWhitespaceParser firstCharParser
+        PPSmalltalkWhitespaceParser firstCharSet
         PPStream peek:
         PPToken #'='
         PPToken hash
@@ -272,12 +257,9 @@
         PPTokenParser asCompilerNode
         PPTokenParser displayName
         PPTokenParser firstSets:into:
-        PPTokenParser id
         PPTokenParser isFirstSetTerminal
         PPTokenParser isTokenParser
-        PPTokenParser isUnique
         PPTokenParser optimize
-        PPTokenParser parseOnX:
         PPTokenParser parser
         PPTokenParser startsWith:
         PPTokenParser whitespace
@@ -288,11 +270,7 @@
         UndefinedObject isAlphaNumeric
         UndefinedObject isDigit
         UndefinedObject isLetter
-        PPPredicateObjectParser firstCharSet
-        PPPredicateObjectParser firstCharSetCached
-        PPSmalltalkWhitespaceParser firstCharSet
         UndefinedObject isSeparator
-        PPSmalltalkWhitespaceParser #'='
     )
 ! !
 
--- a/compiler/tests/Make.proto	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/Make.proto	Wed Apr 15 11:28:09 2015 +0100
@@ -113,7 +113,7 @@
 
 
 # build all packages containing referenced classes for this package
-# they are nor needed to compile the package
+# they are not needed to compile the package (but later, to load it)
 references:
 
 
--- a/compiler/tests/PPCCompilerTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCCompilerTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPAbstractParserTest subclass:#PPCCompilerTest
 	instanceVariableNames:'parser result context'
 	classVariableNames:''
@@ -611,48 +613,6 @@
 	self assert: parser parse: 'zorg' end: 0.	
 !
 
-testGuard1
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: $a asParser.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char = $a ])).
-!
-
-testGuard2
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: #letter asParser.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char isLetter ])).
-!
-
-testGuard3
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: #letter asParser not.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char isLetter not ])).
-!
-
-testGuard4
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: (#letter asParser, #word asParser star).
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char isLetter ])).
-!
-
-testGuard5
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: 'foo' asParser.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char = $f ])).
-!
-
-testGuard6
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: ('foo' asParser trimmingToken asCompilerTree optimizeTree).
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | (char = $f) ]))
-!
-
-testGuard7
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: ('foo' asParser trimmingToken / 'bar' asParser trimmingToken) asCompilerTree optimizeTree.
-	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'.
@@ -678,46 +638,6 @@
 	self assert: parser parse: ' ab'.
 ! !
 
-!PPCCompilerTest methodsFor:'tests - verification'!
-
-testClass
-        | compiledParser normalParser source |
-        normalParser := PPSmalltalkGrammar new.
-        compiledParser := normalParser compile.
-        
-        Class methodsDo: [ :m |
-                source := m sourceCode.
-                self assert: (normalParser parse: source) 
-                          equals: (compiledParser parse: source withContext: self context). 
-        ].
-
-    "Modified: / 05-11-2014 / 23:18:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testObject
-        | compiledParser normalParser source |
-        normalParser := PPSmalltalkGrammar new.
-        compiledParser := normalParser compile.
-        
-        Object methodsDo: [ :m |
-                source := m sourceCode.
-                self assert: (normalParser parse: source) 
-                          equals: (compiledParser parse: source withContext: self context). 
-        ].
-
-    "Modified: / 30-10-2014 / 23:22:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testWhitespace
-	| compiledParser normalParser source |
-	normalParser := PPSmalltalkGrammar new.
-	compiledParser := normalParser compile.
-	
-	source := '  foo ^ 1'.
-	self assert: (normalParser parse: source) 
-		  equals: (compiledParser parse: source withContext: self context).
-! !
-
 !PPCCompilerTest class methodsFor:'documentation'!
 
 version_HG
--- a/compiler/tests/PPCContextMementoTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCContextMementoTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPContextMementoTest subclass:#PPCContextMementoTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/tests/PPCContextTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCContextTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPContextTest subclass:#PPCContextTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/tests/PPCGuardTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCGuardTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 TestCase subclass:#PPCGuardTest
 	instanceVariableNames:'guard compiler'
 	classVariableNames:''
--- a/compiler/tests/PPCMockCompiler.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCMockCompiler.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCMockCompiler
 	instanceVariableNames:'lines'
 	classVariableNames:''
--- a/compiler/tests/PPCNodeCompilingTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCNodeCompilingTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPAbstractParserTest subclass:#PPCNodeCompilingTest
 	instanceVariableNames:'parser context tree result'
 	classVariableNames:''
--- a/compiler/tests/PPCNodeFirstFollowNextTests.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCNodeFirstFollowNextTests.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 TestCase subclass:#PPCNodeFirstFollowNextTests
 	instanceVariableNames:'tree first node followSet'
 	classVariableNames:''
--- a/compiler/tests/PPCNodeTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCNodeTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 TestCase subclass:#PPCNodeTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/tests/PPCOptimizingTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCOptimizingTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 TestCase subclass:#PPCOptimizingTest
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/tests/PPCompiledSmalltalkGrammarResource.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCompiledSmalltalkGrammarResource.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 TestResource subclass:#PPCompiledSmalltalkGrammarResource
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/tests/PPCompiledSmalltalkGrammarTests.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCompiledSmalltalkGrammarTests.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPCompositeParserTest subclass:#PPCompiledSmalltalkGrammarTests
 	instanceVariableNames:''
 	classVariableNames:''
--- a/compiler/tests/stx_goodies_petitparser_compiler_tests.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/stx_goodies_petitparser_compiler_tests.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 LibraryDefinition subclass:#stx_goodies_petitparser_compiler_tests
 	instanceVariableNames:''
 	classVariableNames:''
@@ -64,14 +66,17 @@
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:goodies/petitparser'    "PPCharSetPredicate - referenced by PPCCompilerTest>>testGuard1"
+        #'stx:goodies/petitparser'    "PPCharSetPredicate - referenced by PPCNodeCompilingTest>>testCompileCharSetPredicate"
         #'stx:goodies/petitparser/compiler'    "PPCAbstractLiteralNode - referenced by PPCNodeFirstFollowNextTests>>testFirst1"
-        #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCCompilerTest>>testClass"
+        #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - referenced by PPCompiledSmalltalkGrammarResource>>setUp"
     )
 !