Skip to content

Commit

Permalink
Merge pull request #5744 from MDoerner/PersistQualifyingMember
Browse files Browse the repository at this point in the history
Add qualifying references to identifier references
  • Loading branch information
retailcoder committed May 7, 2021
2 parents 3108e01 + 5ff2308 commit 2026e69
Show file tree
Hide file tree
Showing 10 changed files with 1,034 additions and 342 deletions.
Expand Up @@ -21,74 +21,6 @@ protected IdentifierReferenceInspectionFromDeclarationsBase(IDeclarationFinderPr

protected virtual ICollection<string> DisabledQuickFixes(IdentifierReference reference) => new List<string>();

/// <summary>
/// Gets the possible <see cref="Declaration"/> that qualifies an identifier reference in a member access expression.
/// </summary>
protected IEnumerable<Declaration> GetQualifierCandidates(IdentifierReference reference, DeclarationFinder finder)
{
if (reference.Context.TryGetAncestor<VBAParser.MemberAccessExprContext>(out var memberAccess))
{
var parentModule = Declaration.GetModuleParent(reference.ParentScoping);
var qualifyingExpression = memberAccess.lExpression();
if (qualifyingExpression is VBAParser.SimpleNameExprContext simpleName)
{
if (simpleName.GetText().Equals(Tokens.Me, System.StringComparison.InvariantCultureIgnoreCase))
{
// qualifier is 'Me'
return new[] { parentModule };
}

// todo get the actual qualifying declaration?
return finder.MatchName(simpleName.GetText())
.Where(candidate => !candidate.IdentifierName.Equals(reference.Declaration.IdentifierName, System.StringComparison.InvariantCultureIgnoreCase));
}

if (qualifyingExpression.ChildCount == 1 && qualifyingExpression.GetText().Equals(Tokens.Me, System.StringComparison.InvariantCultureIgnoreCase))
{
// qualifier is 'Me'
return new[] { parentModule };
}
}

if (reference.Context.TryGetAncestor<VBAParser.WithMemberAccessExprContext>(out var dot))
{
// qualifier is a With block
var withBlock = dot.GetAncestor<VBAParser.WithStmtContext>();
return finder.ContainedIdentifierReferences(new QualifiedSelection(reference.QualifiedModuleName, withBlock.GetSelection()))
.Select(r => r.Declaration).Distinct()
.Where(candidate => !candidate.Equals(reference.Declaration));
}

if (reference.Context.TryGetAncestor<VBAParser.CallStmtContext>(out var callStmt))
{
if (reference.Context.TryGetAncestor<VBAParser.LExpressionContext>(out var lExpression))
{
// reference is in lexpression of a call statement

if (lExpression is VBAParser.MemberAccessExprContext member)
{
if (member.lExpression() is VBAParser.SimpleNameExprContext name)
{
if (reference.IdentifierName.Equals(name.identifier().GetText(), System.StringComparison.InvariantCultureIgnoreCase))
{
// unqualified
return Enumerable.Empty<Declaration>();
}

return finder.MatchName(name.identifier().GetText())
.Where(candidate => !candidate.Equals(reference.Declaration));
}

// todo get the actual qualifying declaration?
return finder.MatchName(member.lExpression().children.First().GetText())
.Where(candidate => !candidate.Equals(reference.Declaration));
}
}
}

return Enumerable.Empty<Declaration>();
}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults(DeclarationFinder finder)
{
var objectionableReferences = ObjectionableReferences(finder);
Expand Down
@@ -1,4 +1,5 @@
using System.Collections.Generic;
using System;
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
Expand All @@ -22,40 +23,27 @@ internal ImplicitWorkbookReferenceInspectionBase(IDeclarationFinderProvider decl
"_Global", "_Application", "Global", "Application", "_Workbook", "Workbook"
};

private IReadOnlyList<ModuleDeclaration> _relevantClasses;
private IReadOnlyList<PropertyGetDeclaration> _relevantProperties;

protected Declaration Excel { get; private set; }
protected Declaration Excel(DeclarationFinder finder)
{
return finder.BuiltInDeclarations(DeclarationType.Project)
.FirstOrDefault(project => project.IdentifierName.Equals("Excel", StringComparison.InvariantCultureIgnoreCase));
}

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
if (Excel == null)
{
if (!finder.TryFindProjectDeclaration("Excel", out var excel))
{
return Enumerable.Empty<Declaration>();
}
Excel = excel;
}

if (_relevantClasses == null)
{
_relevantClasses = InterestingClasses
.Select(className => finder.FindClassModule(className, Excel, true))
.OfType<ModuleDeclaration>()
.ToList();
}

if (_relevantProperties == null)
{
_relevantProperties = _relevantClasses
.SelectMany(classDeclaration => classDeclaration.Members)
.OfType<PropertyGetDeclaration>()
.Where(member => InterestingMembers.Contains(member.IdentifierName))
.ToList();
}

return _relevantProperties;
var excel = Excel(finder);
var relevantClasses = InterestingClasses
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>()
.ToList();

var relevantProperties = relevantClasses
.SelectMany(classDeclaration => classDeclaration.Members)
.OfType<PropertyGetDeclaration>()
.Where(member => InterestingMembers.Contains(member.IdentifierName))
.ToList();

return relevantProperties;
}
}
}
@@ -1,4 +1,3 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
Expand Down Expand Up @@ -45,46 +44,37 @@ internal sealed class ImplicitActiveWorkbookReferenceInspection : ImplicitWorkbo
public ImplicitActiveWorkbookReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider) { }

private IReadOnlyList<Declaration> _applicationCandidates;

protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
var qualifiers = base.GetQualifierCandidates(reference, finder);
var isQualified = qualifiers.Any();
var document = Declaration.GetModuleParent(reference.ParentNonScoping) as DocumentModuleDeclaration;

var isHostWorkbook = (document?.SupertypeNames.Contains("Workbook") ?? false)
&& (document?.ProjectId?.Equals(reference.QualifiedModuleName.ProjectId) ?? false);

var isQualified = reference.QualifyingReference != null;
if (!isQualified)
{
var document = Declaration.GetModuleParent(reference.ParentNonScoping) as DocumentModuleDeclaration;

var isHostWorkbook = (document?.SupertypeNames.Contains("Workbook") ?? false)
&& (document?.ProjectId?.Equals(reference.QualifiedModuleName.ProjectId) ?? false);

// unqualified calls aren't referring to ActiveWorkbook only inside a Workbook module:
return !isHostWorkbook;
}
else

if (reference.QualifyingReference.Declaration == null)
{
if (_applicationCandidates == null)
{
var applicationClass = finder.FindClassModule("Application", base.Excel, includeBuiltIn: true);
// note: underscored declarations would be for unqualified calls
var workbookClass = finder.FindClassModule("Workbook", base.Excel, includeBuiltIn: true);
var worksheetClass = finder.FindClassModule("Worksheet", base.Excel, includeBuiltIn: true);
var hostBook = finder.UserDeclarations(DeclarationType.Document)
.Cast<DocumentModuleDeclaration>()
.SingleOrDefault(doc => doc.ProjectId.Equals(reference.QualifiedModuleName.ProjectId)
&& doc.SupertypeNames.Contains("Workbook"));
//This should really only happen on unbound member calls and then the current reference would also be unbound.
//So, if we end up here, we have no idea and bail out.
return false;
}

_applicationCandidates = finder.MatchName("Application")
.Where(m => m.Equals(applicationClass)
|| (m.ParentDeclaration.Equals(workbookClass) && m.DeclarationType.HasFlag(DeclarationType.PropertyGet))
|| (m.ParentDeclaration.Equals(worksheetClass) && m.DeclarationType.HasFlag(DeclarationType.PropertyGet))
|| (m.ParentDeclaration.Equals(hostBook) && m.DeclarationType.HasFlag(DeclarationType.PropertyGet)))
.ToList();
}
var excelProjectId = Excel(finder).ProjectId;
var applicationCandidates = finder.MatchName("Application")
.Where(m => m.ProjectId.Equals(excelProjectId)
&& ( m.DeclarationType == DeclarationType.PropertyGet
|| m.DeclarationType == DeclarationType.ClassModule));

// qualified calls are referring to ActiveWorkbook if qualifier is the Application object:
return _applicationCandidates.Any(candidate => qualifiers.Any(q => q.Equals(candidate)));
}
var qualifyingDeclaration = reference.QualifyingReference.Declaration;

// qualified calls are referring to ActiveWorkbook if qualifier is the Application object:
return applicationCandidates.Any(candidate => qualifyingDeclaration.Equals(candidate));
}

protected override string ResultDescription(IdentifierReference reference)
Expand Down
@@ -1,10 +1,7 @@
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
Expand Down Expand Up @@ -61,10 +58,9 @@ protected override IEnumerable<Declaration> ObjectionableDeclarations(Declaratio

protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
var qualifiers = base.GetQualifierCandidates(reference, finder);
return Declaration.GetModuleParent(reference.ParentScoping) is DocumentModuleDeclaration document
&& document.SupertypeNames.Contains("Workbook")
&& !qualifiers.Any();
&& document.SupertypeNames.Contains("Workbook")
&& reference.QualifyingReference == null;
}

protected override string ResultDescription(IdentifierReference reference)
Expand Down
@@ -1,7 +1,6 @@
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
Expand Down Expand Up @@ -48,7 +47,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
{
return Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document
&& document.SupertypeNames.Contains("Worksheet")
&& !(reference.Context.Parent is Parsing.Grammar.VBAParser.MemberAccessExprContext); // if it's qualified, it's not an implicit reference
&& reference.QualifyingReference == null; // if it's qualified, it's not an implicit reference
}

protected override string ResultDescription(IdentifierReference reference)
Expand Down
10 changes: 6 additions & 4 deletions Rubberduck.Parsing/Symbols/Declaration.cs
Expand Up @@ -8,7 +8,6 @@
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
using Rubberduck.Parsing.Annotations.Concrete;

namespace Rubberduck.Parsing.Symbols
Expand Down Expand Up @@ -365,7 +364,7 @@ private bool IsObjectOrObjectArray
}
}

public void AddReference(
public IdentifierReference AddReference(
QualifiedModuleName module,
Declaration scope,
Declaration parent,
Expand All @@ -382,7 +381,8 @@ private bool IsObjectOrObjectArray
int defaultMemberRecursionDepth = 0,
bool isArrayAccess = false,
bool isProcedureCoercion = false,
bool isInnerRecursiveDefaultMemberAccess = false
bool isInnerRecursiveDefaultMemberAccess = false,
IdentifierReference qualifyingReference = null
)
{
var oldReference = _references.FirstOrDefault(r =>
Expand Down Expand Up @@ -415,8 +415,10 @@ private bool IsObjectOrObjectArray
defaultMemberRecursionDepth,
isArrayAccess,
isProcedureCoercion,
isInnerRecursiveDefaultMemberAccess);
isInnerRecursiveDefaultMemberAccess,
qualifyingReference);
_references.AddOrUpdate(newReference, 1, (key, value) => 1);
return newReference;
}

/// <summary>
Expand Down
6 changes: 5 additions & 1 deletion Rubberduck.Parsing/Symbols/IdentifierReference.cs
Expand Up @@ -30,7 +30,8 @@ public class IdentifierReference : IEquatable<IdentifierReference>
int defaultMemberRecursionDepth = 0,
bool isArrayAccess = false,
bool isProcedureCoercion = false,
bool isInnerRecursiveDefaultMemberAccess = false)
bool isInnerRecursiveDefaultMemberAccess = false,
IdentifierReference qualifyingReference = null)
{
ParentScoping = parentScopingDeclaration;
ParentNonScoping = parentNonScopingDeclaration;
Expand All @@ -48,6 +49,7 @@ public class IdentifierReference : IEquatable<IdentifierReference>
IsProcedureCoercion = isProcedureCoercion;
Annotations = annotations ?? new List<IParseTreeAnnotation>();
IsInnerRecursiveDefaultMemberAccess = isInnerRecursiveDefaultMemberAccess;
QualifyingReference = qualifyingReference;
}

public QualifiedSelection QualifiedSelection { get; }
Expand All @@ -68,6 +70,8 @@ public class IdentifierReference : IEquatable<IdentifierReference>
/// </summary>
public Declaration ParentNonScoping { get; }

public IdentifierReference QualifyingReference { get; }

public bool IsAssignment { get; }

public bool IsSetAssignment { get; }
Expand Down

0 comments on commit 2026e69

Please sign in to comment.