Skip to content

Commit e096043

Browse files
committed
Redesign MemberNotOnInterfaceInspection and IntegerDataTypeInspection
1 parent 21bbebd commit e096043

File tree

3 files changed

+99
-59
lines changed

3 files changed

+99
-59
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/DeclarationInspectionBaseBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ protected virtual IEnumerable<IInspectionResult> DoGetInspectionResults(Qualifie
5454
return DoGetInspectionResults(module, finder);
5555
}
5656

57-
protected IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
57+
protected virtual IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
5858
{
5959
var potentiallyRelevantDeclarations = RelevantDeclarationTypes.Length == 0
6060
? finder.Members(module)
Lines changed: 44 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,9 @@
1-
using System.Collections.Generic;
2-
using System.Globalization;
3-
using System.Linq;
4-
using Rubberduck.Inspections.Abstract;
5-
using Rubberduck.Inspections.Results;
6-
using Rubberduck.JunkDrawer.Extensions;
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Inspections.Extensions;
73
using Rubberduck.Parsing.Grammar;
8-
using Rubberduck.Parsing.Inspections.Abstract;
94
using Rubberduck.Parsing.Symbols;
105
using Rubberduck.Parsing.VBA;
11-
using Rubberduck.Resources;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
127

138
namespace Rubberduck.Inspections.Concrete
149
{
@@ -35,41 +30,57 @@ namespace Rubberduck.Inspections.Concrete
3530
/// End Sub
3631
/// ]]>
3732
/// </example>
38-
public sealed class IntegerDataTypeInspection : InspectionBase
33+
public sealed class IntegerDataTypeInspection : DeclarationInspectionBase
3934
{
40-
public IntegerDataTypeInspection(RubberduckParserState state) : base(state)
41-
{
42-
}
35+
public IntegerDataTypeInspection(RubberduckParserState state)
36+
: base(state)
37+
{ }
4338

44-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
39+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4540
{
46-
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToHashSet();
41+
if (declaration.AsTypeName != Tokens.Integer)
42+
{
43+
return false;
44+
}
4745

48-
var excludeParameterMembers = State.DeclarationFinder.FindEventHandlers().ToHashSet();
49-
excludeParameterMembers.UnionWith(interfaceImplementationMembers);
46+
switch (declaration)
47+
{
48+
case ParameterDeclaration parameter:
49+
return ParameterIsResult(parameter, finder);
50+
case ModuleBodyElementDeclaration member:
51+
return MethodIsResult(member);
52+
default:
53+
return declaration.DeclarationType != DeclarationType.LibraryFunction;
54+
}
55+
}
5056

51-
var result = UserDeclarations
52-
.Where(declaration =>
53-
declaration.AsTypeName == Tokens.Integer &&
54-
!interfaceImplementationMembers.Contains(declaration) &&
55-
declaration.DeclarationType != DeclarationType.LibraryFunction &&
56-
(declaration.DeclarationType != DeclarationType.Parameter || IncludeParameterDeclaration(declaration, excludeParameterMembers)))
57-
.Select(issue =>
58-
new DeclarationInspectionResult(this,
59-
string.Format(Resources.Inspections.InspectionResults.IntegerDataTypeInspection,
60-
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture), issue.IdentifierName),
61-
issue));
57+
private static bool ParameterIsResult(ParameterDeclaration parameter, DeclarationFinder finder)
58+
{
59+
var enclosingMember = parameter.ParentDeclaration;
60+
if (!(enclosingMember is ModuleBodyElementDeclaration member))
61+
{
62+
return false;
63+
}
6264

63-
return result;
65+
return !member.IsInterfaceImplementation
66+
&& member.DeclarationType != DeclarationType.LibraryFunction
67+
&& member.DeclarationType != DeclarationType.LibraryProcedure
68+
&& !finder.FindEventHandlers().Contains(member);
6469
}
6570

66-
private static bool IncludeParameterDeclaration(Declaration parameterDeclaration, ICollection<Declaration> parentDeclarationsToExclude)
71+
private static bool MethodIsResult(ModuleBodyElementDeclaration member)
6772
{
68-
var parentDeclaration = parameterDeclaration.ParentDeclaration;
73+
return !member.IsInterfaceImplementation;
74+
}
6975

70-
return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction &&
71-
parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure &&
72-
!parentDeclarationsToExclude.Contains(parentDeclaration);
76+
protected override string ResultDescription(Declaration declaration)
77+
{
78+
var declarationType = declaration.DeclarationType.ToLocalizedString();
79+
var declarationName = declaration.IdentifierName;
80+
return string.Format(
81+
Resources.Inspections.InspectionResults.IntegerDataTypeInspection,
82+
declarationType,
83+
declarationName);
7384
}
7485
}
7586
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs

Lines changed: 54 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,9 @@
88
using Rubberduck.Parsing.Symbols;
99
using Rubberduck.Parsing.VBA;
1010
using Rubberduck.Inspections.Inspections.Extensions;
11+
using Rubberduck.Parsing;
12+
using Rubberduck.Parsing.VBA.DeclarationCaching;
13+
using Rubberduck.VBEditor;
1114

1215
namespace Rubberduck.Inspections.Concrete
1316
{
@@ -37,36 +40,62 @@ namespace Rubberduck.Inspections.Concrete
3740
/// End Sub
3841
/// ]]>
3942
/// </example>
40-
public sealed class MemberNotOnInterfaceInspection : InspectionBase
43+
public sealed class MemberNotOnInterfaceInspection : DeclarationInspectionBase<Declaration>
4144
{
4245
public MemberNotOnInterfaceInspection(RubberduckParserState state)
43-
: base(state) { }
46+
: base(state)
47+
{ }
4448

45-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
49+
protected override IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
4650
{
47-
// prefilter to reduce searchspace
48-
var unresolved = State.DeclarationFinder.UnresolvedMemberDeclarations()
49-
.Where(decl => !decl.IsIgnoringInspectionResultFor(AnnotationName)).ToList();
51+
return finder.UnresolvedMemberDeclarations(module);
52+
}
53+
54+
protected override (bool isResult, Declaration properties) IsResultDeclarationWithAdditionalProperties(Declaration declaration, DeclarationFinder finder)
55+
{
56+
if (!(declaration is UnboundMemberDeclaration member))
57+
{
58+
return (false, null);
59+
}
60+
61+
var callingContext = member.CallingContext is VBAParser.NewExprContext newExprContext
62+
? (newExprContext.expression() as VBAParser.LExprContext)?.lExpression()
63+
: member.CallingContext;
64+
65+
if (callingContext == null)
66+
{
67+
return (false, null);
68+
}
69+
70+
var callingContextSelection = new QualifiedSelection(declaration.QualifiedModuleName, callingContext.GetSelection());
71+
var usageReferences = finder.IdentifierReferences(callingContextSelection);
72+
var calledDeclaration = usageReferences
73+
.Select(reference => reference.Declaration)
74+
.FirstOrDefault(usageDeclaration => usageDeclaration != null
75+
&& HasResultType(usageDeclaration));
76+
var isResult = calledDeclaration != null
77+
&& calledDeclaration.DeclarationType != DeclarationType.Control; //TODO - remove this exception after resolving #2592. Also simplify to inspect the type directly.
5078

51-
var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
52-
!decl.AsTypeDeclaration.IsUserDefined &&
53-
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
54-
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
55-
.SelectMany(decl => decl.References).ToList();
56-
return unresolved
57-
.Select(access => new
58-
{
59-
access,
60-
callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext)
61-
|| (access.CallingContext is VBAParser.NewExprContext &&
62-
usage.Context.Parent.Parent.Equals(access.CallingContext))
63-
)
64-
})
65-
.Where(memberAccess => memberAccess.callingContext != null &&
66-
memberAccess.callingContext.Declaration.DeclarationType != DeclarationType.Control) //TODO - remove this exception after resolving #2592)
67-
.Select(memberAccess => new DeclarationInspectionResult(this,
68-
string.Format(InspectionResults.MemberNotOnInterfaceInspection, memberAccess.access.IdentifierName,
69-
memberAccess.callingContext.Declaration.AsTypeDeclaration.IdentifierName), memberAccess.access));
79+
return (isResult, calledDeclaration?.AsTypeDeclaration);
80+
}
81+
82+
private static bool HasResultType(Declaration declaration)
83+
{
84+
var typeDeclaration = declaration.AsTypeDeclaration;
85+
return typeDeclaration != null
86+
&& !typeDeclaration.IsUserDefined
87+
&& typeDeclaration is ClassModuleDeclaration classTypeDeclaration
88+
&& classTypeDeclaration.IsExtensible;
89+
}
90+
91+
protected override string ResultDescription(Declaration declaration, Declaration typeDeclaration)
92+
{
93+
var memberName = declaration.IdentifierName;
94+
var typeName = typeDeclaration?.IdentifierName ?? string.Empty;
95+
return string.Format(
96+
InspectionResults.MemberNotOnInterfaceInspection,
97+
memberName,
98+
typeName);
7099
}
71100
}
72101
}

0 commit comments

Comments
 (0)