Skip to content

Commit 236805a

Browse files
authored
Merge pull request #5726 from retailcoder/fixStringSheet
Tweaks worksheet inspection to look for Sheets.Item and Sheets._Default member calls; adjusted tests to correctly load worksheet/workbook supertypes.
2 parents 51f2d13 + d032b22 commit 236805a

File tree

11 files changed

+381
-163
lines changed

11 files changed

+381
-163
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs

Lines changed: 83 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using Rubberduck.CodeAnalysis.Inspections.Abstract;
44
using Rubberduck.CodeAnalysis.Inspections.Attributes;
55
using Rubberduck.Common;
6+
using Rubberduck.Parsing;
67
using Rubberduck.Parsing.Grammar;
78
using Rubberduck.Parsing.Symbols;
89
using Rubberduck.Parsing.VBA;
@@ -59,41 +60,104 @@ public SheetAccessedUsingStringInspection(IDeclarationFinderProvider declaration
5960
_projectsProvider = projectsProvider;
6061
}
6162

62-
private static readonly string[] InterestingMembers =
63+
/// <summary>
64+
/// We're interested in both explicitly and implicitly bound retrievals from a Sheets collection.
65+
/// </summary>
66+
private static readonly string[] InterestingProperties =
6367
{
64-
"Worksheets", // gets a Sheets object containing Worksheet objects.
65-
"Sheets", // gets a Sheets object containing all sheets (not just Worksheet sheets) in the qualifying workbook.
66-
};
67-
68-
private static readonly string[] InterestingClasses =
69-
{
70-
"Workbook", // unqualified member call
71-
"_Workbook", // qualified member call
68+
"Item", // explicit member call
69+
"_Default", // default member call (usually implicit)
7270
};
7371

7472
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
7573
{
7674
if (!finder.TryFindProjectDeclaration("Excel", out var excel))
7775
{
78-
return Enumerable.Empty<Declaration>();
76+
// [RequiredHost] attribute puts this in "should not happen" territory.
77+
yield break;
78+
}
79+
var sheetsClass = (ModuleDeclaration)finder.FindClassModule("Sheets", excel, true);
80+
if (sheetsClass == null)
81+
{
82+
// [RequiredHost] attribute puts this in "should not happen" territory.
83+
yield break;
7984
}
8085

81-
var relevantClasses = InterestingClasses
82-
.Select(className => finder.FindClassModule(className, excel, true))
83-
.OfType<ModuleDeclaration>();
86+
if (sheetsClass != null)
87+
{
88+
foreach (var property in sheetsClass.Members.OfType<PropertyDeclaration>())
89+
{
90+
if (InterestingProperties.Any(name => name.Equals(property.IdentifierName, System.StringComparison.InvariantCultureIgnoreCase)))
91+
{
92+
yield return property;
93+
}
94+
}
95+
}
96+
}
8497

85-
var relevantProperties = relevantClasses
86-
.SelectMany(classDeclaration => classDeclaration.Members)
87-
.OfType<PropertyDeclaration>()
88-
.Where(member => InterestingMembers.Contains(member.IdentifierName));
98+
private static ClassModuleDeclaration GetHostWorkbookDeclaration(DeclarationFinder finder)
99+
{
100+
var documentModuleQMNs = finder.AllModules.Where(m => m.ComponentType == ComponentType.Document);
101+
ClassModuleDeclaration result = null;
102+
foreach (var qmn in documentModuleQMNs)
103+
{
104+
var declaration = finder.ModuleDeclaration(qmn) as ClassModuleDeclaration;
105+
if (declaration.Supertypes.Any(t => t.IdentifierName.Equals("Workbook") && t.ProjectName == "Excel" && !t.IsUserDefined))
106+
{
107+
result = declaration;
108+
break;
109+
}
110+
}
111+
112+
return result ?? throw new System.InvalidOperationException("Failed to find the host Workbook declaration.");
113+
}
89114

90-
return relevantProperties;
115+
private static ClassModuleDeclaration GetHostApplicationDeclaration(DeclarationFinder finder)
116+
{
117+
var result = finder.MatchName("Application").OfType<ClassModuleDeclaration>().FirstOrDefault(t => t.ProjectName == "Excel" && !t.IsUserDefined) as ClassModuleDeclaration;
118+
return result ?? throw new System.InvalidOperationException("Failed to find the host Application declaration.");
91119
}
92120

93121
protected override (bool isResult, string properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
94122
{
95-
var sheetNameArgumentLiteralExpressionContext = SheetNameArgumentLiteralExpressionContext(reference);
123+
if (reference.IdentifierName.Equals(Tokens.Me, System.StringComparison.InvariantCultureIgnoreCase))
124+
{
125+
// if Me is a worksheet module,
126+
return (false, null);
127+
}
96128

129+
var hostWorkbookDeclaration = GetHostWorkbookDeclaration(finder);
130+
131+
var context = reference.Context as VBAParser.MemberAccessExprContext
132+
?? reference.Context.Parent as VBAParser.MemberAccessExprContext
133+
?? reference.Context.Parent.Parent as VBAParser.MemberAccessExprContext;
134+
135+
if (context is VBAParser.MemberAccessExprContext memberAccess)
136+
{
137+
var appObjectDeclaration = GetHostApplicationDeclaration(finder);
138+
var isApplicationQualifier = appObjectDeclaration.References.Any(appRef =>
139+
context.GetSelection().Contains(appRef.Selection)
140+
&& appRef.QualifiedModuleName.Equals(reference.QualifiedModuleName));
141+
142+
if (isApplicationQualifier)
143+
{
144+
// Application.Sheets(...) is referring to the ActiveWorkbook, not necessarily ThisWorkbook.
145+
return (false, null);
146+
}
147+
}
148+
149+
var isHostWorkbookQualifier = hostWorkbookDeclaration.References.Any(thisWorkbookRef =>
150+
context.GetSelection().Contains(thisWorkbookRef.Selection)
151+
&& thisWorkbookRef.QualifiedModuleName.Equals(reference.QualifiedModuleName));
152+
153+
var parentModule = finder.ModuleDeclaration(reference.QualifiedModuleName);
154+
if (!isHostWorkbookQualifier && parentModule is ProceduralModuleDeclaration)
155+
{
156+
// in a standard module the reference is against ActiveWorkbook unless it's explicitly against ThisWorkbook.
157+
return (false, null);
158+
}
159+
160+
var sheetNameArgumentLiteralExpressionContext = SheetNameArgumentLiteralExpressionContext(reference);
97161
if (sheetNameArgumentLiteralExpressionContext?.STRINGLITERAL() == null)
98162
{
99163
return (false, null);

Rubberduck.Parsing/VBA/DeclarationResolving/SynchronousDeclarationResolveRunner.cs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,20 @@ protected override void ResolveDeclarations(IReadOnlyCollection<QualifiedModuleN
3535
foreach(var module in modules)
3636
{
3737
ResolveDeclarations(module, _state.ParseTrees.Find(s => s.Key == module).Value, projects, token);
38+
var declaration = _state.DeclarationFinder.ModuleDeclaration(module);
39+
if (declaration is DocumentModuleDeclaration document)
40+
{
41+
if (document.IdentifierName.Equals("ThisWorkbook", StringComparison.InvariantCultureIgnoreCase))
42+
{
43+
document.AddSupertypeName("Workbook");
44+
document.AddSupertypeName("_Workbook");
45+
}
46+
else if (document.IdentifierName.ToLowerInvariant().Contains("sheet"))
47+
{
48+
document.AddSupertypeName("Worksheet");
49+
document.AddSupertypeName("_Worksheet");
50+
}
51+
}
3852
}
3953
}
4054
catch(OperationCanceledException)
Lines changed: 96 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,96 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Diagnostics;
4+
using System.Linq;
5+
using System.Threading;
6+
using Antlr4.Runtime.Tree;
7+
using NLog;
8+
using Rubberduck.Parsing.Common;
9+
using Rubberduck.Parsing.ComReflection;
10+
using Rubberduck.Parsing.Symbols;
11+
using Rubberduck.Parsing.VBA.DeclarationCaching;
12+
using Rubberduck.Parsing.VBA.Extensions;
13+
using Rubberduck.Parsing.VBA.Parsing;
14+
using Rubberduck.Parsing.VBA.ReferenceManagement.CompilationPasses;
15+
using Rubberduck.VBEditor;
16+
using Rubberduck.VBEditor.Extensions;
17+
18+
namespace Rubberduck.Parsing.VBA.ReferenceManagement
19+
{
20+
/// <summary>
21+
/// An abstraction responsible for getting the SuperType names for a document module.
22+
/// </summary>
23+
public interface IDocumentModuleSuperTypeNamesProvider
24+
{
25+
IEnumerable<string> GetSuperTypeNamesFor(DocumentModuleDeclaration document);
26+
}
27+
28+
/// <summary>
29+
/// Gets the SuperType names for a document module using IComObject.
30+
/// </summary>
31+
public class DocumentModuleSuperTypeNamesProvider : IDocumentModuleSuperTypeNamesProvider
32+
{
33+
private readonly IUserComProjectProvider _userComProjectProvider;
34+
35+
public DocumentModuleSuperTypeNamesProvider(IUserComProjectProvider userComProjectProvider)
36+
{
37+
_userComProjectProvider = userComProjectProvider;
38+
}
39+
40+
// skip IDispatch.. just about everything implements it and RD doesn't need to care about it; don't care about IUnknown either
41+
private static readonly HashSet<string> IgnoredComInterfaces = new HashSet<string>(new[] { "IDispatch", "IUnknown" });
42+
43+
public IEnumerable<string> GetSuperTypeNamesFor(DocumentModuleDeclaration document)
44+
{
45+
var userComProject = _userComProjectProvider.UserProject(document.ProjectId);
46+
if (userComProject == null)
47+
{
48+
return Enumerable.Empty<string>();
49+
}
50+
51+
var comModule = userComProject.Members.SingleOrDefault(m => m.Name == document.ComponentName);
52+
if (comModule == null)
53+
{
54+
return Enumerable.Empty<string>();
55+
}
56+
57+
var inheritedInterfaces = comModule is ComCoClass documentCoClass
58+
? documentCoClass.ImplementedInterfaces.ToList()
59+
: (comModule as ComInterface)?.InheritedInterfaces.ToList();
60+
61+
if (inheritedInterfaces == null)
62+
{
63+
return Enumerable.Empty<string>();
64+
}
65+
66+
var relevantInterfaces = inheritedInterfaces
67+
.Where(i => !i.IsRestricted && !IgnoredComInterfaces.Contains(i.Name))
68+
.ToList();
69+
70+
//todo: Find a way to deal with the VBE's document type assignment and interface behaviour not relying on an assumption about an interface naming conventions.
71+
72+
//Some hosts like Access chose to have a separate hidden interface for each document module and only let that inherit the built-in base interface.
73+
//Since we do not have a declaration for the hidden interface, we have to go one more step up the hierarchy.
74+
var additionalInterfaces = relevantInterfaces
75+
.Where(i => i.Name.Equals("_" + comModule.Name))
76+
.SelectMany(i => i.InheritedInterfaces)
77+
.ToList();
78+
79+
relevantInterfaces.AddRange(additionalInterfaces);
80+
81+
var superTypeNames = relevantInterfaces
82+
.Select(i => i.Name)
83+
.ToList();
84+
85+
//This emulates the VBE's behaviour to allow assignment to the coclass type instead on the interface.
86+
var additionalSuperTypeNames = superTypeNames
87+
.Where(name => name.StartsWith("_"))
88+
.Select(name => name.Substring(1))
89+
.Where(name => !name.Equals(comModule.Name))
90+
.ToList();
91+
92+
superTypeNames.AddRange(additionalSuperTypeNames);
93+
return superTypeNames.Distinct();
94+
}
95+
}
96+
}

Rubberduck.Parsing/VBA/ReferenceManagement/ReferenceResolveRunner.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,12 +20,12 @@ public ReferenceResolveRunner(
2020
IParserStateManager parserStateManager,
2121
IModuleToModuleReferenceManager moduleToModuleReferenceManager,
2222
IReferenceRemover referenceRemover,
23-
IUserComProjectProvider userComProjectProvider)
23+
IDocumentModuleSuperTypeNamesProvider documentModuleSuperTypeNamesProvider)
2424
:base(state,
2525
parserStateManager,
2626
moduleToModuleReferenceManager,
2727
referenceRemover,
28-
userComProjectProvider)
28+
documentModuleSuperTypeNamesProvider)
2929
{}
3030

3131

0 commit comments

Comments
 (0)