Skip to content

Commit

Permalink
Only strip enclosing square brackets from the identifierName of refer…
Browse files Browse the repository at this point in the history
…ences
  • Loading branch information
MDoerner committed Oct 18, 2019
1 parent 2060796 commit d7ee479
Show file tree
Hide file tree
Showing 3 changed files with 55 additions and 692 deletions.
Expand Up @@ -6,7 +6,8 @@
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.VBA;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.Inspections.Concrete
{
Expand Down Expand Up @@ -36,7 +37,7 @@ public sealed class UntypedFunctionUsageInspection : InspectionBase
public UntypedFunctionUsageInspection(RubberduckParserState state)
: base(state) { }

private readonly string[] _tokens = {
private readonly HashSet<string> _tokens = new HashSet<string>{
Tokens.Error,
Tokens.Hex,
Tokens.Oct,
Expand Down Expand Up @@ -64,17 +65,46 @@ public UntypedFunctionUsageInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarations = BuiltInDeclarations
.Where(item =>
_tokens.Any(token => item.IdentifierName == token || item.IdentifierName == "_B_var_" + token) &&
item.Scope.StartsWith("VBE7.DLL;"));
var finder = State.DeclarationFinder;

return declarations.SelectMany(declaration => declaration.References
.Where(item => _tokens.Contains(item.IdentifierName))
.Select(item => new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.UntypedFunctionUsageInspection, item.Declaration.IdentifierName),
State,
item)));
var declarationsToConsider = BuiltInVariantStringFunctionsWithStringTypedVersion(finder);

return declarationsToConsider
.SelectMany(NonStringHintedReferences)
.Select(Result);
}

private IEnumerable<Declaration> BuiltInVariantStringFunctionsWithStringTypedVersion(DeclarationFinder finder)
{
return finder
.BuiltInDeclarations(DeclarationType.Member)
.Where(item => (_tokens.Contains(item.IdentifierName)
|| item.IdentifierName.StartsWith("_B_var_")
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length)))
&& item.Scope.StartsWith("VBE7.DLL;"));
}

private IEnumerable<IdentifierReference> NonStringHintedReferences(Declaration declaration)
{
return declaration.References
.Where(item => _tokens.Contains(item.IdentifierName));
}

private IInspectionResult Result(IdentifierReference reference)
{
return new IdentifierReferenceInspectionResult(
this,
ResultDescription(reference),
State,
reference);
}

private static string ResultDescription(IdentifierReference reference)
{
var declarationName = reference.Declaration.IdentifierName;
return string.Format(
InspectionResults.UntypedFunctionUsageInspection,
declarationName);
}
}
}
Expand Up @@ -124,7 +124,7 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder)
{
var callSiteContext = expression.Context;
var callee = expression.ReferencedDeclaration;
var identifier = callee.IdentifierName;
var identifier = WithEnclosingBracketsRemoved(callSiteContext.GetText());
var selection = callSiteContext.GetSelection();
expression.ReferencedDeclaration.AddReference(
module,
Expand Down Expand Up @@ -164,7 +164,7 @@ private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedMod

var callSiteContext = expression.UnrestrictedNameContext;
var callee = expression.ReferencedDeclaration;
var identifier = callee.IdentifierName;
var identifier = WithEnclosingBracketsRemoved(callSiteContext.GetText());
var selection = callSiteContext.GetSelection();
expression.ReferencedDeclaration.AddReference(
module,
Expand All @@ -180,6 +180,16 @@ private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedMod
isSetAssignment);
}

private static string WithEnclosingBracketsRemoved(string identifierName)
{
if (identifierName.StartsWith("[") && identifierName.EndsWith("]"))
{
return identifierName.Substring(1, identifierName.Length - 2);
}

return identifierName;
}

private void Visit(
ObjectPrintExpression expression,
QualifiedModuleName module,
Expand Down

0 comments on commit d7ee479

Please sign in to comment.