Skip to content

Commit

Permalink
Merge pull request #5594 from MDoerner/FixNegLineNumberDetectedInGoTo…
Browse files Browse the repository at this point in the history
…NegOne

Fix neg line number detected in legitimate go to neg one
  • Loading branch information
bclothier committed Oct 24, 2020
2 parents 6e7c82a + c5ec039 commit 9f05c4e
Show file tree
Hide file tree
Showing 3 changed files with 60 additions and 3 deletions.
@@ -1,9 +1,12 @@
using Antlr4.Runtime;
using System.Linq;
using Antlr4.Runtime;
using Antlr4.Runtime.Tree;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
Expand Down Expand Up @@ -31,6 +34,27 @@ protected override string ResultDescription(QualifiedContext<ParserRuleContext>
return InspectionResults.NegativeLineNumberInspection.ThunderCodeFormat();
}

protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context, DeclarationFinder finder)
{
return !IsOnErrorGotoMinusOne(context.Context)
|| ProcedureHasMinusOneLabel(finder, context);
}

private static bool IsOnErrorGotoMinusOne(ParserRuleContext context)
{
return context is VBAParser.OnErrorStmtContext onErrorStatement
&& "-1".Equals(onErrorStatement.expression()?.GetText().Trim());
}

private static bool ProcedureHasMinusOneLabel(DeclarationFinder finder, QualifiedContext<ParserRuleContext> context)
{
return finder.Members(context.ModuleName, DeclarationType.LineLabel)
.Any(label => label.IdentifierName.Equals("-1")
&& (label.ParentScopeDeclaration
.Context?.GetSelection()
.Contains(context.Context.GetSelection()) ?? false));
}

private class NegativeLineNumberKeywordsListener : InspectionListenerBase<ParserRuleContext>
{
public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)
Expand Down
Expand Up @@ -646,8 +646,8 @@ private void AddIdentifierStatementLabelDeclaration(VBAParser.IdentifierStatemen

private void AddLineNumberLabelDeclaration(VBAParser.LineNumberLabelContext context)
{
var statementText = context.numberLiteral().GetText();
var statementSelection = context.numberLiteral().GetSelection();
var statementText = context.GetText().Trim();
var statementSelection = context.GetSelection();

AddDeclaration(
CreateDeclaration(
Expand Down
Expand Up @@ -224,6 +224,39 @@ GoTo 1
GoTo -5
1
-5:
End Sub")]
[TestCase(1, @"Public Sub Gogo()
On Error GoTo 1
1
-1:
End Sub")]
[TestCase(2, @"Public Sub Gogo()
On Error GoTo -1
1
-1:
End Sub")]
[TestCase(2, @"Public Sub Gogo()
On Error GoTo -1
1:
-1
End Sub")]
[TestCase(0, @"Public Sub Gogo()
On Error GoTo -1
1
End Sub")]
[TestCase(1, @"Public Sub Gogo()
On Error GoTo -2
1
End Sub")]
[TestCase(2, @"Public Sub Gogo()
On Error GoTo -5
1
-5:
End Sub")]
[TestCase(2, @"Public Sub Gogo()
On Error GoTo -5
1:
-5
End Sub")]
public void NegativeLineNumberLabel_ReturnResults(int expectedCount, string inputCode)
{
Expand Down

0 comments on commit 9f05c4e

Please sign in to comment.