Skip to content

Commit 2699ace

Browse files
authored
Merge pull request #4207 from comintern/next
Test for anonymous object access in With blocks. Fixes #3343
2 parents 5d5a355 + 04e4c98 commit 2699ace

File tree

3 files changed

+78
-6
lines changed

3 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
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System.Collections.Generic;
2+
using System.Diagnostics;
23
using System.Linq;
34
using Rubberduck.Common;
45
using Rubberduck.Inspections.Abstract;
@@ -91,6 +92,9 @@ private IEnumerable<IInspectionResult> GetResults(Declaration[] declarations, De
9192

9293
for (var i = 0; i < parameters.Count; i++)
9394
{
95+
//If you hit this assert, congratulations! you've found a test case for https://github.com/rubberduck-vba/Rubberduck/issues/3906
96+
//Please examine the code, and if possible, either fix the indexing on this or upload your failing code to the GitHub issue.
97+
Debug.Assert(parametersAreByRef.Count == parameters.Count);
9498
parametersAreByRef[i] = parametersAreByRef[i] &&
9599
!IsUsedAsByRefParam(declarations, parameters[i]) &&
96100
((VBAParser.ArgContext) parameters[i].Context).BYVAL() == null &&

RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs

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

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

0 commit comments

Comments
 (0)