Fix in codegen for inlined sequence nodes.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 16 Jun 2015 06:45:26 +0100
changeset 489 0ca7a70db0f5
parent 488 19a9c25960ef
child 490 a836cbc0d8df
Fix in codegen for inlined sequence nodes. For inlined sequence nodes, generate nested ifs rather than sequential code which does not work when inlined. The reason is that #codeReturn: in inline generates instvar assignment, not method return, so in sequential code the next child of a sequence will be probed even if previous failed. If that happends, the whole sequence fail and therefore we must generate nested ifs to correctly handle this w.r.t. inlining.
compiler/PPCCodeGenerator.st
compiler/PPCCompiler.st
compiler/PPCMappedActionNode.st
compiler/tests/PPCCodeGeneratorTest.st
compiler/tests/extras/PPTokenizedExpressionGrammarResource.st
--- a/compiler/PPCCodeGenerator.st	Mon Jun 15 19:13:49 2015 +0100
+++ b/compiler/PPCCodeGenerator.st	Tue Jun 16 06:45:26 2015 +0100
@@ -686,7 +686,7 @@
 
 visitSequenceNode: node
 
-    | elementVars mementoVar canBacktrack |
+    | elementVars mementoVar canBacktrack coding |
 
     elementVars := node preferredChildrenVariableNames.
     elementVars do:[:e | 
@@ -708,34 +708,47 @@
         compiler codeAssign: 'Array new: ', node children size asString, '.' to: self retvalVar.
     ].
 
-    compiler 
-          codeAssignParsedValueOf:[ self visit:(node children at:1) ]
-          to:(elementVars at:1).
-    compiler add: 'error ifTrue: [ ^ failure ].'.
-    node returnParsedObjectsAsCollection ifTrue:[
-        compiler add: self retvalVar , ' at: 1 put: ', (elementVars at: 1), '.'.
+    coding := [ :index |
+        | child childValueVar |
+
+        child := node children at: index.
+        childValueVar := elementVars at: index.
+        compiler codeAssignParsedValueOf: [ self visit:child ] 
+                                      to: childValueVar.
+        child acceptsEpsilon ifFalse: [   
+            compiler codeIfErrorThen: [
+                "Handle error in the first element specially"
+                "TODO: JK, please explain here why!!!!!!"
+                index == 1 ifTrue:[                         
+                    compiler add: 'error ifTrue: [ ^ failure ].'.
+                ] ifFalse:[
+                    compiler smartRestore: node from: mementoVar.
+                    compiler codeReturn: 'failure.'.
+                ]
+            ] else:[ 
+                node returnParsedObjectsAsCollection ifTrue:[
+                    compiler add: self retvalVar , ' at: ', index asString, ' put: ', childValueVar, '.'.
+                ].
+                (index < node children size) ifTrue:[ 
+                    coding value: index + 1.
+                ].
+            ]
+
+        ] ifTrue:[
+            node returnParsedObjectsAsCollection ifTrue:[
+                compiler add: self retvalVar , ' at: ', index asString, ' put: ', childValueVar, '.'.
+            ].
+            (index < node children size) ifTrue:[ 
+                coding value: index + 1.
+            ].
+        ]
     ].
-    2 to: (node children size) do: [ :idx  | |child|
-        child := node children at: idx.
-        compiler 
-              codeAssignParsedValueOf:[ self visit:child ]
-              to:(elementVars at:idx).
-      
-        child acceptsEpsilon ifFalse: [   
-            compiler add: 'error ifTrue: [ '.
-            compiler indent.
-            compiler smartRestore: node from: mementoVar.
-            compiler codeReturn: 'failure.'.
-            compiler dedent.
-            compiler add: '].'.
-        ].
-        node returnParsedObjectsAsCollection ifTrue:[
-            compiler add: self retvalVar , ' at: ', idx asString, ' put: ',(elementVars at: idx),'.'.
-        ].
-    ].
+
+    coding value:1.
+
     compiler codeReturn
 
-    "Modified: / 04-06-2015 / 23:47:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 16-06-2015 / 06:38:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitStarAnyNode: node
--- a/compiler/PPCCompiler.st	Mon Jun 15 19:13:49 2015 +0100
+++ b/compiler/PPCCompiler.st	Tue Jun 16 06:45:26 2015 +0100
@@ -218,6 +218,12 @@
     self add: 'self clearError.'.
 !
 
+codeDot
+    self addOnLine:'.'.
+
+    "Created: / 16-06-2015 / 06:09:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeError
     self add: 'self error: ''message notspecified''.'.
 !
@@ -270,6 +276,12 @@
     "Modified: / 10-05-2015 / 07:39:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeIf: condition then: then 
+    self codeIf: condition then: then else: nil
+
+    "Created: / 16-06-2015 / 06:07:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeIf: condition then: then else: else
     currentMethod 
         add: '(';
@@ -285,8 +297,22 @@
             addOnLine:' ifFalse:';
             codeBlock: else.
     ].
+    self codeDot.
 
     "Created: / 01-06-2015 / 22:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-06-2015 / 06:09:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeIfErrorThen: then
+    ^ self codeIf: 'error' then: then else: nil
+
+    "Created: / 16-06-2015 / 06:06:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeIfErrorThen: then else: else
+    ^ self codeIf: 'error' then: then else: else
+
+    "Created: / 16-06-2015 / 06:05:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 codeNextToken
--- a/compiler/PPCMappedActionNode.st	Mon Jun 15 19:13:49 2015 +0100
+++ b/compiler/PPCMappedActionNode.st	Tue Jun 16 06:45:26 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitParser-Parsers'
 !
 
+
 !PPCMappedActionNode methodsFor:'visiting'!
 
 accept: visitor
@@ -17,3 +18,10 @@
     "Created: / 02-06-2015 / 17:27:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PPCMappedActionNode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/PPCCodeGeneratorTest.st	Mon Jun 15 19:13:49 2015 +0100
+++ b/compiler/tests/PPCCodeGeneratorTest.st	Tue Jun 16 06:45:26 2015 +0100
@@ -488,6 +488,45 @@
     "Created: / 15-06-2015 / 18:27:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+testMappedNode3
+    node := ((#letter asParser , #letter asParser) 
+            ==> [:nodes | String with:(nodes first) with:(nodes second) ]) asCompilerTree.
+    node child markForInline.
+
+    self compileTree:node.
+
+    self assert:parser parse:'ab' to:'ab'.
+    self assert:parser parse:'cz' to:'cz'.
+    self assert:parser fail:''.
+
+    "Created: / 16-06-2015 / 06:01:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+testMappedNode4
+    node := ((#letter asParser , #letter asParser) 
+            ==> [:nodes | String with:(nodes first) with:(nodes second) ]) asCompilerTree.
+    node child markForInline.
+
+    self compileTree:node.
+
+    self assert:parser fail:'a'.
+
+    "Created: / 16-06-2015 / 06:13:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+testMappedNode5
+    node := ((#letter asParser , #letter asParser optional) 
+            ==> [:nodes | String with:(nodes first) with:((nodes second) isNil ifTrue:[$?] ifFalse:[nodes second]) ]) asCompilerTree.
+    node child markForInline.
+
+    self compileTree:node.
+
+    self assert:parser parse:'cz' to:'cz'.
+    self assert:parser parse:'c' to:'c?'.
+
+    "Created: / 16-06-2015 / 06:32:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 testMessagePredicate
     | messageNode |
     messageNode := PPCMessagePredicateNode new
--- a/compiler/tests/extras/PPTokenizedExpressionGrammarResource.st	Mon Jun 15 19:13:49 2015 +0100
+++ b/compiler/tests/extras/PPTokenizedExpressionGrammarResource.st	Tue Jun 16 06:45:26 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Extras-Tests-Expressions'
 !
 
+
 !PPTokenizedExpressionGrammarResource methodsFor:'as yet unclassified'!
 
 setUp
@@ -25,3 +26,10 @@
     "Modified: / 26-05-2015 / 07:25:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PPTokenizedExpressionGrammarResource class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+