compiler/PPCTokenCodeGenerator.st
changeset 524 f6f68d32de73
parent 515 b5316ef15274
child 525 751532c8f3db
--- a/compiler/PPCTokenCodeGenerator.st	Mon Aug 17 12:13:16 2015 +0100
+++ b/compiler/PPCTokenCodeGenerator.st	Mon Aug 24 15:34:14 2015 +0100
@@ -3,27 +3,21 @@
 "{ NameSpace: Smalltalk }"
 
 PPCNodeVisitor subclass:#PPCTokenCodeGenerator
-	instanceVariableNames:'compiler scannerGenerator fsaCache'
+	instanceVariableNames:'codeGen'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'PetitCompiler-Visitors'
+	category:'PetitCompiler-Visitors-CodeGenerators'
 !
 
 !PPCTokenCodeGenerator methodsFor:'accessing'!
 
 arguments: args
     super arguments: args.
-    scannerGenerator arguments: args
+    codeGen arguments: args.
 !
 
-compiler
-    ^ compiler
-!
-
-compiler: anObject
-    compiler := anObject.
-    
-    scannerGenerator compiler idGen: compiler idGen.
+clazz: aPPCClass
+    codeGen clazz: aPPCClass
 ! !
 
 !PPCTokenCodeGenerator methodsFor:'code support'!
@@ -32,18 +26,19 @@
     self assert: node isTokenNode.
 
     node isTrimmingTokenNode ifTrue: [ 
-        compiler code: 'self consumeWhitespace.'
+        codeGen code: 'self scan_consumeWhitespace.'
     ]
 !
 
-createTokenInsance: node id: idCode start: startVar end: endVar
-    compiler codeTranscriptShow: 'current token type: ', idCode.
-    compiler codeAssign: idCode, '.' to: 'currentTokenType'.
-    compiler codeAssign: node tokenClass asString, ' on: (context collection) 
+createTokenInstance: node id: idCode start: startVar end: endVar
+    codeGen startInline.
+    codeGen codeTranscriptShow: 'current token type: ', idCode.
+    codeGen codeAssign: node tokenClass asString, ' on: (context collection) 
                                                             start: ', startVar, ' 
                                                             stop: ', endVar, '
                                                             value: nil.'
-               to: 'currentTokenValue'.
+               to: self retvalVar.
+    ^ codeGen stopInline
 !
 
 scan: node start: startVar end: endVar
@@ -51,72 +46,37 @@
         node child name: node name
     ].
 
-    compiler codeAssign: 'context position + 1.' to: startVar.
-    compiler add: ((self generateScan: node child) callOn: 'scanner').
-!
-
-unorderedChoiceFromFollowSet: followSet
-    | followFsas  |
-    
-    ^ fsaCache at: followSet ifAbsentPut: [ 
-        followFsas := followSet collect: [ :followNode | 
-                (followNode asFsa) 
-                    name: (compiler idFor: followNode);
-                    retval: (compiler idFor: followNode); 
-                    yourself
-        ].
-        self unorderedChoiceFromFsas: followFsas.
-    ]
-     
-!
-
-unorderedChoiceFromFsas: fsas
-    | result startState |
-    result := PEGFsa new.
-    startState := PEGFsaState new.
-    
-    result addState: startState.
-    result startState: startState.
-
-    fsas do: [ :fsa | 
-        result adopt: fsa.
-        result addTransitionFrom: startState to: fsa startState.
-    ].
-
-    result determinizeStandard.
-    ^ result
+    codeGen codeAssign: 'context position + 1.' to: startVar.
+    codeGen add: ((self generateScan: node child) callOn: 'scanner').
 ! !
 
 !PPCTokenCodeGenerator methodsFor:'compiling support'!
 
-compileScanner
-    ^ scannerGenerator compileScannerClass
-!
-
 retvalVar
-    ^ compiler currentReturnVariable
+    ^ codeGen currentReturnVariable
 !
 
 startMethodForNode:node
+
     node isMarkedForInline ifTrue:[ 
-        compiler startInline: (compiler idFor: node).
-        compiler codeComment: 'BEGIN inlined code of ' , node printString.
-        compiler indent.
+        codeGen startInline: (codeGen idFor: node).
+        codeGen codeComment: 'BEGIN inlined code of ' , node printString.
+        codeGen indent.
     ] ifFalse:[ 
-        compiler startMethod: (compiler idFor: node).
-        compiler currentMethod category: 'generated - tokens'.
-        compiler codeComment: 'GENERATED by ' , node printString.
-        compiler allocateReturnVariable.
+        codeGen startMethod: (codeGen idFor: node).
+        codeGen currentMethod category: 'generated - tokens'.
+        codeGen codeComment: 'GENERATED by ' , node printString.
+        codeGen allocateReturnVariable.
     ]
 !
 
 stopMethodForNode:aPPCNode
-    ^ aPPCNode isMarkedForInline ifTrue:[ 
-                compiler dedent.
-                compiler add: '"END inlined code of ' , aPPCNode printString , '"'.
-                compiler stopInline.
+    ^ codeGen currentMethod isInline ifTrue:[ 
+                codeGen dedent.
+                codeGen add: '"END inlined code of ' , aPPCNode printString , '"'.
+                codeGen stopInline.
     ] ifFalse:[ 
-                compiler stopMethod
+                codeGen stopMethod
     ].
 ! !
 
@@ -125,147 +85,75 @@
 initialize
     super initialize.
     
-    scannerGenerator := PPCScannerCodeGenerator new.
-    scannerGenerator arguments: arguments.
-    
-    "for the given set of nodes, remember the unordered choice fsa
-        see `unorderedChoiceFromFollowSet:`
-    "
-    fsaCache := Dictionary new.
-! !
-
-!PPCTokenCodeGenerator methodsFor:'scanning'!
-
-generateNextScan: node
-    | epsilon followSet  anFsa |
-    followSet := node followSetWithTokens.
-    
-    epsilon := followSet anySatisfy: [ :e | e acceptsEpsilon ].
-    followSet := followSet reject: [ :e | e acceptsEpsilon ].
-    epsilon ifTrue: [ followSet add: PPCEndOfFileNode instance ].
-    
-    anFsa := self unorderedChoiceFromFollowSet: followSet.
-
-    anFsa name: 'nextToken_', (compiler idFor: node).
-    node nextFsa: anFsa.
-    ^ scannerGenerator generate: anFsa.
-!
-
-generateScan: node
-    | anFsa |
-    anFsa := node asFsa determinize.
-    anFsa name: (compiler idFor: node).
-    anFsa retval: (compiler idFor: node).
-    
-    ^ scannerGenerator generate: anFsa.
+    codeGen := PPCCodeGen new.
 ! !
 
 !PPCTokenCodeGenerator methodsFor:'visiting'!
 
 visitToken: tokenNode
-    |  id  startVar endVar  numberId |
-    self startMethodForNode: tokenNode.
-
-    "Tokens cannot be inlined, 
-        - their result is true/false
-        - the return value is always stored in currentTokenValue
-        - the current token type is always stored in currentTokenType
-    "
+    | scanId id |
     self assert: tokenNode isMarkedForInline not.
-    
-    startVar := compiler allocateTemporaryVariableNamed: 'start'.
-    endVar := compiler allocateTemporaryVariableNamed:  'end'.
-    
-    id := compiler idFor: tokenNode.
-    numberId := compiler numberIdFor: id.
-    
-    compiler add: 'currentTokenType isNil ifFalse: [ ^ currentTokenType == ', id storeString, '].'.
+
+    self startMethodForNode: tokenNode.
     
-"	compiler codeComment: 'number for: ', id storeString, ' is: ', numberId storeString.
-    compiler codeIf: 'scanner match: ', numberId storeString then: [ 
-        compiler codeAssign: '(scanner resultPosition: ', numberId storeString, ').' to: endVar.
-        self createTokenInsance: tokenNode 
-                id: id storeString 
-                start: '(context position + 1)' 
-                end: endVar.
-        
-        compiler code: 'context position: ', endVar, '.'.
-        
-        self consumeWhitespace: tokenNode.
-        compiler codeReturn: 'true'.
-    ].
-    compiler codeIf: 'scanner backtracked not' then: [ 
-        compiler codeReturn: 'false'.
-    ].
-    compiler codeComment: 'No match, no fail, scanner does not know about this...'.	
-"
-    compiler profileTokenRead: id.
+    id := codeGen idFor: tokenNode.
+    scanId := codeGen idFor: tokenNode fsa.
     
-"	self scan: tokenNode start: startVar end: endVar."
-    "	compiler add: 'self assert: scanner isSingleMatch.'."
-"	compiler codeIf: 'scanner match ' then: ["
-
+    codeGen code: 'match isNil ifFalse: [ ^ match == ', id storeString, '].'.
+    codeGen profileTokenRead: id.
+    
     tokenNode child hasName ifFalse: [ 
         tokenNode child name: tokenNode name
     ].
 
-    compiler codeAssign: 'context position + 1.' to: startVar.
-    compiler codeIf: [ compiler code: ((self generateScan: tokenNode child) callOn: 'scanner') ] then: [ 
-        compiler add: 'context position: scanner resultPosition.'.
-        compiler codeAssign: 'context position.' to: endVar.	
+    codeGen codeIf: 'self ', scanId then: [ 
         self consumeWhitespace: tokenNode.
-        self createTokenInsance: tokenNode id: id storeString start: startVar end: endVar.
-        compiler codeReturn: 'true'.
+        codeGen codeReturn: 'true'.
     ] else: [ 
-        compiler code: 'scanner backtrackDistinct.'.
-        compiler code: 'context position: ', startVar, ' - 1.'. 
-        compiler codeReturn: 'false'.
+        codeGen codeReturn: 'false'.
     ].
     
     ^ self stopMethodForNode: tokenNode
 !
 
 visitTokenConsumeNode: node
-    | id   nextScan |
+    | id nextId |
     self startMethodForNode: node.
-    id := (compiler idFor: node child).
+    id := (codeGen idFor: node child).
+    nextId := (codeGen idFor: node nextFsa).
+    
+    "this will inline scanner consumeXY in the parser"
+    node markForInline.
+    
 
-    compiler add: 'self ', id asString, ' ifTrue: ['.
-        compiler indent.
+    codeGen codeIf: 'self ', id asString then: [
+        codeGen codeAssign: [ 
+            self createTokenInstance: node child
+                id: id asString
+                start: 'position + 1'
+                end: 'matchPosition'.
+        ] to: self retvalVar.
 
-        nextScan := self generateNextScan: node.
-        
+
+        codeGen codeAssign: 'context position' to: 'position'; codeDot.
+        codeGen codeAssign: 'position' to: 'matchPosition'; codeDot.
+        codeGen codeAssign: 'nil' to: 'match'; codeDot.		
+    
         node nextFsa hasDistinctRetvals ifTrue: [ 
-            compiler codeAssign: 'currentTokenValue.' to: self retvalVar.
-        
-            compiler add: (nextScan callOn: 'scanner'), '.'.
-            compiler codeIf: 'scanner match' then: [ 
-            compiler add: 'context position: scanner resultPosition.'.
-                self createTokenInsance: node child 
-                        id: 'scanner result' 
-                        start: 'scanner position + 1' 
-                        end: 'scanner resultPosition'.
+            codeGen codeIf: [ codeGen codeOnLine: ('self ', nextId) ] then: [ 
                 self consumeWhitespace: node child.
-                compiler codeReturn.
             ] else: [ 
-                compiler codeComment: 'Looks like there is an error on its way...'.
-                compiler code: 'context position: scanner position.'.
-                compiler codeAssign: 'nil.' to: 'currentTokenType'.
-                compiler codeReturn.
+                self flag: 'imo should do something here and not wait...'.
+                codeGen codeComment: 'Looks like there is an error on its way...'.
             ]
-
-        ] ifFalse: [ 
-            compiler codeAssign: 'nil.' to: 'currentTokenType'.
-            compiler codeReturn: 'currentTokenValue'.
         ].
-        compiler dedent.
-
+        codeGen codeReturn.
+    
     "Token not found"
-    compiler add: '] ifFalse: ['.
-        compiler indent.
-        compiler codeError: id asString, ' expected'.
-        compiler dedent.
-    compiler add: '].'.
+    ] else: [ 
+"		codeGen code: 'PPCScannerError new signalWith: ''', id asString, ' expected'''."
+        codeGen codeReturn: 'nil.'.
+    ].
 
     ^ self stopMethodForNode: node
 !
@@ -274,34 +162,47 @@
     ^ self visitToken: node
 !
 
-visitTrimmingTokenCharacterNode: node
-    |  id     |
-    self startMethodForNode:node.
+visitTokenizingParserNode: node
+    "produces token_XY methods"
+    self visit: node tokens.
 
-    "Tokens cannot be inlined, 
-        - their result is true/false
-        - the return value is always stored in currentTokenValue
-        - the current token type is always stored in currentTokenType
+    "TODO JK: hack alert, I don't like WS handling, think of something smarter,
+        perhaps allow for WS unique per token...
     "
+    self visitWhitespace: node whitespace.
+    
+    "produces tokenConsume_XY methods"
+    ^ self visit: node parser
+!
+
+visitTrimmingTokenCharacterNode: node
+    |  id  |
+    self halt.
     self assert: node isMarkedForInline not.
+
+    self startMethodForNode:node.
     
-    id := compiler idFor: node.
+    id := codeGen idFor: node.
     
-    compiler add: 'currentTokenType isNil ifFalse: [ ^ currentTokenType == ', id storeString, '].'.
-    compiler profileTokenRead: id.
+    codeGen add: 'match isNil ifFalse: [ ^ match == ', id storeString, '].'.
+    codeGen profileTokenRead: id.
 
-    compiler add: '(context peek == ', node child character storeString, ') ifFalse: [ ^ false ].'.
-    compiler add: 'context next.'.
+    codeGen add: '(context uncheckedPeek == ', node child character storeString, ') ifFalse: [ ^ false ].'.
+    codeGen add: 'context next.'.
 
-    self createTokenInsance: node id: id storeString  start: 'context position' end: 'context position'.
+    self createTokenInstance: node id: id storeString  start: 'context position' end: 'context position'.
     self consumeWhitespace: node.
     
-    compiler codeReturn: 'true'.
+    codeGen codeReturn: 'true'.
 
     ^ self stopMethodForNode: node
 !
 
 visitTrimmingTokenNode: node
     ^ self visitToken: node
+!
+
+visitWhitespace: whitespaceNode
+    self assert: whitespaceNode name = 'consumeWhitespace'.
 ! !