Skip to content

Commit d7ee479

Browse files
committed
Only strip enclosing square brackets from the identifierName of references
1 parent 2060796 commit d7ee479

File tree

3 files changed

+55
-692
lines changed

3 files changed

+55
-692
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs

Lines changed: 42 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,8 @@
66
using Rubberduck.Parsing.Inspections.Abstract;
77
using Rubberduck.Resources.Inspections;
88
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.Inspections.Inspections.Extensions;
9+
using Rubberduck.Parsing.Symbols;
10+
using Rubberduck.Parsing.VBA.DeclarationCaching;
1011

1112
namespace Rubberduck.Inspections.Concrete
1213
{
@@ -36,7 +37,7 @@ public sealed class UntypedFunctionUsageInspection : InspectionBase
3637
public UntypedFunctionUsageInspection(RubberduckParserState state)
3738
: base(state) { }
3839

39-
private readonly string[] _tokens = {
40+
private readonly HashSet<string> _tokens = new HashSet<string>{
4041
Tokens.Error,
4142
Tokens.Hex,
4243
Tokens.Oct,
@@ -64,17 +65,46 @@ public UntypedFunctionUsageInspection(RubberduckParserState state)
6465

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

72-
return declarations.SelectMany(declaration => declaration.References
73-
.Where(item => _tokens.Contains(item.IdentifierName))
74-
.Select(item => new IdentifierReferenceInspectionResult(this,
75-
string.Format(InspectionResults.UntypedFunctionUsageInspection, item.Declaration.IdentifierName),
76-
State,
77-
item)));
70+
var declarationsToConsider = BuiltInVariantStringFunctionsWithStringTypedVersion(finder);
71+
72+
return declarationsToConsider
73+
.SelectMany(NonStringHintedReferences)
74+
.Select(Result);
75+
}
76+
77+
private IEnumerable<Declaration> BuiltInVariantStringFunctionsWithStringTypedVersion(DeclarationFinder finder)
78+
{
79+
return finder
80+
.BuiltInDeclarations(DeclarationType.Member)
81+
.Where(item => (_tokens.Contains(item.IdentifierName)
82+
|| item.IdentifierName.StartsWith("_B_var_")
83+
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length)))
84+
&& item.Scope.StartsWith("VBE7.DLL;"));
85+
}
86+
87+
private IEnumerable<IdentifierReference> NonStringHintedReferences(Declaration declaration)
88+
{
89+
return declaration.References
90+
.Where(item => _tokens.Contains(item.IdentifierName));
91+
}
92+
93+
private IInspectionResult Result(IdentifierReference reference)
94+
{
95+
return new IdentifierReferenceInspectionResult(
96+
this,
97+
ResultDescription(reference),
98+
State,
99+
reference);
100+
}
101+
102+
private static string ResultDescription(IdentifierReference reference)
103+
{
104+
var declarationName = reference.Declaration.IdentifierName;
105+
return string.Format(
106+
InspectionResults.UntypedFunctionUsageInspection,
107+
declarationName);
78108
}
79109
}
80110
}

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ private void Visit(
124124
{
125125
var callSiteContext = expression.Context;
126126
var callee = expression.ReferencedDeclaration;
127-
var identifier = callee.IdentifierName;
127+
var identifier = WithEnclosingBracketsRemoved(callSiteContext.GetText());
128128
var selection = callSiteContext.GetSelection();
129129
expression.ReferencedDeclaration.AddReference(
130130
module,
@@ -164,7 +164,7 @@ private void Visit(
164164

165165
var callSiteContext = expression.UnrestrictedNameContext;
166166
var callee = expression.ReferencedDeclaration;
167-
var identifier = callee.IdentifierName;
167+
var identifier = WithEnclosingBracketsRemoved(callSiteContext.GetText());
168168
var selection = callSiteContext.GetSelection();
169169
expression.ReferencedDeclaration.AddReference(
170170
module,
@@ -180,6 +180,16 @@ private void Visit(
180180
isSetAssignment);
181181
}
182182

183+
private static string WithEnclosingBracketsRemoved(string identifierName)
184+
{
185+
if (identifierName.StartsWith("[") && identifierName.EndsWith("]"))
186+
{
187+
return identifierName.Substring(1, identifierName.Length - 2);
188+
}
189+
190+
return identifierName;
191+
}
192+
183193
private void Visit(
184194
ObjectPrintExpression expression,
185195
QualifiedModuleName module,

0 commit comments

Comments
 (0)