Skip to content

Commit 6386d27

Browse files
committed
Split identifier reference inspection bases into generic and non-generic versions
The generic ones take additional properties forwarded to the results as their properties and potentially used in the result description. The non-generic ones do not have soch properties.
1 parent 5c12591 commit 6386d27

32 files changed

+244
-74
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/ArgumentReferenceInspectionFromDeclarationsBase.cs

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,30 @@ protected ArgumentReferenceInspectionFromDeclarationsBase(RubberduckParserState
1414

1515
protected abstract bool IsUnsuitableArgument(ArgumentReference reference, DeclarationFinder finder);
1616

17-
protected virtual (bool isResult, object properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
17+
protected override IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
18+
{
19+
return ObjectionableDeclarations(finder)
20+
.OfType<ParameterDeclaration>()
21+
.SelectMany(parameter => parameter.ArgumentReferences);
22+
}
23+
24+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
1825
{
19-
return (IsUnsuitableArgument(reference, finder), null);
26+
if (!(reference is ArgumentReference argumentReference))
27+
{
28+
return false;
29+
}
30+
31+
return IsUnsuitableArgument(argumentReference, finder);
2032
}
33+
}
34+
35+
public abstract class ArgumentReferenceInspectionFromDeclarationsBase<T> : IdentifierReferenceInspectionFromDeclarationsBase<T>
36+
{
37+
protected ArgumentReferenceInspectionFromDeclarationsBase(RubberduckParserState state)
38+
: base(state) { }
39+
40+
protected abstract (bool isResult, T properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder);
2141

2242
protected override IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
2343
{
@@ -26,11 +46,11 @@ protected override IEnumerable<IdentifierReference> ObjectionableReferences(Decl
2646
.SelectMany(parameter => parameter.ArgumentReferences);
2747
}
2848

29-
protected override (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
49+
protected override (bool isResult, T properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
3050
{
3151
if (!(reference is ArgumentReference argumentReference))
3252
{
33-
return (false, null);
53+
return (false, default);
3454
}
3555

3656
return IsUnsuitableArgumentWithAdditionalProperties(argumentReference, finder);

Rubberduck.CodeAnalysis/Inspections/Abstract/DeclarationInspectionBase.cs

Lines changed: 67 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,4 +72,71 @@ protected virtual IInspectionResult InspectionResult(Declaration declaration)
7272
declaration);
7373
}
7474
}
75+
76+
public abstract class DeclarationInspectionBase<T> : InspectionBase
77+
{
78+
protected readonly DeclarationType[] RelevantDeclarationTypes;
79+
80+
protected DeclarationInspectionBase(RubberduckParserState state, params DeclarationType[] relevantDeclarationTypes)
81+
: base(state)
82+
{
83+
RelevantDeclarationTypes = relevantDeclarationTypes;
84+
}
85+
86+
protected abstract (bool isResult, T properties) IsResultDeclarationWithAdditionalProperties(Declaration declaration, DeclarationFinder finder);
87+
protected abstract string ResultDescription(Declaration declaration, T properties);
88+
89+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
90+
{
91+
var finder = DeclarationFinderProvider.DeclarationFinder;
92+
93+
var results = new List<IInspectionResult>();
94+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
95+
{
96+
if (moduleDeclaration == null)
97+
{
98+
continue;
99+
}
100+
101+
var module = moduleDeclaration.QualifiedModuleName;
102+
results.AddRange(DoGetInspectionResults(module, finder));
103+
}
104+
105+
return results;
106+
}
107+
108+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
109+
{
110+
var finder = DeclarationFinderProvider.DeclarationFinder;
111+
return DoGetInspectionResults(module, finder);
112+
}
113+
114+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
115+
{
116+
var objectionableDeclarationsWithAdditionalProperties = RelevantDeclarationsInModule(module, finder)
117+
.Select(declaration => (declaration, IsResultDeclarationWithAdditionalProperties(declaration, finder)))
118+
.Where(tpl => tpl.Item2.isResult)
119+
.Select(tpl => (tpl.declaration, tpl.Item2.properties));
120+
121+
return objectionableDeclarationsWithAdditionalProperties
122+
.Select(tpl => InspectionResult(tpl.declaration, tpl.properties))
123+
.ToList();
124+
}
125+
126+
protected virtual IEnumerable<Declaration> RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
127+
{
128+
return RelevantDeclarationTypes
129+
.SelectMany(declarationType => DeclarationFinderProvider.DeclarationFinder.Members(module, declarationType))
130+
.Distinct();
131+
}
132+
133+
protected virtual IInspectionResult InspectionResult(Declaration declaration, T properties)
134+
{
135+
return new DeclarationInspectionResult(
136+
this,
137+
ResultDescription(declaration, properties),
138+
declaration,
139+
properties: properties);
140+
}
141+
}
75142
}

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 58 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,13 +16,67 @@ protected IdentifierReferenceInspectionBase(RubberduckParserState state)
1616
{}
1717

1818
protected abstract bool IsResultReference(IdentifierReference reference, DeclarationFinder finder);
19-
protected abstract string ResultDescription(IdentifierReference reference, dynamic properties = null);
19+
protected abstract string ResultDescription(IdentifierReference reference);
2020

21-
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
21+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
{
23-
return (IsResultReference(reference, finder), null);
23+
var finder = DeclarationFinderProvider.DeclarationFinder;
24+
25+
var results = new List<IInspectionResult>();
26+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
27+
{
28+
if (moduleDeclaration == null)
29+
{
30+
continue;
31+
}
32+
33+
var module = moduleDeclaration.QualifiedModuleName;
34+
results.AddRange(DoGetInspectionResults(module, finder));
35+
}
36+
37+
return results;
2438
}
2539

40+
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
41+
{
42+
var objectionableReferences = ReferencesInModule(module, finder)
43+
.Where(reference => IsResultReference(reference, finder));
44+
45+
return objectionableReferences
46+
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
47+
.ToList();
48+
}
49+
50+
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
51+
{
52+
var finder = DeclarationFinderProvider.DeclarationFinder;
53+
return DoGetInspectionResults(module, finder);
54+
}
55+
56+
protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module, DeclarationFinder finder)
57+
{
58+
return finder.IdentifierReferences(module);
59+
}
60+
61+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
62+
{
63+
return new IdentifierReferenceInspectionResult(
64+
this,
65+
ResultDescription(reference),
66+
declarationFinderProvider,
67+
reference);
68+
}
69+
}
70+
71+
public abstract class IdentifierReferenceInspectionBase<T> : InspectionBase
72+
{
73+
protected IdentifierReferenceInspectionBase(RubberduckParserState state)
74+
: base(state)
75+
{ }
76+
77+
protected abstract (bool isResult, T properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder);
78+
protected abstract string ResultDescription(IdentifierReference reference, T properties);
79+
2680
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2781
{
2882
var finder = DeclarationFinderProvider.DeclarationFinder;
@@ -65,7 +119,7 @@ protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedM
65119
return finder.IdentifierReferences(module);
66120
}
67121

68-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, dynamic properties = null)
122+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, T properties)
69123
{
70124
return new IdentifierReferenceInspectionResult(
71125
this,

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionFromDeclarationsBase.cs

Lines changed: 58 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -16,24 +16,22 @@ protected IdentifierReferenceInspectionFromDeclarationsBase(RubberduckParserStat
1616
{}
1717

1818
protected abstract IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder);
19-
protected abstract string ResultDescription(IdentifierReference reference, dynamic properties = null);
19+
protected abstract string ResultDescription(IdentifierReference reference);
2020

2121
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
{
2323
var finder = DeclarationFinderProvider.DeclarationFinder;
2424
var objectionableReferences = ObjectionableReferences(finder);
2525
var resultReferences = ResultReferences(objectionableReferences, finder);
2626
return resultReferences
27-
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
27+
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
2828
.ToList();
2929
}
3030

31-
private IEnumerable<(IdentifierReference reference, object properties)> ResultReferences(IEnumerable<IdentifierReference> potentialResultReferences, DeclarationFinder finder)
31+
private IEnumerable<IdentifierReference> ResultReferences(IEnumerable<IdentifierReference> potentialResultReferences, DeclarationFinder finder)
3232
{
3333
return potentialResultReferences
34-
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
35-
.Where(tpl => tpl.Item2.isResult)
36-
.Select(tpl => (tpl.reference, tpl.Item2.properties));
34+
.Where(reference => IsResultReference(reference, finder));
3735
}
3836

3937
protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
@@ -45,9 +43,60 @@ protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(Decla
4543

4644
protected virtual bool IsResultReference(IdentifierReference reference, DeclarationFinder finder) => true;
4745

48-
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
46+
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
47+
{
48+
var finder = DeclarationFinderProvider.DeclarationFinder;
49+
var objectionableReferences = ObjectionableReferences(finder)
50+
.Where(reference => reference.QualifiedModuleName.Equals(module));
51+
var resultReferences = ResultReferences(objectionableReferences, finder);
52+
return resultReferences
53+
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
54+
.ToList();
55+
}
56+
57+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
58+
{
59+
return new IdentifierReferenceInspectionResult(
60+
this,
61+
ResultDescription(reference),
62+
declarationFinderProvider,
63+
reference);
64+
}
65+
}
66+
67+
public abstract class IdentifierReferenceInspectionFromDeclarationsBase<T> : InspectionBase
68+
{
69+
protected IdentifierReferenceInspectionFromDeclarationsBase(RubberduckParserState state)
70+
: base(state)
71+
{ }
72+
73+
protected abstract IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder);
74+
protected abstract (bool isResult, T properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder);
75+
protected abstract string ResultDescription(IdentifierReference reference, T properties);
76+
77+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
78+
{
79+
var finder = DeclarationFinderProvider.DeclarationFinder;
80+
var objectionableReferences = ObjectionableReferences(finder);
81+
var resultReferences = ResultReferences(objectionableReferences, finder);
82+
return resultReferences
83+
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
84+
.ToList();
85+
}
86+
87+
private IEnumerable<(IdentifierReference reference, T properties)> ResultReferences(IEnumerable<IdentifierReference> potentialResultReferences, DeclarationFinder finder)
88+
{
89+
return potentialResultReferences
90+
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
91+
.Where(tpl => tpl.Item2.isResult)
92+
.Select(tpl => (tpl.reference, tpl.Item2.properties));
93+
}
94+
95+
protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
4996
{
50-
return (IsResultReference(reference, finder), null);
97+
var objectionableDeclarations = ObjectionableDeclarations(finder);
98+
return objectionableDeclarations
99+
.SelectMany(declaration => declaration.References);
51100
}
52101

53102
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
@@ -61,7 +110,7 @@ protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleN
61110
.ToList();
62111
}
63112

64-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, dynamic properties = null)
113+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, T properties)
65114
{
66115
return new IdentifierReferenceInspectionResult(
67116
this,

Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88

99
namespace Rubberduck.Inspections.Inspections.Abstract
1010
{
11-
public abstract class IsMissingInspectionBase : ArgumentReferenceInspectionFromDeclarationsBase
11+
public abstract class IsMissingInspectionBase : ArgumentReferenceInspectionFromDeclarationsBase<ParameterDeclaration>
1212
{
1313
protected IsMissingInspectionBase(RubberduckParserState state)
1414
: base(state) { }

Rubberduck.CodeAnalysis/Inspections/Abstract/MemberAccessMayReturnNothingInspectionBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ private static IEnumerable<INode> GetReferenceNodes(INode node)
100100
}
101101
}
102102

103-
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
103+
protected override string ResultDescription(IdentifierReference reference)
104104
{
105105
var semiQualifiedName = $"{reference.Declaration.ParentDeclaration.IdentifierName}.{reference.IdentifierName}";
106106
return string.Format(ResultTemplate, semiQualifiedName);

Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs

Lines changed: 3 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
7878
/// End Sub
7979
/// ]]>
8080
/// </example>
81-
public class ArgumentWithIncompatibleObjectTypeInspection : ArgumentReferenceInspectionFromDeclarationsBase
81+
public class ArgumentWithIncompatibleObjectTypeInspection : ArgumentReferenceInspectionFromDeclarationsBase<string>
8282
{
8383
private readonly ISetTypeResolver _setTypeResolver;
8484

@@ -103,7 +103,7 @@ private static bool ToBeConsidered(Declaration declaration)
103103
&& declaration.IsObject;
104104
}
105105

106-
protected override (bool isResult, object properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
106+
protected override (bool isResult, string properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
107107
{
108108
var argumentSetTypeName = ArgumentSetTypeName(reference, finder);
109109

@@ -115,12 +115,6 @@ protected override (bool isResult, object properties) IsUnsuitableArgumentWithAd
115115
return (true, argumentSetTypeName);
116116
}
117117

118-
protected override bool IsUnsuitableArgument(ArgumentReference reference, DeclarationFinder finder)
119-
{
120-
//No need to implement this since we overwrite IsUnsuitableArgumentWithAdditionalProperties.
121-
throw new System.NotImplementedException();
122-
}
123-
124118
private string ArgumentSetTypeName(IdentifierReference argumentReference, DeclarationFinder finder)
125119
{
126120
var argumentExpression = argumentReference.Context as VBAParser.ExpressionContext;
@@ -163,12 +157,11 @@ private static bool HasSubType(Declaration declaration, string typeName)
163157
return classType.Supertypes.Select(supertype => supertype.QualifiedModuleName.ToString()).Contains(typeName);
164158
}
165159

166-
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
160+
protected override string ResultDescription(IdentifierReference reference, string argumentTypeName)
167161
{
168162
var parameterName = reference.Declaration.IdentifierName;
169163
var parameterTypeName = reference.Declaration.FullAsTypeName;
170164
var argumentExpression = reference.Context.GetText();
171-
var argumentTypeName = (string)properties;
172165
return string.Format(InspectionResults.SetAssignmentWithIncompatibleObjectTypeInspection, parameterName, parameterTypeName, argumentExpression, argumentTypeName);
173166
}
174167
}

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
103103
&& setStmtContext.expression().GetText().Equals(Tokens.Nothing);
104104
}
105105

106-
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
106+
protected override string ResultDescription(IdentifierReference reference)
107107
{
108108
return Description;
109109
}

Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultMemberRequiredInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ protected override bool IsResultReference(IdentifierReference failedIndexedDefau
7373
return true;
7474
}
7575

76-
protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess, dynamic properties = null)
76+
protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
7777
{
7878
var expression = failedIndexedDefaultMemberAccess.IdentifierName;
7979
var typeName = failedIndexedDefaultMemberAccess.Declaration?.FullAsTypeName;

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ApplicationWorksheetFunctionInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -88,7 +88,7 @@ protected override IEnumerable<Declaration> ObjectionableDeclarations(Declaratio
8888
.Where(decl => worksheetFunctionNames.Contains(decl.IdentifierName));
8989
}
9090

91-
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
91+
protected override string ResultDescription(IdentifierReference reference)
9292
{
9393
return string.Format(InspectionResults.ApplicationWorksheetFunctionInspection, reference.IdentifierName);
9494
}

0 commit comments

Comments
 (0)