Skip to content

Commit 4343e99

Browse files
committed
Refactor (fix) MemberNotOnInterfaceInspection to collect Declarations from resolver.
1 parent 7d0b65f commit 4343e99

File tree

7 files changed

+130
-68
lines changed

7 files changed

+130
-68
lines changed
Lines changed: 12 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -1,26 +1,15 @@
1-
using System;
2-
using System.Collections.Generic;
1+
using System.Collections.Generic;
32
using System.Linq;
4-
using Antlr4.Runtime;
53
using Rubberduck.Inspections.Abstract;
64
using Rubberduck.Inspections.Resources;
75
using Rubberduck.Inspections.Results;
8-
using Rubberduck.Parsing;
9-
using Rubberduck.Parsing.Grammar;
106
using Rubberduck.Parsing.Symbols;
117
using Rubberduck.Parsing.VBA;
12-
using Rubberduck.VBEditor;
138

149
namespace Rubberduck.Inspections
1510
{
1611
public sealed class MemberNotOnInterfaceInspection : InspectionBase
1712
{
18-
private static readonly List<Type> InterestingTypes = new List<Type>
19-
{
20-
typeof(VBAParser.MemberAccessExprContext),
21-
typeof(VBAParser.WithMemberAccessExprContext)
22-
};
23-
2413
public MemberNotOnInterfaceInspection(RubberduckParserState state, CodeInspectionSeverity defaultSeverity = CodeInspectionSeverity.Warning)
2514
: base(state, defaultSeverity)
2615
{
@@ -32,51 +21,20 @@ public MemberNotOnInterfaceInspection(RubberduckParserState state, CodeInspectio
3221

3322
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3423
{
24+
var unresolved = State.DeclarationFinder.UnresolvedMemberDeclarations().Where(decl => !IsIgnoringInspectionResultFor(decl, AnnotationName)).ToList();
25+
3526
var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
36-
decl.ParentDeclaration.DeclarationType != DeclarationType.Project &&
27+
decl.AsTypeDeclaration.IsBuiltIn &&
3728
decl.AsTypeDeclaration.DeclarationType == DeclarationType.ClassModule &&
38-
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible &&
39-
decl.References.Any(usage => InterestingTypes.Contains(usage.Context.Parent.GetType())))
40-
.ToList();
29+
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
30+
.SelectMany(decl => decl.References).ToList();
4131

42-
//Unfortunately finding implemented members is fairly expensive, so group by the return type.
43-
return (from access in targets.GroupBy(t => t.AsTypeDeclaration)
44-
let typeDeclaration = access.Key
45-
let typeMembers = new HashSet<string>(BuiltInDeclarations.Where(d => d.ParentDeclaration != null && d.ParentDeclaration.Equals(typeDeclaration))
46-
.Select(d => d.IdentifierName)
47-
.Distinct())
48-
from references in access.Select(usage => usage.References.Where(r => InterestingTypes.Contains(r.Context.Parent.GetType())))
49-
from reference in references.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
50-
let identifier = reference.Context.Parent.GetChild(reference.Context.Parent.ChildCount - 1)
51-
where !typeMembers.Contains(identifier.GetText())
52-
let pseudoDeclaration = CreatePseudoDeclaration((ParserRuleContext) identifier, reference)
53-
where !pseudoDeclaration.Annotations.Any()
54-
select new MemberNotOnInterfaceInspectionResult(this, pseudoDeclaration, (ParserRuleContext) identifier, typeDeclaration))
55-
.Cast<InspectionResultBase>().ToList();
56-
}
57-
58-
//Builds a throw-away Declaration for the indentifiers found by the inspection. These aren't (and shouldn't be) created by the parser.
59-
//Used to pass to the InspectionResult to make it selectable.
60-
private static Declaration CreatePseudoDeclaration(ParserRuleContext context, IdentifierReference reference)
61-
{
62-
return new Declaration(
63-
new QualifiedMemberName(reference.QualifiedModuleName, context.GetText()),
64-
null,
65-
null,
66-
string.Empty,
67-
string.Empty,
68-
false,
69-
false,
70-
Accessibility.Implicit,
71-
DeclarationType.Variable,
72-
context,
73-
context.GetSelection(),
74-
false,
75-
null,
76-
true,
77-
null,
78-
null,
79-
true);
32+
return (from access in unresolved
33+
let callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext))
34+
where callingContext != null
35+
select
36+
new MemberNotOnInterfaceInspectionResult(this, access, callingContext.Declaration.AsTypeDeclaration))
37+
.ToList();
8038
}
8139
}
8240
}

RetailCoder.VBE/Inspections/Results/MemberNotOnInterfaceInspectionResult.cs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -9,14 +9,12 @@ namespace Rubberduck.Inspections.Results
99
{
1010
public class MemberNotOnInterfaceInspectionResult : InspectionResultBase
1111
{
12-
private readonly ParserRuleContext _member;
1312
private readonly Declaration _asTypeDeclaration;
1413
private IEnumerable<QuickFixBase> _quickFixes;
1514

16-
public MemberNotOnInterfaceInspectionResult(IInspection inspection, Declaration target, ParserRuleContext member, Declaration asTypeDeclaration)
15+
public MemberNotOnInterfaceInspectionResult(IInspection inspection, Declaration target, Declaration asTypeDeclaration)
1716
: base(inspection, target)
1817
{
19-
_member = member;
2018
_asTypeDeclaration = asTypeDeclaration;
2119
}
2220

@@ -26,14 +24,14 @@ public override IEnumerable<QuickFixBase> QuickFixes
2624
{
2725
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
2826
{
29-
new IgnoreOnceQuickFix(_member, QualifiedSelection, Inspection.AnnotationName)
27+
new IgnoreOnceQuickFix(Target.Context, QualifiedSelection, Inspection.AnnotationName)
3028
});
3129
}
3230
}
3331

3432
public override string Description
3533
{
36-
get { return string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, _member.GetText(), _asTypeDeclaration.IdentifierName); }
34+
get { return string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, Target.IdentifierName, _asTypeDeclaration.IdentifierName); }
3735
}
3836
}
3937
}

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -285,6 +285,7 @@
285285
<Compile Include="Symbols\IdentifierReferenceListener.cs" />
286286
<Compile Include="Symbols\ConstantDeclaration.cs" />
287287
<Compile Include="ComReflection\XmlPersistableDeclarations.cs" />
288+
<Compile Include="Symbols\UnboundMemberDeclaration.cs" />
288289
<Compile Include="Syntax\SyntaxTree.cs" />
289290
<Compile Include="Syntax\TextSpan.cs" />
290291
<Compile Include="VBA\AttributeParser.cs" />

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using NLog;
22
using Rubberduck.Parsing.Annotations;
3+
using Rubberduck.Parsing.Binding;
34
using Rubberduck.VBEditor;
45
using System;
56
using System.Collections.Concurrent;
@@ -37,6 +38,7 @@ public class DeclarationFinder
3738
private readonly ConcurrentDictionary<string, Declaration[]> _declarationsByName;
3839
private readonly ConcurrentDictionary<QualifiedModuleName, Declaration[]> _declarations;
3940
private readonly ConcurrentDictionary<QualifiedMemberName, IList<Declaration>> _undeclared;
41+
private readonly ConcurrentBag<UnboundMemberDeclaration> _unresolved;
4042
private readonly ConcurrentDictionary<QualifiedModuleName, IAnnotation[]> _annotations;
4143
private readonly ConcurrentDictionary<Declaration, Declaration[]> _parametersByParent;
4244
private readonly ConcurrentDictionary<DeclarationType, Declaration[]> _userDeclarationsByType;
@@ -94,6 +96,7 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
9496
));
9597

9698
_undeclared = new ConcurrentDictionary<QualifiedMemberName, IList<Declaration>>(new Dictionary<QualifiedMemberName, IList<Declaration>>());
99+
_unresolved = new ConcurrentBag<UnboundMemberDeclaration>(new List<UnboundMemberDeclaration>());
97100
_annotationService = new AnnotationService(this);
98101

99102
var implementsInstructions = UserDeclarations(DeclarationType.ClassModule).SelectMany(cls =>
@@ -174,6 +177,14 @@ public IEnumerable<Declaration> UserDeclarations(DeclarationType type)
174177
return result;
175178
}
176179

180+
public IEnumerable<UnboundMemberDeclaration> UnresolvedMemberDeclarations()
181+
{
182+
lock (ThreadLock)
183+
{
184+
return _unresolved.ToArray();
185+
}
186+
}
187+
177188
public IEnumerable<Declaration> FindHandlersForWithEventsField(Declaration field)
178189
{
179190
Declaration[] result;
@@ -485,6 +496,27 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
485496
return undeclaredLocal;
486497
}
487498

499+
public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExprContext context, IBoundExpression withExpression)
500+
{
501+
502+
//The only forms we care about right now are MemberAccessExprContext or WithMemberAccessExprContext.
503+
var access = (ParserRuleContext)context.GetChild<VBAParser.MemberAccessExprContext>(0)
504+
?? context.GetChild<VBAParser.WithMemberAccessExprContext>(0);
505+
if (access == null)
506+
{
507+
return;
508+
}
509+
510+
var identifier = access.GetChild<VBAParser.UnrestrictedIdentifierContext>(0);
511+
var annotations = _annotationService.FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line);
512+
513+
var declaration = new UnboundMemberDeclaration(parentDeclaration, identifier,
514+
(access is VBAParser.MemberAccessExprContext) ? (ParserRuleContext)access.children[0] : withExpression.Context,
515+
annotations);
516+
517+
_unresolved.Add(declaration);
518+
}
519+
488520
public Declaration OnBracketedExpression(string expression, ParserRuleContext context)
489521
{
490522
var hostApp = FindProject(_hostApp == null ? "VBA" : _hostApp.ApplicationName);

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -151,18 +151,27 @@ private void ResolveDefault(
151151
bool isAssignmentTarget = false,
152152
bool hasExplicitLetStatement = false)
153153
{
154+
var withExpression = GetInnerMostWithExpression();
154155
var boundExpression = _bindingService.ResolveDefault(
155156
_moduleDeclaration,
156157
_currentParent,
157158
expression,
158-
GetInnerMostWithExpression(),
159+
withExpression,
159160
statementContext);
160161
if (boundExpression.Classification == ExpressionClassification.ResolutionFailed)
161162
{
162-
Logger.Warn(
163-
string.Format(
164-
"Default Context: Failed to resolve {0}. Binding as much as we can.",
165-
expression.GetText()));
163+
var lexpr = expression as VBAParser.LExprContext ?? expression.GetChild<VBAParser.LExprContext>(0);
164+
if (lexpr != null)
165+
{
166+
_declarationFinder.AddUnboundContext(_currentParent, lexpr, withExpression);
167+
}
168+
else
169+
{
170+
Logger.Warn(
171+
string.Format(
172+
"Default Context: Failed to resolve {0}. Binding as much as we can.",
173+
expression.GetText()));
174+
}
166175
}
167176
_boundExpressionVisitor.AddIdentifierReferences(boundExpression, _qualifiedModuleName, _currentScope, _currentParent, isAssignmentTarget, hasExplicitLetStatement);
168177
}
Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
using System.Collections.Generic;
2+
using Antlr4.Runtime;
3+
using Rubberduck.Parsing.Annotations;
4+
using Rubberduck.VBEditor;
5+
6+
namespace Rubberduck.Parsing.Symbols
7+
{
8+
/// <summary>
9+
/// These declarations are created from unresolved member accesses in the DeclarationFinder and are collected for use by inspections. They
10+
/// should NOT be added to the Declaration collections in the parser state.
11+
/// </summary>
12+
public class UnboundMemberDeclaration : Declaration
13+
{
14+
/// <summary>
15+
/// Context on the LHS of the member access.
16+
/// </summary>
17+
public ParserRuleContext CallingContext { get; private set; }
18+
19+
public UnboundMemberDeclaration(Declaration parentDeclaration, ParserRuleContext unboundIdentifier, ParserRuleContext callingContext, IEnumerable<IAnnotation> annotations) :
20+
base(new QualifiedMemberName(parentDeclaration.QualifiedName.QualifiedModuleName, unboundIdentifier.GetText()),
21+
parentDeclaration,
22+
parentDeclaration,
23+
"Variant",
24+
string.Empty,
25+
false,
26+
false,
27+
Accessibility.Implicit,
28+
DeclarationType.UnresolvedMember,
29+
unboundIdentifier,
30+
unboundIdentifier.GetSelection(),
31+
false,
32+
null,
33+
false,
34+
annotations)
35+
{
36+
CallingContext = callingContext;
37+
}
38+
}
39+
}

RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs

Lines changed: 29 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -15,12 +15,16 @@ namespace RubberduckTests.Inspections
1515
[TestClass]
1616
public class MemberNotOnInterfaceInspectionTests
1717
{
18-
private static ParseCoordinator ArrangeParser(string inputCode)
18+
private static ParseCoordinator ArrangeParser(string inputCode, string library = "Scripting")
1919
{
2020
var builder = new MockVbeBuilder();
2121
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
2222
.AddComponent("Codez", ComponentType.StandardModule, inputCode)
23-
.AddReference("Scripting", MockVbeBuilder.LibraryPathScripting, 1, 0, true)
23+
.AddReference(library,
24+
library.Equals("Scripting") ? MockVbeBuilder.LibraryPathScripting : MockVbeBuilder.LibraryPathMsExcel,
25+
1,
26+
library.Equals("Scripting") ? 0 : 8,
27+
true)
2428
.Build();
2529

2630
var vbe = builder.AddProject(project).Build();
@@ -29,7 +33,7 @@ private static ParseCoordinator ArrangeParser(string inputCode)
2933
mockHost.SetupAllProperties();
3034
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
3135

32-
parser.State.AddTestLibrary("Scripting.1.0.xml");
36+
parser.State.AddTestLibrary(library.Equals("Scripting") ? "Scripting.1.0.xml" : "Excel.1.8.xml");
3337
return parser;
3438
}
3539

@@ -81,6 +85,28 @@ Dim dict As Dictionary
8185
Assert.AreEqual(1, inspectionResults.Count());
8286
}
8387

88+
[TestMethod]
89+
[DeploymentItem(@"Testfiles\")]
90+
[TestCategory("Inspections")]
91+
public void MemberNotOnInterface_ReturnsResult_ApplicationObject()
92+
{
93+
const string inputCode =
94+
@"Sub Foo()
95+
Application.NonMember
96+
End Sub";
97+
98+
//Arrange
99+
var parser = ArrangeParser(inputCode, "Excel");
100+
101+
parser.Parse(new CancellationTokenSource());
102+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
103+
104+
var inspection = new MemberNotOnInterfaceInspection(parser.State);
105+
var inspectionResults = inspection.GetInspectionResults();
106+
107+
Assert.AreEqual(1, inspectionResults.Count());
108+
}
109+
84110
[TestMethod]
85111
[DeploymentItem(@"Testfiles\")]
86112
[TestCategory("Inspections")]
@@ -155,7 +181,6 @@ Debug.Print x.NonMember
155181
[TestCategory("Inspections")]
156182
public void MemberNotOnInterface_ReturnsResult_WithBlock()
157183
{
158-
Assert.Inconclusive("This is currently not working.");
159184
const string inputCode =
160185
@"Sub Foo()
161186
Dim dict As New Dictionary

0 commit comments

Comments
 (0)