Skip to content

Commit 21ba584

Browse files
committed
Test for anonymous object access in With blocks. Closes #3343
1 parent c7cecf6 commit 21ba584

File tree

2 files changed

+78
-6
lines changed

2 files changed

+78
-6
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Grammar;
56
using Rubberduck.Parsing.Inspections.Abstract;
67
using Rubberduck.Resources.Inspections;
78
using Rubberduck.Parsing.Symbols;
@@ -23,12 +24,19 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2324
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
2425
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
2526
.SelectMany(decl => decl.References).ToList();
26-
return from access in unresolved
27-
let callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext))
28-
where callingContext != null
29-
select new DeclarationInspectionResult(this,
30-
string.Format(InspectionResults.MemberNotOnInterfaceInspection, access.IdentifierName, callingContext.Declaration.AsTypeDeclaration.IdentifierName),
31-
access);
27+
return unresolved
28+
.Select(access => new
29+
{
30+
access,
31+
callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext)
32+
|| (access.CallingContext is VBAParser.NewExprContext &&
33+
usage.Context.Parent.Parent.Equals(access.CallingContext))
34+
)
35+
})
36+
.Where(memberAccess => memberAccess.callingContext != null)
37+
.Select(memberAccess => new DeclarationInspectionResult(this,
38+
string.Format(InspectionResults.MemberNotOnInterfaceInspection, memberAccess.access.IdentifierName,
39+
memberAccess.callingContext.Declaration.AsTypeDeclaration.IdentifierName), memberAccess.access));
3240
}
3341
}
3442
}

RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs

Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -255,6 +255,70 @@ Dim dict As Dictionary
255255
}
256256
}
257257

258+
#region https://github.com/rubberduck-vba/Rubberduck/issues/3343
259+
260+
[Test]
261+
[Category("Inspections")]
262+
public void MemberNotOnInterface_WithNewReturnsResult()
263+
{
264+
const string inputCode =
265+
@"Sub Foo()
266+
With New Dictionary
267+
Debug.Print .FooBar
268+
End With
269+
End Sub";
270+
271+
using (var state = ArrangeParserAndParse(inputCode))
272+
{
273+
var inspection = new MemberNotOnInterfaceInspection(state);
274+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
275+
276+
Assert.AreEqual(1, inspectionResults.Count());
277+
}
278+
}
279+
280+
[Test]
281+
[Category("Inspections")]
282+
public void MemberNotOnInterface_DoesNotReturnResult_WithNewBlockBangNotation()
283+
{
284+
const string inputCode =
285+
@"Sub Foo()
286+
With New Dictionary
287+
!FooBar = 42
288+
End With
289+
End Sub";
290+
291+
using (var state = ArrangeParserAndParse(inputCode))
292+
{
293+
var inspection = new MemberNotOnInterfaceInspection(state);
294+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
295+
296+
Assert.IsFalse(inspectionResults.Any());
297+
}
298+
}
299+
300+
[Test]
301+
[Category("Inspections")]
302+
public void MemberNotOnInterface_DoesNotReturnResult_WithNewBlockOnInterface()
303+
{
304+
const string inputCode =
305+
@"Sub Foo()
306+
With New Dictionary
307+
.Add 42, 42
308+
End With
309+
End Sub";
310+
311+
using (var state = ArrangeParserAndParse(inputCode))
312+
{
313+
var inspection = new MemberNotOnInterfaceInspection(state);
314+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
315+
316+
Assert.IsFalse(inspectionResults.Any());
317+
}
318+
}
319+
320+
#endregion
321+
258322
[Test]
259323
[Category("Inspections")]
260324
public void MemberNotOnInterface_CatchesInvalidUseOfMember()

0 commit comments

Comments
 (0)