Skip to content

Commit 68355cb

Browse files
committed
Simplify ObjectVariableNotSetInspection
It now works using failed Let coercion references.
1 parent 70cce4a commit 68355cb

File tree

3 files changed

+815
-25
lines changed

3 files changed

+815
-25
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs

Lines changed: 49 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,18 @@
1-
using System.Collections.Generic;
1+
using System;
2+
using System.Collections.Generic;
23
using System.Linq;
4+
using Antlr4.Runtime;
35
using Rubberduck.Inspections.Abstract;
46
using Rubberduck.Inspections.Results;
57
using Rubberduck.Parsing.Inspections.Abstract;
68
using Rubberduck.Resources.Inspections;
79
using Rubberduck.Parsing.Symbols;
810
using Rubberduck.Parsing.VBA;
911
using Rubberduck.Inspections.Inspections.Extensions;
12+
using Rubberduck.Parsing;
13+
using Rubberduck.Parsing.Grammar;
1014
using Rubberduck.Parsing.VBA.DeclarationCaching;
15+
using Rubberduck.VBEditor;
1116

1217
namespace Rubberduck.Inspections.Concrete
1318
{
@@ -45,10 +50,9 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4550
{
4651
var finder = State.DeclarationFinder;
4752

48-
var failedLetResolutionAssignments = FailedLetResolutionAssignments(finder);
49-
var interestingOtherReferences = InterestingReferences();
53+
var failedLetResolutionResults = FailedLetResolutionResults(finder);
5054

51-
return failedLetResolutionAssignments.Concat(interestingOtherReferences)
55+
return failedLetResolutionResults
5256
.Select(reference =>
5357
new IdentifierReferenceInspectionResult(
5458
this,
@@ -57,7 +61,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5761
reference));
5862
}
5963

60-
private IEnumerable<IdentifierReference> FailedLetResolutionAssignments(DeclarationFinder finder)
64+
private IEnumerable<IdentifierReference> FailedLetResolutionResults(DeclarationFinder finder)
6165
{
6266
var results = new List<IdentifierReference>();
6367
foreach (var moduleDeclaration in finder.UserDeclarations(DeclarationType.Module))
@@ -67,33 +71,55 @@ private IEnumerable<IdentifierReference> FailedLetResolutionAssignments(Declarat
6771
continue;
6872
}
6973

70-
var failedLetCoercionAssignmentsInModule = finder
71-
.FailedLetCoercions(moduleDeclaration.QualifiedModuleName)
72-
.Where(reference => reference.IsAssignment);
73-
74+
var module = moduleDeclaration.QualifiedModuleName;
75+
var failedLetCoercionAssignmentsInModule = FailedLetResolutionAssignments(module, finder);
76+
var possiblyObjectLhsLetAssignmentsWithFailedLetResolutionOnRhs = PossiblyObjectLhsLetAssignmentsWithNonValueOnRhs(module, finder);
7477
results.AddRange(failedLetCoercionAssignmentsInModule);
78+
results.AddRange(possiblyObjectLhsLetAssignmentsWithFailedLetResolutionOnRhs);
7579
}
7680

7781
return results.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName));
7882
}
7983

80-
private IEnumerable<IdentifierReference> InterestingReferences()
84+
private static IEnumerable<IdentifierReference> FailedLetResolutionAssignments(QualifiedModuleName module, DeclarationFinder finder)
8185
{
82-
var result = new List<IdentifierReference>();
83-
foreach (var moduleReferences in State.DeclarationFinder.IdentifierReferences())
84-
{
85-
var module = State.DeclarationFinder.ModuleDeclaration(moduleReferences.Key);
86-
if (module == null || !module.IsUserDefined || module.IsIgnoringInspectionResultFor(AnnotationName))
87-
{
88-
// module isn't user code (?), or this inspection is ignored at module-level
89-
continue;
90-
}
86+
return finder.FailedLetCoercions(module)
87+
.Where(reference => reference.IsAssignment);
88+
}
9189

92-
result.AddRange(moduleReferences.Value.Where(reference => !reference.IsSetAssignment
93-
&& VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State)));
94-
}
90+
private static IEnumerable<IdentifierReference> PossiblyObjectLhsLetAssignmentsWithNonValueOnRhs(QualifiedModuleName module, DeclarationFinder finder)
91+
{
92+
return PossiblyObjectLhsLetAssignments(module, finder)
93+
.Where(tpl => finder.FailedLetCoercions(module)
94+
.Any(reference => reference.Selection.Equals(tpl.rhs.GetSelection()))
95+
|| Tokens.Nothing.Equals(tpl.rhs.GetText(), StringComparison.InvariantCultureIgnoreCase))
96+
.Select(tpl => tpl.assignment);
97+
}
98+
99+
private static IEnumerable<(IdentifierReference assignment, ParserRuleContext rhs)> PossiblyObjectLhsLetAssignments(QualifiedModuleName module, DeclarationFinder finder)
100+
{
101+
return PossiblyObjectNonSetAssignments(module, finder)
102+
.Select(reference => (reference, RhsOfLetAssignment(reference)))
103+
.Where(tpl => tpl.Item2 != null);
104+
}
105+
106+
private static ParserRuleContext RhsOfLetAssignment(IdentifierReference letAssignment)
107+
{
108+
var letStatement = letAssignment.Context.Parent as VBAParser.LetStmtContext;
109+
return letStatement?.expression();
110+
}
111+
112+
private static IEnumerable<IdentifierReference> PossiblyObjectNonSetAssignments(QualifiedModuleName module, DeclarationFinder finder)
113+
{
114+
var assignments = finder.IdentifierReferences(module)
115+
.Where(reference => reference.IsAssignment
116+
&& !reference.IsSetAssignment
117+
&& (reference.IsNonIndexedDefaultMemberAccess
118+
|| Tokens.Variant.Equals(reference.Declaration.AsTypeName, StringComparison.InvariantCultureIgnoreCase)));
119+
var unboundAssignments = finder.UnboundDefaultMemberAccesses(module)
120+
.Where(reference => reference.IsAssignment);
95121

96-
return result.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName));
122+
return assignments.Concat(unboundAssignments);
97123
}
98124
}
99125
}

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5672,7 +5672,7 @@ End Sub
56725672
[TestCase(" For Each fooBar In cls.Baz : Foo = 42 : Next", 24, 31)]
56735673
[TestCase(" Foo = cls.Baz Is fooBar", 11, 18)]
56745674
[TestCase(" Foo = fooBar Is cls.Baz", 21, 28)]
5675-
public void NonLetCoercionExpressionHasNoFeiledLetCoercionReference(string statement, int selectionStartColumn, int selectionEndColumn)
5675+
public void NonLetCoercionExpressionHasNoFailedLetCoercionReference(string statement, int selectionStartColumn, int selectionEndColumn)
56765676
{
56775677
var class1Code = @"
56785678
Public Function Foo() As Long

0 commit comments

Comments
 (0)