compiler/PPCScannerCodeGenerator.st
changeset 516 3b81c9e53352
parent 503 ff58cd9f1f3c
parent 515 b5316ef15274
child 517 9a7fa841f12e
--- a/compiler/PPCScannerCodeGenerator.st	Fri Jul 31 14:07:31 2015 +0100
+++ b/compiler/PPCScannerCodeGenerator.st	Mon Aug 17 12:56:02 2015 +0100
@@ -4,7 +4,7 @@
 
 Object subclass:#PPCScannerCodeGenerator
 	instanceVariableNames:'codeGen fsa backlinkStates backlinkTransitions arguments openSet
-		joinPoints incommingTransitions methodCache id'
+		incommingTransitions methodCache id resultStrategy fsaCache'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Scanner'
@@ -18,6 +18,14 @@
 
 arguments: anObject
     arguments := anObject
+!
+
+codeGen
+    ^ codeGen 
+!
+
+compiler
+    ^ self codeGen 
 ! !
 
 !PPCScannerCodeGenerator methodsFor:'analysis'!
@@ -31,16 +39,17 @@
     ].
 !
 
-analyzeJoinPoints
-    | joinTransitions |
-    joinTransitions := fsa joinTransitions.
-    joinTransitions := joinTransitions reject: [ :t | self isBacklinkDestination: t destination ].
-    joinPoints := IdentityDictionary new.
-    
-    joinTransitions do: [ :t |
-        (joinPoints at: t destination ifAbsentPut: [ IdentitySet new ]) add: t.
+analyzeDistinctRetvals
+    (fsa hasDistinctRetvals) ifTrue: [
+        resultStrategy := PPCDistinctResultStrategy new
+            codeGen: codeGen;
+            yourself
+    ] ifFalse: [ 
+        resultStrategy := PPCUniversalResultStrategy new
+            codeGen: codeGen;
+            tokens: fsa retvals asArray;
+            yourself
     ]
-    
 !
 
 analyzeTransitions
@@ -58,17 +67,6 @@
     ^ backlinkStates at: state ifAbsentPut: [ OrderedCollection new ] 
 !
 
-closedJoinPoints
-    | closed |
-    closed := IdentitySet new.
-    
-    joinPoints keysAndValuesDo: [ :key :value | 
-        value isEmpty ifTrue: [ closed add: key ].
-    ].
-
-    ^ closed
-!
-
 containsBacklink: state
     state transitions do: [ :t |
         (self isBacklink:  t) ifTrue: [ ^ true ]
@@ -93,37 +91,62 @@
     ^ (self backlinksTo: state)  isEmpty not
 !
 
-isJoinPoint: state
-    "Please note that joinPoints are removed as the compilaction proceeds"
-    ^ joinPoints keys includes: state
+startsSimpleLoop: state
+    |   |
+
+    "
+        This accepts more or less something like $a star
+        for now.. might extend later
+    "
+    ((self incommingTransitionsFor: state) size == 2) ifFalse: [ ^ false ].
+    ^ (state transitions select: [ :t | t destination == state ]) size == 1
+    
+! !
+
+!PPCScannerCodeGenerator methodsFor:'caching'!
+
+cache: anFsa method: method
+    fsaCache at: anFsa put: method
 !
 
-joinTransitionsTo: joinPoint "state"
-    ^ joinPoints at: joinPoint ifAbsent: [ #() ]
+cachedValueForIsomorphicFsa: anFsa
+    | key |
+    key := fsaCache keys detect: [ :e | e isIsomorphicTo: anFsa ].
+    ^ fsaCache at: key
+!
+
+isomorphicIsCached: anFsa
+    ^ fsaCache keys anySatisfy: [ :e | e isIsomorphicTo: anFsa ]
 ! !
 
 !PPCScannerCodeGenerator methodsFor:'code generation'!
 
 generate
+    | method |
     self assert: fsa isDeterministic.
     self assert: fsa isWithoutEpsilons.
     self assert: fsa checkConsistency.
 
+    (self isomorphicIsCached: fsa) ifTrue: [ 
+        ^ self cachedValueForIsomorphicFsa: fsa 
+    ].
 
     self analyzeBacklinks.
-    self analyzeJoinPoints.
     self analyzeTransitions.
+    self analyzeDistinctRetvals.
     
     openSet := IdentitySet new.
-    
     codeGen startMethod: (codeGen idFor: fsa).
     codeGen codeComment: (Character codePoint: 13) asString, fsa asString.
+    resultStrategy reset.
 
     self generateFor: fsa startState.
 
-    codeGen stopMethod.	
-        
-    ^ self compileScannerClass new
+    method := codeGen stopMethod.	
+    self cache: fsa method: method.
+    
+    ^ method.
+
 
 
 !
@@ -131,50 +154,66 @@
 generate: aPEGFsa
     fsa := aPEGFsa.
 
-    fsa compact.
+    self assert: fsa isDeterministic.
+    self assert: fsa isWithoutPriorities.
+    
+    fsa minimize.
     fsa checkSanity.
     
     ^ self generate
 !
 
+generateAndCompile
+    self generate.
+    ^ self compile
+!
+
+generateAndCompile: aPEGFsa
+    fsa := aPEGFsa.
+
+    fsa minimize.
+    fsa checkSanity.
+    
+    ^ self generateAndCompile
+!
+
 generateFinalFor: state
-    state isFinal ifFalse: [  ^ self ].
+    ^ self generateFinalFor: state offset: 0
+!
 
-    codeGen codeRecordMatch: state retval priority: state priority.
+generateFinalFor: state offset: offset
+    state retvalsAndInfosDo: [:retval :info |
+        info isFinal ifTrue: [ 
+            info isFsaFailure ifTrue: [ 
+                resultStrategy recordFailure: retval offset: offset
+            ] ifFalse: [ 
+                resultStrategy recordMatch: retval offset: offset
+            ]
+        ].
+    ]
 !
 
 generateFor: state
-"	(self isJoinPoint: state) ifTrue: [ 
-        ^ codeGen codeComment: 'join point generation postponed...'
-    ].
-"
     codeGen cachedValue: (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 generateStartMethod: state.
-"	(self isBacklinkDestination: state) ifTrue: [ 
-        codeGen codeStartBlock.
+    (self startsSimpleLoop: state) ifTrue: [ 
+        ^ self generateSimpleLoopFor: state
     ].
-"
-    self generateFinalFor: state.
-    self generateNextFor: state.
-    self generateTransitionsFor: state.
-
-"	(self isBacklinkDestination: state) ifTrue: [ 
-        codeGen codeEndBlockWhileTrue.
-    ].
-"
-    self generateStopMethod: state.
+    
+    ^ self generateStandardFor: state
 !
 
 generateForSingleTransition: t from: state
     
     (self isJoinPoint: t destination) ifTrue: [ self removeJoinTransition: t ].
     
-    codeGen codeAssertPeek: (t characterSet) orReturn: state priority.
+    codeGen codeAssertPeek: t ifFalse: [ 
+        resultStrategy returnResult: state 
+    ].
 "	(self isBacklink: t) ifTrue: [ 
         codeGen add: 'true'
     ] ifFalse: [ 
@@ -184,20 +223,18 @@
     self generateFor: t destination
 !
 
-generateForTransition: t from: state	
-    (self isJoinPoint: t destination) ifTrue: [ self removeJoinTransition: t   ].
-    
+generateForTransition: t from: state		
 "	(self isBacklink: t) ifTrue: [ 
         codeGen codeAssertPeek: (t characterSet) ifTrue: [ 
             codeGen add: 'true'
         ]
     ] ifFalse: [ 
-        codeGen codeAssertPeek: (t characterSet) ifTrue: [
+        codeGen codeAssertPeek: (t characterSet) ifTrue: [.
             self generateFor: t destination.
         ].
     ].
 "
-    codeGen codeAssertPeek: (t characterSet) ifTrue: [
+    codeGen codeAssertPeek: t ifTrue: [
         self generateFor: t destination.
     ].
     codeGen codeIfFalse.
@@ -209,7 +246,33 @@
 !
 
 generateReturnFor: state
-    codeGen codeNlReturnResult: state priority.
+    codeGen codeNl.
+    resultStrategy returnResult: state.
+!
+
+generateSimpleLoopFor: state
+    | selfTransition |
+    selfTransition := state transitions detect: [ :t | t destination == state ].
+    
+    codeGen codeStartBlock.
+    codeGen codeNextChar.
+    codeGen codeNl.
+    codeGen codeAssertPeek: selfTransition.
+    codeGen codeEndBlockWhileTrue.
+
+    "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.
+    
+!
+
+generateStandardFor: state
+    self generateStartMethod: state.
+    self generateFinalFor: state.
+    self generateNextFor: state.
+    self generateTransitionsFor: state.
+
+    self generateStopMethod: state.
 !
 
 generateStartMethod: state
@@ -234,20 +297,19 @@
     codeGen codeComment: 'STOP - Generated from state: ', state asString.
 !
 
-generateTransitionsFor: state
-    (state transitions size = 0) ifTrue: [  
+generateTransitions: transitions for: state
+    (transitions size = 0) ifTrue: [  
         self generateReturnFor: state.
         ^ self	
     ].
 
-    (state transitions size = 1) ifTrue: [  
+"	(state transitions size = 1) ifTrue: [  
         self generateForSingleTransition: state transitions anyOne from: state.
         ^ self
-    ].
-
+    ]."
 
     codeGen codeNl.
-    state transitions do: [ :t |
+    transitions do: [ :t |
         self generateForTransition: t from: state
     ].
 
@@ -255,7 +317,7 @@
     self generateReturnFor: state.
     codeGen dedent.
     codeGen codeNl.
-    state transitions size timesRepeat: [ codeGen addOnLine: ']' ].
+    transitions size timesRepeat: [ codeGen addOnLine: ']' ].
     codeGen addOnLine: '.'.
     
 
@@ -268,12 +330,38 @@
         self generateFor: jp.
     ]
 "
+!
+
+generateTransitionsFor: state
+    ^ self generateTransitions: state transitions for: state
+!
+
+setMaxNumericId
+    codeGen addConstant: codeGen idGen numericIds size as: #MaxSymbolNumber 
+!
+
+setTokens
+    | tokens |
+    tokens := Array new: codeGen idGen numericIdCache size.
+    
+    codeGen idGen numericIdCache keysAndValuesDo: [ :key :value |
+        tokens at: value put: key
+    ].
+
+    codeGen addConstant: tokens as: #Tokens 
 ! !
 
 !PPCScannerCodeGenerator methodsFor:'compiling'!
 
+compile
+    ^ self compileScannerClass new
+!
+
 compileScannerClass
     | builder |
+    self setMaxNumericId.
+    self setTokens.
+    
     builder := PPCClassBuilder new.
     
     builder compiledClassName: arguments scannerName.
@@ -291,16 +379,6 @@
     
     codeGen := PPCFSACodeGen new.
     arguments := PPCArguments default.
+    fsaCache := IdentityDictionary new.
 ! !
 
-!PPCScannerCodeGenerator methodsFor:'support'!
-
-removeJoinPoint: state
-    self assert: (joinPoints at: state) size = 0.
-    joinPoints removeKey: state
-!
-
-removeJoinTransition: t
-    (self joinTransitionsTo: t destination) remove: t ifAbsent: [ self error: 'this should not happen' ].
-! !
-