Skip to content

Commit 0a47a0d

Browse files
authored
Merge pull request #1887 from Hosch250/Issue1873
Fix the line label rule(s) in the grammar. Add tests.
2 parents 13e5fba + e340b0a commit 0a47a0d

File tree

9 files changed

+3030
-3042
lines changed

9 files changed

+3030
-3042
lines changed

Rubberduck.Parsing/Grammar/VBAParser.cs

Lines changed: 2966 additions & 2992 deletions
Large diffs are not rendered by default.

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -546,10 +546,9 @@ complexType :
546546

547547
fieldLength : MULT whiteSpace? (numberLiteral | identifierValue);
548548

549-
statementLabelDefinition : statementLabel whiteSpace? COLON;
550-
statementLabel : identifierStatementLabel | lineNumberLabel;
551-
identifierStatementLabel : unrestrictedIdentifier;
552-
lineNumberLabel : numberLiteral;
549+
statementLabelDefinition : identifierStatementLabel | lineNumberLabel;
550+
identifierStatementLabel : unrestrictedIdentifier whiteSpace? COLON;
551+
lineNumberLabel : numberLiteral whiteSpace? COLON?;
553552

554553
numberLiteral : HEXLITERAL | OCTLITERAL | FLOATLITERAL | INTEGERLITERAL;
555554

Rubberduck.Parsing/Grammar/VBAParserBaseListener.cs

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -3140,19 +3140,6 @@ public virtual void EnterVariableListStmt([NotNull] VBAParser.VariableListStmtCo
31403140
/// <param name="context">The parse tree.</param>
31413141
public virtual void ExitVariableListStmt([NotNull] VBAParser.VariableListStmtContext context) { }
31423142

3143-
/// <summary>
3144-
/// Enter a parse tree produced by <see cref="VBAParser.statementLabel"/>.
3145-
/// <para>The default implementation does nothing.</para>
3146-
/// </summary>
3147-
/// <param name="context">The parse tree.</param>
3148-
public virtual void EnterStatementLabel([NotNull] VBAParser.StatementLabelContext context) { }
3149-
/// <summary>
3150-
/// Exit a parse tree produced by <see cref="VBAParser.statementLabel"/>.
3151-
/// <para>The default implementation does nothing.</para>
3152-
/// </summary>
3153-
/// <param name="context">The parse tree.</param>
3154-
public virtual void ExitStatementLabel([NotNull] VBAParser.StatementLabelContext context) { }
3155-
31563143
/// <summary>
31573144
/// Enter a parse tree produced by <see cref="VBAParser.addOp"/>.
31583145
/// <para>The default implementation does nothing.</para>

Rubberduck.Parsing/Grammar/VBAParserBaseVisitor.cs

Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -2661,17 +2661,6 @@ public partial class VBAParserBaseVisitor<Result> : AbstractParseTreeVisitor<Res
26612661
/// <return>The visitor result.</return>
26622662
public virtual Result VisitVariableListStmt([NotNull] VBAParser.VariableListStmtContext context) { return VisitChildren(context); }
26632663

2664-
/// <summary>
2665-
/// Visit a parse tree produced by <see cref="VBAParser.statementLabel"/>.
2666-
/// <para>
2667-
/// The default implementation returns the result of calling <see cref="AbstractParseTreeVisitor{Result}.VisitChildren(IRuleNode)"/>
2668-
/// on <paramref name="context"/>.
2669-
/// </para>
2670-
/// </summary>
2671-
/// <param name="context">The parse tree.</param>
2672-
/// <return>The visitor result.</return>
2673-
public virtual Result VisitStatementLabel([NotNull] VBAParser.StatementLabelContext context) { return VisitChildren(context); }
2674-
26752664
/// <summary>
26762665
/// Visit a parse tree produced by <see cref="VBAParser.addOp"/>.
26772666
/// <para>

Rubberduck.Parsing/Grammar/VBAParserListener.cs

Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -2736,17 +2736,6 @@ public interface IVBAParserListener : IParseTreeListener {
27362736
/// <param name="context">The parse tree.</param>
27372737
void ExitVariableListStmt([NotNull] VBAParser.VariableListStmtContext context);
27382738

2739-
/// <summary>
2740-
/// Enter a parse tree produced by <see cref="VBAParser.statementLabel"/>.
2741-
/// </summary>
2742-
/// <param name="context">The parse tree.</param>
2743-
void EnterStatementLabel([NotNull] VBAParser.StatementLabelContext context);
2744-
/// <summary>
2745-
/// Exit a parse tree produced by <see cref="VBAParser.statementLabel"/>.
2746-
/// </summary>
2747-
/// <param name="context">The parse tree.</param>
2748-
void ExitStatementLabel([NotNull] VBAParser.StatementLabelContext context);
2749-
27502739
/// <summary>
27512740
/// Enter a parse tree produced by the <c>addOp</c>
27522741
/// labeled alternative in <see cref="VBAParser.expression"/>.

Rubberduck.Parsing/Grammar/VBAParserVisitor.cs

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1742,13 +1742,6 @@ public interface IVBAParserVisitor<Result> : IParseTreeVisitor<Result> {
17421742
/// <return>The visitor result.</return>
17431743
Result VisitVariableListStmt([NotNull] VBAParser.VariableListStmtContext context);
17441744

1745-
/// <summary>
1746-
/// Visit a parse tree produced by <see cref="VBAParser.statementLabel"/>.
1747-
/// </summary>
1748-
/// <param name="context">The parse tree.</param>
1749-
/// <return>The visitor result.</return>
1750-
Result VisitStatementLabel([NotNull] VBAParser.StatementLabelContext context);
1751-
17521745
/// <summary>
17531746
/// Visit a parse tree produced by the <c>addOp</c>
17541747
/// labeled alternative in <see cref="VBAParser.expression"/>.

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -699,14 +699,22 @@ public override void EnterArgList(VBAParser.ArgListContext context)
699699

700700
public override void EnterStatementLabelDefinition(VBAParser.StatementLabelDefinitionContext context)
701701
{
702+
var statementText = context.identifierStatementLabel() != null
703+
? context.identifierStatementLabel().unrestrictedIdentifier().GetText()
704+
: context.lineNumberLabel().numberLiteral().GetText();
705+
706+
var statementSelection = context.identifierStatementLabel() != null
707+
? context.identifierStatementLabel().unrestrictedIdentifier().GetSelection()
708+
: context.lineNumberLabel().numberLiteral().GetSelection();
709+
702710
AddDeclaration(
703711
CreateDeclaration(
704-
context.statementLabel().GetText(),
712+
statementText,
705713
null,
706714
Accessibility.Private,
707715
DeclarationType.LineLabel,
708716
context,
709-
context.statementLabel().GetSelection(),
717+
statementSelection,
710718
true,
711719
null,
712720
null));

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 49 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -245,7 +245,7 @@ End Sub
245245
}
246246

247247
[TestMethod]
248-
public void SingleLineIfStatementLabel_IsReferenceToLabel()
248+
public void SingleLineIfStatementLabel_IsReferenceToLabel_NumberLabelHasColon()
249249
{
250250
// arrange
251251
var code = @"
@@ -266,6 +266,54 @@ End Sub
266266
Assert.AreEqual("DoSomething", reference.ParentScoping.IdentifierName);
267267
}
268268

269+
[TestMethod]
270+
public void SingleLineIfStatementLabel_IsReferenceToLabel_NumberLabelNoColon()
271+
{
272+
// arrange
273+
var code = @"
274+
Public Sub DoSomething()
275+
Dim fizz As Integer
276+
fizz = 5
277+
If fizz = 5 Then Exit Sub
278+
279+
If True Then 5
280+
5
281+
End Sub
282+
";
283+
// act
284+
var state = Resolve(code);
285+
286+
// assert
287+
var declaration = state.AllUserDeclarations.Single(item =>
288+
item.DeclarationType == DeclarationType.LineLabel && item.IdentifierName == "5");
289+
290+
var reference = declaration.References.SingleOrDefault();
291+
Assert.IsNotNull(reference);
292+
Assert.AreEqual("DoSomething", reference.ParentScoping.IdentifierName);
293+
}
294+
295+
[TestMethod]
296+
public void SingleLineIfStatementLabel_IsReferenceToLabel_IdentifierLabel()
297+
{
298+
// arrange
299+
var code = @"
300+
Public Sub DoSomething()
301+
If True Then GoTo foo
302+
foo:
303+
End Sub
304+
";
305+
// act
306+
var state = Resolve(code);
307+
308+
// assert
309+
var declaration = state.AllUserDeclarations.Single(item =>
310+
item.DeclarationType == DeclarationType.LineLabel && item.IdentifierName == "foo");
311+
312+
var reference = declaration.References.SingleOrDefault();
313+
Assert.IsNotNull(reference);
314+
Assert.AreEqual("DoSomething", reference.ParentScoping.IdentifierName);
315+
}
316+
269317
[TestMethod]
270318
public void ProjectUdtSameNameFirstProjectThenUdt_FirstReferenceIsToProject()
271319
{

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -776,9 +776,10 @@ public void TestLineLabelStatement()
776776
Sub Test()
777777
a:
778778
10:
779+
15
779780
End Sub";
780781
var parseResult = Parse(code);
781-
AssertTree(parseResult.Item1, parseResult.Item2, "//statementLabelDefinition", matches => matches.Count == 2);
782+
AssertTree(parseResult.Item1, parseResult.Item2, "//statementLabelDefinition", matches => matches.Count == 3);
782783
}
783784

784785
[TestMethod]

0 commit comments

Comments
 (0)