Skip to content

Commit 5fcc213

Browse files
authored
Merge pull request #5234 from MDoerner/FixUntypedFunctionInspection
Fix untyped function inspection
2 parents 61c6db9 + d7ee479 commit 5fcc213

File tree

5 files changed

+112
-706
lines changed

5 files changed

+112
-706
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs

Lines changed: 46 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,11 @@
66
using System.Collections.Generic;
77
using System.Linq;
88
using Rubberduck.Parsing.Symbols;
9-
using Rubberduck.Inspections.Inspections.Extensions;
109
using Rubberduck.Common;
10+
using Rubberduck.Inspections.Inspections.Extensions;
11+
using Rubberduck.Parsing.VBA.DeclarationCaching;
12+
using Rubberduck.Parsing.VBA.Extensions;
13+
using Rubberduck.VBEditor;
1114

1215
namespace Rubberduck.Inspections.Concrete
1316
{
@@ -39,19 +42,48 @@ public EmptyMethodInspection(RubberduckParserState state)
3942

4043
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4144
{
42-
var allInterfaces = new HashSet<ClassModuleDeclaration>(State.DeclarationFinder.FindAllUserInterfaces());
43-
44-
return State.DeclarationFinder.UserDeclarations(DeclarationType.Member)
45-
.Where(member => !allInterfaces.Any(userInterface => userInterface.QualifiedModuleName == member.QualifiedModuleName)
46-
&& !(member is ModuleBodyElementDeclaration mbe && mbe.Block.ContainsExecutableStatements()))
47-
48-
.Select(result => new DeclarationInspectionResult(this,
49-
string.Format(InspectionResults.EmptyMethodInspection,
50-
Resources.RubberduckUI.ResourceManager
51-
.GetString("DeclarationType_" + result.DeclarationType)
52-
.Capitalize(),
53-
result.IdentifierName),
54-
result));
45+
var finder = State.DeclarationFinder;
46+
47+
var userInterfaces = UserInterfaces(finder);
48+
var emptyMethods = EmptyNonInterfaceMethods(finder, userInterfaces);
49+
50+
return emptyMethods.Select(Result);
51+
}
52+
53+
private static ICollection<QualifiedModuleName> UserInterfaces(DeclarationFinder finder)
54+
{
55+
return finder
56+
.FindAllUserInterfaces()
57+
.Select(decl => decl.QualifiedModuleName)
58+
.ToHashSet();
59+
}
60+
61+
private static IEnumerable<Declaration> EmptyNonInterfaceMethods(DeclarationFinder finder, ICollection<QualifiedModuleName> userInterfaces)
62+
{
63+
return finder
64+
.UserDeclarations(DeclarationType.Member)
65+
.Where(member => !userInterfaces.Contains(member.QualifiedModuleName)
66+
&& member is ModuleBodyElementDeclaration moduleBodyElement
67+
&& !moduleBodyElement.Block.ContainsExecutableStatements());
68+
}
69+
70+
private IInspectionResult Result(Declaration member)
71+
{
72+
return new DeclarationInspectionResult(
73+
this,
74+
ResultDescription(member),
75+
member);
76+
}
77+
78+
private static string ResultDescription(Declaration member)
79+
{
80+
var identifierName = member.IdentifierName;
81+
var declarationType = member.DeclarationType.ToLocalizedString();
82+
83+
return string.Format(
84+
InspectionResults.EmptyMethodInspection,
85+
declarationType,
86+
identifierName);
5587
}
5688
}
5789
}

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,

RubberduckTests/Inspections/EmptyMethodInspectionTests.cs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -118,6 +118,17 @@ Sub Foo()
118118
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
119119
}
120120

121+
[Test]
122+
[Category("Inspections")]
123+
public void EmptyMethod_DeclareStatement_NoResult()
124+
{
125+
string inputCode =
126+
$@"
127+
Private Declare PtrSafe Function GetKeyState Lib ""user32.dll"" (ByVal nVirtKey As Long) As Integer
128+
";
129+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
130+
}
131+
121132
private void CheckActualEmptyBlockCountEqualsExpected(string interfaceCode, string concreteCode, int expectedCount)
122133
{
123134
var builder = new MockVbeBuilder();

0 commit comments

Comments
 (0)