Skip to content

Commit

Permalink
Merge pull request #5726 from retailcoder/fixStringSheet
Browse files Browse the repository at this point in the history
Tweaks worksheet inspection to look for Sheets.Item and Sheets._Default member calls; adjusted tests to correctly load worksheet/workbook supertypes.
  • Loading branch information
retailcoder committed Apr 19, 2021
2 parents 51f2d13 + d032b22 commit 236805a
Show file tree
Hide file tree
Showing 11 changed files with 381 additions and 163 deletions.
Expand Up @@ -3,6 +3,7 @@
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Common;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
Expand Down Expand Up @@ -59,41 +60,104 @@ public SheetAccessedUsingStringInspection(IDeclarationFinderProvider declaration
_projectsProvider = projectsProvider;
}

private static readonly string[] InterestingMembers =
/// <summary>
/// We're interested in both explicitly and implicitly bound retrievals from a Sheets collection.
/// </summary>
private static readonly string[] InterestingProperties =
{
"Worksheets", // gets a Sheets object containing Worksheet objects.
"Sheets", // gets a Sheets object containing all sheets (not just Worksheet sheets) in the qualifying workbook.
};

private static readonly string[] InterestingClasses =
{
"Workbook", // unqualified member call
"_Workbook", // qualified member call
"Item", // explicit member call
"_Default", // default member call (usually implicit)
};

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
if (!finder.TryFindProjectDeclaration("Excel", out var excel))
{
return Enumerable.Empty<Declaration>();
// [RequiredHost] attribute puts this in "should not happen" territory.
yield break;
}
var sheetsClass = (ModuleDeclaration)finder.FindClassModule("Sheets", excel, true);
if (sheetsClass == null)
{
// [RequiredHost] attribute puts this in "should not happen" territory.
yield break;
}

var relevantClasses = InterestingClasses
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>();
if (sheetsClass != null)
{
foreach (var property in sheetsClass.Members.OfType<PropertyDeclaration>())
{
if (InterestingProperties.Any(name => name.Equals(property.IdentifierName, System.StringComparison.InvariantCultureIgnoreCase)))
{
yield return property;
}
}
}
}

var relevantProperties = relevantClasses
.SelectMany(classDeclaration => classDeclaration.Members)
.OfType<PropertyDeclaration>()
.Where(member => InterestingMembers.Contains(member.IdentifierName));
private static ClassModuleDeclaration GetHostWorkbookDeclaration(DeclarationFinder finder)
{
var documentModuleQMNs = finder.AllModules.Where(m => m.ComponentType == ComponentType.Document);
ClassModuleDeclaration result = null;
foreach (var qmn in documentModuleQMNs)
{
var declaration = finder.ModuleDeclaration(qmn) as ClassModuleDeclaration;
if (declaration.Supertypes.Any(t => t.IdentifierName.Equals("Workbook") && t.ProjectName == "Excel" && !t.IsUserDefined))
{
result = declaration;
break;
}
}

return result ?? throw new System.InvalidOperationException("Failed to find the host Workbook declaration.");
}

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

protected override (bool isResult, string properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
{
var sheetNameArgumentLiteralExpressionContext = SheetNameArgumentLiteralExpressionContext(reference);
if (reference.IdentifierName.Equals(Tokens.Me, System.StringComparison.InvariantCultureIgnoreCase))
{
// if Me is a worksheet module,
return (false, null);
}

var hostWorkbookDeclaration = GetHostWorkbookDeclaration(finder);

var context = reference.Context as VBAParser.MemberAccessExprContext
?? reference.Context.Parent as VBAParser.MemberAccessExprContext
?? reference.Context.Parent.Parent as VBAParser.MemberAccessExprContext;

if (context is VBAParser.MemberAccessExprContext memberAccess)
{
var appObjectDeclaration = GetHostApplicationDeclaration(finder);
var isApplicationQualifier = appObjectDeclaration.References.Any(appRef =>
context.GetSelection().Contains(appRef.Selection)
&& appRef.QualifiedModuleName.Equals(reference.QualifiedModuleName));

if (isApplicationQualifier)
{
// Application.Sheets(...) is referring to the ActiveWorkbook, not necessarily ThisWorkbook.
return (false, null);
}
}

var isHostWorkbookQualifier = hostWorkbookDeclaration.References.Any(thisWorkbookRef =>
context.GetSelection().Contains(thisWorkbookRef.Selection)
&& thisWorkbookRef.QualifiedModuleName.Equals(reference.QualifiedModuleName));

var parentModule = finder.ModuleDeclaration(reference.QualifiedModuleName);
if (!isHostWorkbookQualifier && parentModule is ProceduralModuleDeclaration)
{
// in a standard module the reference is against ActiveWorkbook unless it's explicitly against ThisWorkbook.
return (false, null);
}

var sheetNameArgumentLiteralExpressionContext = SheetNameArgumentLiteralExpressionContext(reference);
if (sheetNameArgumentLiteralExpressionContext?.STRINGLITERAL() == null)
{
return (false, null);
Expand Down
Expand Up @@ -35,6 +35,20 @@ protected override void ResolveDeclarations(IReadOnlyCollection<QualifiedModuleN
foreach(var module in modules)
{
ResolveDeclarations(module, _state.ParseTrees.Find(s => s.Key == module).Value, projects, token);
var declaration = _state.DeclarationFinder.ModuleDeclaration(module);
if (declaration is DocumentModuleDeclaration document)
{
if (document.IdentifierName.Equals("ThisWorkbook", StringComparison.InvariantCultureIgnoreCase))
{
document.AddSupertypeName("Workbook");
document.AddSupertypeName("_Workbook");
}
else if (document.IdentifierName.ToLowerInvariant().Contains("sheet"))
{
document.AddSupertypeName("Worksheet");
document.AddSupertypeName("_Worksheet");
}
}
}
}
catch(OperationCanceledException)
Expand Down
@@ -0,0 +1,96 @@
using System;
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using System.Threading;
using Antlr4.Runtime.Tree;
using NLog;
using Rubberduck.Parsing.Common;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Parsing.VBA.Extensions;
using Rubberduck.Parsing.VBA.Parsing;
using Rubberduck.Parsing.VBA.ReferenceManagement.CompilationPasses;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.Extensions;

namespace Rubberduck.Parsing.VBA.ReferenceManagement
{
/// <summary>
/// An abstraction responsible for getting the SuperType names for a document module.
/// </summary>
public interface IDocumentModuleSuperTypeNamesProvider
{
IEnumerable<string> GetSuperTypeNamesFor(DocumentModuleDeclaration document);
}

/// <summary>
/// Gets the SuperType names for a document module using IComObject.
/// </summary>
public class DocumentModuleSuperTypeNamesProvider : IDocumentModuleSuperTypeNamesProvider
{
private readonly IUserComProjectProvider _userComProjectProvider;

public DocumentModuleSuperTypeNamesProvider(IUserComProjectProvider userComProjectProvider)
{
_userComProjectProvider = userComProjectProvider;
}

// skip IDispatch.. just about everything implements it and RD doesn't need to care about it; don't care about IUnknown either
private static readonly HashSet<string> IgnoredComInterfaces = new HashSet<string>(new[] { "IDispatch", "IUnknown" });

public IEnumerable<string> GetSuperTypeNamesFor(DocumentModuleDeclaration document)
{
var userComProject = _userComProjectProvider.UserProject(document.ProjectId);
if (userComProject == null)
{
return Enumerable.Empty<string>();
}

var comModule = userComProject.Members.SingleOrDefault(m => m.Name == document.ComponentName);
if (comModule == null)
{
return Enumerable.Empty<string>();
}

var inheritedInterfaces = comModule is ComCoClass documentCoClass
? documentCoClass.ImplementedInterfaces.ToList()
: (comModule as ComInterface)?.InheritedInterfaces.ToList();

if (inheritedInterfaces == null)
{
return Enumerable.Empty<string>();
}

var relevantInterfaces = inheritedInterfaces
.Where(i => !i.IsRestricted && !IgnoredComInterfaces.Contains(i.Name))
.ToList();

//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.

//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.
//Since we do not have a declaration for the hidden interface, we have to go one more step up the hierarchy.
var additionalInterfaces = relevantInterfaces
.Where(i => i.Name.Equals("_" + comModule.Name))
.SelectMany(i => i.InheritedInterfaces)
.ToList();

relevantInterfaces.AddRange(additionalInterfaces);

var superTypeNames = relevantInterfaces
.Select(i => i.Name)
.ToList();

//This emulates the VBE's behaviour to allow assignment to the coclass type instead on the interface.
var additionalSuperTypeNames = superTypeNames
.Where(name => name.StartsWith("_"))
.Select(name => name.Substring(1))
.Where(name => !name.Equals(comModule.Name))
.ToList();

superTypeNames.AddRange(additionalSuperTypeNames);
return superTypeNames.Distinct();
}
}
}
Expand Up @@ -20,12 +20,12 @@ public class ReferenceResolveRunner : ReferenceResolveRunnerBase
IParserStateManager parserStateManager,
IModuleToModuleReferenceManager moduleToModuleReferenceManager,
IReferenceRemover referenceRemover,
IUserComProjectProvider userComProjectProvider)
IDocumentModuleSuperTypeNamesProvider documentModuleSuperTypeNamesProvider)
:base(state,
parserStateManager,
moduleToModuleReferenceManager,
referenceRemover,
userComProjectProvider)
documentModuleSuperTypeNamesProvider)
{}


Expand Down

0 comments on commit 236805a

Please sign in to comment.