Some more work on error recovery.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 20 Sep 2013 01:55:35 +0100
changeset 96 12fe1a59dfd1
parent 95 78bcbdfd9361
child 97 062cd1535107
Some more work on error recovery.
SmallSense__SmalltalkParser.st
SmallSense__SmalltalkParserTests.st
--- a/SmallSense__SmalltalkParser.st	Wed Sep 18 02:36:36 2013 +0100
+++ b/SmallSense__SmalltalkParser.st	Fri Sep 20 01:55:35 2013 +0100
@@ -3,7 +3,7 @@
 "{ NameSpace: SmallSense }"
 
 SyntaxHighlighter subclass:#SmalltalkParser
-	instanceVariableNames:'error'
+	instanceVariableNames:'errorRecovery error'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SmallSense-Smalltalk'
@@ -31,6 +31,15 @@
     "Created: / 27-11-2011 / 09:45:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!SmalltalkParser methodsFor:'initialization'!
+
+initialize
+    super initialize.
+    errorRecovery := true
+
+    "Created: / 19-09-2013 / 11:25:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !SmalltalkParser methodsFor:'parsing'!
 
 blockStatementList
@@ -141,6 +150,83 @@
 
     "Created: / 14-12-1999 / 15:11:37 / cg"
     "Created: / 09-07-2011 / 22:23:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+statement
+    "parse a statement; return a node-tree or #Error.
+
+     statement ::= '^' expression
+                   | PRIMITIVECODE
+                   | expression
+    "
+
+    |expr node lnr code pos|
+
+    pos := tokenPosition.
+
+    (tokenType == $^) ifTrue:[
+        ^ self returnStatement
+    ].
+
+    (tokenType == #Primitive) ifTrue:[
+        code := tokenValue.
+        node := PrimitiveNode code:code.
+        node startPosition: tokenPosition endPosition: source position + 1.
+        self nextToken.
+        node isOptional ifFalse:[
+            hasNonOptionalPrimitiveCode := true
+        ].
+        hasPrimitiveCode := true.
+        ^ node
+    ].
+
+    (tokenType == #EOF) ifTrue:[
+        currentBlock notNil ifTrue:[
+            self syntaxError:'missing '']'' at end of block'.
+            errorRecovery ifTrue:[
+                tokenType := $].
+                ^ error.
+            ].
+        ] ifFalse:[
+            self syntaxError:'period after last statement'.
+            errorRecovery ifTrue:[
+                tokenType := $..
+                ^ error.
+            ].  
+        ].
+        ^ #Error
+    ].
+
+    (tokenType == $.) ifTrue:[
+        (parserFlags allowEmptyStatements
+        or:[parserFlags allowSqueakExtensions == true]) ifTrue:[
+            "/ allow empty statement
+            self warnAboutEmptyStatement.
+            node := StatementNode expression:nil.
+            node startPosition:pos.
+            ^ node
+        ].
+    ].
+
+    lnr := tokenLineNr.
+
+    expr := self expression.
+    (expr == #Error) ifTrue:[^ #Error].
+
+"/    classToCompileFor notNil ifTrue:[
+"/        currentBlock isNil ifTrue:[
+"/            expr isPrimary ifTrue:[
+"/                self warning:'useless computation - missing ^ ?'
+"/            ]
+"/        ]
+"/    ].
+
+    node := StatementNode expression:expr.
+    parserFlags fullLineNumberInfo ifTrue:[node lineNumber:lnr].
+    node startPosition:pos.
+    ^ node
+
+    "Created: / 19-09-2013 / 11:32:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !SmalltalkParser methodsFor:'parsing-expressions'!
@@ -168,7 +254,7 @@
         "/ would be parsed as unary message foo; detect this here, instead of high up in the calling hierarchy,
         "/ where it is difficult to provide a reasonable error message
         tokenType == #':=' ifTrue:[
-            | positionOfPeriod exprLast |
+            | positionOfPeriod exprLast exprLastParent |
 
             "/ Find the very last unary send node, Consider:
             "/    x := 2
@@ -180,8 +266,10 @@
             "/    x := 2 between: 0 and: self max
             "/    y := false  
 
+            exprLastParent := nil.
             exprLast := expr.
             [ exprLast isMessage and: [ exprLast isUnaryMessage not ] ] whileTrue:[
+                exprLastParent := exprLast.
                 exprLast := exprLast args last.
             ].
             (exprLast isMessage and: [ exprLast isUnaryMessage ] ) ifTrue:[
@@ -189,6 +277,13 @@
             ].
             positionOfPeriod notNil ifTrue:[
                 "/Try to recover
+                "/ Strip the last unary message whose selector is actually a variable name..."
+                exprLastParent notNil ifTrue:[
+                    exprLastParent args at: exprLastParent args size put: exprLast receiver.
+                ] ifFalse:[
+                    "/ no nesting, the expr itself is errorneouts...    
+                     expr := expr receiver.
+                ].
                 expr := ParseErrorNode new
                         startPosition:expr startPosition endPosition: positionOfPeriod - 1;
                         errorString: ('":=" unexpected. Probably missing "." in previous expression.');
@@ -203,7 +298,7 @@
     ^ expr
 
     "Created: / 16-09-2013 / 17:23:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 16-09-2013 / 23:18:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 19-09-2013 / 11:47:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 primary
--- a/SmallSense__SmalltalkParserTests.st	Wed Sep 18 02:36:36 2013 +0100
+++ b/SmallSense__SmalltalkParserTests.st	Fri Sep 20 01:55:35 2013 +0100
@@ -843,6 +843,145 @@
     "Created: / 20-02-2011 / 18:54:11 / Jakub <zelenja7@fel.cvut.cz>"
 !
 
+test45
+    |collector|
+    collector := self 
+                doForSource:'
+                    | a b |
+                    a := [self pr   
+                    b := self navigationState isFullClassSourceBrowser
+                                                    or:[self isJavaMethod and:[JavaMethod showFullSource]].     
+                    '.
+    self assert:collector notNil.
+    self assert:collector tree notNil.
+    self assert:collector tree expression isAssignment.
+    self assert:collector tree expression expression isBlock.
+    self assert:collector tree expression expression statements isStatement.
+    self assert:collector tree expression expression statements expression isErrorNode.
+    self assert:collector tree expression expression statements expression children first isMessage.
+    self assert:collector tree expression expression statements expression children first selector = 'pr'.
+
+    "Created: / 19-09-2013 / 11:19:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test46
+    |collector|
+    collector := self 
+                doForSource:'
+                    | a b |
+                    a := a and:[self pr   
+                    b := self navigationState isFullClassSourceBrowser
+                                                    or:[self isJavaMethod and:[JavaMethod showFullSource]].     
+                    '.
+    self assert:collector notNil.
+    self assert:collector tree notNil.
+    self assert:collector tree expression isAssignment.
+    self assert:collector tree expression expression isMessage.
+    self assert:collector tree expression expression args last isBlock.
+    self assert:collector tree expression expression args last statements expression isErrorNode.
+    self assert:collector tree expression expression args last statements expression children first isMessage.
+    self assert:collector tree expression expression args last statements expression children first selector = 'pr'.
+
+    "Created: / 19-09-2013 / 11:48:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test47
+    |collector|
+    collector := self 
+                doForSource:'
+                    |mthd doScrollToTop code codeView doAutoFormat doSyntaxColoring doUpdateCode prevMthd doShowFullClassSource |
+
+                    doAutoFormat := self doAutoFormat value and:[RBFormatter notNil and:[mthd prog
+                    doShowFullClassSource := self navigationState isFullClassSourceBrowser
+                                                or:[mthd isJavaMethod and:[JavaMethod showFullSource]].
+                    doUpdateCode := true.
+                    codeView := self codeView.
+                    self assert:codeView notNil.
+
+                    code := self sourceOfMethod:mthd.
+                    code isText ifTrue:[
+                        "/Already done...
+                        doSyntaxColoring := false.
+                    ] ifFalse:[
+                        "/Do no coloring here if CodeView2 is used,
+                        "/since CodeView2 itself cares about the coloring!!
+                        "/Not working correctly -> do the coloring until fixed in CodeView2
+                        "/JV: Then make a bug report because otherwise it won''t be
+                        "/    ever fixed.
+                        "(UserPreferences current useCodeView2In: #Browser)"false ifTrue:[
+                            doSyntaxColoring := code size < 2000
+                        ] ifFalse:[
+                            doSyntaxColoring := self doSyntaxColoring value == true.
+                        ].
+                    ].
+
+
+                    doAutoFormat ifTrue:[
+                        Error catch:[
+                            code := RBFormatter format:code
+                        ].
+                    ].
+
+                    doShowFullClassSource ifTrue:[
+                        "As whole class source coce is shown,
+                         there is no need to set codeview''s content if previous method
+                         belonged to the same class. Code is already shown, we need only
+                         to scrool to it..."
+                        "hmm...hmm...how implement it in a better, more generic way?"        
+                        mthd isSynthetic not ifTrue:[
+                            prevMthd := navigationState lastMethodShownInCodeView.
+                            prevMthd notNil ifTrue:[
+                                doUpdateCode := prevMthd isSynthetic or:[mthd mclass ~~ prevMthd mclass]
+                            ].
+
+
+                        ].
+                    ].
+                    doUpdateCode ifTrue:[
+                        doSyntaxColoring ifTrue:[
+                            "/ immediate coloring, if code is not too large;
+                            "/ otherwise, do it in the background.
+                            code size < 2000 " 10000 " ifTrue:[
+                                Error handle:[:ex |
+                                    Transcript showCR:''error in syntaxHighlighter: '',ex description.
+                                ] do:[
+                                    code := self syntaxHighlightedCodeFor:code method:mthd.
+                                ].
+                            ] ifFalse:[
+                                self enqueueDelayedStartSyntaxHighlightProcess.
+                            ].
+
+                            [
+                                codeView modifiedChannel removeDependent:self.
+                                codeView modified:false.
+                                self showCode:code scrollToTop:doScrollToTop.
+                            ] ensure:[
+                                codeView modifiedChannel addDependent:self.
+                            ]
+                        ] ifFalse:[
+                            self showCode:code scrollToTop:doScrollToTop.
+                        ].
+                    ].
+                    navigationState lastMethodShownInCodeView: mthd.
+
+                    "/ scroll, for file-based classes (java, ruby, etc.)
+                    doShowFullClassSource ifTrue:[
+                        mthd sourceLineNumber ~~ 1 ifTrue:[
+                            doScrollToTop ifTrue:[ "/ifFalse:[
+                                codeView scrollToLine:mthd sourceLineNumber
+                            ]
+                        ].
+                    ].
+                    self codeAspect:(code ifNil:[nil] ifNotNil:[SyntaxHighlighter codeAspectMethod]).
+                    self normalLabel.
+                    self updatePackageInfoForMethod:mthd.'.
+
+    self assert: collector tree notNil.
+
+    "Created: / 19-09-2013 / 11:54:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-09-2013 / 00:58:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 test5
     |collector|
 
@@ -953,6 +1092,11 @@
 
 !SmalltalkParserTests class methodsFor:'documentation'!
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: SmallSenseParserTests.st 7694 2011-04-04 19:53:25Z vranyj1 $'
 ! !