Skip to content

Commit b8b0b7d

Browse files
committed
Allow multiple WithEvents declarations in variable list. Closes #4591
1 parent 27f3dab commit b8b0b7d

File tree

4 files changed

+76
-3
lines changed

4 files changed

+76
-3
lines changed

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -549,9 +549,9 @@ upperBound : constantExpression;
549549

550550
constantExpression : expression;
551551

552-
variableStmt : (DIM | STATIC | visibility) whiteSpace (WITHEVENTS whiteSpace)? variableListStmt;
552+
variableStmt : (DIM | STATIC | visibility) whiteSpace variableListStmt;
553553
variableListStmt : variableSubStmt (whiteSpace? COMMA whiteSpace? variableSubStmt)*;
554-
variableSubStmt : identifier (whiteSpace? LPAREN whiteSpace? (subscripts whiteSpace?)? RPAREN)? (whiteSpace asTypeClause)?;
554+
variableSubStmt : (WITHEVENTS whiteSpace)? identifier (whiteSpace? LPAREN whiteSpace? (subscripts whiteSpace?)? RPAREN)? (whiteSpace asTypeClause)?;
555555

556556
whileWendStmt :
557557
WHILE whiteSpace expression endOfStatement

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -685,7 +685,7 @@ public override void EnterVariableSubStmt(VBAParser.VariableSubStmtContext conte
685685
? Tokens.Variant
686686
: asTypeClause.type().GetText()
687687
: SymbolList.TypeHintToTypeName[typeHint];
688-
var withEvents = parent.WITHEVENTS() != null;
688+
var withEvents = context.WITHEVENTS() != null;
689689
var isAutoObject = asTypeClause != null && asTypeClause.NEW() != null;
690690
bool isArray = context.LPAREN() != null;
691691
AddDeclaration(

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3517,6 +3517,20 @@ End Type
35173517
AssertTree(parseResult.Item1, parseResult.Item2, "//unrestrictedIdentifier", matches => matches.Count == 1);
35183518
}
35193519

3520+
3521+
[Test]
3522+
[Category("Parser")]
3523+
[TestCase("Private WithEvents foo As EventSource, WithEvents bar As EventSource", 2)]
3524+
[TestCase("Private WithEvents foo As EventSource, bar As EventSource", 2)]
3525+
[TestCase("Private foo As EventSource, WithEvents bar As EventSource", 2)]
3526+
[TestCase("Private foo As EventSource, bar As EventSource", 2)]
3527+
[TestCase("Private WithEvents foo As EventSource", 1)]
3528+
public void WithEventsInVariableList(string code, int count)
3529+
{
3530+
var parseResult = Parse(code);
3531+
AssertTree(parseResult.Item1, parseResult.Item2, "//variableSubStmt", matches => matches.Count == count);
3532+
}
3533+
35203534
private Tuple<VBAParser, ParserRuleContext> Parse(string code, PredictionMode predictionMode = null)
35213535
{
35223536
var stream = new AntlrInputStream(code);
Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using System.Runtime.ExceptionServices;
4+
using System.Threading;
5+
using NUnit.Framework;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.VBEditor;
8+
using Rubberduck.VBEditor.SafeComWrappers;
9+
using RubberduckTests.Mocks;
10+
11+
namespace RubberduckTests.Symbols
12+
{
13+
[TestFixture]
14+
public class VariableDeclarationTests
15+
{
16+
[Test]
17+
[TestCase("Private WithEvents foo As EventSource", true)]
18+
[TestCase("Private foo As EventSource", false)]
19+
[Category("Resolver")]
20+
public void WithEventsIsResolvedCorrectly(string declaration, bool withEvents)
21+
{
22+
var variables = ArrangeAndGetVariableDeclarations(ComponentType.ClassModule, declaration);
23+
var foo = variables.Single();
24+
Assert.AreEqual(withEvents, foo.IsWithEvents);
25+
}
26+
27+
[Test]
28+
[TestCase("Private WithEvents {0} As EventSource, WithEvents {1} As EventSource", "foo", "bar", true, true)]
29+
[TestCase("Private {0} As EventSource, WithEvents {1} As EventSource", "foo", "bar", false, true)]
30+
[TestCase("Private WithEvents {0} As EventSource, {1} As EventSource", "foo", "bar", true, false)]
31+
[TestCase("Private {0} As EventSource, {1} As EventSource", "foo", "bar", false, false)]
32+
[Category("Resolver")]
33+
public void WithEventsIsResolvedCorrectlyVariableList(string template, string first, string second, bool firstEvents, bool secondEvents)
34+
{
35+
var variables = ArrangeAndGetVariableDeclarations(ComponentType.ClassModule, string.Format(template, first, second));
36+
Assert.AreEqual(2, variables.Count);
37+
Assert.AreEqual(firstEvents, variables.Single(variable => variable.IdentifierName.Equals(first)).IsWithEvents);
38+
Assert.AreEqual(secondEvents, variables.Single(variable => variable.IdentifierName.Equals(second)).IsWithEvents);
39+
}
40+
41+
private List<VariableDeclaration> ArrangeAndGetVariableDeclarations(ComponentType moduleType, string code)
42+
{
43+
var vbe = new MockVbeBuilder()
44+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
45+
.AddComponent("UnderTest", moduleType, code, new Selection(1, 1))
46+
.AddProjectToVbeBuilder()
47+
.Build();
48+
49+
using (var parser = MockParser.Create(vbe.Object))
50+
{
51+
parser.Parse(new CancellationTokenSource());
52+
53+
return parser.State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
54+
.Cast<VariableDeclaration>()
55+
.ToList();
56+
}
57+
}
58+
}
59+
}

0 commit comments

Comments
 (0)