Skip to content

Commit 205e3dd

Browse files
committed
Fix KeywordUsedAsMemberInspection
The problem was that the inspection normalized the names too much. The identifier name is already the name without the outermost brackets and spacesaround bracketed identifiers do matter. Also makes several inspections use the declaration inspection base class.
1 parent cc1327e commit 205e3dd

18 files changed

+232
-193
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/DeclarationInspectionBase.cs

Lines changed: 32 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,20 @@ namespace Rubberduck.Inspections.Abstract
1212
public abstract class DeclarationInspectionBase : InspectionBase
1313
{
1414
protected readonly DeclarationType[] RelevantDeclarationTypes;
15+
protected readonly DeclarationType[] ExcludeDeclarationTypes;
1516

1617
protected DeclarationInspectionBase(RubberduckParserState state, params DeclarationType[] relevantDeclarationTypes)
1718
: base(state)
1819
{
1920
RelevantDeclarationTypes = relevantDeclarationTypes;
21+
ExcludeDeclarationTypes = new DeclarationType[0];
22+
}
23+
24+
protected DeclarationInspectionBase(RubberduckParserState state, DeclarationType[] relevantDeclarationTypes, DeclarationType[] excludeDeclarationTypes)
25+
: base(state)
26+
{
27+
RelevantDeclarationTypes = relevantDeclarationTypes;
28+
ExcludeDeclarationTypes = excludeDeclarationTypes;
2029
}
2130

2231
protected abstract bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder);
@@ -59,9 +68,13 @@ private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleNam
5968

6069
protected virtual IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
6170
{
62-
return RelevantDeclarationTypes
63-
.SelectMany(declarationType => DeclarationFinderProvider.DeclarationFinder.Members(module, declarationType))
64-
.Distinct();
71+
var potentiallyRelevantDeclarations = RelevantDeclarationTypes.Length == 0
72+
? finder.AllUserDeclarations
73+
: RelevantDeclarationTypes
74+
.SelectMany(declarationType => finder.Members(module, declarationType))
75+
.Distinct();
76+
return potentiallyRelevantDeclarations
77+
.Where(declaration => !ExcludeDeclarationTypes.Contains(declaration.DeclarationType));
6578
}
6679

6780
protected virtual IInspectionResult InspectionResult(Declaration declaration)
@@ -76,11 +89,20 @@ protected virtual IInspectionResult InspectionResult(Declaration declaration)
7689
public abstract class DeclarationInspectionBase<T> : InspectionBase
7790
{
7891
protected readonly DeclarationType[] RelevantDeclarationTypes;
92+
protected readonly DeclarationType[] ExcludeDeclarationTypes;
7993

8094
protected DeclarationInspectionBase(RubberduckParserState state, params DeclarationType[] relevantDeclarationTypes)
8195
: base(state)
8296
{
8397
RelevantDeclarationTypes = relevantDeclarationTypes;
98+
ExcludeDeclarationTypes = new DeclarationType[0];
99+
}
100+
101+
protected DeclarationInspectionBase(RubberduckParserState state, DeclarationType[] relevantDeclarationTypes, DeclarationType[] excludeDeclarationTypes)
102+
: base(state)
103+
{
104+
RelevantDeclarationTypes = relevantDeclarationTypes;
105+
ExcludeDeclarationTypes = excludeDeclarationTypes;
84106
}
85107

86108
protected abstract (bool isResult, T properties) IsResultDeclarationWithAdditionalProperties(Declaration declaration, DeclarationFinder finder);
@@ -125,9 +147,13 @@ private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleNam
125147

126148
protected virtual IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
127149
{
128-
return RelevantDeclarationTypes
129-
.SelectMany(declarationType => DeclarationFinderProvider.DeclarationFinder.Members(module, declarationType))
130-
.Distinct();
150+
var potentiallyRelevantDeclarations = RelevantDeclarationTypes.Length == 0
151+
? finder.AllUserDeclarations
152+
: RelevantDeclarationTypes
153+
.SelectMany(declarationType => finder.Members(module, declarationType))
154+
.Distinct();
155+
return potentiallyRelevantDeclarations
156+
.Where(declaration => ! ExcludeDeclarationTypes.Contains(declaration.DeclarationType));
131157
}
132158

133159
protected virtual IInspectionResult InspectionResult(Declaration declaration, T properties)
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
using Rubberduck.Parsing.Symbols;
2+
using Rubberduck.Parsing.VBA;
3+
using Rubberduck.Parsing.VBA.DeclarationCaching;
4+
5+
namespace Rubberduck.Inspections.Abstract
6+
{
7+
public abstract class ImplicitTypeInspectionBase : DeclarationInspectionBase
8+
{
9+
protected ImplicitTypeInspectionBase(RubberduckParserState state, params DeclarationType[] relevantDeclarationTypes)
10+
:base(state, relevantDeclarationTypes)
11+
{ }
12+
13+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
14+
{
15+
return !declaration.IsTypeSpecified;
16+
}
17+
}
18+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 15 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,10 @@
1-
using System.Collections.Generic;
21
using System.Linq;
3-
using Antlr4.Runtime;
4-
using Rubberduck.Common;
52
using Rubberduck.Inspections.Abstract;
6-
using Rubberduck.Inspections.Results;
7-
using Rubberduck.Parsing;
8-
using Rubberduck.Parsing.Inspections.Abstract;
93
using Rubberduck.Resources.Inspections;
104
using Rubberduck.Parsing.Symbols;
115
using Rubberduck.Parsing.VBA;
126
using Rubberduck.Inspections.Inspections.Extensions;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
138

149
namespace Rubberduck.Inspections.Concrete
1510
{
@@ -37,23 +32,25 @@ namespace Rubberduck.Inspections.Concrete
3732
/// End Sub
3833
/// ]]>
3934
/// </example>
40-
public sealed class ConstantNotUsedInspection : InspectionBase
35+
public sealed class ConstantNotUsedInspection : DeclarationInspectionBase
4136
{
4237
public ConstantNotUsedInspection(RubberduckParserState state)
43-
: base(state) { }
38+
: base(state, DeclarationType.Constant) { }
4439

45-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
40+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4641
{
47-
var results = State.DeclarationFinder.UserDeclarations(DeclarationType.Constant)
48-
.Where(declaration => declaration.Context != null
49-
&& !declaration.References.Any())
50-
.ToList();
42+
return declaration?.Context != null
43+
&& !declaration.References.Any();
44+
}
5145

52-
return results.Select(issue =>
53-
new DeclarationInspectionResult(this,
54-
string.Format(InspectionResults.IdentifierNotUsedInspection, issue.DeclarationType.ToLocalizedString(), issue.IdentifierName),
55-
issue,
56-
new QualifiedContext<ParserRuleContext>(issue.QualifiedName.QualifiedModuleName, ((dynamic)issue.Context).identifier())));
46+
protected override string ResultDescription(Declaration declaration)
47+
{
48+
var declarationType = declaration.DeclarationType.ToLocalizedString();
49+
var declarationName = declaration.IdentifierName;
50+
return string.Format(
51+
InspectionResults.IdentifierNotUsedInspection,
52+
declarationType,
53+
declarationName);
5754
}
5855
}
5956
}

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@
1010
using Rubberduck.Inspections.Inspections.Extensions;
1111
using Rubberduck.JunkDrawer.Extensions;
1212
using Rubberduck.Parsing.VBA.DeclarationCaching;
13-
using Rubberduck.Parsing.VBA.Extensions;
1413
using Rubberduck.VBEditor;
1514

1615
namespace Rubberduck.Inspections.Concrete

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs

Lines changed: 15 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,11 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
1+
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
53
using Rubberduck.Parsing.Grammar;
6-
using Rubberduck.Parsing.Inspections.Abstract;
74
using Rubberduck.Resources.Inspections;
85
using Rubberduck.Parsing.Symbols;
96
using Rubberduck.Parsing.VBA;
10-
using Rubberduck.Parsing.VBA.Extensions;
11-
using Rubberduck.VBEditor.SafeComWrappers;
12-
using Rubberduck.Inspections.Inspections.Extensions;
13-
using Rubberduck.JunkDrawer.Extensions;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
8+
using Rubberduck.Parsing.VBA.Parsing;
149

1510
namespace Rubberduck.Inspections.Concrete
1611
{
@@ -20,34 +15,29 @@ namespace Rubberduck.Inspections.Concrete
2015
/// <why>
2116
/// An empty module does not need to exist and can be safely removed.
2217
/// </why>
23-
public sealed class EmptyModuleInspection : InspectionBase
18+
public sealed class EmptyModuleInspection : DeclarationInspectionBase
2419
{
2520
private readonly EmptyModuleVisitor _emptyModuleVisitor;
21+
private readonly IParseTreeProvider _parseTreeProvider;
2622

2723
public EmptyModuleInspection(RubberduckParserState state)
28-
: base(state)
24+
: base(state, new []{DeclarationType.Module}, new []{DeclarationType.Document})
2925
{
3026
_emptyModuleVisitor = new EmptyModuleVisitor();
27+
_parseTreeProvider = state;
3128
}
3229

33-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
30+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
3431
{
35-
var modulesToInspect = State.DeclarationFinder.AllModules
36-
.Where(qmn => qmn.ComponentType == ComponentType.ClassModule
37-
|| qmn.ComponentType == ComponentType.StandardModule).ToHashSet();
32+
var module = declaration.QualifiedModuleName;
33+
var tree = _parseTreeProvider.GetParseTree(module, CodeKind.CodePaneCode);
3834

39-
var treesToInspect = State.ParseTrees.Where(kvp => modulesToInspect.Contains(kvp.Key));
40-
41-
var emptyModules = treesToInspect
42-
.Where(kvp => _emptyModuleVisitor.Visit(kvp.Value))
43-
.Select(kvp => kvp.Key)
44-
.ToHashSet();
45-
46-
var emptyModuleDeclarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Module)
47-
.Where(declaration => emptyModules.Contains(declaration.QualifiedName.QualifiedModuleName));
35+
return _emptyModuleVisitor.Visit(tree);
36+
}
4837

49-
return emptyModuleDeclarations.Select(declaration =>
50-
new DeclarationInspectionResult(this, string.Format(InspectionResults.EmptyModuleInspection, declaration.IdentifierName), declaration));
38+
protected override string ResultDescription(Declaration declaration)
39+
{
40+
return string.Format(InspectionResults.EmptyModuleInspection, declaration.IdentifierName);
5141
}
5242
}
5343

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs

Lines changed: 10 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,8 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
31
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
5-
using Rubberduck.Parsing.Inspections.Abstract;
62
using Rubberduck.Resources.Inspections;
73
using Rubberduck.Parsing.Symbols;
84
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
96

107
namespace Rubberduck.Inspections.Concrete
118
{
@@ -30,10 +27,10 @@ namespace Rubberduck.Inspections.Concrete
3027
/// End Sub
3128
/// ]]>
3229
/// </example>
33-
public sealed class ImplicitPublicMemberInspection : InspectionBase
30+
public sealed class ImplicitPublicMemberInspection : DeclarationInspectionBase
3431
{
3532
public ImplicitPublicMemberInspection(RubberduckParserState state)
36-
: base(state) { }
33+
: base(state, ProcedureTypes) { }
3734

3835
private static readonly DeclarationType[] ProcedureTypes =
3936
{
@@ -44,15 +41,14 @@ public ImplicitPublicMemberInspection(RubberduckParserState state)
4441
DeclarationType.PropertySet
4542
};
4643

47-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
44+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4845
{
49-
var issues = from item in UserDeclarations
50-
where ProcedureTypes.Contains(item.DeclarationType)
51-
&& item.Accessibility == Accessibility.Implicit
52-
select new DeclarationInspectionResult(this,
53-
string.Format(InspectionResults.ImplicitPublicMemberInspection, item.IdentifierName),
54-
item);
55-
return issues;
46+
return declaration.Accessibility == Accessibility.Implicit;
47+
}
48+
49+
protected override string ResultDescription(Declaration declaration)
50+
{
51+
return string.Format(InspectionResults.ImplicitPublicMemberInspection, declaration.IdentifierName);
5652
}
5753
}
5854
}
Lines changed: 5 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,7 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
3-
using Antlr4.Runtime;
41
using Rubberduck.Inspections.Abstract;
5-
using Rubberduck.Inspections.Results;
6-
using Rubberduck.Parsing;
7-
using Rubberduck.Parsing.Inspections.Abstract;
82
using Rubberduck.Resources.Inspections;
93
using Rubberduck.Parsing.Symbols;
104
using Rubberduck.Parsing.VBA;
11-
using Rubberduck.Inspections.Inspections.Extensions;
125

136
namespace Rubberduck.Inspections.Concrete
147
{
@@ -32,20 +25,15 @@ namespace Rubberduck.Inspections.Concrete
3225
/// End Function
3326
/// ]]>
3427
/// </example>
35-
public sealed class ImplicitVariantReturnTypeInspection : InspectionBase
28+
public sealed class ImplicitVariantReturnTypeInspection : ImplicitTypeInspectionBase
3629
{
3730
public ImplicitVariantReturnTypeInspection(RubberduckParserState state)
38-
: base(state) { }
31+
: base(state, DeclarationType.Function)
32+
{}
3933

40-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
34+
protected override string ResultDescription(Declaration declaration)
4135
{
42-
var issues = from item in State.DeclarationFinder.UserDeclarations(DeclarationType.Function)
43-
where !item.IsTypeSpecified
44-
let issue = new {Declaration = item, QualifiedContext = new QualifiedContext<ParserRuleContext>(item.QualifiedName, item.Context)}
45-
select new DeclarationInspectionResult(this,
46-
string.Format(InspectionResults.ImplicitVariantReturnTypeInspection, item.IdentifierName),
47-
item);
48-
return issues;
36+
return string.Format(InspectionResults.ImplicitVariantReturnTypeInspection, declaration.IdentifierName);
4937
}
5038
}
5139
}
Lines changed: 28 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,37 +1,40 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
3-
using Rubberduck.Inspections.Abstract;
1+
using Rubberduck.Inspections.Abstract;
42
using Rubberduck.Parsing.VBA;
5-
using Rubberduck.Parsing.Inspections.Abstract;
6-
using Rubberduck.Inspections.Results;
73
using Rubberduck.Parsing.Symbols;
84
using Rubberduck.Resources.Inspections;
95

10-
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
6+
namespace Rubberduck.Inspections.Concrete
117
{
12-
public sealed class ImplicitlyTypedConstInspection : InspectionBase
8+
/// <summary>
9+
/// Warns about constants that don't have an explicitly defined type.
10+
/// </summary>
11+
/// <why>
12+
/// All constants have a declared type, whether a type is specified or not. The implicit type is determined by the compiler based on the value, which is not always the expected type.
13+
/// </why>
14+
/// <example hasResults="true">
15+
/// <![CDATA[
16+
/// Const myInteger = 12345
17+
/// ]]>
18+
/// </example>
19+
/// <example hasResults="false">
20+
/// <![CDATA[
21+
/// Const myInteger As Integer = 12345
22+
/// ]]>
23+
/// </example>
24+
/// <example hasResults="false">
25+
/// <![CDATA[
26+
/// Const myInteger% = 12345
27+
/// ]]>
28+
/// </example>
29+
public sealed class ImplicitlyTypedConstInspection : ImplicitTypeInspectionBase
1330
{
1431
public ImplicitlyTypedConstInspection(RubberduckParserState state)
15-
: base(state) { }
32+
: base(state, DeclarationType.Constant)
33+
{}
1634

17-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
35+
protected override string ResultDescription(Declaration declaration)
1836
{
19-
var declarationFinder = DeclarationFinderProvider.DeclarationFinder;
20-
21-
var implicitlyTypedConsts = declarationFinder.UserDeclarations(DeclarationType.Constant)
22-
.Where(declaration => !declaration.IsTypeSpecified);
23-
24-
return implicitlyTypedConsts.Select(Result);
25-
}
26-
27-
private IInspectionResult Result(Declaration declaration)
28-
{
29-
var description = string.Format(InspectionResults.ImplicitlyTypedConstInspection, declaration.IdentifierName);
30-
31-
return new DeclarationInspectionResult(
32-
this,
33-
description,
34-
declaration);
37+
return string.Format(InspectionResults.ImplicitlyTypedConstInspection, declaration.IdentifierName);
3538
}
3639
}
3740
}

Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@
88
using Rubberduck.Parsing.Inspections.Abstract;
99
using Rubberduck.Parsing.Symbols;
1010
using Rubberduck.Parsing.VBA;
11-
using Rubberduck.Parsing.VBA.Extensions;
1211
using Rubberduck.Resources;
1312

1413
namespace Rubberduck.Inspections.Concrete

0 commit comments

Comments
 (0)