compiler/PPCScannerCodeGenerator.st
changeset 524 f6f68d32de73
parent 515 b5316ef15274
child 525 751532c8f3db
--- a/compiler/PPCScannerCodeGenerator.st	Mon Aug 17 12:13:16 2015 +0100
+++ b/compiler/PPCScannerCodeGenerator.st	Mon Aug 24 15:34:14 2015 +0100
@@ -3,8 +3,8 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#PPCScannerCodeGenerator
-	instanceVariableNames:'codeGen fsa backlinkStates backlinkTransitions arguments openSet
-		incommingTransitions methodCache id resultStrategy fsaCache'
+	instanceVariableNames:'codeGen fsa arguments incommingTransitions resultStrategy
+		fsaCache'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Scanner'
@@ -17,7 +17,8 @@
 !
 
 arguments: anObject
-    arguments := anObject
+    arguments := anObject.
+    codeGen arguments: anObject.
 !
 
 codeGen
@@ -30,26 +31,24 @@
 
 !PPCScannerCodeGenerator methodsFor:'analysis'!
 
-analyzeBacklinks
-    backlinkTransitions := fsa backTransitions.
-    backlinkStates := IdentityDictionary new.
-    
-    backlinkTransitions do: [ :t |
-        (self backlinksTo: (t destination)) add: t.
-    ].
-!
-
 analyzeDistinctRetvals
-    (fsa hasDistinctRetvals) ifTrue: [
-        resultStrategy := PPCDistinctResultStrategy new
+    (fsa hasNoRetvals) ifTrue: [
+        ^ resultStrategy := PPCNoResultStrategy new
             codeGen: codeGen;
             yourself
-    ] ifFalse: [ 
-        resultStrategy := PPCUniversalResultStrategy new
+    ].
+
+
+    (fsa hasDistinctRetvals) ifTrue: [
+        ^ resultStrategy := PPCDistinctResultStrategy new
             codeGen: codeGen;
-            tokens: fsa retvals asArray;
             yourself
-    ]
+    ].
+
+    resultStrategy := PPCUniversalResultStrategy new
+        codeGen: codeGen;
+        tokens: fsa retvals asArray;
+        yourself
 !
 
 analyzeTransitions
@@ -63,8 +62,8 @@
     ].
 !
 
-backlinksTo: state
-    ^ backlinkStates at: state ifAbsentPut: [ OrderedCollection new ] 
+clazz: aPPCClass
+    codeGen clazz: aPPCClass
 !
 
 containsBacklink: state
@@ -83,12 +82,23 @@
     ^ incommingTransitions  at: state ifAbsentPut: [ IdentitySet new ]
 !
 
-isBacklink: transition
-    ^ backlinkTransitions includes: transition
+isSingleTerminatingRetval: state
+    (state retvals size == 1 and: [ state isFinal ]) ifFalse: [ ^ false ].
+    
+    state transitions isEmpty ifTrue: [ ^ true ].
+    ((state transitions size == 1) and: [state destination == state]) ifTrue: [ ^ self startsSimpleLoop: state ].
+    
+    ^ false
 !
 
-isBacklinkDestination: state
-    ^ (self backlinksTo: state)  isEmpty not
+isSingleTransitionFsa
+    fsa allTransitions size == 1 ifFalse: [ ^ false ].
+    "do not allow loop!!"
+    fsa startState destination == fsa startState ifTrue: [ ^ false ].
+    "so far only single char allowed"
+    fsa startState transition isCharacterTransition ifFalse: [ ^ false ].
+    fsa startState transition isSingleCharacter ifFalse: [ ^ false ].
+    ^ true
 !
 
 startsSimpleLoop: state
@@ -106,7 +116,7 @@
 !PPCScannerCodeGenerator methodsFor:'caching'!
 
 cache: anFsa method: method
-    fsaCache at: anFsa put: method
+    ^ fsaCache at: anFsa put: method
 !
 
 cachedValueForIsomorphicFsa: anFsa
@@ -116,37 +126,33 @@
 !
 
 isomorphicIsCached: anFsa
-    ^ fsaCache keys anySatisfy: [ :e | e isIsomorphicTo: anFsa ]
+    ^ fsaCache keys anySatisfy: [ :e | (e isIsomorphicTo: anFsa) and: [ e name = anFsa name ] ]
 ! !
 
 !PPCScannerCodeGenerator methodsFor:'code generation'!
 
 generate
-    | method |
     self assert: fsa isDeterministic.
     self assert: fsa isWithoutEpsilons.
     self assert: fsa checkConsistency.
 
     (self isomorphicIsCached: fsa) ifTrue: [ 
+        "JK: please not, right now, checks for isomorphism and name
+            this might be improved in future and name can be 'reused'
+        "
         ^ self cachedValueForIsomorphicFsa: fsa 
     ].
 
-    self analyzeBacklinks.
     self analyzeTransitions.
     self analyzeDistinctRetvals.
     
-    openSet := IdentitySet new.
     codeGen startMethod: (codeGen idFor: fsa).
-    codeGen codeComment: (Character codePoint: 13) asString, fsa asString.
+"	codeGen codeComment: (Character codePoint: 13) asString, fsa asString."
     resultStrategy reset.
 
     self generateFor: fsa startState.
 
-    method := codeGen stopMethod.	
-    self cache: fsa method: method.
-    
-    ^ method.
-
+    ^ self cache: fsa method: codeGen stopMethod.
 
 
 !
@@ -182,6 +188,16 @@
 !
 
 generateFinalFor: state offset: offset
+    "Handle one retval specially"
+    (self isSingleTerminatingRetval: state) ifTrue: [  
+        state isFsaFailure ifTrue: [ 
+            resultStrategy returnFailure: state retval offset: offset.
+        ] ifFalse: [ 
+            resultStrategy returnMatch: state retval offset: offset.
+        ].
+        ^ self
+    ].
+
     state retvalsAndInfosDo: [:retval :info |
         info isFinal ifTrue: [ 
             info isFsaFailure ifTrue: [ 
@@ -194,12 +210,26 @@
 !
 
 generateFor: state
-    codeGen cachedValue: (codeGen idFor: state) ifPresent: [ :method | 
+    codeGen cachedMethod: (codeGen idFor: state) ifPresent: [ :method | 
         "if state is already cached, it has multiple incomming links.
      	 In such a case, it is compiled as a method, thus return immediatelly"
         ^ codeGen codeAbsoluteReturn:  method call
     ].
 
+    self flag: 'TODO JK: Hack alert, fix this:'.
+    (state isKindOf: PEGFsaParserState) ifTrue: [ 
+        | id |
+        self assert: state transitions isEmpty.
+        id := codeGen idFor: state parser defaultName: 'parser'.
+        codeGen addConstant: state parser as: id.
+        codeGen code: id, ' parseOn: context'.
+        ^ self
+    ].
+
+    (self isSingleTransitionFsa) ifTrue: [ 
+        ^ self generateForSingleTransitionFsa: state.
+    ].
+
     (self startsSimpleLoop: state) ifTrue: [ 
         ^ self generateSimpleLoopFor: state
     ].
@@ -207,20 +237,21 @@
     ^ self generateStandardFor: state
 !
 
-generateForSingleTransition: t from: state.
+generateForSingleTransitionFsa: startState
+    | transition |
+    self assert: fsa startState == startState.
     
-    (self isJoinPoint: t destination) ifTrue: [ self removeJoinTransition: t ].
+    transition := startState transition.
     
-    codeGen codeAssertPeek: t ifFalse: [ 
-        resultStrategy returnResult: state 
-    ].
-"	(self isBacklink: t) ifTrue: [ 
-        codeGen add: 'true'
+    transition isSingleCharacter ifTrue: [ 
+        codeGen codeIf: 'context peek == ', transition character storeString then: [ 
+            codeGen code: 'self step'; codeDot.
+            self generateFinalFor: transition destination.
+        ]. 
+        codeGen codeReturn: 'false'.
     ] ifFalse: [ 
-        self generateFor: t destination.
+        self error: 'should be implemented'
     ]
-"
-    self generateFor: t destination
 !
 
 generateForTransition: t from: state		
@@ -246,8 +277,12 @@
 !
 
 generateReturnFor: state
-    codeGen codeNl.
-    resultStrategy returnResult: state.
+"	codeGen codeNl."
+    (self isSingleTerminatingRetval: state) ifFalse: [ 
+        resultStrategy returnResult: state.
+    ] ifTrue: [ 
+ 		"return already generated within the match"	
+    ]
 !
 
 generateSimpleLoopFor: state
@@ -262,7 +297,9 @@
 
     "Last transition did not passed the loop, therefore, we have to record succes with offset -1"
     self generateFinalFor: state offset: 1.
-    self generateTransitions: (state transitions reject: [ :t | t == selfTransition  ]) for: state.
+    self generateTransitions: (state transitions reject: [ :t | t == selfTransition  ]) 
+            for: state 
+            offset: 1.
     
 !
 
@@ -275,7 +312,8 @@
     self generateStopMethod: state.
 !
 
-generateStartMethod: state.
+generateStartMethod: state
+    | id |
     id := codeGen idFor: state.
 
     codeGen codeComment: 'START - Generated from state: ', state asString.
@@ -297,19 +335,18 @@
     codeGen codeComment: 'STOP - Generated from state: ', state asString.
 !
 
-generateTransitions: transitions for: state
+generateTransitions: transitions for: state offset: offset
     (transitions size = 0) ifTrue: [  
-        self generateReturnFor: state.
+        (offset > 0 and: [ state isFinal not ]) ifTrue:  [ 
+            codeGen codeIf: 'currentChar isNil' then: nil else: [ 
+                codeGen codeOnLine: 'context skip: -', offset asString 
+            ].
+        ].
         ^ self	
     ].
 
-"	(state transitions size = 1) ifTrue: [  
-        self generateForSingleTransition: state transitions anyOne from: state.
-        ^ self
-    ]."
-
-    codeGen codeNl.
-    transitions do: [ :t |
+"	codeGen codeNl.
+"	transitions do: [ :t |
         self generateForTransition: t from: state
     ].
 
@@ -317,8 +354,8 @@
     self generateReturnFor: state.
     codeGen dedent.
     codeGen codeNl.
-    transitions size timesRepeat: [ codeGen addOnLine: ']' ].
-    codeGen addOnLine: '.'.
+    transitions size timesRepeat: [ codeGen codeOnLine: ']' ].
+    codeGen codeDot.
     
 
 "	self closedJoinPoints isEmpty ifFalse: [ 
@@ -333,7 +370,7 @@
 !
 
 generateTransitionsFor: state
-    ^ self generateTransitions: state transitions for: state
+    ^ self generateTransitions: state transitions for: state offset: 0
 !
 
 setMaxNumericId
@@ -365,9 +402,9 @@
     builder := PPCClassBuilder new.
     
     builder compiledClassName: arguments scannerName.
-    builder compiledSuperclass: PPCScanner.
-    builder methodDictionary: codeGen methodDictionary.
-    builder constants: codeGen constants.
+    builder compiledSuperclass: arguments scannerSuperclass.
+    builder methodDictionary: codeGen clazz methodDictionary.
+    builder constants: codeGen clazz constants.
 
     ^ builder compileClass.	
 ! !