compiler/PPCCompiler.st
changeset 422 116d2b2af905
parent 421 7e08b31e0dae
child 428 b879012e366e
--- a/compiler/PPCCompiler.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/PPCCompiler.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#PPCCompiler
 	instanceVariableNames:'compilerStack compiledParser cache inlining debug profile
 		currentMethod guards ids tokenMode rootNode'
@@ -19,10 +21,6 @@
 
 !PPCCompiler methodsFor:'accessing'!
 
-fastMode
-	^ tokenMode
-!
-
 inlining
 	^ inlining
 !
@@ -114,18 +112,6 @@
 	currentMethod addVariable: name.
 !
 
-allowInline
-	currentMethod allowInline
-!
-
-cache: id as: value
-	cache at: id put: value.
-!
-
-cachedValue: id
-	^ cache at: id ifAbsent: [ nil ]
-!
-
 call: anotherMethod
 	currentMethod add: anotherMethod call.
 !
@@ -166,14 +152,6 @@
 		^ 'context lwRestore: ', mementoName, '.'.
 	].
 	^ 'context restore: ', mementoName, '.'.
-!
-
-startTokenMode
-	tokenMode := true
-!
-
-stopTokenMode
-	tokenMode := false
 ! !
 
 !PPCCompiler methodsFor:'code generation - ids'!
@@ -214,6 +192,14 @@
 
 !PPCCompiler methodsFor:'code generation - support'!
 
+cache: id as: value
+	cache at: id put: value.
+!
+
+cachedValue: id
+	^ cache at: id ifAbsent: [ nil ]
+!
+
 checkCache: id
 	| method  |
 	"Check if method is hand written"
@@ -433,48 +419,6 @@
 
 !PPCCompiler methodsFor:'guard'!
 
-addSequenceGuard: parser
-
-	| firsts  guardSet guardSetId |
-	(self guards not or: [(guardSet := self guardCharSet: parser) isNil]) ifTrue: [ ^ self].
-
-	firsts := (parser firstSetSuchThat: [ :e | (e isKindOf: PPTokenParser) or: [ e isTerminal ] ]).
-	
-	"If we start with PPTokenParser, we should invoke the whitespace parser"
-	(firsts allSatisfy: [ :e | e isKindOf: PPTokenParser ]) ifTrue: [  
-		guardSetId := (self idFor: guardSet prefixed: #guard).
-		self addConstant: guardSet as: guardSetId.
-		self add: 'wsParser parseOn: context.'.
-		self add: 'context atEnd ifTrue: [ ^ self error ].'.
-		self add: '(', guardSetId, ' value: context peek) ifFalse: [ ^ self error ].'.
-	].
-
-	(firsts allSatisfy: [ :e | e isTerminal ]) ifTrue: [  
-		guardSetId := (self idFor: guardSet prefixed: #guard).
-		self addConstant: guardSet as: guardSetId.
-		self add: 'context atEnd ifTrue: [ ^ self error ].'.
-		self add: '(', guardSetId, ' value: context peek) ifFalse: [ ^ self error ].'.
-	].
-!
-
-guardCharSet: parser
-	| fs charSet   |
-	"No Guards fro trimming parser so far"
-	(parser firstSetSuchThat: [ :e | e isKindOf: PPCTrimNode ]) isEmpty ifFalse: [ ^ nil ].
-
-	"Makes no sense to do guard for epsilon parse"
-	(parser acceptsEpsilon) ifTrue: [ ^ nil ].
-
-	fs := parser firstSet.
-	fs do: [ :p |
-		"If we can accept epsilon guard does not make sense"
-		p isNullable ifTrue: [ ^ nil ].
-	].
-	
-	charSet := PPCharSetPredicate on: [:char | fs anySatisfy: [:e | (e firstCharParser parse: char asString) isPetitFailure not ]].
-	^ charSet
-!
-
 guards
 	^ guards
 !