Skip to content

Commit c1a77dd

Browse files
authored
Merge pull request #4423 from comintern/next
Bug fixes for Excel specific inspections
2 parents 8ec3ddf + 236e91d commit c1a77dd

File tree

3 files changed

+201
-83
lines changed

3 files changed

+201
-83
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,

Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs

Lines changed: 39 additions & 51 deletions
Original file line numberDiff line numberDiff line change
@@ -17,57 +17,54 @@ namespace Rubberduck.Inspections.Concrete
1717
[RequiredLibrary("Excel")]
1818
public class SheetAccessedUsingStringInspection : InspectionBase
1919
{
20-
public SheetAccessedUsingStringInspection(RubberduckParserState state) : base(state)
21-
{
22-
}
20+
public SheetAccessedUsingStringInspection(RubberduckParserState state) : base(state) { }
2321

24-
private static readonly string[] Targets =
22+
private static readonly string[] InterestingMembers =
2523
{
2624
"Worksheets", "Sheets"
2725
};
2826

27+
private static readonly string[] InterestingClasses =
28+
{
29+
"_Global", "_Application", "Global", "Application", "Workbook"
30+
};
31+
2932
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3033
{
3134
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
3235
if (excel == null)
3336
{
34-
return Enumerable.Empty<IInspectionResult>();
35-
37+
return Enumerable.Empty<IInspectionResult>();
3638
}
3739

38-
var modules = new[]
39-
{
40-
State.DeclarationFinder.FindClassModule("_Global", excel, true),
41-
State.DeclarationFinder.FindClassModule("_Application", excel, true),
42-
State.DeclarationFinder.FindClassModule("Global", excel, true),
43-
State.DeclarationFinder.FindClassModule("Application", excel, true),
44-
State.DeclarationFinder.FindClassModule("Workbook", excel, true),
45-
};
46-
47-
var references = Targets
48-
.SelectMany(target => modules.SelectMany(module => State.DeclarationFinder.FindMemberMatches(module, target)))
49-
.Where(declaration => declaration.References.Any())
50-
.SelectMany(declaration => declaration.References
51-
.Where(reference =>
52-
!IsIgnoringInspectionResultFor(reference, AnnotationName) && IsAccessedWithStringLiteralParameter(reference))
53-
.Select(reference => new IdentifierReferenceInspectionResult(this,
54-
InspectionResults.SheetAccessedUsingStringInspection, State, reference)));
40+
var targetProperties = BuiltInDeclarations
41+
.OfType<PropertyDeclaration>()
42+
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
43+
.ToList();
44+
45+
var references = targetProperties.SelectMany(declaration => declaration.References
46+
.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName) &&
47+
IsAccessedWithStringLiteralParameter(reference))
48+
.Select(reference => new IdentifierReferenceInspectionResult(this,
49+
InspectionResults.SheetAccessedUsingStringInspection, State, reference)));
5550

5651
var issues = new List<IdentifierReferenceInspectionResult>();
5752

5853
foreach (var reference in references)
5954
{
60-
var component = GetVBComponentMatchingSheetName(reference);
61-
if (component != null)
55+
using (var component = GetVBComponentMatchingSheetName(reference))
6256
{
57+
if (component == null)
58+
{
59+
continue;
60+
}
6361
using (var properties = component.Properties)
6462
{
6563
reference.Properties.CodeName = (string)properties.Single(property => property.Name == "CodeName").Value;
6664
}
6765
issues.Add(reference);
6866
}
6967
}
70-
7168
return issues;
7269
}
7370

@@ -101,47 +98,38 @@ private IVBComponent GetVBComponentMatchingSheetName(IdentifierReferenceInspecti
10198
var sheetName = FormatSheetName(sheetArgumentContext.GetText());
10299
var project = State.Projects.First(p => p.ProjectId == reference.QualifiedName.ProjectId);
103100

104-
105-
//return project.VBComponents.FirstOrDefault(c =>
106-
// c.Type == ComponentType.Document &&
107-
// (string)c.Properties.First(property => property.Name == "Name").Value == sheetName);
108101
using (var components = project.VBComponents)
109102
{
110-
for (var i = 0; i < components.Count; i++)
103+
foreach (var component in components)
111104
{
112-
using (var component = components[i])
113105
using (var properties = component.Properties)
114106
{
115-
if (component.Type == ComponentType.Document)
107+
if (component.Type != ComponentType.Document)
116108
{
117-
for (var j = 0; j < properties.Count; j++)
109+
component.Dispose();
110+
continue;
111+
}
112+
foreach (var property in properties)
113+
{
114+
var found = property.Name.Equals("Name") && ((string)property.Value).Equals(sheetName);
115+
property.Dispose();
116+
if (found)
118117
{
119-
using (var property = properties[j])
120-
{
121-
if (property.Name == "Name" && (string)property.Value == sheetName)
122-
{
123-
return component;
124-
}
125-
}
126-
}
118+
return component;
119+
}
127120
}
128121
}
122+
component.Dispose();
129123
}
130-
131124
return null;
132125
}
133126
}
134127

135128
private static string FormatSheetName(string sheetName)
136129
{
137-
var formattedName = sheetName.First() == '"' ? sheetName.Skip(1) : sheetName;
138-
139-
if (sheetName.Last() == '"')
140-
{
141-
formattedName = formattedName.Take(formattedName.Count() - 1);
142-
}
143-
144-
return string.Concat(formattedName);
130+
return sheetName.StartsWith("\"") && sheetName.EndsWith("\"")
131+
? sheetName.Substring(1, sheetName.Length - 2)
132+
: sheetName;
145133
}
146134
}
147135
}

RubberduckTests/Inspections/ImplicitActiveWorkbookReferenceInspectionTests.cs

Lines changed: 144 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,142 @@ 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_DimAsTypeWorksheets_NotReported()
117+
{
118+
const string inputCode =
119+
@"
120+
Sub foo()
121+
Dim allSheets As Worksheets
122+
End Sub";
123+
124+
const int expected = 0;
125+
var actual = ArrangeAndGetInspectionCount(inputCode);
126+
127+
Assert.AreEqual(expected, actual);
128+
}
129+
130+
[Test]
131+
[Category("Inspections")]
132+
public void ImplicitActiveWorkbookReference_DimAsTypeSheets_NotReported()
133+
{
134+
const string inputCode =
135+
@"
136+
Sub foo()
137+
Dim allSheets As Sheets
138+
End Sub";
139+
140+
const int expected = 0;
141+
var actual = ArrangeAndGetInspectionCount(inputCode);
142+
143+
Assert.AreEqual(expected, actual);
144+
}
145+
146+
[Test]
147+
[Category("Inspections")]
148+
public void ImplicitActiveWorkbookReference_DimAsTypeNames_NotReported()
149+
{
150+
const string inputCode =
151+
@"
152+
Sub foo()
153+
Dim allNames As Names
154+
End Sub";
155+
156+
const int expected = 0;
157+
var actual = ArrangeAndGetInspectionCount(inputCode);
158+
159+
Assert.AreEqual(expected, actual);
39160
}
40161

41162
[Test]
@@ -51,9 +172,17 @@ Dim sheet As Worksheet
51172
Set sheet = Worksheets(""Sheet1"")
52173
End Sub";
53174

175+
const int expected = 0;
176+
var actual = ArrangeAndGetInspectionCount(inputCode);
177+
178+
Assert.AreEqual(expected, actual);
179+
}
180+
181+
private int ArrangeAndGetInspectionCount(string code)
182+
{
54183
var builder = new MockVbeBuilder();
55184
var project = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
56-
.AddComponent("Class1", ComponentType.ClassModule, inputCode)
185+
.AddComponent("Module1", ComponentType.StandardModule, code)
57186
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
58187
.Build();
59188
var vbe = builder.AddProject(project).Build();
@@ -64,7 +193,7 @@ Dim sheet As Worksheet
64193
var inspection = new ImplicitActiveWorkbookReferenceInspection(state);
65194
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
66195

67-
Assert.AreEqual(0, inspectionResults.Count());
196+
return inspectionResults.Count();
68197
}
69198
}
70199

0 commit comments

Comments
 (0)