Skip to content

Commit 9c3643f

Browse files
committed
Fix ImplementInterfaceMemberInspection
There was an invalid cast because the inspection assumed that everything returnes by ClassModuleDeclaration.Member was a module body element. However, there are module variables as well. This commit rewrites the inspection completely and makes it use the base class.
1 parent 5d7369a commit 9c3643f

File tree

3 files changed

+53
-30
lines changed

3 files changed

+53
-30
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/DeclarationInspectionBase.cs

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Parsing.Inspections.Abstract;
55
using Rubberduck.Parsing.Symbols;
66
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
78
using Rubberduck.VBEditor;
89

910
namespace Rubberduck.Inspections.Abstract
@@ -20,11 +21,13 @@ protected DeclarationInspectionBase(RubberduckParserState state, params Declarat
2021
RelevantDeclarationTypes = relevantDeclarationTypes;
2122
}
2223

23-
protected abstract bool IsResultDeclaration(Declaration declaration);
24+
protected abstract bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder);
2425
protected abstract string ResultDescription(Declaration declaration);
2526

2627
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2728
{
29+
var finder = DeclarationFinderProvider.DeclarationFinder;
30+
2831
var results = new List<IInspectionResult>();
2932
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
3033
{
@@ -34,23 +37,29 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3437
}
3538

3639
var module = moduleDeclaration.QualifiedModuleName;
37-
results.AddRange(DoGetInspectionResults(module));
40+
results.AddRange(DoGetInspectionResults(module, finder));
3841
}
3942

4043
return results;
4144
}
4245

4346
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
4447
{
45-
var objectionableDeclarations = RelevantDeclarationsInModule(module)
46-
.Where(IsResultDeclaration);
48+
var finder = DeclarationFinderProvider.DeclarationFinder;
49+
return DoGetInspectionResults(module, finder);
50+
}
51+
52+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
53+
{
54+
var objectionableDeclarations = RelevantDeclarationsInModule(module, finder)
55+
.Where(declaration => IsResultDeclaration(declaration, finder));
4756

4857
return objectionableDeclarations
4958
.Select(InspectionResult)
5059
.ToList();
5160
}
5261

53-
protected virtual IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module)
62+
protected virtual IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
5463
{
5564
return RelevantDeclarationTypes
5665
.SelectMany(declarationType => DeclarationFinderProvider.DeclarationFinder.Members(module, declarationType))

Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueAlwaysDiscardedInspection.cs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ public FunctionReturnValueAlwaysDiscardedInspection(RubberduckParserState state)
5353
:base(state, DeclarationType.Function)
5454
{}
5555

56-
protected override bool IsResultDeclaration(Declaration declaration)
56+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
5757
{
5858
if (!(declaration is ModuleBodyElementDeclaration moduleBodyElementDeclaration))
5959
{
@@ -66,8 +66,6 @@ protected override bool IsResultDeclaration(Declaration declaration)
6666
return false;
6767
}
6868

69-
var finder = DeclarationFinderProvider.DeclarationFinder;
70-
7169
if (moduleBodyElementDeclaration.IsInterfaceMember)
7270
{
7371
return IsInterfaceIssue(moduleBodyElementDeclaration, finder);
Lines changed: 38 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,11 @@
11
using Rubberduck.Inspections.Abstract;
2-
using Rubberduck.Inspections.Results;
3-
using Rubberduck.Parsing.Inspections.Abstract;
42
using Rubberduck.Resources.Inspections;
5-
using System.Collections.Generic;
63
using System.Linq;
74
using Rubberduck.Parsing.Symbols;
85
using Rubberduck.Inspections.Inspections.Extensions;
96
using Rubberduck.Common;
10-
using System;
117
using Rubberduck.Parsing.Annotations;
8+
using Rubberduck.Parsing.VBA.DeclarationCaching;
129

1310
namespace Rubberduck.Inspections.Concrete
1411
{
@@ -38,30 +35,49 @@ namespace Rubberduck.Inspections.Concrete
3835
/// End Sub
3936
/// ]]>
4037
/// </example>
41-
internal class ImplementedInterfaceMemberInspection : InspectionBase
38+
internal class ImplementedInterfaceMemberInspection : DeclarationInspectionBase
4239
{
4340
public ImplementedInterfaceMemberInspection(Parsing.VBA.RubberduckParserState state)
44-
: base(state) { }
41+
: base(state, DeclarationType.ClassModule)
42+
{}
4543

46-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
44+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4745
{
48-
var annotatedAsInterface = State.DeclarationFinder.Classes
49-
.Where(cls => cls.Annotations.Any(an => an.Annotation is InterfaceAnnotation)).Cast<ClassModuleDeclaration>();
46+
if (!IsInterfaceDeclaration(declaration))
47+
{
48+
return false;
49+
}
5050

51-
var implementedAndOrAnnotatedInterfaceModules = State.DeclarationFinder.FindAllUserInterfaces()
52-
.Union(annotatedAsInterface);
51+
var moduleBodyElements = finder.Members(declaration, DeclarationType.Member)
52+
.OfType<ModuleBodyElementDeclaration>();
5353

54-
return implementedAndOrAnnotatedInterfaceModules
55-
.SelectMany(interfaceModule => interfaceModule.Members
56-
.Where(member => ((ModuleBodyElementDeclaration)member).Block.ContainsExecutableStatements(true)))
57-
.Select(result => new DeclarationInspectionResult(this,
58-
string.Format(InspectionResults.ImplementedInterfaceMemberInspection,
59-
result.QualifiedModuleName.ToString(),
60-
Resources.RubberduckUI.ResourceManager
61-
.GetString("DeclarationType_" + result.DeclarationType)
62-
.Capitalize(),
63-
result.IdentifierName),
64-
result));
54+
return moduleBodyElements
55+
.Any(member => member.Block.ContainsExecutableStatements(true));
56+
}
57+
58+
private static bool IsInterfaceDeclaration(Declaration declaration)
59+
{
60+
if (!(declaration is ClassModuleDeclaration classModule))
61+
{
62+
return false;
63+
}
64+
return classModule.IsInterface
65+
|| declaration.Annotations.Any(an => an.Annotation is InterfaceAnnotation);
66+
}
67+
68+
protected override string ResultDescription(Declaration declaration)
69+
{
70+
var qualifiedName = declaration.QualifiedModuleName.ToString();
71+
var declarationType = Resources.RubberduckUI.ResourceManager
72+
.GetString("DeclarationType_" + declaration.DeclarationType)
73+
.Capitalize();
74+
var identifierName = declaration.IdentifierName;
75+
76+
return string.Format(
77+
InspectionResults.ImplementedInterfaceMemberInspection,
78+
qualifiedName,
79+
declarationType,
80+
identifierName);
6581
}
6682
}
6783
}

0 commit comments

Comments
 (0)