Skip to content

Commit b612280

Browse files
committed
Make the remaining identifier reference inspections use the base classes if apprpriate
Some are left as-is because using the base classes would hurt readablity.
1 parent c4c35f6 commit b612280

File tree

5 files changed

+206
-102
lines changed

5 files changed

+206
-102
lines changed

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

Lines changed: 19 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
54
using Rubberduck.Parsing.Inspections;
6-
using Rubberduck.Parsing.Inspections.Abstract;
75
using Rubberduck.Parsing.Symbols;
86
using Rubberduck.Resources.Inspections;
97
using Rubberduck.Parsing.VBA;
10-
using Rubberduck.Inspections.Inspections.Extensions;
8+
using Rubberduck.Parsing.VBA.DeclarationCaching;
119

1210
namespace Rubberduck.Inspections.Concrete
1311
{
@@ -38,7 +36,7 @@ namespace Rubberduck.Inspections.Concrete
3836
/// ]]>
3937
/// </example>
4038
[RequiredLibrary("Excel")]
41-
public sealed class ImplicitActiveWorkbookReferenceInspection : InspectionBase
39+
public sealed class ImplicitActiveWorkbookReferenceInspection : IdentifierReferenceInspectionFromDeclarationsBase
4240
{
4341
public ImplicitActiveWorkbookReferenceInspection(RubberduckParserState state)
4442
: base(state) { }
@@ -53,27 +51,31 @@ public ImplicitActiveWorkbookReferenceInspection(RubberduckParserState state)
5351
"_Global", "_Application", "Global", "Application"
5452
};
5553

56-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
54+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
5755
{
58-
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
56+
var excel = finder.Projects
57+
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
5958
if (excel == null)
6059
{
61-
return Enumerable.Empty<IInspectionResult>();
60+
return Enumerable.Empty<Declaration>();
6261
}
6362

64-
var targetProperties = BuiltInDeclarations
63+
var relevantClasses = InterestingClasses
64+
.Select(className => finder.FindClassModule(className, excel, true))
65+
.OfType<ModuleDeclaration>();
66+
67+
var relevantProperties = relevantClasses
68+
.SelectMany(classDeclaration => classDeclaration.Members)
6569
.OfType<PropertyGetDeclaration>()
66-
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
67-
.ToList();
70+
.Where(member => InterestingMembers.Contains(member.IdentifierName));
6871

69-
// only inspects references, must filter ignores manually, because default filtering doesn't work here
70-
var members = targetProperties.SelectMany(item =>
71-
item.References.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName)));
72+
return relevantProperties;
73+
}
7274

73-
return members.Select(issue => new IdentifierReferenceInspectionResult(this,
74-
string.Format(InspectionResults.ImplicitActiveWorkbookReferenceInspection, issue.Context.GetText()),
75-
State,
76-
issue));
75+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
76+
{
77+
var referenceText = reference.Context.GetText();
78+
return string.Format(InspectionResults.ImplicitActiveWorkbookReferenceInspection, referenceText);
7779
}
7880
}
7981
}

Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousLetAssignmentInspection.cs

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -45,12 +45,9 @@ namespace Rubberduck.Inspections.Concrete
4545
/// </example>
4646
public sealed class SuspiciousLetAssignmentInspection : InspectionBase
4747
{
48-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
49-
5048
public SuspiciousLetAssignmentInspection(RubberduckParserState state)
5149
: base(state)
5250
{
53-
_declarationFinderProvider = state;
5451
Severity = CodeInspectionSeverity.Warning;
5552
}
5653

@@ -73,7 +70,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7370

7471
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
7572
{
76-
var finder = _declarationFinderProvider.DeclarationFinder;
73+
var finder = DeclarationFinderProvider.DeclarationFinder;
7774
return BoundLhsInspectionResults(module, finder)
7875
.Concat(UnboundLhsInspectionResults(module, finder));
7976
}
@@ -92,7 +89,7 @@ private IEnumerable<IInspectionResult> BoundLhsInspectionResults(QualifiedModule
9289

9390
if (rhsDefaultMemberAccess != null)
9491
{
95-
var result = InspectionResult(assignment, rhsDefaultMemberAccess, isUnbound, _declarationFinderProvider);
92+
var result = InspectionResult(assignment, rhsDefaultMemberAccess, isUnbound);
9693
results.Add(result);
9794
}
9895
}
@@ -133,12 +130,12 @@ private bool IsImplicitDefaultMemberAssignment(IdentifierReference reference)
133130
return (unboundRhsDefaultMemberAccess, true);
134131
}
135132

136-
private IInspectionResult InspectionResult(IdentifierReference lhsReference, IdentifierReference rhsReference, bool isUnbound, IDeclarationFinderProvider declarationFinderProvider)
133+
private IInspectionResult InspectionResult(IdentifierReference lhsReference, IdentifierReference rhsReference, bool isUnbound)
137134
{
138135
var result = new IdentifierReferenceInspectionResult(
139136
this,
140137
ResultDescription(lhsReference, rhsReference),
141-
declarationFinderProvider,
138+
DeclarationFinderProvider,
142139
lhsReference);
143140
result.Properties.RhSReference = rhsReference;
144141
if (isUnbound)
@@ -169,7 +166,7 @@ private IEnumerable<IInspectionResult> UnboundLhsInspectionResults(QualifiedModu
169166

170167
if (rhsDefaultMemberAccess != null)
171168
{
172-
var result = InspectionResult(assignment, rhsDefaultMemberAccess, true, _declarationFinderProvider);
169+
var result = InspectionResult(assignment, rhsDefaultMemberAccess, true);
173170
results.Add(result);
174171
}
175172
}

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 93 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,15 @@
44
using Antlr4.Runtime;
55
using Rubberduck.Inspections.Abstract;
66
using Rubberduck.Inspections.Results;
7+
using Rubberduck.JunkDrawer.Extensions;
78
using Rubberduck.Parsing;
89
using Rubberduck.Parsing.Grammar;
910
using Rubberduck.Parsing.Inspections.Abstract;
1011
using Rubberduck.Resources.Inspections;
1112
using Rubberduck.Parsing.Symbols;
1213
using Rubberduck.Parsing.VBA;
14+
using Rubberduck.Parsing.VBA.DeclarationCaching;
15+
using Rubberduck.VBEditor;
1316

1417
namespace Rubberduck.Inspections.Concrete
1518
{
@@ -41,7 +44,7 @@ namespace Rubberduck.Inspections.Concrete
4144
/// ]]>
4245
/// </example>
4346
[SuppressMessage("ReSharper", "LoopCanBeConvertedToQuery")]
44-
public sealed class UnassignedVariableUsageInspection : InspectionBase
47+
public sealed class UnassignedVariableUsageInspection : IdentifierReferenceInspectionFromDeclarationsBase
4548
{
4649
public UnassignedVariableUsageInspection(RubberduckParserState state)
4750
: base(state) { }
@@ -55,32 +58,97 @@ public UnassignedVariableUsageInspection(RubberduckParserState state)
5558
"VBA6.DLL;VBA.Strings.LenB"
5659
};
5760

58-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
61+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
5962
{
60-
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
61-
.Where(declaration => !declaration.IsArray &&
62-
State.DeclarationFinder.MatchName(declaration.AsTypeName)
63-
.All(d => d.DeclarationType != DeclarationType.UserDefinedType)
64-
&& !declaration.IsSelfAssigned
65-
&& !declaration.References.Any(reference => reference.IsAssignment));
66-
67-
var excludedDeclarations = BuiltInDeclarations.Where(decl => IgnoredFunctions.Contains(decl.QualifiedName.ToString())).ToList();
68-
69-
return declarations
70-
.Where(d => d.References.Any() && !excludedDeclarations.Any(excl => DeclarationReferencesContainsReference(excl, d)))
71-
.SelectMany(d => d.References.Where(r => !IsAssignedByRefArgument(r.ParentScoping, r)))
72-
.Distinct()
73-
.Where(r => !r.Context.TryGetAncestor<VBAParser.RedimStmtContext>(out _) && !IsArraySubscriptAssignment(r))
74-
.Select(r => new IdentifierReferenceInspectionResult(this,
75-
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
76-
State,
77-
r)).ToList();
63+
return finder.UserDeclarations(DeclarationType.Variable)
64+
.Where(declaration => !declaration.IsArray
65+
&& !declaration.IsSelfAssigned
66+
&& finder.MatchName(declaration.AsTypeName)
67+
.All(d => d.DeclarationType != DeclarationType.UserDefinedType)
68+
&& !declaration.References
69+
.Any(reference => reference.IsAssignment));
7870
}
7971

80-
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
72+
//We override this in order to look up the argument usage exclusion references only once.
73+
protected override IEnumerable<IdentifierReference> ObjectionableReferences(DeclarationFinder finder)
74+
{
75+
var excludedReferenceSelections = DeclarationsWithExcludedArgumentUsage(finder)
76+
.SelectMany(SingleVariableArgumentSelections)
77+
.ToHashSet();
78+
79+
return base.ObjectionableReferences(finder)
80+
.Where(reference => !excludedReferenceSelections.Contains(reference.QualifiedSelection));
81+
}
82+
83+
private IEnumerable<ModuleBodyElementDeclaration> DeclarationsWithExcludedArgumentUsage(DeclarationFinder finder)
84+
{
85+
var vbaProjects = finder.Projects
86+
.Where(project => project.IdentifierName == "VBA" && !project.IsUserDefined)
87+
.ToList();
88+
89+
if (!vbaProjects.Any())
90+
{
91+
return new List<ModuleBodyElementDeclaration>();
92+
}
93+
94+
var stringModules = vbaProjects
95+
.Select(project => finder.FindStdModule("Strings", project, true))
96+
.OfType<ModuleDeclaration>()
97+
.ToList();
98+
99+
if (!stringModules.Any())
100+
{
101+
return new List<ModuleBodyElementDeclaration>();
102+
}
103+
104+
return stringModules
105+
.SelectMany(module => module.Members)
106+
.Where(decl => IgnoredFunctions.Contains(decl.QualifiedName.ToString()))
107+
.OfType<ModuleBodyElementDeclaration>();
108+
}
109+
110+
private static IEnumerable<QualifiedSelection> SingleVariableArgumentSelections(ModuleBodyElementDeclaration member)
111+
{
112+
return member.Parameters
113+
.SelectMany(parameter => parameter.ArgumentReferences)
114+
.Select(SingleVariableArgumentSelection)
115+
.Where(maybeSelection => maybeSelection.HasValue)
116+
.Select(selection => selection.Value);
117+
}
118+
119+
private static QualifiedSelection? SingleVariableArgumentSelection(ArgumentReference argumentReference)
120+
{
121+
var argumentContext = argumentReference.Context as VBAParser.LExprContext;
122+
if (!(argumentContext?.lExpression() is VBAParser.SimpleNameExprContext name))
123+
{
124+
return null;
125+
}
126+
127+
return new QualifiedSelection(argumentReference.QualifiedModuleName, name.GetSelection());
128+
}
129+
130+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
131+
{
132+
//FIXME: stop filtering out too many results.
133+
return reference != null
134+
&& !IsAssignedByRefArgument(reference.ParentScoping, reference, finder)
135+
&& !IsArraySubscriptAssignment(reference)
136+
&& !reference.Context.TryGetAncestor<VBAParser.RedimStmtContext>(out _);
137+
138+
}
139+
140+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
141+
{
142+
var identifierName = reference.IdentifierName;
143+
return string.Format(
144+
InspectionResults.UnassignedVariableUsageInspection,
145+
identifierName);
146+
}
147+
148+
private static bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference, DeclarationFinder finder)
81149
{
82150
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
83-
var parameter = State.DeclarationFinder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, enclosingProcedure);
151+
var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, enclosingProcedure);
84152

85153
// note: not recursive, by design.
86154
return parameter != null
@@ -90,28 +158,12 @@ private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierR
90158

91159
private static bool IsArraySubscriptAssignment(IdentifierReference reference)
92160
{
161+
//FIXME: stop returning true for too many cases.
93162
var isLetAssignment = reference.Context.TryGetAncestor<VBAParser.LetStmtContext>(out var letStmt);
94163
var isSetAssignment = reference.Context.TryGetAncestor<VBAParser.SetStmtContext>(out var setStmt);
95164

96-
return isLetAssignment && letStmt.lExpression() is VBAParser.IndexExprContext ||
97-
isSetAssignment && setStmt.lExpression() is VBAParser.IndexExprContext;
98-
}
99-
100-
private static bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
101-
{
102-
foreach (var targetReference in target.References)
103-
{
104-
foreach (var reference in parentDeclaration.References)
105-
{
106-
var context = (ParserRuleContext)reference.Context.Parent;
107-
if (context.GetSelection().Contains(targetReference.Selection))
108-
{
109-
return true;
110-
}
111-
}
112-
}
113-
114-
return false;
165+
return isLetAssignment && letStmt.lExpression() is VBAParser.IndexExprContext
166+
|| isSetAssignment && setStmt.lExpression() is VBAParser.IndexExprContext;
115167
}
116168
}
117169
}

Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs

Lines changed: 16 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,7 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
54
using Rubberduck.Parsing.Grammar;
6-
using Rubberduck.Parsing.Inspections.Abstract;
75
using Rubberduck.Resources.Inspections;
86
using Rubberduck.Parsing.VBA;
97
using Rubberduck.Parsing.Symbols;
@@ -32,7 +30,7 @@ namespace Rubberduck.Inspections.Concrete
3230
/// End Sub
3331
/// ]]>
3432
/// </example>
35-
public sealed class UntypedFunctionUsageInspection : InspectionBase
33+
public sealed class UntypedFunctionUsageInspection : IdentifierReferenceInspectionFromDeclarationsBase
3634
{
3735
public UntypedFunctionUsageInspection(RubberduckParserState state)
3836
: base(state) { }
@@ -63,48 +61,37 @@ public UntypedFunctionUsageInspection(RubberduckParserState state)
6361
Tokens.UCase
6462
};
6563

66-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
64+
protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
6765
{
68-
var finder = State.DeclarationFinder;
69-
70-
var declarationsToConsider = BuiltInVariantStringFunctionsWithStringTypedVersion(finder);
71-
72-
return declarationsToConsider
73-
.SelectMany(NonStringHintedReferences)
74-
.Select(Result);
66+
return BuiltInVariantStringFunctionsWithStringTypedVersion(finder);
7567
}
7668

7769
private IEnumerable<Declaration> BuiltInVariantStringFunctionsWithStringTypedVersion(DeclarationFinder finder)
7870
{
7971
return finder
8072
.BuiltInDeclarations(DeclarationType.Member)
81-
.Where(item => (_tokens.Contains(item.IdentifierName)
82-
|| item.IdentifierName.StartsWith("_B_var_")
83-
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length)))
84-
&& item.Scope.StartsWith("VBE7.DLL;"));
73+
.Where(item => item.Scope.StartsWith("VBE7.DLL;")
74+
&& (_tokens.Contains(item.IdentifierName)
75+
|| item.IdentifierName.StartsWith("_B_var_")
76+
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length))));
8577
}
8678

87-
private IEnumerable<IdentifierReference> NonStringHintedReferences(Declaration declaration)
79+
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)
8880
{
89-
return declaration.References
90-
.Where(item => _tokens.Contains(item.IdentifierName));
81+
var declarationName = reference.Declaration.IdentifierName;
82+
return string.Format(
83+
InspectionResults.UntypedFunctionUsageInspection,
84+
declarationName);
9185
}
9286

93-
private IInspectionResult Result(IdentifierReference reference)
87+
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
9488
{
95-
return new IdentifierReferenceInspectionResult(
96-
this,
97-
ResultDescription(reference),
98-
State,
99-
reference);
89+
return IsNotStringHinted(reference);
10090
}
10191

102-
private static string ResultDescription(IdentifierReference reference)
92+
private bool IsNotStringHinted(IdentifierReference reference)
10393
{
104-
var declarationName = reference.Declaration.IdentifierName;
105-
return string.Format(
106-
InspectionResults.UntypedFunctionUsageInspection,
107-
declarationName);
94+
return _tokens.Contains(reference.IdentifierName);
10895
}
10996
}
11097
}

0 commit comments

Comments
 (0)