Skip to content

Commit 9a7d34c

Browse files
committed
Add ImplicitContainingWorkbookReferenceInspection and ImplicitContainingWorksheetReferenceInspection
These two find unqualified references inside the corresponding document modules to certain members that point to the ActiveWorkbook or ActiveSheet when used unqualified outside the appropriate document modules. That the reference is actually to the containing document can be surprising. Because of that, they should be qualified with Me. This also removes the corresponding false-positives for the ImplicitActiveSheetReferenceInspection and ImplicitActiveWorkbookReferenceInspection. Technically, both the containing and active workbook/worksheet types now share a common base inspection handling (most of) the selection of the declarations whose references can be suspicious.
1 parent 80e1347 commit 9a7d34c

21 files changed

+873
-117
lines changed
Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
6+
7+
namespace Rubberduck.CodeAnalysis.Inspections.Abstract
8+
{
9+
internal abstract class ImplicitSheetReferenceInspectionBase : IdentifierReferenceInspectionFromDeclarationsBase
10+
{
11+
public ImplicitSheetReferenceInspectionBase(IDeclarationFinderProvider declarationFinderProvider)
12+
: base(declarationFinderProvider)
13+
{ }
14+
15+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
16+
{
17+
var excel = finder.Projects
18+
.SingleOrDefault(item => !item.IsUserDefined
19+
&& item.IdentifierName == "Excel");
20+
if (excel == null)
21+
{
22+
return Enumerable.Empty<Declaration>();
23+
}
24+
25+
var globalModules = GlobalObjectClassNames
26+
.Select(className => finder.FindClassModule(className, excel, true))
27+
.OfType<ModuleDeclaration>();
28+
29+
return globalModules
30+
.SelectMany(moduleClass => moduleClass.Members)
31+
.Where(declaration => TargetMemberNames.Contains(declaration.IdentifierName)
32+
&& declaration.DeclarationType.HasFlag(DeclarationType.Member)
33+
&& declaration.AsTypeName == "Range");
34+
}
35+
36+
private static readonly string[] GlobalObjectClassNames =
37+
{
38+
"Global", "_Global"
39+
};
40+
41+
private static readonly string[] TargetMemberNames =
42+
{
43+
"Cells", "Range", "Columns", "Rows"
44+
};
45+
}
46+
}
Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
6+
7+
namespace Rubberduck.CodeAnalysis.Inspections.Abstract
8+
{
9+
internal abstract class ImplicitWorkbookReferenceInspectionBase : IdentifierReferenceInspectionFromDeclarationsBase
10+
{
11+
internal ImplicitWorkbookReferenceInspectionBase(IDeclarationFinderProvider declarationFinderProvider)
12+
: base(declarationFinderProvider)
13+
{ }
14+
15+
private static readonly string[] InterestingMembers =
16+
{
17+
"Worksheets", "Sheets", "Names"
18+
};
19+
20+
private static readonly string[] InterestingClasses =
21+
{
22+
"_Global", "_Application", "Global", "Application"
23+
};
24+
25+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
26+
{
27+
var excel = finder.Projects
28+
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
29+
if (excel == null)
30+
{
31+
return Enumerable.Empty<Declaration>();
32+
}
33+
34+
var relevantClasses = InterestingClasses
35+
.Select(className => finder.FindClassModule(className, excel, true))
36+
.OfType<ModuleDeclaration>();
37+
38+
var relevantProperties = relevantClasses
39+
.SelectMany(classDeclaration => classDeclaration.Members)
40+
.OfType<PropertyGetDeclaration>()
41+
.Where(member => InterestingMembers.Contains(member.IdentifierName));
42+
43+
return relevantProperties;
44+
}
45+
}
46+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs

Lines changed: 6 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
1+
using System.Linq;
32
using Rubberduck.CodeAnalysis.Inspections.Abstract;
43
using Rubberduck.CodeAnalysis.Inspections.Attributes;
54
using Rubberduck.Parsing.Symbols;
@@ -10,7 +9,7 @@
109
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1110
{
1211
/// <summary>
13-
/// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls that implicitly refer to ActiveSheet.
12+
/// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls inside worksheet modules.
1413
/// </summary>
1514
/// <reference name="Excel" />
1615
/// <why>
@@ -42,43 +41,18 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
4241
/// </module>
4342
/// </example>
4443
[RequiredLibrary("Excel")]
45-
internal sealed class ImplicitActiveSheetReferenceInspection : IdentifierReferenceInspectionFromDeclarationsBase
44+
internal sealed class ImplicitActiveSheetReferenceInspection : ImplicitSheetReferenceInspectionBase
4645
{
4746
public ImplicitActiveSheetReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
4847
: base(declarationFinderProvider)
4948
{}
5049

51-
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
50+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
5251
{
53-
var excel = finder.Projects
54-
.SingleOrDefault(item => !item.IsUserDefined
55-
&& item.IdentifierName == "Excel");
56-
if (excel == null)
57-
{
58-
return Enumerable.Empty<Declaration>();
59-
}
60-
61-
var globalModules = GlobalObjectClassNames
62-
.Select(className => finder.FindClassModule(className, excel, true))
63-
.OfType<ModuleDeclaration>();
64-
65-
return globalModules
66-
.SelectMany(moduleClass => moduleClass.Members)
67-
.Where(declaration => TargetMemberNames.Contains(declaration.IdentifierName)
68-
&& declaration.DeclarationType.HasFlag(DeclarationType.Member)
69-
&& declaration.AsTypeName == "Range");
52+
return !(Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document)
53+
|| !document.SupertypeNames.Contains("Worksheet");
7054
}
7155

72-
private static readonly string[] GlobalObjectClassNames =
73-
{
74-
"Global", "_Global"
75-
};
76-
77-
private static readonly string[] TargetMemberNames =
78-
{
79-
"Cells", "Range", "Columns", "Rows"
80-
};
81-
8256
protected override string ResultDescription(IdentifierReference reference)
8357
{
8458
return string.Format(

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 7 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -40,41 +40,22 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
4040
/// </module>
4141
/// </example>
4242
[RequiredLibrary("Excel")]
43-
internal sealed class ImplicitActiveWorkbookReferenceInspection : IdentifierReferenceInspectionFromDeclarationsBase
43+
internal sealed class ImplicitActiveWorkbookReferenceInspection : ImplicitWorkbookReferenceInspectionBase
4444
{
4545
public ImplicitActiveWorkbookReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
4646
: base(declarationFinderProvider)
4747
{}
4848

49-
private static readonly string[] InterestingMembers =
49+
private static readonly List<string> _alwaysActiveWorkbookReferenceParents = new List<string>
5050
{
51-
"Worksheets", "Sheets", "Names"
51+
"_Application", "Application"
5252
};
5353

54-
private static readonly string[] InterestingClasses =
54+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
5555
{
56-
"_Global", "_Application", "Global", "Application"
57-
};
58-
59-
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
60-
{
61-
var excel = finder.Projects
62-
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
63-
if (excel == null)
64-
{
65-
return Enumerable.Empty<Declaration>();
66-
}
67-
68-
var relevantClasses = InterestingClasses
69-
.Select(className => finder.FindClassModule(className, excel, true))
70-
.OfType<ModuleDeclaration>();
71-
72-
var relevantProperties = relevantClasses
73-
.SelectMany(classDeclaration => classDeclaration.Members)
74-
.OfType<PropertyGetDeclaration>()
75-
.Where(member => InterestingMembers.Contains(member.IdentifierName));
76-
77-
return relevantProperties;
56+
return !(Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document)
57+
|| !document.SupertypeNames.Contains("Workbook")
58+
|| _alwaysActiveWorkbookReferenceParents.Contains(reference.Declaration.ParentDeclaration.IdentifierName);
7859
}
7960

8061
protected override string ResultDescription(IdentifierReference reference)
Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
4+
using Rubberduck.CodeAnalysis.Inspections.Attributes;
5+
using Rubberduck.Parsing.Symbols;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
8+
using Rubberduck.Resources.Inspections;
9+
10+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
11+
{
12+
/// <summary>
13+
/// Locates unqualified Workbook.Worksheets/Sheets/Names member calls inside workbook document modules that implicitly refer to the containing workbook.
14+
/// </summary>
15+
/// <reference name="Excel" />
16+
/// <why>
17+
/// Implicit references inside a workbook document module can be mistakes for implicit references to the active workbook, which is the behavior in all other modules
18+
/// By explicitly qualifying these member calls with Me, the ambiguity can be resolved.
19+
/// </why>
20+
/// <example hasResult="true">
21+
/// <module name="ThisWorkbook" type="Document Module">
22+
/// <![CDATA[
23+
/// Private Sub Example()
24+
/// Dim summarySheet As Worksheet
25+
/// Set summarySheet = Worksheets("Summary") ' unqualified Worksheets is implicitly querying the containing workbook's Worksheets collection.
26+
/// End Sub
27+
/// ]]>
28+
/// </module>
29+
/// </example>
30+
/// <example hasResult="false">
31+
/// <module name="ThisWorkbook" type="Document Module">
32+
/// <![CDATA[
33+
/// Private Sub Example()
34+
/// Dim summarySheet As Worksheet
35+
/// Set summarySheet = Me.Worksheets("Summary")
36+
/// End Sub
37+
/// ]]>
38+
/// </module>
39+
/// </example>
40+
[RequiredLibrary("Excel")]
41+
internal sealed class ImplicitContainingWorkbookReferenceInspection : ImplicitWorkbookReferenceInspectionBase
42+
{
43+
public ImplicitContainingWorkbookReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
44+
: base(declarationFinderProvider)
45+
{ }
46+
47+
private static readonly List<string> _alwaysActiveWorkbookReferenceParents = new List<string>
48+
{
49+
"_Application", "Application"
50+
};
51+
52+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
53+
{
54+
return base.ObjectionableDeclarations(finder)
55+
.Where(declaration => !_alwaysActiveWorkbookReferenceParents.Contains(declaration.ParentDeclaration.IdentifierName));
56+
}
57+
58+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
59+
{
60+
return Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document
61+
&& document.SupertypeNames.Contains("Workbook");
62+
}
63+
64+
protected override string ResultDescription(IdentifierReference reference)
65+
{
66+
var referenceText = reference.Context.GetText();
67+
return string.Format(
68+
InspectionResults.ImplicitContainingWorkbookReferenceInspection,
69+
referenceText);
70+
}
71+
}
72+
}
Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
using System.Linq;
2+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
3+
using Rubberduck.CodeAnalysis.Inspections.Attributes;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
7+
using Rubberduck.Resources.Inspections;
8+
9+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
10+
{
11+
/// <summary>
12+
/// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls inside worksheet modules that implicitly refer to the containing sheet.
13+
/// </summary>
14+
/// <reference name="Excel" />
15+
/// <why>
16+
/// Implicit references inside a worksheet document module can be mistakes for implicit references to the active worksheet, which is the behavior in all other places.
17+
/// By explicitly qualifying these member calls with Me, the ambiguity can be resolved.
18+
/// </why>
19+
/// <example hasResult="true">
20+
/// <module name="Sheet1" type="Document Module">
21+
/// <![CDATA[
22+
/// Private Sub Example()
23+
/// Dim foo As Range
24+
/// Set foo = Range("A1") ' Worksheet.Range implicitly from containing worksheet
25+
/// End Sub
26+
/// ]]>
27+
/// </module>
28+
/// </example>
29+
/// <example hasResult="false">
30+
/// <module name="Sheet1" type="Document Module">
31+
/// <![CDATA[
32+
/// Private Sub Example()
33+
/// Dim foo As Range
34+
/// Set foo = Me.Range("A1")
35+
/// End Sub
36+
/// ]]>
37+
/// </module>
38+
/// </example>
39+
[RequiredLibrary("Excel")]
40+
internal sealed class ImplicitContainingWorksheetReferenceInspection : ImplicitSheetReferenceInspectionBase
41+
{
42+
public ImplicitContainingWorksheetReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
43+
: base(declarationFinderProvider)
44+
{}
45+
46+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
47+
{
48+
return Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document
49+
&& document.SupertypeNames.Contains("Worksheet");
50+
}
51+
52+
protected override string ResultDescription(IdentifierReference reference)
53+
{
54+
return string.Format(
55+
InspectionResults.ImplicitContainingWorksheetReferenceInspection,
56+
reference.Declaration.IdentifierName);
57+
}
58+
}
59+
}

0 commit comments

Comments
 (0)