Skip to content

Commit 6cb105d

Browse files
committed
Do not issue neg line number results for On Error GoTo -1 unless there is a line number -1
This PR also fixes a declaration resolver bug that removed the minus sign from negative line labels.
1 parent 8695c05 commit 6cb105d

File tree

3 files changed

+60
-3
lines changed

3 files changed

+60
-3
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs

Lines changed: 25 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,12 @@
1-
using Antlr4.Runtime;
1+
using System.Linq;
2+
using Antlr4.Runtime;
23
using Antlr4.Runtime.Tree;
34
using Rubberduck.CodeAnalysis.Inspections.Abstract;
45
using Rubberduck.Parsing;
56
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Parsing.Symbols;
68
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.Parsing.VBA.DeclarationCaching;
710
using Rubberduck.Resources.Inspections;
811

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

37+
protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context, DeclarationFinder finder)
38+
{
39+
return !IsOnErrorGotoMinusOne(context.Context)
40+
|| ProcedureHasMinusOneLabel(finder, context);
41+
}
42+
43+
private static bool IsOnErrorGotoMinusOne(ParserRuleContext context)
44+
{
45+
return context is VBAParser.OnErrorStmtContext onErrorStatement
46+
&& "-1".Equals(onErrorStatement.expression()?.GetText().Trim());
47+
}
48+
49+
private static bool ProcedureHasMinusOneLabel(DeclarationFinder finder, QualifiedContext<ParserRuleContext> context)
50+
{
51+
return finder.Members(context.ModuleName, DeclarationType.LineLabel)
52+
.Any(label => label.IdentifierName.Equals("-1")
53+
&& (label.ParentScopeDeclaration
54+
.Context?.GetSelection()
55+
.Contains(context.Context.GetSelection()) ?? false));
56+
}
57+
3458
private class NegativeLineNumberKeywordsListener : InspectionListenerBase<ParserRuleContext>
3559
{
3660
public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -646,8 +646,8 @@ private void AddIdentifierStatementLabelDeclaration(VBAParser.IdentifierStatemen
646646

647647
private void AddLineNumberLabelDeclaration(VBAParser.LineNumberLabelContext context)
648648
{
649-
var statementText = context.numberLiteral().GetText();
650-
var statementSelection = context.numberLiteral().GetSelection();
649+
var statementText = context.GetText().Trim();
650+
var statementSelection = context.GetSelection();
651651

652652
AddDeclaration(
653653
CreateDeclaration(

RubberduckTests/Inspections/ThunderCode/ThunderCodeInspectionTests.cs

Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -224,6 +224,39 @@ GoTo 1
224224
GoTo -5
225225
1
226226
-5:
227+
End Sub")]
228+
[TestCase(1, @"Public Sub Gogo()
229+
On Error GoTo 1
230+
1
231+
-1:
232+
End Sub")]
233+
[TestCase(2, @"Public Sub Gogo()
234+
On Error GoTo -1
235+
1
236+
-1:
237+
End Sub")]
238+
[TestCase(2, @"Public Sub Gogo()
239+
On Error GoTo -1
240+
1:
241+
-1
242+
End Sub")]
243+
[TestCase(0, @"Public Sub Gogo()
244+
On Error GoTo -1
245+
1
246+
End Sub")]
247+
[TestCase(1, @"Public Sub Gogo()
248+
On Error GoTo -2
249+
1
250+
End Sub")]
251+
[TestCase(2, @"Public Sub Gogo()
252+
On Error GoTo -5
253+
1
254+
-5:
255+
End Sub")]
256+
[TestCase(2, @"Public Sub Gogo()
257+
On Error GoTo -5
258+
1:
259+
-5
227260
End Sub")]
228261
public void NegativeLineNumberLabel_ReturnResults(int expectedCount, string inputCode)
229262
{

0 commit comments

Comments
 (0)