Skip to content

Commit 3ebe7c2

Browse files
committed
Pass along result properties to the ResultDescription method of the identifier reference inspection base classes
Also moves further inspections to the base classes.
1 parent 92efa31 commit 3ebe7c2

32 files changed

+149
-155
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/ArgumentReferenceInspectionFromDeclarationsBase.cs

Lines changed: 3 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -19,15 +19,11 @@ protected virtual (bool isResult, object properties) IsUnsuitableArgumentWithAdd
1919
return (IsUnsuitableArgument(reference, finder), null);
2020
}
2121

22-
protected override IEnumerable<(IdentifierReference reference, object properties)> ObjectionableReferences(DeclarationFinder finder)
22+
protected override IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
2323
{
2424
return ObjectionableDeclarations(finder)
25-
.OfType<ModuleBodyElementDeclaration>()
26-
.SelectMany(declaration => declaration.Parameters)
27-
.SelectMany(parameter => parameter.ArgumentReferences)
28-
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
29-
.Where(tpl => tpl.Item2.isResult)
30-
.Select(tpl => ((IdentifierReference) tpl.reference, tpl.Item2.properties)); ;
25+
.OfType<ParameterDeclaration>()
26+
.SelectMany(parameter => parameter.ArgumentReferences);
3127
}
3228

3329
protected override (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ public IdentifierReferenceInspectionBase(RubberduckParserState state)
1616
{}
1717

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

2121
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
2222
{
@@ -69,7 +69,7 @@ protected virtual IInspectionResult InspectionResult(IdentifierReference referen
6969
{
7070
return new IdentifierReferenceInspectionResult(
7171
this,
72-
ResultDescription(reference),
72+
ResultDescription(reference, properties),
7373
declarationFinderProvider,
7474
reference,
7575
properties);

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionFromDeclarationsBase.cs

Lines changed: 17 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -16,27 +16,33 @@ protected IdentifierReferenceInspectionFromDeclarationsBase(RubberduckParserStat
1616
{}
1717

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

2121
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
{
2323
var finder = DeclarationFinderProvider.DeclarationFinder;
2424
var objectionableReferences = ObjectionableReferences(finder);
25-
return objectionableReferences
25+
var resultReferences = ResultReferences(objectionableReferences, finder);
26+
return resultReferences
2627
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
2728
.ToList();
2829
}
2930

30-
protected virtual IEnumerable<(IdentifierReference reference, object properties)> ObjectionableReferences(DeclarationFinder finder)
31+
private IEnumerable<(IdentifierReference reference, object properties)> ResultReferences(IEnumerable<IdentifierReference> potentialResultReferences, DeclarationFinder finder)
3132
{
32-
var objectionableDeclarations = ObjectionableDeclarations(finder);
33-
return objectionableDeclarations
34-
.SelectMany(declaration => declaration.References)
33+
return potentialResultReferences
3534
.Select(reference => (reference, IsResultReferenceWithAdditionalProperties(reference, finder)))
3635
.Where(tpl => tpl.Item2.isResult)
3736
.Select(tpl => (tpl.reference, tpl.Item2.properties));
3837
}
3938

39+
protected virtual IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
40+
{
41+
var objectionableDeclarations = ObjectionableDeclarations(finder);
42+
return objectionableDeclarations
43+
.SelectMany(declaration => declaration.References);
44+
}
45+
4046
protected virtual bool IsResultReference(IdentifierReference reference, DeclarationFinder finder) => true;
4147

4248
protected virtual (bool isResult, object properties) IsResultReferenceWithAdditionalProperties(IdentifierReference reference, DeclarationFinder finder)
@@ -47,9 +53,10 @@ protected virtual (bool isResult, object properties) IsResultReferenceWithAdditi
4753
protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
4854
{
4955
var finder = DeclarationFinderProvider.DeclarationFinder;
50-
var objectionableReferences = ObjectionableReferences(finder);
51-
return objectionableReferences
52-
.Where(tpl => tpl.reference.QualifiedModuleName.Equals(module))
56+
var objectionableReferences = ObjectionableReferences(finder)
57+
.Where(reference => reference.QualifiedModuleName.Equals(module));
58+
var resultReferences = ResultReferences(objectionableReferences, finder);
59+
return resultReferences
5360
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
5461
.ToList();
5562
}
@@ -58,7 +65,7 @@ protected virtual IInspectionResult InspectionResult(IdentifierReference referen
5865
{
5966
return new IdentifierReferenceInspectionResult(
6067
this,
61-
ResultDescription(reference),
68+
ResultDescription(reference, properties),
6269
declarationFinderProvider,
6370
reference,
6471
properties);

Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,9 +48,11 @@ protected IReadOnlyList<Declaration> IsMissingDeclarations(DeclarationFinder fin
4848
var isMissing = informationModules
4949
.SelectMany(module => module.Members)
5050
.Where(decl => IsMissingQualifiedNames.Contains(decl.QualifiedName.ToString()))
51-
.ToList();
51+
.OfType<ModuleBodyElementDeclaration>();
5252

53-
return isMissing;
53+
return isMissing
54+
.SelectMany(declaration => declaration.Parameters)
55+
.ToList();
5456
}
5557

5658
protected ParameterDeclaration ParameterForReference(ArgumentReference reference, DeclarationFinder finder)

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

Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs

Lines changed: 28 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Inspections.Abstract;
45
using Rubberduck.Inspections.Inspections.Extensions;
56
using Rubberduck.Inspections.Results;
67
using Rubberduck.Parsing.Grammar;
@@ -77,53 +78,47 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
7778
/// End Sub
7879
/// ]]>
7980
/// </example>
80-
public class ArgumentWithIncompatibleObjectTypeInspection : InspectionBase
81+
public class ArgumentWithIncompatibleObjectTypeInspection : ArgumentReferenceInspectionFromDeclarationsBase
8182
{
82-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
8383
private readonly ISetTypeResolver _setTypeResolver;
8484

8585
public ArgumentWithIncompatibleObjectTypeInspection(RubberduckParserState state, ISetTypeResolver setTypeResolver)
8686
: base(state)
8787
{
88-
_declarationFinderProvider = state;
8988
_setTypeResolver = setTypeResolver;
9089

9190
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
9291
Severity = CodeInspectionSeverity.Error;
9392
}
9493

95-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
94+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
9695
{
97-
var finder = _declarationFinderProvider.DeclarationFinder;
98-
99-
var strictlyTypedObjectParameters = finder.DeclarationsWithType(DeclarationType.Parameter)
100-
.Where(ToBeConsidered)
101-
.OfType<ParameterDeclaration>();
102-
103-
var offendingArguments = strictlyTypedObjectParameters
104-
.SelectMany(param => param.ArgumentReferences)
105-
.Select(argumentReference => ArgumentReferenceWithArgumentTypeName(argumentReference, finder))
106-
.Where(argumentReferenceWithTypeName => argumentReferenceWithTypeName.argumentTypeName != null
107-
&& !ArgumentPossiblyLegal(
108-
argumentReferenceWithTypeName.argumentReference.Declaration,
109-
argumentReferenceWithTypeName.argumentTypeName));
110-
111-
return offendingArguments
112-
// Ignoring the Declaration disqualifies all assignments
113-
.Where(argumentReferenceWithTypeName => !argumentReferenceWithTypeName.Item1.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
114-
.Select(argumentReference => InspectionResult(argumentReference, _declarationFinderProvider));
96+
return finder.DeclarationsWithType(DeclarationType.Parameter)
97+
.Where(ToBeConsidered);
11598
}
11699

117100
private static bool ToBeConsidered(Declaration declaration)
118101
{
119-
return declaration != null
120-
&& declaration.AsTypeDeclaration != null
102+
return declaration?.AsTypeDeclaration != null
121103
&& declaration.IsObject;
122104
}
123105

124-
private (IdentifierReference argumentReference, string argumentTypeName) ArgumentReferenceWithArgumentTypeName(IdentifierReference argumentReference, DeclarationFinder finder)
106+
protected override (bool isResult, object properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
125107
{
126-
return (argumentReference, ArgumentSetTypeName(argumentReference, finder));
108+
var argumentSetTypeName = ArgumentSetTypeName(reference, finder);
109+
110+
if (argumentSetTypeName == null || ArgumentPossiblyLegal(reference.Declaration, argumentSetTypeName))
111+
{
112+
return (false, null);
113+
}
114+
115+
return (true, argumentSetTypeName);
116+
}
117+
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();
127122
}
128123

129124
private string ArgumentSetTypeName(IdentifierReference argumentReference, DeclarationFinder finder)
@@ -146,7 +141,7 @@ private bool ArgumentPossiblyLegal(Declaration parameterDeclaration , string ass
146141
|| HasSubType(parameterDeclaration, assignedTypeName);
147142
}
148143

149-
private bool HasBaseType(Declaration declaration, string typeName)
144+
private static bool HasBaseType(Declaration declaration, string typeName)
150145
{
151146
var ownType = declaration.AsTypeDeclaration;
152147
if (ownType == null || !(ownType is ClassModuleDeclaration classType))
@@ -157,7 +152,7 @@ private bool HasBaseType(Declaration declaration, string typeName)
157152
return classType.Subtypes.Select(subtype => subtype.QualifiedModuleName.ToString()).Contains(typeName);
158153
}
159154

160-
private bool HasSubType(Declaration declaration, string typeName)
155+
private static bool HasSubType(Declaration declaration, string typeName)
161156
{
162157
var ownType = declaration.AsTypeDeclaration;
163158
if (ownType == null || !(ownType is ClassModuleDeclaration classType))
@@ -168,20 +163,12 @@ private bool HasSubType(Declaration declaration, string typeName)
168163
return classType.Supertypes.Select(supertype => supertype.QualifiedModuleName.ToString()).Contains(typeName);
169164
}
170165

171-
private IInspectionResult InspectionResult((IdentifierReference argumentReference, string argumentTypeName) argumentReferenceWithTypeName, IDeclarationFinderProvider declarationFinderProvider)
172-
{
173-
var (argumentReference, argumentTypeName) = argumentReferenceWithTypeName;
174-
return new IdentifierReferenceInspectionResult(this,
175-
ResultDescription(argumentReference, argumentTypeName),
176-
declarationFinderProvider,
177-
argumentReference);
178-
}
179-
180-
private string ResultDescription(IdentifierReference argumentReference, string argumentTypeName)
166+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
181167
{
182-
var parameterName = argumentReference.Declaration.IdentifierName;
183-
var parameterTypeName = argumentReference.Declaration.FullAsTypeName;
184-
var argumentExpression = argumentReference.Context.GetText();
168+
var parameterName = reference.Declaration.IdentifierName;
169+
var parameterTypeName = reference.Declaration.FullAsTypeName;
170+
var argumentExpression = reference.Context.GetText();
171+
var argumentTypeName = (string)properties;
185172
return string.Format(InspectionResults.SetAssignmentWithIncompatibleObjectTypeInspection, parameterName, parameterTypeName, argumentExpression, argumentTypeName);
186173
}
187174
}

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

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

108-
protected override string ResultDescription(IdentifierReference reference)
108+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
109109
{
110110
return Description;
111111
}

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)
76+
protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess, dynamic properties = null)
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)
91+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
9292
{
9393
return string.Format(InspectionResults.ApplicationWorksheetFunctionInspection, reference.IdentifierName);
9494
}

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@ protected override IEnumerable<Declaration> ObjectionableDeclarations(Declaratio
7575
"Cells", "Range", "Columns", "Rows"
7676
};
7777

78-
protected override string ResultDescription(IdentifierReference reference)
78+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
7979
{
8080
return string.Format(
8181
InspectionResults.ImplicitActiveSheetReferenceInspection,

0 commit comments

Comments
 (0)