Skip to content

Commit 68d737f

Browse files
committed
Limit inpected references for inspection. Closes #3909, closes #4326
1 parent b300113 commit 68d737f

File tree

2 files changed

+130
-32
lines changed

2 files changed

+130
-32
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 18 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Inspections.Results;
55
using Rubberduck.Parsing.Inspections;
66
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Symbols;
78
using Rubberduck.Resources.Inspections;
89
using Rubberduck.Parsing.VBA;
910

@@ -15,32 +16,32 @@ public sealed class ImplicitActiveWorkbookReferenceInspection : InspectionBase
1516
public ImplicitActiveWorkbookReferenceInspection(RubberduckParserState state)
1617
: base(state) { }
1718

18-
private static readonly string[] Targets =
19+
private static readonly string[] InterestingMembers =
1920
{
20-
"Worksheets", "Sheets", "Names", "_Default"
21+
"Worksheets", "Sheets", "Names"
22+
};
23+
24+
private static readonly string[] InterestingClasses =
25+
{
26+
"_Global", "_Application", "Global", "Application"
2127
};
2228

2329
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2430
{
2531
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
26-
if (excel == null) { return Enumerable.Empty<IInspectionResult>(); }
27-
28-
var modules = new[]
32+
if (excel == null)
2933
{
30-
State.DeclarationFinder.FindClassModule("_Global", excel, true),
31-
State.DeclarationFinder.FindClassModule("_Application", excel, true),
32-
State.DeclarationFinder.FindClassModule("Global", excel, true),
33-
State.DeclarationFinder.FindClassModule("Application", excel, true),
34-
State.DeclarationFinder.FindClassModule("Sheets", excel, true),
35-
};
34+
return Enumerable.Empty<IInspectionResult>();
35+
}
3636

37-
var members = Targets
38-
.SelectMany(target => modules.SelectMany(module =>
39-
State.DeclarationFinder.FindMemberMatches(module, target)))
40-
.Where(item => item.References.Any())
41-
.SelectMany(item => item.References.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName)))
37+
var targetProperties = BuiltInDeclarations
38+
.OfType<PropertyGetDeclaration>()
39+
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
4240
.ToList();
43-
41+
42+
var members = targetProperties.SelectMany(item =>
43+
item.References.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName)));
44+
4445
return members.Select(issue => new IdentifierReferenceInspectionResult(this,
4546
string.Format(InspectionResults.ImplicitActiveWorkbookReferenceInspection, issue.Context.GetText()),
4647
State,

RubberduckTests/Inspections/ImplicitActiveWorkbookReferenceInspectionTests.cs

Lines changed: 112 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System.Threading;
33
using NUnit.Framework;
44
using Rubberduck.Inspections.Concrete;
5-
using Rubberduck.Parsing.VBA;
65
using Rubberduck.VBEditor.SafeComWrappers;
76
using RubberduckTests.Mocks;
87

@@ -22,20 +21,110 @@ Dim sheet As Worksheet
2221
Set sheet = Worksheets(""Sheet1"")
2322
End Sub";
2423

25-
var builder = new MockVbeBuilder();
26-
var project = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
27-
.AddComponent("Class1", ComponentType.ClassModule, inputCode)
28-
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
29-
.Build();
30-
var vbe = builder.AddProject(project).Build();
24+
const int expected = 1;
25+
var actual = ArrangeAndGetInspectionCount(inputCode);
3126

32-
using (var state = MockParser.CreateAndParse(vbe.Object))
33-
{
34-
var inspection = new ImplicitActiveWorkbookReferenceInspection(state);
35-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
27+
Assert.AreEqual(expected, actual);
28+
}
3629

37-
Assert.AreEqual(1, inspectionResults.Count());
38-
}
30+
[Test]
31+
[Category("Inspections")]
32+
public void ImplicitActiveWorkbookReference_ExplicitApplication()
33+
{
34+
const string inputCode =
35+
@"
36+
Sub foo()
37+
Dim sheet As Worksheet
38+
Set sheet = Application.Worksheets(""Sheet1"")
39+
End Sub";
40+
41+
const int expected = 1;
42+
var actual = ArrangeAndGetInspectionCount(inputCode);
43+
44+
Assert.AreEqual(expected, actual);
45+
}
46+
47+
[Test]
48+
[Category("Inspections")]
49+
public void ImplicitActiveWorkbookReference_ReportsSheets()
50+
{
51+
const string inputCode =
52+
@"
53+
Sub foo()
54+
Dim sheet As Worksheet
55+
Set sheet = Sheets(""Sheet1"")
56+
End Sub";
57+
58+
const int expected = 1;
59+
var actual = ArrangeAndGetInspectionCount(inputCode);
60+
61+
Assert.AreEqual(expected, actual);
62+
}
63+
64+
[Test]
65+
[Category("Inspections")]
66+
public void ImplicitActiveWorkbookReference_ReportsNames()
67+
{
68+
const string inputCode =
69+
@"
70+
Sub foo()
71+
Names.Add ""foo"", Rows(1)
72+
End Sub";
73+
74+
const int expected = 1;
75+
var actual = ArrangeAndGetInspectionCount(inputCode);
76+
77+
Assert.AreEqual(expected, actual);
78+
}
79+
80+
[Test]
81+
[Category("Inspections")]
82+
public void ImplicitActiveWorkbookReference_ExplicitReference_NotReported()
83+
{
84+
const string inputCode =
85+
@"
86+
Sub foo()
87+
Dim book As Workbook
88+
Dim sheet As Worksheet
89+
Set sheet = book.Worksheets(1)
90+
End Sub";
91+
92+
const int expected = 0;
93+
var actual = ArrangeAndGetInspectionCount(inputCode);
94+
95+
Assert.AreEqual(expected, actual);
96+
}
97+
98+
[Test]
99+
[Category("Inspections")]
100+
public void ImplicitActiveWorkbookReference_ExplicitParameterReference_NotReported()
101+
{
102+
const string inputCode =
103+
@"
104+
Sub foo(book As Workbook)
105+
Debug.Print book.Worksheets.Count
106+
End Sub";
107+
108+
const int expected = 0;
109+
var actual = ArrangeAndGetInspectionCount(inputCode);
110+
111+
Assert.AreEqual(expected, actual);
112+
}
113+
114+
[Test]
115+
[Category("Inspections")]
116+
public void ImplicitActiveWorkbookReference_DimAsTypeSheets_NotReported()
117+
{
118+
const string inputCode =
119+
@"
120+
Sub foo()
121+
Dim allSheets As Sheets
122+
End Sub";
123+
124+
const int expected = 0;
125+
var actual = ArrangeAndGetInspectionCount(inputCode);
126+
127+
Assert.AreEqual(expected, actual);
39128
}
40129

41130
[Test]
@@ -51,9 +140,17 @@ Dim sheet As Worksheet
51140
Set sheet = Worksheets(""Sheet1"")
52141
End Sub";
53142

143+
const int expected = 0;
144+
var actual = ArrangeAndGetInspectionCount(inputCode);
145+
146+
Assert.AreEqual(expected, actual);
147+
}
148+
149+
private int ArrangeAndGetInspectionCount(string code)
150+
{
54151
var builder = new MockVbeBuilder();
55152
var project = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
56-
.AddComponent("Class1", ComponentType.ClassModule, inputCode)
153+
.AddComponent("Module1", ComponentType.StandardModule, code)
57154
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
58155
.Build();
59156
var vbe = builder.AddProject(project).Build();
@@ -64,7 +161,7 @@ Dim sheet As Worksheet
64161
var inspection = new ImplicitActiveWorkbookReferenceInspection(state);
65162
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
66163

67-
Assert.AreEqual(0, inspectionResults.Count());
164+
return inspectionResults.Count();
68165
}
69166
}
70167

0 commit comments

Comments
 (0)