PPCConfiguration refactoring: [10/10]: Cleaned up compilation API
authorJan Vrany <jan.vrany@fit.cvut.cz>
Mon, 07 Sep 2015 11:53:38 +0100
changeset 538 16e8536f5cfb
parent 537 fb212e14d1f4
child 540 694ad2f97c65
PPCConfiguration refactoring: [10/10]: Cleaned up compilation API The main compilation method is now PPParser>>compileWithOptions: Removed oither old and unused compilation methods from PPParser and other PetitCompiler classes.
compiler/PPCCheckingVisitor.st
compiler/PPCCodeGen.st
compiler/PPCCodeGenerator.st
compiler/PPCCompilationContext.st
compiler/PPCCompilationOptions.st
compiler/PPCCompiler.st
compiler/PPCInlinedMethod.st
compiler/PPCStarMessagePredicateNode.st
compiler/benchmarks/Make.proto
compiler/benchmarks/PPCBenchmark.st
compiler/benchmarks/PPCSmalltalkNoopParser.st
compiler/benchmarks/abbrev.stc
compiler/benchmarks/bc.mak
compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st
compiler/extensions.st
compiler/stx_goodies_petitparser_compiler.st
compiler/tests/PPCCodeGeneratorTest.st
compiler/tests/PPCDistinctScannerTest.st
compiler/tests/PPCNodeFirstFollowNextTests.st
compiler/tests/PPCNodeTest.st
compiler/tests/PPCOptimizeChoicesTest.st
compiler/tests/PPCOverlappingTokensTest.st
compiler/tests/PPCTokenizingCodeGeneratorTest.st
compiler/tests/PPCTokenizingTest.st
compiler/tests/PPCUnivarsalGuardTest.st
compiler/tests/PPCUniversalOptimizationTest.st
compiler/tests/PPCUniversalTest.st
compiler/tests/extras/PPCAbstractParserTest.st
compiler/tests/extras/PPCCompositeParserTest.st
compiler/tests/extras/PPCExpressionGrammarTest.st
compiler/tests/extras/PPCExpressionGrammarTest_Tokenized.st
compiler/tests/extras/PPCExpressionGrammarTest_Universal.st
compiler/tests/extras/PPCLL1ExpressionGrammarTest.st
compiler/tests/extras/PPCLL1ExpressionGrammarTest_Tokenized.st
compiler/tests/extras/PPCLL1ExpressionGrammarTest_Universal.st
compiler/tests/extras/PPCLRPCompiledParserSmokeTest.st
compiler/tests/extras/PPCLRPCompiledParserSmokeTest_Universal.st
compiler/tests/extras/PPCSmalltalkGrammarTests.st
compiler/tests/extras/PPCSmalltalkGrammarTests_Tokenized.st
compiler/tests/extras/PPCSmalltalkGrammarTests_Universal.st
compiler/tests/extras/PPCSmalltalkGrammarVerificationTest_Tokenized.st
compiler/tests/extras/PPCSmalltalkGrammarVerificationTest_Universal.st
compiler/tests/extras/PPCSmalltalkParserTests.st
compiler/tests/extras/PPCSmalltalkParserTests_Tokenized.st
compiler/tests/extras/PPCSmalltalkParserTests_Universal.st
compiler/tests/extras/PPCSmalltalkParserVerificationTest_Tokenized.st
compiler/tests/extras/PPCSmalltalkParserVerificationTest_Universal.st
compiler/tests/extras/PPCSmalltalkTests.st
compiler/tests/extras/PPCompiledJavaResource.st
compiler/tests/extras/PPExpressionGrammarVerificationTest_Tokenized.st
compiler/tests/extras/PPExpressionGrammarVerificationTest_Universal.st
compiler/tests/extras/PPLL1ExpressionGrammarTest.st
compiler/tests/extras/abbrev.stc
--- a/compiler/PPCCheckingVisitor.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCCheckingVisitor.st	Mon Sep 07 11:53:38 2015 +0100
@@ -11,14 +11,13 @@
 
 !PPCCheckingVisitor methodsFor:'visiting'!
 
-visitNode: node
+beforeAccept: node
     | message |
 
-    super visitNode: node.
     message := node check.
-    message notNil ifTrue:[ self error: message ].
+    message notNil ifTrue:[ self error: message ].       
     ^node
 
-    "Created: / 04-09-2015 / 10:23:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 07-09-2015 / 13:05:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/PPCCodeGen.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCCodeGen.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,9 +14,9 @@
 new
     "return an initialized instance"
 
-    ^ self on: PPCCompilationOptions default
+    ^ self on: PPCCompilationOptions new
 
-    "Modified: / 24-08-2015 / 23:39:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 on: aPPCArguments
--- a/compiler/PPCCodeGenerator.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCCodeGenerator.st	Mon Sep 07 11:53:38 2015 +0100
@@ -356,8 +356,8 @@
 
                     parent := variableNode parent.
                     "Check for <barg> at: <number>"
-                    ((parent selector == #at:) and:[ parent options first isLiteralNumber ]) ifTrue:[ 
-                        blockMatches at: parent put: (childValueVars at: parent options first value).
+                    ((parent selector == #at:) and:[ parent arguments first isLiteralNumber ]) ifTrue:[ 
+                        blockMatches at: parent put: (childValueVars at: parent arguments first value).
                     ] ifFalse:[ 
                         "Check for <barg> first / second / ..."
                         | i |
@@ -417,7 +417,7 @@
         codeGen code: blockBody.    
     ]
 
-    "Modified: / 27-07-2015 / 15:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 13:00:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitAndNode: node
--- a/compiler/PPCCompilationContext.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCCompilationContext.st	Mon Sep 07 11:53:38 2015 +0100
@@ -29,8 +29,19 @@
     ^ options
 !
 
-options:aPPCCompilationOptions
-    options := aPPCCompilationOptions.
+options:optionsOrOptionArray
+    "Set options used for compilation. 
+     `optionsOrOptionArray` may be either an instance of
+     PPCCompilationOptions or and array specifing options.
+     See PPCCompilationOptions class>>from: for details."
+
+    optionsOrOptionArray isSequenceable ifTrue:[ 
+        options := PPCCompilationOptions from: optionsOrOptionArray
+    ] ifFalse:[
+        options := optionsOrOptionArray.
+    ]
+
+    "Modified: / 07-09-2015 / 10:42:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parserClass
@@ -64,8 +75,8 @@
 initialize
     "Invoked when a new instance is created."
 
-    options := PPCCompilationOptions default.
+    options := PPCCompilationOptions new.
 
-    "Modified: / 26-08-2015 / 19:49:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/PPCCompilationOptions.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCCompilationOptions.st	Mon Sep 07 11:53:38 2015 +0100
@@ -9,16 +9,27 @@
 	category:'PetitCompiler-Core'
 !
 
-!PPCCompilationOptions class methodsFor:'as yet unclassified'!
+!PPCCompilationOptions class methodsFor:'instance creation'!
+
+from: aCollection
+    "Initialized options from an array containing option: value pairs.
+     Example:
 
-default
-    ^ self new
+         PPCCompilationOptions from: { #tokenize: true }
+    "
+    ^ self new initializeFrom: aCollection
+
+    "
+        PPCCompilationOptions from: #( tokenize: true )
+    "
+
+    "Created: / 07-09-2015 / 10:25:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 new
-    ^ self basicNew 
-        initialize;
-        yourself
+    "return an initialized instance"
+
+    ^ self basicNew initialize.
 ! !
 
 !PPCCompilationOptions methodsFor:'initialization'!
@@ -26,6 +37,26 @@
 initialize
     super initialize.
     options := IdentityDictionary new
+!
+
+initializeFrom: aSequenceableCollection
+    aSequenceableCollection size even ifFalse:[ 
+        self error: 'Invalid options'
+    ].
+    1 to: aSequenceableCollection size by: 2 do:[:i |  
+        | option value |
+
+        option := aSequenceableCollection at: i.
+        value  := aSequenceableCollection at: i + 1.
+
+        [ 
+            self perform: option asSymbol with: value
+        ] on: MessageNotUnderstood do:[:ex |    
+            self error: 'Invalid option: ', option storeString.
+        ]
+    ].
+
+    "Created: / 07-09-2015 / 10:36:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCCompilationOptions methodsFor:'options'!
--- a/compiler/PPCCompiler.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCCompiler.st	Mon Sep 07 11:53:38 2015 +0100
@@ -12,38 +12,16 @@
 
 !PPCCompiler class methodsFor:'as yet unclassified'!
 
-default
-    ^ self universal
-!
+new
+    ^ self basicNew initialize
 
-new
-    ^ self basicNew
-        initialize;
-        yourself
+    "Modified: / 07-09-2015 / 11:06:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-tokenizing
-    | options |
-
-    options := PPCCompilationOptions default.
-    options tokenize:true.
-    ^ (PPCCompiler new)
-        options:options;
-        yourself
+newWithOptions: options
+    ^ self new options: options
 
-    "Modified: / 04-09-2015 / 16:21:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-universal
-    | options |
-
-    options := PPCCompilationOptions default.
-    options tokenize:false.
-    ^ (PPCCompiler new)
-        options:options;
-        yourself
-
-    "Modified: / 04-09-2015 / 16:21:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 07-09-2015 / 11:06:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCCompiler methodsFor:'accessing'!
@@ -58,8 +36,8 @@
     "Modified: / 26-08-2015 / 19:48:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-options: aPPCCompilationOptions
-    context options: aPPCCompilationOptions
+options: options
+    context options: options
 
     "Created: / 26-08-2015 / 19:56:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -133,9 +111,11 @@
 !PPCCompiler methodsFor:'compiling'!
 
 compile: aPPParser
+    "Compiles given parser. Return an *instance* of the compiler
+     parser which is ready to use (repeatedly)"
+
     | time |
-    self input: aPPParser.
-    
+    self input: aPPParser.    
     time := [ self compile ] timeToRun.
     ((Smalltalk respondsTo:#isSmalltalkX) and:[Smalltalk isSmalltalkX]) ifFalse:[ 
         "Assume Pharo"
@@ -146,6 +126,7 @@
     ^ ir
 
     "Modified: / 17-08-2015 / 13:06:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 07-09-2015 / 10:49:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCCompiler methodsFor:'initialization'!
--- a/compiler/PPCInlinedMethod.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCInlinedMethod.st	Mon Sep 07 11:53:38 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Compiler-Codegen'
 !
 
+
 !PPCInlinedMethod methodsFor:'as yet unclassified'!
 
 call
@@ -56,3 +57,10 @@
    "Created: / 23-04-2015 / 21:06:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PPCInlinedMethod class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/PPCStarMessagePredicateNode.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/PPCStarMessagePredicateNode.st	Mon Sep 07 11:53:38 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Nodes'
 !
 
+
 !PPCStarMessagePredicateNode methodsFor:'accessing'!
 
 defaultName
@@ -46,3 +47,10 @@
     ^ visitor visitStarMessagePredicateNode: self
 ! !
 
+!PPCStarMessagePredicateNode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/benchmarks/Make.proto	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/benchmarks/Make.proto	Mon Sep 07 11:53:38 2015 +0100
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/jv/calipel/s -I$(INCLUDE_TOP)/stx/goodies/petitparser -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/java -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk/tests -I$(INCLUDE_TOP)/stx/goodies/petitparser/tests -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic
+LOCALINCLUDES= -I$(INCLUDE_TOP)/jv/calipel/s -I$(INCLUDE_TOP)/stx/goodies/petitparser -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler -I$(INCLUDE_TOP)/stx/goodies/petitparser/compiler/tests/extras -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/java -I$(INCLUDE_TOP)/stx/goodies/petitparser/parsers/smalltalk -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
@@ -104,13 +104,8 @@
 	cd ../../../../libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../../refactoryBrowser/parser && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../../../libbasic2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd ../../../../libview && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../ && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd ../../../../libview2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../parsers/smalltalk && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd ../../../sunit && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd ../../tests && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd ../../parsers/smalltalk/tests && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 
 
 
--- a/compiler/benchmarks/PPCBenchmark.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/benchmarks/PPCBenchmark.st	Mon Sep 07 11:53:38 2015 +0100
@@ -3,8 +3,8 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#PPCBenchmark
-	instanceVariableNames:'sources report contextClass compile parser context input
-		compiler profile repetitions'
+	instanceVariableNames:'sources report contextClass compile parser context input compiler
+		profile repetitions'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Benchmarks-Core'
@@ -323,8 +323,8 @@
 benchmarkSmalltalkParserCompiled
     | time |
 
-    compiler := PPCCompiler default.
-    parser := PPSmalltalkParser new compileUsingCompiler:compiler.
+    compiler := PPCCompiler new.
+    parser := compiler compile: (PPSmalltalkParser new).
     context := PPCContext new.
     context initializeFor:parser.
     input := sources smalltalkSourcesBig.
@@ -338,6 +338,8 @@
         reportInput:input
         time:time
         name:'Smalltalk Parser Compiled'.
+
+    "Modified: / 07-09-2015 / 11:38:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
@@ -553,23 +555,27 @@
 !
 
 setupExpressionGrammarCompiled
-    compiler := PPCCompiler universal.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
     compiler options parserName:#PPCompiledExpressionGrammar.
     compiler options scannerName:#PPCompiledExpressionScanner.
-    parser := PPExpressionGrammar new compileUsingCompiler:compiler.
+    parser := compiler compile: (PPExpressionGrammar new).
     context := self context.
     context initializeFor:parser.
     input := sources expressionSourcesMedium.
+
+    "Modified: / 07-09-2015 / 11:38:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupExpressionGrammarTokenized
-    compiler := PPCCompiler tokenizing.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
     compiler options parserName:#PPTokenizedExpressionGrammar.
     compiler options scannerName:#PPTokenizedExpressionScanner.
-    parser := PPExpressionGrammar new compileUsingCompiler:compiler.
+    parser := compiler compile: (PPExpressionGrammar new).
     context := self context.
     context initializeFor:parser.
     input := sources expressionSourcesMedium.
+
+    "Modified: / 07-09-2015 / 11:36:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupJavaSyntax
@@ -602,23 +608,27 @@
 !
 
 setupLL1ExpressionGrammarCompiled
-    compiler := PPCCompiler universal.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
     compiler options parserName:#PPCompiledLL1ExpressionGrammar.
     compiler options scannerName:#PPCompiledLL1ExpressionScanner.
-    parser := PPLL1ExpressionGrammar new compileUsingCompiler:compiler.
+    parser := compiler compile: (PPLL1ExpressionGrammar new).
     context := self context.
     context initializeFor:parser.
     input := sources expressionSourcesBig.
+
+    "Modified: / 07-09-2015 / 11:37:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupLL1ExpressionGrammarTokenized
-    compiler := PPCCompiler tokenizing.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
     compiler options parserName:#PPTokenizedLL1ExpressionGrammar.
     compiler options scannerName:#PPTokenizedLL1ExpressionScanner.
-    parser := PPLL1ExpressionGrammar new compileUsingCompiler:compiler.
+    parser := compiler compile: (PPLL1ExpressionGrammar new).
     context := self context.
     context initializeFor:parser.
     input := sources expressionSourcesBig.
+
+    "Modified: / 07-09-2015 / 11:36:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupLRPParser
@@ -632,13 +642,14 @@
 !
 
 setupLRPParserCompiled
-    compiler := PPCCompiler universal.
-    parser := PPCLRPParser new compileUsingCompiler:compiler.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
+    parser := compiler compile: (PPCLRPParser new).
     context := self context.
     context initializeFor:parser.
     input := PPCLRPSourcesResource current sources
 
     "Created: / 18-08-2015 / 16:35:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:37:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupLRPParser_johanfabry_39     
@@ -665,10 +676,10 @@
 !
 
 setupSmalltalkGrammarCompiled
-    compiler := PPCCompiler universal.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
     compiler options parserName:#'PPSmalltalkGrammarC_Unviersal'.
     compiler options profile:profile.
-    parser := PPSmalltalkGrammar new compileUsingCompiler:compiler.
+    parser := compiler compile: (PPSmalltalkGrammar new).
     context := self context.
     context initializeFor:parser.
     profile ifTrue:[
@@ -676,14 +687,16 @@
     ] ifFalse:[
         input := sources smalltalkSourcesBig.
     ]
+
+    "Modified: / 07-09-2015 / 11:37:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupSmalltalkGrammarTokenized
-    compiler := PPCCompiler tokenizing.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
     compiler options parserName:#'PPSmalltalkGrammarC_Tokenizing'.
     compiler options scannerName:#'PPSmalltalkGrammarC_Scanner'.
     compiler options profile:profile.
-    parser := PPSmalltalkGrammar new compileUsingCompiler:compiler.
+    parser := compiler compile: (PPSmalltalkGrammar new).
     context := self context.
     context initializeFor:parser.
     profile ifTrue:[
@@ -691,26 +704,30 @@
     ] ifFalse:[
         input := sources smalltalkSourcesBig.
     ]
+
+    "Modified: / 07-09-2015 / 11:36:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupSmalltalkNoopParserCompiled
-    compiler := PPCCompiler universal.
-    parser := PPCSmalltalkNoopParser new compileUsingCompiler:compiler.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
+    parser := compiler compile: (PPCSmalltalkNoopParser new).
     context := PPCContext new.
     context initializeFor:parser.
     input := sources smalltalkSourcesBig.
 
     "Created: / 16-05-2015 / 09:44:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:37:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupSmalltalkNoopParserTokenized
-    compiler := PPCCompiler tokenizing.
-    parser := PPCSmalltalkNoopParser new compileUsingCompiler:compiler.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
+    parser := compiler compile: (PPCSmalltalkNoopParser new).
     context := PPCContext new.
     context initializeFor:parser.
     input := sources smalltalkSourcesBig.
 
     "Created: / 16-05-2015 / 09:44:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:36:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupSmalltalkParser
@@ -722,19 +739,23 @@
 !
 
 setupSmalltalkParserCompiled
-    compiler := PPCCompiler universal.
-    parser := PPSmalltalkParser new compileUsingCompiler:compiler.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
+    parser := compiler compile: (PPSmalltalkParser new).
     context := self context.
     context initializeFor:parser.
     input := sources smalltalkSourcesBig.
+
+    "Modified: / 07-09-2015 / 11:37:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setupSmalltalkParserTokenized
-    compiler := PPCCompiler tokenizing.
-    parser := PPSmalltalkParser new compileUsingCompiler:compiler.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
+    parser := compiler compile: (PPSmalltalkParser new).
     context := self context.
     context initializeFor:parser.
     input := sources smalltalkSourcesBig.
+
+    "Modified: / 07-09-2015 / 11:36:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 teardownExpressionGrammarTokenized
--- a/compiler/benchmarks/PPCSmalltalkNoopParser.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/benchmarks/PPCSmalltalkNoopParser.st	Mon Sep 07 11:53:38 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Benchmarks-Parsers'
 !
 
+
 !PPCSmalltalkNoopParser methodsFor:'accessing'!
 
 startExpression
@@ -342,3 +343,10 @@
     "Modified: / 15-05-2015 / 08:54:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PPCSmalltalkNoopParser class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/benchmarks/abbrev.stc	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/benchmarks/abbrev.stc	Mon Sep 07 11:53:38 2015 +0100
@@ -4,5 +4,5 @@
 PPCBenchmark PPCBenchmark stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Core' 0
 PPCLRPParser_johanfabry_39 PPCLRPParser_johanfabry_39 stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Core' 0
 PPCSmalltalkNoopParser PPCSmalltalkNoopParser stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Parsers' 0
+stx_goodies_petitparser_compiler_benchmarks stx_goodies_petitparser_compiler_benchmarks stx:goodies/petitparser/compiler/benchmarks '* Projects & Packages *' 3
 PPCSmalltalkNoopParserTests PPCSmalltalkNoopParserTests stx:goodies/petitparser/compiler/benchmarks 'PetitCompiler-Benchmarks-Parsers-Tests' 1
-stx_goodies_petitparser_compiler_benchmarks stx_goodies_petitparser_compiler_benchmarks stx:goodies/petitparser/compiler/benchmarks '* Projects & Packages *' 3
--- a/compiler/benchmarks/bc.mak	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/benchmarks/bc.mak	Mon Sep 07 11:53:38 2015 +0100
@@ -35,7 +35,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\jv\calipel\s -I$(INCLUDE_TOP)\stx\goodies\petitparser -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\java -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk\tests -I$(INCLUDE_TOP)\stx\goodies\petitparser\tests -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic
+LOCALINCLUDES= -I$(INCLUDE_TOP)\jv\calipel\s -I$(INCLUDE_TOP)\stx\goodies\petitparser -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler -I$(INCLUDE_TOP)\stx\goodies\petitparser\compiler\tests\extras -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\java -I$(INCLUDE_TOP)\stx\goodies\petitparser\parsers\smalltalk -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\libbasic
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
@@ -54,13 +54,8 @@
 	pushd ..\..\..\..\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\..\refactoryBrowser\parser & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\..\..\libbasic2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\..\..\libview & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\.. & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\..\..\libview2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\parsers\smalltalk & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\..\sunit & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\tests & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\..\parsers\smalltalk\tests & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 
 
 
--- a/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/benchmarks/stx_goodies_petitparser_compiler_benchmarks.st	Mon Sep 07 11:53:38 2015 +0100
@@ -61,10 +61,7 @@
     ^ #(
         #'stx:goodies/petitparser'    "PPCompositeParser - superclass of PPCLRPParser_johanfabry_39"
         #'stx:goodies/petitparser/parsers/smalltalk'    "PPSmalltalkGrammar - superclass of PPCSmalltalkNoopParser"
-        #'stx:goodies/petitparser/parsers/smalltalk/tests'    "PPSmalltalkGrammarTests - superclass of PPCSmalltalkNoopParserTests"
-        #'stx:goodies/petitparser/tests'    "PPAbstractParserTest - superclass of PPCSmalltalkNoopParserTests"
-        #'stx:goodies/sunit'    "TestAsserter - superclass of PPCSmalltalkNoopParserTests"
-        #'stx:libbasic'    "LibraryDefinition - superclass of stx_goodies_petitparser_compiler_benchmarks"
+        #'stx:libbasic'    "Autoload - superclass of PPCSmalltalkNoopParserTests"
     )
 !
 
@@ -110,8 +107,8 @@
         PPCBenchmark
         #'PPCLRPParser_johanfabry_39'
         PPCSmalltalkNoopParser
+        #'stx_goodies_petitparser_compiler_benchmarks'
         (PPCSmalltalkNoopParserTests autoload)
-        #'stx_goodies_petitparser_compiler_benchmarks'
     )
 !
 
--- a/compiler/extensions.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/extensions.st	Mon Sep 07 11:53:38 2015 +0100
@@ -399,55 +399,28 @@
 !PPParser methodsFor:'*petitcompiler'!
 
 compile
-    ^ self compile: PPCCompilationOptions default
-
-    "Modified: / 24-08-2015 / 23:39:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!PPParser methodsFor:'*petitcompiler'!
+    ^ self compileWithOptions: PPCCompilationOptions new
 
-compile:options 
-    | compiler |
-
-    self assert:(options isKindOf:PPCCompilationOptions).
-    compiler := PPCCompiler default.
-    compiler context options:options.
-    ^ compiler compile:self
-
-    "Modified: / 28-08-2015 / 14:25:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:54:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
 
-compile: options andParse: input
-    ^ (self compile: options) parse: input
-! !
-
-!PPParser methodsFor:'*petitcompiler'!
+compileWithOptions: options
+    "Compile receiver with given options. Return 
+     an *instance* of the compiler parser which is 
+     ready to use (repeatedly). 
 
-compileAs: name
-    | options |
-    options := PPCCompilationOptions default.
-    options name: name.
-    
-    ^ self compile: options
-
-    "Modified: / 24-08-2015 / 23:39:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!PPParser methodsFor:'*petitcompiler'!
-
-compileTokenizing
+     `options` may be either an instance of PPCCompilationOptions
+     or an array specifying options like #( tokenizing: true debug: false )
+    " 
     | compiler |
 
-    compiler := PPCCompiler tokenizing.
-    ^ self compileUsingCompiler: compiler
-! !
+    compiler := PPCCompiler new.
+    compiler options: options.
+    ^compiler compile: self
 
-!PPParser methodsFor:'*petitcompiler'!
-
-compileUsingCompiler:aPPCCompiler 
-    ^ aPPCCompiler compile:self
+    "Created: / 07-09-2015 / 10:52:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPParser methodsFor:'*petitcompiler'!
--- a/compiler/stx_goodies_petitparser_compiler.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/stx_goodies_petitparser_compiler.st	Mon Sep 07 11:53:38 2015 +0100
@@ -285,8 +285,6 @@
         PPParser asCompilerTree
         PPParser bridge
         PPParser compile
-        PPParser compile:
-        PPParser compile:andParse:
         PPParser firstSetSuchThat:
         PPParser firstSetSuchThat:into:openSet:
         PPParser id
@@ -341,13 +339,11 @@
         PPContext atWs
         PPContext methodInvoked:
         PPContext setWs
-        PPParser compileAs:
         PPParser javaToken
         PPContext skipSeparators
         PPEndOfInputParser asCompilerNode
         PPParser allNodesDo:seen:
         PPSmalltalkWhitespaceParser hash
-        PPParser compileTokenizing
         PPCompositeParser asCompilerNode
         PPSequenceParser map:
         Object canHavePPCId
@@ -362,7 +358,7 @@
         RBLiteralValueNode isLiteralNumber
         RBProgramNode isLiteralNumber
         UndefinedObject codePoint
-        PPParser compileUsingCompiler:
+        PPParser compileWithOptions:
     )
 ! !
 
--- a/compiler/tests/PPCCodeGeneratorTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCCodeGeneratorTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -24,7 +24,7 @@
 !
 
 setUp
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             tokenize:false;
             profile:true;
             yourself.
@@ -35,7 +35,7 @@
                 }.
     compiler options:options.
 
-    "Modified: / 04-09-2015 / 16:22:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 tearDown
--- a/compiler/tests/PPCDistinctScannerTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCDistinctScannerTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -53,13 +53,15 @@
 !
 
 setUp
-    compiler := PPCCompiler tokenizing.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
+
+    "Modified: / 07-09-2015 / 11:36:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testConsumeToken
     | parser |
     parser := self fooToken, self overlappingToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
     scanner stream: 'foobaz' asPetitStream.
@@ -75,7 +77,7 @@
 testConsumeToken2
     | parser |
     parser := self fooToken, self barToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
     scanner stream: 'foobar' asPetitStream.
@@ -91,7 +93,7 @@
 testScan
     | parser |
     parser := self aToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -108,7 +110,7 @@
 testScan2
     | parser |
     parser := self fooToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -125,7 +127,7 @@
 testScan3
     | parser |
     parser := self fooToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -142,7 +144,7 @@
 testScan4
     | parser |
     parser := self fooToken, self idToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -165,7 +167,7 @@
 testSequence
     | parser result |
     parser := self fooTrimmingToken, self idTrimmingToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -195,7 +197,7 @@
 testToken
     | parser |
     parser := self fooToken, self idTrimmingToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -213,7 +215,7 @@
 testTrimmingScan
     | parser |
     parser := self fooTrimmingToken, self idTrimmingToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
@@ -230,7 +232,7 @@
 testTrimmingToken
     | parser result |
     parser := self fooTrimmingToken, self idTrimmingToken.
-    parser compileUsingCompiler:compiler.
+    compiler compile: parser.
     
     scanner := (Smalltalk at: compiler context options scannerName) new.
 
--- a/compiler/tests/PPCNodeFirstFollowNextTests.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCNodeFirstFollowNextTests.st	Mon Sep 07 11:53:38 2015 +0100
@@ -24,10 +24,10 @@
 !PPCNodeFirstFollowNextTests methodsFor:'setup'!
 
 setUp
-    compiler := PPCCompiler default.
+    compiler := PPCCompiler new.
     compiler context options generate:false.
 
-    "Modified: / 28-08-2015 / 14:17:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:38:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCNodeFirstFollowNextTests methodsFor:'support'!
@@ -75,7 +75,7 @@
 !
 
 treeFrom: parser
-    ^ parser compileUsingCompiler: compiler
+    ^ compiler compile: parser
 
     "Modified: / 07-09-2015 / 10:08:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
--- a/compiler/tests/PPCNodeTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCNodeTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -147,14 +147,14 @@
 !
 
 setUp
-    compiler := PPCCompiler default.
+    compiler := PPCCompiler new.
     compiler context options generate:false.
 
-    "Modified: / 28-08-2015 / 14:19:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:38:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 treeFrom: parser
-    ^ parser compileUsingCompiler: compiler
+    ^ compiler compile: parser
 
     "Modified: / 07-09-2015 / 10:06:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
--- a/compiler/tests/PPCOptimizeChoicesTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCOptimizeChoicesTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -12,7 +12,7 @@
 !PPCOptimizeChoicesTest methodsFor:'as yet unclassified'!
 
 asPPCTree: parser
-    ^ parser compileUsingCompiler: compiler
+    ^ compiler compile: parser
 
     "Modified: / 07-09-2015 / 10:08:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -22,7 +22,7 @@
 
     super setUp.
     visitor := PPCOptimizeChoices new.
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             profile:true;
             generate:false;
             tokenize:false;
@@ -31,7 +31,7 @@
     compiler passes:{ PPCCacheFirstFollowPass }.
     compiler options:options.
 
-    "Modified: / 04-09-2015 / 16:21:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testHasCommonPrefix
--- a/compiler/tests/PPCOverlappingTokensTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCOverlappingTokensTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -34,9 +34,9 @@
 !
 
 compile: aPPParser
-    parser := aPPParser compileUsingCompiler: compiler
+    parser := compiler compile: aPPParser.
 
-    "Modified: / 07-09-2015 / 10:08:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 12:36:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 context	
@@ -44,12 +44,12 @@
 !
 
 setUp
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             profile:true;
             tokenize:true;
             yourself.
     compiler := PPCCompiler new.
-    compiler context options:options.
+    compiler options:options.
     self cleanClass.
     fooToken := ('foo' asParser token trim)
             name:'foo';
@@ -67,7 +67,7 @@
             name:'assignment';
             yourself.
 
-    "Modified: / 04-09-2015 / 16:21:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:05:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 tearDown
--- a/compiler/tests/PPCTokenizingCodeGeneratorTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCTokenizingCodeGeneratorTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -35,7 +35,7 @@
 !
 
 setUp
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             profile:true;
             tokenize:true;
             yourself.
@@ -50,7 +50,7 @@
             }.
     compiler options:options.
 
-    "Modified: / 04-09-2015 / 16:21:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 tearDown
--- a/compiler/tests/PPCTokenizingTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCTokenizingTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -44,7 +44,7 @@
 !
 
 setUp
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             profile:true;
             tokenize:true;
             yourself.
@@ -52,7 +52,7 @@
     compiler context options:options.
     self cleanClass.
 
-    "Modified: / 04-09-2015 / 16:21:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 tearDown
@@ -67,7 +67,7 @@
     p1 := a1 star.
     p2 := a2.
     
-    parser := p1 / p2 compileUsingCompiler:compiler.
+    parser := compiler compile: (p1 / p2).
 
     self assert: parser parse: ''.
     self assert: result isEmpty.
@@ -87,8 +87,8 @@
 !
 
 testChoiceOrder
-    parser := (('a' asParser token , 'b' asParser token) / 'a' asParser token) 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: (('a' asParser token , 'b' asParser token) / 'a' asParser token).
+
     
     self assert: parser parse: 'ab'.
     self assert: result first inputValue = 'a'.
@@ -98,7 +98,8 @@
     self assert: result inputValue = 'a'.
 
     self assert: parser fail: '_'.
-    
+
+    "Modified: / 07-09-2015 / 12:36:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testChoiceOrder2
@@ -106,7 +107,7 @@
     p1 := 'a' asParser token, 'b' asParser token.
     p2 := 'b' asParser token / 'a' asParser token.
     
-    parser := p1 / p2 compileUsingCompiler:compiler.
+    parser := compiler compile: (p1 / p2).
     
     self assert: parser parse: 'ab'.
     self assert: result first inputValue = 'a'.
@@ -130,7 +131,7 @@
     p1 := a1, 'b' asParser token.
     p2 := a2.
     
-    parser := p1 / p2 compileUsingCompiler:compiler.
+    parser := compiler compile: (p1 / p2).
     
     self assert: parser parse: 'ab'.
     self assert: result first inputValue = 'a'.
@@ -151,7 +152,7 @@
     p1 := a1, 'b' asParser token.
     p2 := 'b' asParser token / a2.
     
-    parser := p1 / p2 compileUsingCompiler:compiler.
+    parser := compiler compile: (p1 / p2).
     
     self assert: parser parse: 'ab'.
     self assert: result first inputValue = 'a'.
@@ -168,41 +169,42 @@
 !
 
 testCompileAnd
-    parser := (('foo' asParser token and) / ('bar' asParser token and)) 
-                    , 'bar' asParser token compileUsingCompiler:compiler.
+    parser := compiler compile:(('foo' asParser token and) / ('bar' asParser token and)) 
+                    , 'bar' asParser token.
     
     self assert: parser parse: 'bar'.
     self assert: result second inputValue = 'bar'.
+
+    "Modified: / 07-09-2015 / 12:36:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileChoice
-    parser := ('foo' asParser / 'bar' asParser) token 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser / 'bar' asParser) token.
+
+    self assert: parser parse: 'foo'.
+    self assert: result inputValue = 'foo'.
+    self assert: parser parse: 'bar'.
+    self assert: result inputValue = 'bar'.
+    self assert: parser fail: '_'.
+
+    "Modified: / 07-09-2015 / 12:35:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+testCompileChoice2
+    parser := compiler compile:('foo' asParser token trim / 'bar' asParser token trim).
     
     self assert: parser parse: 'foo'.
     self assert: result inputValue = 'foo'.
     self assert: parser parse: 'bar'.
     self assert: result inputValue = 'bar'.
     self assert: parser fail: '_'.
-    
-!
 
-testCompileChoice2
-    parser := ('foo' asParser token trim / 'bar' asParser token trim) 
-                    compileUsingCompiler:compiler.
-    
-    self assert: parser parse: 'foo'.
-    self assert: result inputValue = 'foo'.
-    self assert: parser parse: 'bar'.
-    self assert: result inputValue = 'bar'.
-    self assert: parser fail: '_'.
-    
+    "Modified: / 07-09-2015 / 12:36:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileComplex1
-    parser := ('foo' asParser token , 'bar' asParser token) 
-                    / ('foo' asParser token , 'baz' asParser token) 
-                        compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser token , 'bar' asParser token) 
+                    / ('foo' asParser token , 'baz' asParser token).
     
     self assert: parser parse: 'foobar'.
     self assert: result second inputValue = 'bar'.
@@ -211,30 +213,32 @@
     self assert: result second inputValue = 'baz'.
 
     self assert: parser fail: 'foobaq'.
-    
+
+    "Modified: / 07-09-2015 / 12:36:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileComplex2
-    parser := ('foo' asParser token , 'bar' asParser token) star , 'foo' asParser token 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile:('foo' asParser token , 'bar' asParser token) star , 'foo' asParser token.
     
     self assert: parser parse: 'foobarfoobarfoo'.
     self assert: parser parse: 'foo'.
 
     self assert: parser fail: 'bar'.
-    
+
+    "Modified: / 07-09-2015 / 12:37:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileComplex3
-    parser :=	(('foo' asParser token , 'bar' asParser token) star , 'foo' asParser token) 
-                    / ('foo' asParser token , 'baz' asParser token) 
-                        compileUsingCompiler:compiler.
+    parser := compiler compile: (('foo' asParser token , 'bar' asParser token) star , 'foo' asParser token) 
+                    / ('foo' asParser token , 'baz' asParser token).
+
     
     self assert: parser parse: 'foobarfoobarfoo'.
     self assert: parser parse: 'foo'.
 
     self assert: parser fail: 'bar'.
-    
+
+    "Modified: / 07-09-2015 / 12:37:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileEmptytoken
@@ -244,16 +248,18 @@
     epsilon := '' asParser token.
     
     self should: [
-        (start , epsilon , stop) compileUsingCompiler:compiler.
+        compiler compile: (start , epsilon , stop)
     ] raise: Exception.
-"	
+"       
     self assert: parser parse: '()'.
     self assert: parser fail: '('.
 "
+
+    "Modified: / 07-09-2015 / 12:40:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileLiteral
-    parser := 'foo' asParser token compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser token).
     
     self assert: parser parse: 'foo'.
     self assert: result inputValue = 'foo'.
@@ -261,17 +267,19 @@
 !
 
 testCompileSequence
-    parser := ('foo' asParser token) , ('bar' asParser token) 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser token) , ('bar' asParser token).
+
     
     self assert: parser parse: 'foobar'.
     self assert: result first inputValue = 'foo'.
     self assert: result second inputValue = 'bar'.
+
+    "Modified: / 07-09-2015 / 12:40:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileSequence2
-    parser := ('foo' asParser trimmingToken) , ('bar' asParser trimmingToken) 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser trimmingToken) , ('bar' asParser trimmingToken).
+
     
     self assert: parser parse: 'foobar'.
     self assert: result first inputValue = 'foo'.
@@ -284,11 +292,13 @@
     self assert: parser parse: '  foo  bar'.
     self assert: result first inputValue = 'foo'.
     self assert: result second inputValue = 'bar'.
+
+    "Modified: / 07-09-2015 / 12:40:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileSequence3
-    parser := 	('foo' asParser trimmingToken) , ('bar' asParser trimmingToken) 
-                     , ('baz' asParser trimmingToken) compileUsingCompiler:compiler.
+    parser :=   compiler compile: ('foo' asParser trimmingToken) , ('bar' asParser trimmingToken) 
+                     , ('baz' asParser trimmingToken).
     
     self assert: parser parse: 'foobarbaz'.
     self assert: result first inputValue = 'foo'.
@@ -298,10 +308,12 @@
     self assert: result first inputValue = 'foo'.
     self assert: result second inputValue = 'bar'.
     self assert: result third inputValue = 'baz'.
+
+    "Modified: / 07-09-2015 / 12:39:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileStar
-    parser := 'foo' asParser token star compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser token star).
     
     self assert: parser parse: 'foo'.
     self assert: result first inputValue = 'foo'.
@@ -311,8 +323,8 @@
 !
 
 testCompileStar2
-    parser := ('foo' asParser token , 'bar' asParser token) star 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser token , 'bar' asParser token) star.
+
     
     self assert: parser parse: 'foobar'.
     self assert: context tokenReads size = 1.
@@ -320,12 +332,13 @@
     self assert: parser parse: 'bar' end: 0.
     self assert: result isEmpty.
     self assert: context tokenReads size = 1.
-        
+
+    "Modified: / 07-09-2015 / 12:39:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileStar3
-    parser := 'a' asParser trimmingToken star , 'b' asParser trimmingToken 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: ('a' asParser trimmingToken star , 'b' asParser trimmingToken).
+
     
     self assert: parser parse: 'ab'.
     self assert: parser parse: 'aaab'.
@@ -333,6 +346,8 @@
     self assert: result first size = 3.
             
     self assert: parser fail: 'ac'.
+
+    "Modified: / 07-09-2015 / 12:39:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileTokenComplex2
@@ -346,7 +361,7 @@
         name: 'optionsWith'; 
         yourself.
 
-    parser := optionsWith compileUsingCompiler:compiler.
+    parser := compiler compile: (optionsWith).
     self assert: parser parse: '|'.
 
     self assert: parser parse: ']' end: 0.
@@ -372,7 +387,7 @@
     
     tricky := (a1 asParser, choice1) / (b2 asParser, choice2).
 
-    parser := tricky compileUsingCompiler:compiler.
+    parser := compiler compile: (tricky).
     self assert: parser parse: '||'.
 
     self assert: parser parse: '|]'.
@@ -409,7 +424,7 @@
 
     arrayItem := arrayLiteral / symbolLiteral.
 
-    parser := arrayItem compileUsingCompiler:compiler.
+    parser := compiler compile: (arrayItem).
 
     self assert: parser parse: '#(foo)'.
     self assert: parser parse: '#foo'.
@@ -418,7 +433,7 @@
 !
 
 testCompileTrim
-    parser := 'foo' asParser token trim end compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser token trim end).
     
     self assert: parser parse: 'foo'.
     self assert: result inputValue = 'foo'.
@@ -439,7 +454,7 @@
 testTokenCharacter
     | token |
     token := $a asParser token.
-    parser := token plus compileUsingCompiler:compiler.
+    parser := compiler compile: (token plus).
 
     self assert: parser parse: 'a'.
     self assert: result first inputValue = 'a'.
@@ -452,7 +467,7 @@
 testTokenCharacter2
     | token |
     token := $a asParser token.
-    parser := token plus compileUsingCompiler:compiler.
+    parser := compiler compile: (token plus).
 
     self assert: parser parse: 'aaa'.
     self assert: result first inputValue = 'a'.
@@ -467,7 +482,7 @@
 testTokenName
     | token |
     token := 'foo' asParser token name: 'fooToken'; yourself.
-    parser := token plus compileUsingCompiler:compiler.
+    parser := compiler compile: (token plus).
 
     self assert: parser parse: 'foofoo'.
     self assert: result first inputValue = 'foo'.
@@ -486,7 +501,7 @@
         propertyAt: 'trimmingToken' put: true; 
         yourself.
     
-    parser := trimmingToken plus compileUsingCompiler:compiler.
+    parser := compiler compile: (trimmingToken plus).
 
     self assert: parser parse: ' foo '.
     self assert: result first inputValue = 'foo'.
@@ -506,7 +521,7 @@
         propertyAt: 'trimmingToken' put: true; 
         yourself.
     
-    parser := trimmingToken plus compileUsingCompiler:compiler.
+    parser := compiler compile: (trimmingToken plus).
 
     self assert: parser parse: ' foo foo '.
     self assert: result first inputValue = 'foo'.
@@ -527,7 +542,7 @@
         propertyAt: 'trimmingToken' put: true; 
         yourself.
     
-    parser := trimmingToken plus compileUsingCompiler:compiler.
+    parser := compiler compile: (trimmingToken plus).
 
     self assert: parser parse: ' foo  foo  foo  '.
     self assert: result first inputValue = 'foo'.
--- a/compiler/tests/PPCUnivarsalGuardTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCUnivarsalGuardTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -22,14 +22,14 @@
 !
 
 setUp
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             profile:true;
             tokenize:false;
             yourself.
     compiler := PPCCompiler new.
     compiler context options:options
 
-    "Modified: / 04-09-2015 / 16:21:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 tearDown
@@ -44,74 +44,79 @@
 !PPCUnivarsalGuardTest methodsFor:'tests - guard'!
 
 testChoiceGuard
-    parser := ('foo' asParser trimmingToken / 'bar' asParser trimmingToken 
-                    / $d asParser trimmingToken plus) compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser trimmingToken / 'bar' asParser trimmingToken 
+                    / $d asParser trimmingToken plus).
     
     self assert: parser parse: 'foo'.
-    self assert: result inputValue = 'foo'.	
+    self assert: result inputValue = 'foo'.     
     self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'token' ]).
 
     self assert: parser parse: 'bar'.
-    self assert: result inputValue = 'bar'.	
+    self assert: result inputValue = 'bar'.     
 
     self assert: parser parse: ' foo'.
-    self assert: result inputValue = 'foo'.	
+    self assert: result inputValue = 'foo'.     
 
     self assert: parser parse: '  d'.
-    self assert: result first inputValue = 'd'.	
+    self assert: result first inputValue = 'd'.         
 
     self assert: parser fail: ''.
     self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'predicate' ]).
     self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'token' ]).
 
-    self assert: parser fail: 'zorg'.		
+    self assert: parser fail: 'zorg'.           
     self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'token' ]).
+
+    "Modified: / 07-09-2015 / 12:39:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testEmptyChoiceGuard
-    parser := ('foo' asParser trimmingToken / 'bar' asParser trimmingToken 
-                    / $d asParser trimmingToken star) compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser trimmingToken / 'bar' asParser trimmingToken 
+                    / $d asParser trimmingToken star).
     
     self assert: parser parse: 'foo'.
-    self assert: result inputValue = 'foo'.	
+    self assert: result inputValue = 'foo'.     
 
     self assert: parser parse: 'bar'.
-    self assert: result inputValue = 'bar'.	
+    self assert: result inputValue = 'bar'.     
 
     self assert: parser parse: ' foo'.
-    self assert: result inputValue = 'foo'.	
+    self assert: result inputValue = 'foo'.     
 
     self assert: parser parse: '  d'.
-    self assert: result first inputValue = 'd'.	
+    self assert: result first inputValue = 'd'.         
 
     self assert: parser parse: ''.
 
-    self assert: parser parse: 'zorg' end: 0.	
+    self assert: parser parse: 'zorg' end: 0.
+
+    "Modified: / 07-09-2015 / 12:39:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testGuardSmalltlakToken
-    parser := (#letter asParser , #word asParser star) smalltalkToken 
-                    compileUsingCompiler:compiler.
-    
+    parser := compiler compile: (#letter asParser , #word asParser star) smalltalkToken.
+
     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' ]).
+
+    "Modified (format): / 07-09-2015 / 12:39:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testSequenceGuard
-    parser := ((#any asParser , #any asParser) wrapped , (#any asParser , #any asParser)) 
-                    compileUsingCompiler:compiler.
-    
-    self assert: parser parse: 'fooo' to: #(#($f $o) #($o $o)).	
-    self assert: parser parse: 'fo oo' to: #(#($f $o) #($  $o)) end: 4.	
+    parser := compiler compile: ((#any asParser , #any asParser) wrapped , (#any asParser , #any asParser)).
+
+    self assert: parser parse: 'fooo' to: #(#($f $o) #($o $o)).         
+    self assert: parser parse: 'fo oo' to: #(#($f $o) #($  $o)) end: 4.         
     self assert: parser fail: 'fo'.
-    
+
+    "Modified: / 07-09-2015 / 12:39:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testTrimmerGuard
-    parser := $a asParser trim , $b asParser compileUsingCompiler:compiler.
+    parser := compiler compile: ($a asParser trim , $b asParser).
     
     self assert: parser parse: 'ab'.
     self assert: parser parse: ' ab'.
--- a/compiler/tests/PPCUniversalOptimizationTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCUniversalOptimizationTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -16,7 +16,9 @@
 !
 
 optimize: aPPParser
-    ^ aPPParser compileUsingCompiler:compiler.
+    ^ compiler compile: aPPParser
+
+    "Modified: / 07-09-2015 / 12:38:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setUp
--- a/compiler/tests/PPCUniversalTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/PPCUniversalTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -41,7 +41,7 @@
 !PPCUniversalTest methodsFor:'tests - compiling'!
 
 testCompileAnd
-    parser := #digit asParser and compileUsingCompiler:compiler.
+    parser := compiler compile: (#digit asParser and).
     
     self assert: parser parse: '1' to: $1 end: 0.
     self assert: parser fail: 'a'.
@@ -61,7 +61,7 @@
 !
 
 testCompileAnyStar
-    parser := #any asParser star compileUsingCompiler:compiler.
+    parser := compiler compile: (#any asParser star).
     
     
     self assert: parser parse: 'aaa' to: { $a. $a . $a }.
@@ -71,7 +71,7 @@
 
 testCompileBlock
     parser := (#letter asParser) plus ==> [ :res | res collect: [:each | each asUppercase ]].
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     
     self assert: parser parse: 'foo' to: { $F . $O . $O}.
     self assert: parser parse: 'bar' to: { $B . $A . $R}.
@@ -79,17 +79,17 @@
 !
 
 testCompileCharacter
-    parser := $a asParser compileUsingCompiler:compiler.
+    parser := compiler compile: ($a asParser).
     
     self assert: parser parse: 'a'  to: $a.
     self assert: parser fail: 'b'.
 
-    parser := $# asParser compileUsingCompiler:compiler.
+    parser := compiler compile: ($# asParser).
     self assert: parser parse: '#'.
 !
 
 testCompileChoice
-    parser := (#digit asParser / #letter asParser) compileUsingCompiler:compiler.
+    parser := compiler compile: ((#digit asParser / #letter asParser)).
     
     self assert: parser parse: '1' to: $1.
     self assert: parser parse: 'a' to: $a.
@@ -98,7 +98,7 @@
 !
 
 testCompileChoice2
-    parser := ('true' asParser / 'false' asParser) compileUsingCompiler:compiler.
+    parser := compiler compile: (('true' asParser / 'false' asParser)).
     
     self assert: parser parse: 'true' to: 'true'.
     self assert: parser parse: 'false' to: 'false'.
@@ -107,26 +107,26 @@
 !
 
 testCompileLiteral
-    parser := 'foo' asParser compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser).
     
     self assert: parser parse: 'foo'  to: 'foo'.
     self assert: parser parse: 'foobar'  to: 'foo' end: 3.
     self assert: parser fail: 'boo'.
     
-    parser := '#[' asParser compileUsingCompiler:compiler.
+    parser := compiler compile: ('#[' asParser).
     self assert: parser parse: '#[1]' to: '#[' end: 2.
 !
 
 testCompileLiteral2
     | quote |
     quote := '''' asParser.
-    parser := (quote , $a asParser) compileUsingCompiler:compiler.	
+    parser := compiler compile: ((quote , $a asParser)).	
     self assert: parser parse: '''a'  to: {'''' . $a}.	
 !
 
 testCompileNegate
     parser := #letter asParser negate star, #letter asParser.
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     
     self assert: parser parse: '...a' to: { { $. . $. . $. } . $a }.
     self assert: parser parse: 'aaa' to: { {} . $a } end: 1.
@@ -134,7 +134,7 @@
 !
 
 testCompileNil
-    parser := nil asParser compileUsingCompiler:compiler.
+    parser := compiler compile: (nil asParser).
     
     self assert: parser parse: 'a' to: nil end: 0.
     self assert: parser parse: '' to: nil end: 0.
@@ -144,23 +144,23 @@
 !
 
 testCompileNot
-    parser := #digit asParser not compileUsingCompiler:compiler.
+    parser := compiler compile: (#digit asParser not).
     
     self assert: parser parse: 'a' to: nil end: 0.
     self assert: parser fail: '1'.
     self assert: parser parse: '' to: nil end: 0.
 
     parser := 'foo' asParser, $: asParser not.
-    parser := parser compileUsingCompiler:compiler.	
+    parser := compiler compile: (parser).	
     self assert: parser parse: 'foo' to: { 'foo'. nil } end: 3.
     
     parser := 'foo' asParser, $: asParser not, 'bar' asParser.
-    parser := parser compileUsingCompiler:compiler.	
+    parser := compiler compile: (parser).	
     self assert: parser parse: 'foobar' to: { 'foo'. nil . 'bar' } end: 6.
 !
 
 testCompileNot2
-    parser := ($a asParser , $b asParser) not compileUsingCompiler:compiler.
+    parser := compiler compile: (($a asParser , $b asParser) not).
         
     self assert: parser parse: '' to: nil end: 0.
     self assert: parser parse: 'a' to: nil end: 0.
@@ -169,14 +169,14 @@
 !
 
 testCompileNot3
-    parser := ('foo' asParser not , 'fee' asParser) compileUsingCompiler:compiler.
+    parser := compiler compile: (('foo' asParser not , 'fee' asParser)).
         
     self assert: parser parse: 'fee' to: #(nil 'fee').
     self assert: parser fail: 'foo'.
 !
 
 testCompileNotLiteral
-    parser := 'foo' asParser not compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser not).
     self assert: parser class methodDictionary size = 1.
 
     self assert: parser parse: 'bar' to: nil end: 0.
@@ -201,7 +201,7 @@
 !
 
 testCompileOptional
-    parser := #digit asParser optional compileUsingCompiler:compiler.
+    parser := compiler compile: (#digit asParser optional).
     
     self assert: parser parse: '1' to: $1.
     self assert: parser parse: 'a' to: nil end: 0.
@@ -212,7 +212,7 @@
 !
 
 testCompilePlus
-    parser := #letter asParser plus compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser plus).
     
     self assert: parser parse: 'lorem' to: {$l. $o. $r. $e. $m} .
     self assert: parser parse: 'a123' to: {$a} end: 1.
@@ -223,7 +223,7 @@
 !
 
 testCompilePredicate
-    parser := #digit asParser compileUsingCompiler:compiler.
+    parser := compiler compile: (#digit asParser).
     
     self assert: parser parse: '1' to: $1.
     self assert: parser parse: '0' to: $0.
@@ -231,14 +231,14 @@
 !
 
 testCompilePredicate2
-    parser := #space asParser compileUsingCompiler:compiler.
+    parser := compiler compile: (#space asParser).
     
     self assert: parser parse: ' ' to: Character space.
     self assert: parser fail: 'a'.
 !
 
 testCompileSequence
-    parser := (#digit asParser , #letter asParser) compileUsingCompiler:compiler.
+    parser := compiler compile: ((#digit asParser , #letter asParser)).
     
     self assert: parser parse: '1a' to: {$1 .$a}.
     
@@ -246,25 +246,25 @@
 !
 
 testCompileSequence2
-    parser := (#digit asParser , #space asParser , #letter asParser) 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: (#digit asParser , #space asParser , #letter asParser).
     
-    self assert: parser parse: '9 c' to: {$9 . Character space. $c }.	
+    self assert: parser parse: '9 c' to: {$9 . Character space. $c }.   
     self assert: parser fail: '9c'.
-    
+
+    "Modified: / 07-09-2015 / 12:38:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileSequence3
-    parser := (#any asParser , #any asParser , #any asParser) 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: (#any asParser , #any asParser , #any asParser).
     
-    self assert: parser parse: 'foo' to: #($f $o $o).	
+    self assert: parser parse: 'foo' to: #($f $o $o).   
     self assert: parser fail: 'fo'.
-    
+
+    "Modified: / 07-09-2015 / 12:38:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCompileStar
-    parser := #letter asParser star compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser star).
     
     self assert: parser parse: 'lorem' to: {$l. $o. $r. $e. $m} .
     self assert: parser parse: '' to: {}.
@@ -273,7 +273,7 @@
 !
 
 testCompileStarLiteral
-    parser := 'foo' asParser star compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser star).
     
     self assert: parser parse: 'foo' to: #('foo' ) .
     self assert: parser parse: 'foofoo' to: #('foo' 'foo') .
@@ -283,7 +283,7 @@
 !
 
 testCompileStarPredicate
-    parser := #letter asParser star compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser star).
     
     self assert: parser parse: 'foo' to: #($f $o $o ) .
     self assert: parser parse: '' to: #().
@@ -292,7 +292,7 @@
 
 testCompileSymbolBlock
     parser := (#letter asParser) plus ==> #second.
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     
     self assert: parser parse: 'foo' to: $o.
     self assert: parser parse: 'bar' to: $a.
@@ -301,7 +301,7 @@
 !
 
 testCompileTrim
-    parser := $a asParser trim compileUsingCompiler:compiler.
+    parser := compiler compile: ($a asParser trim).
     
     self assert: parser fail: ''.
     self assert: parser parse: 'a' to: $a.
@@ -315,7 +315,7 @@
     token1 := (#letter asParser) plus trimmingToken.
     token2 := (#letter asParser) plus trimmingToken.
     
-    parser := (token1 , token2) compileUsingCompiler:compiler.
+    parser := compiler compile: ((token1 , token2)).
     
     self assert: parser parse: 'foo bar'.
     self assert: parser parse: ' foo bar '.
@@ -326,7 +326,7 @@
     token1 := (#letter asParser) plus trimmingToken.
     token2 := (#letter asParser) plus trimmingToken / 'foo' asParser trimmingToken.
     
-    parser := (token1 , token2) compileUsingCompiler:compiler.
+    parser := compiler compile: ((token1 , token2)).
     
     self assert: parser parse: 'foo bar'.
     self assert: parser parse: ' foo bar '.
@@ -337,7 +337,7 @@
     token1 := ($a asParser, $b asParser) trimmingToken name: 'token1'.
     token2 := (token1 not, $c asParser) trimmingToken name: 'token2'.
     
-    parser := (token1 / token2) compileUsingCompiler:compiler.
+    parser := compiler compile: ((token1 / token2)).
 
     self assert: (parser class methodDictionary includesKey: #'token1').
     self assert: (parser class methodDictionary includesKey: #'token1_fast').
@@ -355,8 +355,7 @@
 !PPCUniversalTest methodsFor:'tests - extra'!
 
 testCompileSmalltalkToken
-    parser := (#letter asParser , ((#letter asParser / #digit asParser) star)) 
-                    smalltalkToken compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser , ((#letter asParser / #digit asParser) star)) smalltalkToken.
     
     self assert: parser parse: 'foo'.
     self assert: result inputValue = 'foo'.
@@ -382,6 +381,8 @@
         "one more to make sure :)"
     '.
     self assert: result inputValue = 'foo'.
+
+    "Modified: / 07-09-2015 / 12:38:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testCycle
@@ -391,15 +392,14 @@
     block := ${ asParser, p1, $} asParser / nil asParser.
     p1 setParser: block.
     
-    parser := block compileUsingCompiler:compiler.
+    parser := compiler compile: (block).
     self assert: parser parse: '{}' to: { ${. nil . $} }.
     self assert: parser parse: '{{}}' to: { ${. { ${ . nil . $} } . $} }.
     
 !
 
 testSmalltalkToken
-    parser := (#letter asParser , (#digit asParser / #letter asParser) star) 
-                    smalltalkToken compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser , (#digit asParser / #letter asParser) star) smalltalkToken.
     
     self assert: parser class methodDictionary size = 5.
     self assert: parser parse: 'foo'.
@@ -407,7 +407,9 @@
     self assert: context invocationCount = 8.
     self assert: context rememberCount = 0.
     self assert: context lwRememberCount = 0.
-    self assert: context lwRestoreCount = 0.	
+    self assert: context lwRestoreCount = 0.
+
+    "Modified: / 07-09-2015 / 12:38:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testSmalltalkToken2
@@ -419,25 +421,27 @@
         name: 'kw';
         yourself.
     
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     
     self assert: parser parse: 'foo:'.
     self assert: result inputValue = 'foo:'.
 !
 
 testToken
-    parser := (#letter asParser , (#digit asParser / #letter asParser) star) flatten 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser , (#digit asParser / #letter asParser) star) flatten.
+
     
     self assert: parser parse: 'foo' to: 'foo'.
     self assert: parser parse: 'a' to: 'a'.
     self assert: parser parse: 'f123a' to: 'f123a'.
     self assert: parser fail: ''.
+
+    "Modified: / 07-09-2015 / 12:38:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testToken2
-    parser := (#letter asParser , (#digit asParser / #letter asParser) star) token 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser , (#digit asParser / #letter asParser) star) token.
+
     
     self assert: parser class methodDictionary size = 4.
     self assert: parser parse: 'foo'.
@@ -445,12 +449,14 @@
     self assert: context invocationCount = 6.
     self assert: context rememberCount = 0.
     self assert: context lwRememberCount = 0.
-    self assert: context lwRestoreCount = 0.	
+    self assert: context lwRestoreCount = 0.
+
+    "Modified: / 07-09-2015 / 12:37:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testTrimmingToken
-    parser := (#letter asParser , (#digit asParser / #letter asParser) star) 
-                    trimmingToken compileUsingCompiler:compiler.
+    parser := compiler compile: (#letter asParser , (#digit asParser / #letter asParser) star) 
+                    trimmingToken.
 
     self assert: parser class methodDictionary size = 4.
     self assert: parser parse: 'foo'.
@@ -459,7 +465,7 @@
     self assert: context invocationCount = 6.
     self assert: context rememberCount = 0.
     self assert: context lwRememberCount = 0.
-    self assert: context lwRestoreCount = 0.	
+    self assert: context lwRestoreCount = 0.    
 
     self assert: parser parse: ' foo '.
     self assert: result inputValue = 'foo'.
@@ -471,54 +477,58 @@
     self assert: context invocationCount = 1.
     self assert: context rememberCount = 0.
     self assert: context lwRememberCount = 0.
-    self assert: context lwRestoreCount = 0.	
+    self assert: context lwRestoreCount = 0.    
 
 
     self assert: parser fail: ''.
+
+    "Modified: / 07-09-2015 / 12:37:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testTrimmingToken2
 
-    parser := 'foo' asParser trimmingToken , 'bar' asParser trimmingToken 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile:  ('foo' asParser trimmingToken , 'bar' asParser trimmingToken).
+
     
     self assert: parser parse: 'foobar'.
     self assert: result first inputValue = 'foo'.
-    self assert: result second inputValue = 'bar'.	
+    self assert: result second inputValue = 'bar'.      
     self assert: context invocationCount = 3.
 
     self assert: parser parse: ' foobar'.
     self assert: result first inputValue = 'foo'.
-    self assert: result second inputValue = 'bar'.	
+    self assert: result second inputValue = 'bar'.      
     self assert: context invocationCount = 3.
-    self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'token' ]).	
+    self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'token' ]).      
         
     self assert: parser fail: 'bar'.
     self assert: context invocationCount = 2.
-"	self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'token' ]).	"
-    
+"       self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'token' ]).         "
+
+    "Modified: / 07-09-2015 / 12:37:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testTrimmingToken3
 
-    parser := ('foo' asParser trimmingToken / 'bar' asParser trimmingToken) 
-                    compileUsingCompiler:compiler.
+    parser := compiler compile: ('foo' asParser trimmingToken / 'bar' asParser trimmingToken).
     
     self assert: parser parse: 'foo'.
     self assert: result inputValue = 'foo'.
     self assert: context invocationCount = 2.
 
     self assert: parser parse: ' bar'.
-    self assert: result inputValue = 'bar'.	
+    self assert: result inputValue = 'bar'.     
     self assert: context invocationCount = 2.
-    self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'token' ]).	
+    self assert: (context invocations anySatisfy: [ :e | e beginsWith: 'token' ]).      
         
     self assert: parser fail: 'baz'.
     self assert: context invocationCount = 2.
     
     self assert: parser fail: 'zaz'.
     self assert: context invocationCount = 1.
-    self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'token' ]).	
+    self assert: (context invocations noneSatisfy: [ :e | e beginsWith: 'token' ]).
+
+    "Modified: / 07-09-2015 / 12:37:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testTrimmingTokenNested
@@ -527,7 +537,7 @@
     identifier := (kw not, (#letter asParser, #word asParser star)) trimmingToken name: #identifier.
     
     parser := identifier / kw.
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     self assert: parser class methodDictionary size = 5.
 
     self assert: parser parse: 'foo'.
@@ -543,7 +553,7 @@
     identifier := (kw not, (#letter asParser, #word asParser star)) trimmingToken name: #identifier.
     
     parser := identifier / kw.
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     self assert: parser class methodDictionary size = 5.
 
     self assert: parser parse: 'foo'.
@@ -559,7 +569,7 @@
     identifier := (kw not, (#letter asParser, #word asParser star)) trimmingToken name: #identifier.
     
     parser := identifier / kw.
-    parser := parser compileUsingCompiler:compiler.
+    parser := compiler compile: (parser).
     self assert: parser class methodDictionary size = 8.
     self assert: (parser class methodDictionary values anySatisfy: [ :m | m selector = #kw ]).
     self assert: (parser class methodDictionary values anySatisfy: [ :m | m selector = #kw_fast ]).
@@ -576,7 +586,7 @@
 !PPCUniversalTest methodsFor:'tests - ids'!
 
 setUp
-    options := (PPCCompilationOptions default)
+    options := (PPCCompilationOptions new)
             profile:true;
             debug:true;
             tokenize:false;
@@ -584,7 +594,7 @@
     compiler := PPCCompiler new.
     compiler context options:options
 
-    "Modified: / 04-09-2015 / 16:21:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 10:22:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCUniversalTest class methodsFor:'documentation'!
--- a/compiler/tests/extras/PPCAbstractParserTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCAbstractParserTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -105,7 +105,7 @@
     compiler options parserName: self compiledParserClassName.
     compiler options scannerName: self compiledScannerClassName.
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
--- a/compiler/tests/extras/PPCCompositeParserTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCCompositeParserTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -29,6 +29,22 @@
 
 !PPCCompositeParserTest class methodsFor:'utilities'!
 
+generateTests
+    "Regenerate all generated test cases"
+
+    {
+
+        PPExpressionGrammarTest .
+
+        PPSmalltalkGrammarTests .
+        PPSmalltalkParserTests .
+
+
+    } do:[:each | self generateTestsFor: each ]
+
+    "Created: / 07-09-2015 / 11:28:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 generateTestsFor: baseTestClass
     | compiledBaseTestClassName |
 
@@ -80,8 +96,8 @@
         category: 'PetitCompiler-Extras-Tests-Misc'.
 
     compiledUniversalTestClass compile: 
-'compilerConfiguration
-    ^ PPCConfiguration universal'
+'compiler
+    ^ PPCCompiler newWithOptions: #( #tokenize: false ) '
     classified: 'accessing'.
     
                              
@@ -92,11 +108,12 @@
         category: 'PetitCompiler-Extras-Tests-Misc'.
 
     compiledTokenizedTestClass compile: 
-'compilerConfiguration
-    ^ PPCConfiguration tokenizing'
+'compiler
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )'
     classified: 'accessing'.
 
     "Created: / 31-07-2015 / 07:26:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 12:58:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCCompositeParserTest methodsFor:'accessing'!
@@ -173,7 +190,7 @@
     compiler := self compiler.
     compiler options parserName: self compiledParserClassName.
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
--- a/compiler/tests/extras/PPCExpressionGrammarTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCExpressionGrammarTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,9 +6,10 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Expressions'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
+
 !PPCExpressionGrammarTest class methodsFor:'resources'!
 
 resources
@@ -91,7 +92,7 @@
     compiler := self compiler.
     compiler options parserName: self compiledParserClassName.
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
@@ -105,3 +106,10 @@
     "Created: / 29-07-2015 / 16:33:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PPCExpressionGrammarTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/PPCExpressionGrammarTest_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCExpressionGrammarTest_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,14 +6,14 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Expressions'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 
 !PPCExpressionGrammarTest_Tokenized methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
 ! !
 
 !PPCExpressionGrammarTest_Tokenized class methodsFor:'documentation'!
--- a/compiler/tests/extras/PPCExpressionGrammarTest_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCExpressionGrammarTest_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,12 +6,12 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Expressions'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCExpressionGrammarTest_Universal methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false ) 
 ! !
 
--- a/compiler/tests/extras/PPCLL1ExpressionGrammarTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCLL1ExpressionGrammarTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -91,7 +91,7 @@
     compiler := self compiler.
     compiler options parserName: self compiledParserClassName.
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
--- a/compiler/tests/extras/PPCLL1ExpressionGrammarTest_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCLL1ExpressionGrammarTest_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -12,6 +12,8 @@
 !PPCLL1ExpressionGrammarTest_Tokenized methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: true )
+
+    "Modified: / 07-09-2015 / 11:36:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPCLL1ExpressionGrammarTest_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCLL1ExpressionGrammarTest_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -13,7 +13,9 @@
 !PPCLL1ExpressionGrammarTest_Universal methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
+
+    "Modified: / 07-09-2015 / 11:37:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCLL1ExpressionGrammarTest_Universal class methodsFor:'documentation'!
--- a/compiler/tests/extras/PPCLRPCompiledParserSmokeTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCLRPCompiledParserSmokeTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -88,7 +88,7 @@
     compiler := self compiler.
     compiler options parserName: self compiledParserClassName.
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
--- a/compiler/tests/extras/PPCLRPCompiledParserSmokeTest_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCLRPCompiledParserSmokeTest_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -12,6 +12,8 @@
 !PPCLRPCompiledParserSmokeTest_Universal methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
+
+    "Modified: / 07-09-2015 / 11:37:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkGrammarTests.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkGrammarTests.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,7 +6,7 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Smalltalk'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCSmalltalkGrammarTests class methodsFor:'resources'!
@@ -96,10 +96,8 @@
 
     compiler := self compiler.
     compiler options parserName: self compiledParserClassName.
-    compiler options scannerName: self compiledScannerClassName.
-        
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
--- a/compiler/tests/extras/PPCSmalltalkGrammarTests_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkGrammarTests_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,12 +6,12 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Smalltalk'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCSmalltalkGrammarTests_Tokenized methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkGrammarTests_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkGrammarTests_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,12 +6,12 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Smalltalk'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCSmalltalkGrammarTests_Universal methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false ) 
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkGrammarVerificationTest_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkGrammarVerificationTest_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,8 +14,9 @@
 compiler
     "Return compiler to use when compiling parser (as instance of PPCConfiguration)"
     
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: true )
 
     "Created: / 29-07-2015 / 19:54:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:36:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkGrammarVerificationTest_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkGrammarVerificationTest_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,8 +14,9 @@
 compiler
     "Return compiler to use when compiling parser (as instance of PPCConfiguration)"
     
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
 
     "Created: / 29-07-2015 / 19:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:37:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkParserTests.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkParserTests.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,7 +6,7 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Smalltalk'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCSmalltalkParserTests class methodsFor:'resources'!
@@ -96,10 +96,8 @@
 
     compiler := self compiler.
     compiler options parserName: self compiledParserClassName.
-    compiler options scannerName: self compiledScannerClassName.	
-    
     time := Time millisecondsToRun: [
-        self petitParser compileUsingCompiler:compiler.
+        compiler compile: self petitParser.
     ].
     Transcript show: self petitParserClass name ; show:' compiled in: '; show: time asString; show: 'ms'; cr.
 
--- a/compiler/tests/extras/PPCSmalltalkParserTests_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkParserTests_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,12 +6,12 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Smalltalk'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCSmalltalkParserTests_Tokenized methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkParserTests_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkParserTests_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -6,12 +6,12 @@
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Extras-Tests-Smalltalk'
+	category:'PetitCompiler-Extras-Tests-Misc'
 !
 
 !PPCSmalltalkParserTests_Universal methodsFor:'accessing'!
 
 compiler
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false ) 
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkParserVerificationTest_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkParserVerificationTest_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,8 +14,9 @@
 compiler
     "Return compiler to use when compiling parser (as instance of PPCConfiguration)"
     
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: true )
 
     "Created: / 29-07-2015 / 19:54:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:36:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkParserVerificationTest_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkParserVerificationTest_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,8 +14,9 @@
 compiler
     "Return compiler to use when compiling parser (as instance of PPCConfiguration)"
     
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
 
     "Created: / 29-07-2015 / 19:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:37:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPCSmalltalkTests.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCSmalltalkTests.st	Mon Sep 07 11:53:38 2015 +0100
@@ -3,7 +3,7 @@
 "{ NameSpace: Smalltalk }"
 
 TestCase subclass:#PPCSmalltalkTests
-	instanceVariableNames:'compiler options result'
+	instanceVariableNames:'compiler result'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Extras-Tests-Smalltalk'
@@ -17,27 +17,25 @@
 !
 
 setUp
-    options := PPCArguments default
-        profile: true;
-        yourself.
-        
-    compiler := PPCTokenizingConfiguration new
-        options: options;
-        yourself.
+    compiler := PPCCompiler newWithOptions: #(profile: true)
+
+    "Modified: / 07-09-2015 / 11:10:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testSmalltakToken
     | token1  |
-    token1 := 'a' asParser smalltalkToken compileUsingCompiler:compiler.
+    token1 := compiler compile: 'a' asParser smalltalkToken.
     
     self assert: ((token1 parse: 'a') class == PPSmalltalkToken).
     self assert: (token1 parse: '"comment" a "another comment"') inputValue = 'a'
+
+    "Modified: / 07-09-2015 / 12:36:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testSmalltakToken2
     | parser compiled  |
     parser := 'a' asParser smalltalkToken, 'b' asParser smalltalkToken.
-    compiled := parser compileUsingCompiler:compiler.
+    compiled := compiler compile: parser.
     
     self assert: compiled parse: 'ab'.
     self assert: compiled parse: '"comment" a "another comment" b '.
--- a/compiler/tests/extras/PPCompiledJavaResource.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPCompiledJavaResource.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,16 +14,16 @@
 setUp
     | time  compiler |
 
-    compiler := PPCCompiler universal.
+    compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
     compiler options parserName:#PPCompiledJavaSyntax.
     time := Time 
-            millisecondsToRun:[ PPJavaSyntax new compileUsingCompiler:compiler. ].
+            millisecondsToRun:[ compiler compile:  PPJavaSyntax new ].
     Transcript
         show:'Java Syntax compiled in: ';
         show:time asString;
         show:'ms';
         cr.
 
-    "Modified: / 10-05-2015 / 07:45:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 12:37:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPExpressionGrammarVerificationTest_Tokenized.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPExpressionGrammarVerificationTest_Tokenized.st	Mon Sep 07 11:53:38 2015 +0100
@@ -15,9 +15,9 @@
 compiler
     "Return compiler to use when compiling parser (as instance of PPCConfiguration)"
     
-    ^ PPCCompiler tokenizing
+    ^ PPCCompiler newWithOptions: #( #tokenize: true )
 
-    "Modified: / 29-07-2015 / 17:07:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:36:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPExpressionGrammarVerificationTest_Tokenized class methodsFor:'documentation'!
--- a/compiler/tests/extras/PPExpressionGrammarVerificationTest_Universal.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPExpressionGrammarVerificationTest_Universal.st	Mon Sep 07 11:53:38 2015 +0100
@@ -14,8 +14,8 @@
 compiler
     "Return compiler to use when compiling parser (as instance of PPCConfiguration)"
     
-    ^ PPCCompiler universal
+    ^ PPCCompiler newWithOptions: #( #tokenize: false )
 
-    "Modified: / 29-07-2015 / 17:06:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 11:37:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/compiler/tests/extras/PPLL1ExpressionGrammarTest.st	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/PPLL1ExpressionGrammarTest.st	Mon Sep 07 11:53:38 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Extras-Tests-Expressions'
 !
 
+
 !PPLL1ExpressionGrammarTest methodsFor:'as yet unclassified'!
 
 parserClass
@@ -98,3 +99,10 @@
     self assert: result third = 3.
 ! !
 
+!PPLL1ExpressionGrammarTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/extras/abbrev.stc	Mon Sep 07 08:20:46 2015 +0100
+++ b/compiler/tests/extras/abbrev.stc	Mon Sep 07 11:53:38 2015 +0100
@@ -11,8 +11,8 @@
 PPCLRPSourcesResource PPCLRPSourcesResource stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-LRP' 1
 PPCResources PPCResources stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Support' 1
 PPCSetUpBeforeTearDownAfterResource PPCSetUpBeforeTearDownAfterResource stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Support' 2
-PPCSmalltalkGrammarTests PPCSmalltalkGrammarTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
-PPCSmalltalkParserTests PPCSmalltalkParserTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
+PPCSmalltalkGrammarTests PPCSmalltalkGrammarTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
+PPCSmalltalkParserTests PPCSmalltalkParserTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
 PPCSmalltalkTests PPCSmalltalkTests stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
 PPCompiledJavaResource PPCompiledJavaResource stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Java' 1
 PPCompiledJavaSyntaxTest PPCompiledJavaSyntaxTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Java' 1
@@ -21,21 +21,21 @@
 PPLL1ExpressionGrammar PPLL1ExpressionGrammar stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 0
 PPLL1ExpressionGrammarTest PPLL1ExpressionGrammarTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
 stx_goodies_petitparser_compiler_tests_extras stx_goodies_petitparser_compiler_tests_extras stx:goodies/petitparser/compiler/tests/extras '* Projects & Packages *' 3
-PPCExpressionGrammarTest PPCExpressionGrammarTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
+PPCExpressionGrammarTest PPCExpressionGrammarTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
 PPCExpressionGrammarVerificationTest PPCExpressionGrammarVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
 PPCLL1ExpressionGrammarTest PPCLL1ExpressionGrammarTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
 PPCLRPAction PPCLRPAction stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-LRP' 0
 PPCLRPCompiledParserSmokeTest PPCLRPCompiledParserSmokeTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-LRP' 1
 PPCLRPContainedElement PPCLRPContainedElement stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-LRP' 0
 PPCLRPSpawn PPCLRPSpawn stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-LRP' 0
-PPCSmalltalkGrammarTests_Tokenized PPCSmalltalkGrammarTests_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
-PPCSmalltalkGrammarTests_Universal PPCSmalltalkGrammarTests_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
+PPCSmalltalkGrammarTests_Tokenized PPCSmalltalkGrammarTests_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
+PPCSmalltalkGrammarTests_Universal PPCSmalltalkGrammarTests_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
 PPCSmalltalkGrammarVerificationTest PPCSmalltalkGrammarVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
-PPCSmalltalkParserTests_Tokenized PPCSmalltalkParserTests_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
-PPCSmalltalkParserTests_Universal PPCSmalltalkParserTests_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
+PPCSmalltalkParserTests_Tokenized PPCSmalltalkParserTests_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
+PPCSmalltalkParserTests_Universal PPCSmalltalkParserTests_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
 PPCSmalltalkParserVerificationTest PPCSmalltalkParserVerificationTest stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Smalltalk' 1
-PPCExpressionGrammarTest_Tokenized PPCExpressionGrammarTest_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
-PPCExpressionGrammarTest_Universal PPCExpressionGrammarTest_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
+PPCExpressionGrammarTest_Tokenized PPCExpressionGrammarTest_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
+PPCExpressionGrammarTest_Universal PPCExpressionGrammarTest_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Misc' 1
 PPCLL1ExpressionGrammarTest_Tokenized PPCLL1ExpressionGrammarTest_Tokenized stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
 PPCLL1ExpressionGrammarTest_Universal PPCLL1ExpressionGrammarTest_Universal stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-Expressions' 1
 PPCLRPComment PPCLRPComment stx:goodies/petitparser/compiler/tests/extras 'PetitCompiler-Extras-Tests-LRP' 0