Skip to content

Commit c491534

Browse files
committed
Addresses Inspection False Positive: Issue 5456
Modifies IsResultReference(...) to avoid flagging an unused assignment that preceeds a GoTo/Resume statement that branches execution to a line in the procedure where the assignment could be used.
1 parent 77df36f commit c491534

File tree

2 files changed

+86
-2
lines changed

2 files changed

+86
-2
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 36 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using Rubberduck.Inspections.CodePathAnalysis;
66
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
77
using Rubberduck.Inspections.CodePathAnalysis.Nodes;
8+
using Rubberduck.Parsing;
89
using Rubberduck.Parsing.Grammar;
910
using Rubberduck.Parsing.Symbols;
1011
using Rubberduck.Parsing.VBA;
@@ -67,7 +68,7 @@ private IEnumerable<IdentifierReference> UnusedAssignments(Declaration localVari
6768
return UnusedAssignmentReferences(tree);
6869
}
6970

70-
public static List<IdentifierReference> UnusedAssignmentReferences(INode node)
71+
private static List<IdentifierReference> UnusedAssignmentReferences(INode node)
7172
{
7273
var nodes = new List<IdentifierReference>();
7374

@@ -98,7 +99,8 @@ public static List<IdentifierReference> UnusedAssignmentReferences(INode node)
9899

99100
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
100101
{
101-
return !IsAssignmentOfNothing(reference);
102+
return !(IsAssignmentOfNothing(reference)
103+
|| DisqualifiedByResumeOrGoToStatements(reference, finder));
102104
}
103105

104106
private static bool IsAssignmentOfNothing(IdentifierReference reference)
@@ -108,6 +110,38 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
108110
&& setStmtContext.expression().GetText().Equals(Tokens.Nothing);
109111
}
110112

113+
private static bool DisqualifiedByResumeOrGoToStatements(IdentifierReference resultCandidate, DeclarationFinder finder)
114+
{
115+
var relevantLabels = finder.DeclarationsWithType(DeclarationType.LineLabel)
116+
.Where(label => resultCandidate.ParentScoping.Equals(label.ParentDeclaration));
117+
118+
if (!relevantLabels.Any())
119+
{
120+
return false;
121+
}
122+
123+
var lineNumbersForNonAssignmentReferencesOfResultCandidateDeclaration =
124+
resultCandidate.Declaration.References
125+
.Where(rf => !rf.IsAssignment)
126+
.Select(rf => rf.Context.Stop.Line);
127+
128+
if (!lineNumbersForNonAssignmentReferencesOfResultCandidateDeclaration.Any())
129+
{
130+
return false;
131+
}
132+
133+
var labelReferencesAffectingExecutionPath = relevantLabels.SelectMany(d => d.References)
134+
.Where(labelReference => LabelReferencedByJumpStatementAfterResultCandidateAssignment(labelReference, resultCandidate));
135+
136+
return labelReferencesAffectingExecutionPath.Any(labelReference => labelReference.Declaration.Context.Stop.Line < resultCandidate.Context.Start.Line
137+
&& labelReference.Declaration.Context.Start.Line < lineNumbersForNonAssignmentReferencesOfResultCandidateDeclaration.Max());
138+
}
139+
140+
private static bool LabelReferencedByJumpStatementAfterResultCandidateAssignment(IdentifierReference labelReference, IdentifierReference resultCandidate)
141+
=> labelReference.Context.Start.Line > resultCandidate.Context.Stop.Line
142+
&& (labelReference.Context.TryGetAncestor<VBAParser.ResumeStmtContext>(out _)
143+
|| labelReference.Context.TryGetAncestor<VBAParser.GoToStmtContext>(out _));
144+
111145
protected override string ResultDescription(IdentifierReference reference)
112146
{
113147
return Description;

RubberduckTests/Inspections/AssignmentNotUsedInspectionTests.cs

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -259,6 +259,56 @@ Dim foo As Long
259259
Assert.AreEqual(0, results.Count());
260260
}
261261

262+
//https://github.com/rubberduck-vba/Rubberduck/issues/5456
263+
[TestCase("Resume CleanExit")]
264+
[TestCase("GoTo CleanExit")]
265+
public void IgnoresAssignmentWhereExecutionPathModifiedByJumpStatementCouldIncludeUse(string statement)
266+
{
267+
string code =
268+
$@"
269+
Public Function Inverse(value As Double) As Double
270+
Dim ratio As Double
271+
ratio = 0# 'assigment not used - flagged
272+
On Error Goto ErrorHandler
273+
ratio = 1# / value
274+
CleanExit:
275+
Inverse = ratio
276+
Exit Function
277+
ErrorHandler:
278+
ratio = -1# 'assigment not used evaluation disqualified by Resume/GoTo - not flagged
279+
{statement}
280+
End Function
281+
";
282+
var results = InspectionResultsForStandardModule(code);
283+
Assert.AreEqual(1, results.Count());
284+
}
285+
286+
[TestCase("Resume IgnoreRatio")]
287+
[TestCase("GoTo IgnoreRatio")]
288+
public void FlagsAssignmentWhereExecutionPathModifiedByJumpStatementCouldNotIncludeUse(string statement)
289+
{
290+
string code =
291+
$@"
292+
Public Function Inverse(value As Double) As Double
293+
Inverse = 0#
294+
Dim ratio As Double
295+
On Error Goto ErrorHandler
296+
ratio = 1# / value
297+
Inverse = ratio
298+
299+
IgnoreRatio:
300+
Exit Function
301+
ErrorHandler:
302+
'assignment not used since jump is to IgnoreRatio:
303+
'and all ratio references below IgnoreRatio: are assignments
304+
ratio = 0#
305+
{statement}
306+
End Function
307+
";
308+
var results = InspectionResultsForStandardModule(code);
309+
Assert.AreEqual(1, results.Count());
310+
}
311+
262312
protected override IInspection InspectionUnderTest(RubberduckParserState state)
263313
{
264314
return new AssignmentNotUsedInspection(state, new Walker());

0 commit comments

Comments
 (0)