Skip to content

Commit 2060796

Browse files
committed
Stop considering declare statements for EmptyMethodInspection
1 parent 61c6db9 commit 2060796

File tree

2 files changed

+57
-14
lines changed

2 files changed

+57
-14
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
}

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)