Skip to content

Commit

Permalink
still broken, something is off in identifier reference resolver (not …
Browse files Browse the repository at this point in the history
…looking at implemented interfaces?)
  • Loading branch information
retailcoder committed Jun 12, 2019
1 parent f7e3273 commit 421b820
Showing 1 changed file with 19 additions and 14 deletions.
@@ -1,6 +1,7 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.CodePathAnalysis.Nodes;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Inspections;
Expand All @@ -12,6 +13,7 @@
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Parsing;
using Rubberduck.VBEditor.ComManagement.TypeLibs;

namespace Rubberduck.Inspections.Concrete
{
Expand Down Expand Up @@ -54,11 +56,6 @@ public class SheetAccessedUsingStringInspection : InspectionBase
"Worksheets", "Sheets"
};

private static readonly string[] InterestingClasses =
{
"Workbook", "ThisWorkbook" // "_Global", "_Application", "Global", "Application", "Workbook"
};

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
Expand All @@ -69,7 +66,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

var targetProperties = BuiltInDeclarations
.OfType<PropertyDeclaration>()
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
.Where(x => InterestingMembers.Contains(x.IdentifierName) && x.ParentDeclaration?.IdentifierName == "_Workbook")
.ToList();

var references = targetProperties.SelectMany(declaration => declaration.References
Expand Down Expand Up @@ -99,21 +96,29 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
return issues;
}

private static bool IsAccessedWithStringLiteralParameter(IdentifierReference reference)
private bool IsAccessedWithStringLiteralParameter(IdentifierReference reference)
{
if (reference.Context.Parent.Parent is VBAParser.IndexExprContext qualifiedMemberCall)
{
return HasStringLiteralParameter(qualifiedMemberCall)
&& qualifiedMemberCall
?.GetAncestor<VBAParser.MemberAccessExprContext>()
?.lExpression().GetChild<VBAParser.SimpleNameExprContext>()
?.GetText() == "ThisWorkbook";
// member call is qualified; true if the qualifier is ThisWorkbook.
if (HasStringLiteralParameter(qualifiedMemberCall))
{
var qualifier = qualifiedMemberCall?.GetAncestor<VBAParser.MemberAccessExprContext>()
?.lExpression().GetChild<VBAParser.SimpleNameExprContext>()
?.GetText();
var project = State.DeclarationFinder.FindProject(reference.QualifiedModuleName.ProjectName, reference.ParentScoping);
if (State.DeclarationFinder.FindClassModule(qualifier, project) is ClassModuleDeclaration documentModule)
{
//return documentModule.ClassType == DocClassType.ExcelWorkbook;
}
}
}

// member call is unqualified; true if reference is inside the ThisWorkbook module.
return reference.Context.Parent is VBAParser.IndexExprContext unqualifiedMemberCall
&& HasStringLiteralParameter(unqualifiedMemberCall)
&& reference.ParentScoping.QualifiedModuleName.ComponentType == ComponentType.Document
&& reference.ParentScoping.QualifiedModuleName.ComponentName == "ThisWorkbook";
&& reference.ParentScoping is DocumentModuleDeclaration document
/*&& document.ClassType == DocClassType.ExcelWorkbook*/;
}

private static bool HasStringLiteralParameter(VBAParser.IndexExprContext context)
Expand Down

0 comments on commit 421b820

Please sign in to comment.