Skip to content

Commit 9bd8d08

Browse files
Andrin Meierretailcoder
authored andcommitted
Fix TypeOfIs expression resolver (#1562)
* clean up file statements (fixes #1487) * consider members in supertypes as members of enclosing module (fixes #1489) * remove temp fix (should be fixed with #1489) * add support for Circle and Scale special forms (fixes #1498) * fix foreign names (#1521) * speed up all parsers by using the "two-stage parsing" approach * reenable "function return value not used" inspection * clean up * fix typeof expression resolver
1 parent e063c79 commit 9bd8d08

File tree

2 files changed

+83
-28
lines changed

2 files changed

+83
-28
lines changed

Rubberduck.Parsing/Binding/DefaultBindingContext.cs

Lines changed: 21 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -280,18 +280,6 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
280280
return new ParenthesizedDefaultBinding(expression, expressionBinding);
281281
}
282282

283-
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.TypeofexprContext expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext)
284-
{
285-
// To make the grammar we treat a type-of-is expression as a construct of the form "TYPEOF expression", where expression
286-
// is always "expression IS expression".
287-
var body = (VBAParser.RelationalOpContext)expression.expression();
288-
dynamic booleanExpression = body.expression()[0];
289-
var booleanExpressionBinding = Visit(module, parent, booleanExpression, withBlockVariable, StatementResolutionContext.Undefined);
290-
dynamic typeExpression = body.expression()[1];
291-
var typeExpressionBinding = VisitType(module, parent, typeExpression, withBlockVariable, StatementResolutionContext.Undefined);
292-
return new TypeOfIsDefaultBinding(expression, booleanExpressionBinding, typeExpressionBinding);
293-
}
294-
295283
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.PowOpContext expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext)
296284
{
297285
return VisitBinaryOp(module, parent, expression, expression.expression()[0], expression.expression()[1], withBlockVariable, StatementResolutionContext.Undefined);
@@ -324,9 +312,30 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
324312

325313
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.RelationalOpContext expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext)
326314
{
315+
// To make the grammar we treat a type-of-is expression as a construct of the form "TYPEOF expression", where expression
316+
// is always "expression IS expression".
317+
if (expression.expression()[0] is VBAParser.TypeofexprContext)
318+
{
319+
return VisitTypeOf(module, parent, expression, (VBAParser.TypeofexprContext)expression.expression()[0], expression.expression()[1], withBlockVariable, StatementResolutionContext.Undefined);
320+
}
327321
return VisitBinaryOp(module, parent, expression, expression.expression()[0], expression.expression()[1], withBlockVariable, StatementResolutionContext.Undefined);
328322
}
329323

324+
private IExpressionBinding VisitTypeOf(
325+
Declaration module,
326+
Declaration parent,
327+
VBAParser.RelationalOpContext typeOfIsExpression,
328+
VBAParser.TypeofexprContext typeOfLeftPartExpression,
329+
ParserRuleContext typeExpression,
330+
IBoundExpression withBlockVariable,
331+
StatementResolutionContext statementContext)
332+
{
333+
dynamic booleanExpression = typeOfLeftPartExpression.expression();
334+
var booleanExpressionBinding = Visit(module, parent, booleanExpression, withBlockVariable, StatementResolutionContext.Undefined);
335+
var typeExpressionBinding = VisitType(module, parent, (dynamic)typeExpression, withBlockVariable, StatementResolutionContext.Undefined);
336+
return new TypeOfIsDefaultBinding(typeOfIsExpression, booleanExpressionBinding, typeExpressionBinding);
337+
}
338+
330339
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.LogicalAndOpContext expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext)
331340
{
332341
return VisitBinaryOp(module, parent, expression, expression.expression()[0], expression.expression()[1], withBlockVariable, StatementResolutionContext.Undefined);

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 62 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ private RubberduckParserState Resolve(params string[] classes)
6060
return parser.State;
6161
}
6262

63-
private RubberduckParserState Resolve(params Tuple<string,vbext_ComponentType>[] components)
63+
private RubberduckParserState Resolve(params Tuple<string, vbext_ComponentType>[] components)
6464
{
6565
var builder = new MockVbeBuilder();
6666
var projectBuilder = builder.ProjectBuilder("TestProject", vbext_ProjectProtection.vbext_pp_none);
@@ -107,6 +107,52 @@ End Function
107107
Assert.AreEqual(1, declaration.References.Count(item => item.IsAssignment));
108108
}
109109

110+
[TestMethod]
111+
public void TypeOfIsExpression_BooleanExpressionIsReferenceToLocalVariable()
112+
{
113+
// arrange
114+
var code_class1 = @"
115+
Public Function Foo() As String
116+
Dim a As Object
117+
anything = TypeOf a Is Class2
118+
End Function
119+
";
120+
// We only use the second class as as target of the type expression, its contents don't matter.
121+
var code_class2 = string.Empty;
122+
123+
// act
124+
var state = Resolve(code_class1, code_class2);
125+
126+
// assert
127+
var declaration = state.AllUserDeclarations.Single(item =>
128+
item.DeclarationType == DeclarationType.Variable && item.IdentifierName == "a");
129+
130+
Assert.AreEqual(1, declaration.References.Count());
131+
}
132+
133+
[TestMethod]
134+
public void TypeOfIsExpression_TypeExpressionIsReferenceToClass()
135+
{
136+
// arrange
137+
var code_class1 = @"
138+
Public Function Foo() As String
139+
Dim a As Object
140+
anything = TypeOf a Is Class2
141+
End Function
142+
";
143+
// We only use the second class as as target of the type expression, its contents don't matter.
144+
var code_class2 = string.Empty;
145+
146+
// act
147+
var state = Resolve(code_class1, code_class2);
148+
149+
// assert
150+
var declaration = state.AllUserDeclarations.Single(item =>
151+
item.DeclarationType == DeclarationType.ClassModule && item.IdentifierName == "Class2");
152+
153+
Assert.AreEqual(1, declaration.References.Count());
154+
}
155+
110156
[TestMethod]
111157
public void FunctionCall_IsReferenceToFunctionDeclaration()
112158
{
@@ -285,18 +331,18 @@ Public foo As Integer
285331
";
286332
var class1 = Tuple.Create(code_class1, vbext_ComponentType.vbext_ct_ClassModule);
287333
var class2 = Tuple.Create(code_class2, vbext_ComponentType.vbext_ct_ClassModule);
288-
334+
289335
// act
290336
var state = Resolve(class1, class2);
291-
337+
292338
// assert
293339
var declaration = state.AllUserDeclarations.Single(item => item.DeclarationType == DeclarationType.Variable && item.IdentifierName == "foo");
294-
340+
295341
var reference = declaration.References.SingleOrDefault(item => item.IsAssignment);
296342
Assert.IsNull(reference);
297343
}
298344

299-
[TestMethod]
345+
[TestMethod]
300346
public void PublicVariableCall_IsReferenceToVariableDeclaration()
301347
{
302348
// arrange
@@ -311,7 +357,7 @@ Public foo As Integer
311357
";
312358
// act
313359
var state = Resolve(
314-
Tuple.Create(code_class1, vbext_ComponentType.vbext_ct_ClassModule),
360+
Tuple.Create(code_class1, vbext_ComponentType.vbext_ct_ClassModule),
315361
Tuple.Create(code_class2, vbext_ComponentType.vbext_ct_StdModule));
316362

317363
// assert
@@ -451,7 +497,7 @@ End Sub
451497
var declaration = state.AllUserDeclarations.Single(item =>
452498
item.DeclarationType == DeclarationType.Parameter && item.IdentifierName == "foo");
453499

454-
Assert.IsNotNull(declaration.References.SingleOrDefault(item =>
500+
Assert.IsNotNull(declaration.References.SingleOrDefault(item =>
455501
item.ParentScoping.IdentifierName == "DoSomething"));
456502
}
457503

@@ -768,7 +814,7 @@ End Sub
768814

769815
// assert
770816
var declaration = state.AllUserDeclarations.Single(item =>
771-
item.DeclarationType == DeclarationType.Parameter
817+
item.DeclarationType == DeclarationType.Parameter
772818
&& item.IdentifierName == "values"
773819
&& item.IsArray);
774820

@@ -927,7 +973,7 @@ End Sub
927973
&& item.ParentDeclaration.IdentifierName == "FooBarBaz");
928974

929975
Assert.IsNotNull(declaration.References.SingleOrDefault(item =>
930-
!item.IsAssignment
976+
!item.IsAssignment
931977
&& item.ParentScoping.IdentifierName == "DoSomething"
932978
&& item.ParentScoping.DeclarationType == DeclarationType.Procedure));
933979

@@ -984,7 +1030,7 @@ End Sub
9841030
item.DeclarationType == DeclarationType.Enumeration
9851031
&& item.IdentifierName == "FooBarBaz");
9861032

987-
Assert.IsNotNull(declaration.References.SingleOrDefault(item =>
1033+
Assert.IsNotNull(declaration.References.SingleOrDefault(item =>
9881034
item.ParentScoping.IdentifierName == "DoSomething"
9891035
&& item.ParentScoping.DeclarationType == DeclarationType.Procedure));
9901036
}
@@ -1029,7 +1075,7 @@ Private Function Foo(ByVal bar As Integer)
10291075

10301076
var state = Resolve(code);
10311077

1032-
var declaration = state.AllUserDeclarations.Single(item =>
1078+
var declaration = state.AllUserDeclarations.Single(item =>
10331079
item.DeclarationType == DeclarationType.Variable
10341080
&& item.IsArray
10351081
&& item.ParentScopeDeclaration.IdentifierName == "DoSomething");
@@ -1212,7 +1258,7 @@ End Sub
12121258
if (declaration.Project.Name != declaration.AsTypeName)
12131259
{
12141260
Assert.Inconclusive("variable should be named after project.");
1215-
}
1261+
}
12161262
var usages = declaration.References;
12171263

12181264
Assert.AreEqual(2, usages.Count());
@@ -1239,7 +1285,7 @@ End Sub
12391285
item.DeclarationType == DeclarationType.UserDefinedTypeMember
12401286
&& item.IdentifierName == "Foo");
12411287

1242-
var usages = declaration.References.Where(item =>
1288+
var usages = declaration.References.Where(item =>
12431289
item.ParentScoping.IdentifierName == "DoSomething");
12441290

12451291
Assert.AreEqual(1, usages.Count());
@@ -1272,12 +1318,12 @@ End Sub
12721318
&& item.AsTypeName == item.Project.Name
12731319
&& item.IdentifierName == item.ParentDeclaration.IdentifierName);
12741320

1275-
var usages = declaration.References.Where(item =>
1321+
var usages = declaration.References.Where(item =>
12761322
item.ParentScoping.IdentifierName == "DoSomething");
12771323

12781324
Assert.AreEqual(2, usages.Count());
12791325
}
1280-
1326+
12811327
[TestMethod]
12821328
public void GivenUDT_NamedAfterModule_LocalAsTypeResolvesToUDT()
12831329
{
@@ -1303,7 +1349,7 @@ End Sub
13031349
item.DeclarationType == DeclarationType.UserDefinedType
13041350
&& item.IdentifierName == item.ComponentName);
13051351

1306-
var usages = declaration.References.Where(item =>
1352+
var usages = declaration.References.Where(item =>
13071353
item.ParentScoping.IdentifierName == "DoSomething");
13081354

13091355
Assert.AreEqual(1, usages.Count());

0 commit comments

Comments
 (0)