Skip to content

Commit d70d3cb

Browse files
authored
Merge pull request #5193 from BZngr/5143_FalseNegative
ImplementedInterfaceMemberInspection evals Annotated-only and implemented interfaces
2 parents 2774943 + 728c627 commit d70d3cb

File tree

2 files changed

+56
-22
lines changed

2 files changed

+56
-22
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplementedInterfaceMemberInspection.cs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,13 @@
77
using Rubberduck.Parsing.Symbols;
88
using Rubberduck.Inspections.Inspections.Extensions;
99
using Rubberduck.Common;
10+
using System;
11+
using Rubberduck.Parsing.Annotations;
1012

1113
namespace Rubberduck.Inspections.Concrete
1214
{
1315
/// <summary>
14-
/// Identifies members of class modules that are used as interfaces, but that have a concrete implementation.
16+
/// Identifies class modules that define an interface with one or more members containing a concrete implementation.
1517
/// </summary>
1618
/// <why>
1719
/// Interfaces provide an abstract, unified programmatic access to different objects; concrete implementations of their members should be in a separate module that 'Implements' the interface.
@@ -43,7 +45,13 @@ public ImplementedInterfaceMemberInspection(Parsing.VBA.RubberduckParserState st
4345

4446
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4547
{
46-
return State.DeclarationFinder.FindAllUserInterfaces()
48+
var annotatedAsInterface = State.DeclarationFinder.Classes
49+
.Where(cls => cls.Annotations.Any(an => an.Annotation is InterfaceAnnotation)).Cast<ClassModuleDeclaration>();
50+
51+
var implementedAndOrAnnotatedInterfaceModules = State.DeclarationFinder.FindAllUserInterfaces()
52+
.Union(annotatedAsInterface);
53+
54+
return implementedAndOrAnnotatedInterfaceModules
4755
.SelectMany(interfaceModule => interfaceModule.Members
4856
.Where(member => ((ModuleBodyElementDeclaration)member).Block.ContainsExecutableStatements(true)))
4957
.Select(result => new DeclarationInspectionResult(this,

RubberduckTests/Inspections/ImplementedInterfaceMemberInspectionTests.cs

Lines changed: 46 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,13 @@
44
using RubberduckTests.Mocks;
55
using Rubberduck.Inspections.Concrete;
66
using Rubberduck.VBEditor.SafeComWrappers;
7+
using Rubberduck.Parsing.Inspections.Abstract;
8+
using Rubberduck.Parsing.VBA;
79

810
namespace RubberduckTests.Inspections
911
{
1012
[TestFixture]
11-
public class ImplementedInterfaceMemberInspectionTests
13+
public class ImplementedInterfaceMemberInspectionTests : InspectionTestsBase
1214
{
1315
[Test]
1416
[Category("Inspections")]
@@ -38,7 +40,7 @@ End Sub
3840
Public Sub IClass1_DoSomethingElse(ByVal a As Integer)
3941
MsgBox ""?""
4042
End Sub";
41-
CheckActualEmptyBlockCountEqualsExpected(interfaceCode, concreteCode, 0);
43+
CheckActualEmptyBlockCountEqualsExpected(("IClass1", interfaceCode), ("Class1", concreteCode), 0);
4244
}
4345

4446
[Test]
@@ -59,7 +61,7 @@ Private Sub IClass1_DoSomething(ByVal a As Integer)
5961
End Sub
6062
Public Sub IClass1_DoSomethingElse(ByVal a As Integer)
6163
End Sub";
62-
CheckActualEmptyBlockCountEqualsExpected(interfaceCode, concreteCode, 1);
64+
CheckActualEmptyBlockCountEqualsExpected(("IClass1", interfaceCode), ("Class1", concreteCode), 1);
6365
}
6466

6567
[Test]
@@ -81,7 +83,7 @@ public void ImplementedInterfaceMember_VariousStatements_DontReturnResult(string
8183
MsgBox ""?""
8284
End Sub";
8385

84-
CheckActualEmptyBlockCountEqualsExpected(interfaceCode, concreteCode, 0);
86+
CheckActualEmptyBlockCountEqualsExpected(("IClass1", interfaceCode), ("Class1", concreteCode), 0);
8587
}
8688

8789
[Test]
@@ -117,28 +119,52 @@ public void ImplementedInterfaceMember_VariousStatements_ReturnResult(string sta
117119
Sub IClass1_Qux()
118120
End Sub";
119121

120-
CheckActualEmptyBlockCountEqualsExpected(interfaceCode, concreteCode, 1);
122+
CheckActualEmptyBlockCountEqualsExpected(("IClass1", interfaceCode), ("Class1", concreteCode), 1);
121123
}
122124

123-
private void CheckActualEmptyBlockCountEqualsExpected(string interfaceCode, string concreteCode, int expectedCount)
125+
//https://github.com/rubberduck-vba/Rubberduck/issues/5143
126+
[TestCase(@"MsgBox ""?""","", 1)] //No implementers, only the annotation marks interface class
127+
[TestCase("", "", 0)] //Annotated only, but no implementers - no result
128+
[TestCase(@"MsgBox ""?""", "Implements IClass1", 1)] //Annotated and an Implementer yields a single inspection result
129+
[Category("Inspections")]
130+
public void ImplementedInterfaceMember_AnnotatedOnly_ReturnsResult(string interfaceBody, string implementsStatement, int expected)
124131
{
125-
var builder = new MockVbeBuilder();
126-
var project = builder.ProjectBuilder("TestProject1", ProjectProtection.Unprotected)
127-
.AddComponent("IClass1", ComponentType.ClassModule, interfaceCode)
128-
.AddComponent("Class1", ComponentType.ClassModule, concreteCode)
129-
.Build();
130-
var vbe = builder.AddProject(project).Build();
131-
132-
using (var state = MockParser.CreateAndParse(vbe.Object))
133-
{
132+
var interfaceCode =
133+
$@"
134+
'@Interface
135+
136+
Public Sub DoSomething(ByVal a As Integer)
137+
End Sub
138+
Public Sub DoSomethingElse(ByVal a As Integer)
139+
{interfaceBody}
140+
End Sub";
141+
var concreteCode =
142+
$@"
143+
144+
{implementsStatement}
145+
146+
Private Sub IClass1_DoSomething(ByVal a As Integer)
147+
MsgBox ""?""
148+
End Sub
149+
Public Sub IClass1_DoSomethingElse(ByVal a As Integer)
150+
End Sub";
151+
CheckActualEmptyBlockCountEqualsExpected(("IClass1", interfaceCode), ("Class1", concreteCode), expected);
152+
}
134153

135-
var inspection = new ImplementedInterfaceMemberInspection(state);
136-
var inspector = InspectionsHelper.GetInspector(inspection);
137-
var actualResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
154+
private void CheckActualEmptyBlockCountEqualsExpected((string identifier, string code) interfaceDef, (string identifier, string code) implementerDef, int expectedCount)
155+
{
156+
var modules = new(string, string, ComponentType)[]
157+
{
158+
(interfaceDef.identifier, interfaceDef.code, ComponentType.ClassModule),
159+
(implementerDef.identifier, implementerDef.code, ComponentType.ClassModule)
160+
};
138161

139-
Assert.AreEqual(expectedCount, actualResults.Count());
140-
}
162+
Assert.AreEqual(expectedCount, InspectionResultsForModules(modules).Count());
163+
}
141164

165+
protected override IInspection InspectionUnderTest(RubberduckParserState state)
166+
{
167+
return new ImplementedInterfaceMemberInspection(state);
142168
}
143169
}
144170
}

0 commit comments

Comments
 (0)