Skip to content

Commit c444b25

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 c444b25

File tree

2 files changed

+402
-2
lines changed

2 files changed

+402
-2
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 139 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
using System.Collections.Generic;
22
using System.Linq;
3+
using Antlr4.Runtime;
34
using Rubberduck.CodeAnalysis.Inspections.Abstract;
45
using Rubberduck.CodeAnalysis.Inspections.Extensions;
56
using Rubberduck.Inspections.CodePathAnalysis;
67
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
78
using Rubberduck.Inspections.CodePathAnalysis.Nodes;
9+
using Rubberduck.Parsing;
810
using Rubberduck.Parsing.Grammar;
911
using Rubberduck.Parsing.Symbols;
1012
using Rubberduck.Parsing.VBA;
@@ -67,7 +69,7 @@ private IEnumerable<IdentifierReference> UnusedAssignments(Declaration localVari
6769
return UnusedAssignmentReferences(tree);
6870
}
6971

70-
public static List<IdentifierReference> UnusedAssignmentReferences(INode node)
72+
private static List<IdentifierReference> UnusedAssignmentReferences(INode node)
7173
{
7274
var nodes = new List<IdentifierReference>();
7375

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

99101
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
100102
{
101-
return !IsAssignmentOfNothing(reference);
103+
return !(IsAssignmentOfNothing(reference)
104+
|| IsPotentiallyUsedViaResumeOrGoToExecutionBranch(reference, finder));
102105
}
103106

104107
private static bool IsAssignmentOfNothing(IdentifierReference reference)
@@ -108,6 +111,140 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
108111
&& setStmtContext.expression().GetText().Equals(Tokens.Nothing);
109112
}
110113

114+
/// <summary>
115+
/// Filters false positive result references due to GoTo and Resume statements. e.g.,
116+
/// An ErrorHandler block that branches execution to a location where the asignment may be used.
117+
/// </summary>
118+
/// <remarks>
119+
/// Excludes Assignment references that meet the following conditions:
120+
/// 1. Preceed a GoTo or Resume statement that branches execution to a line before the
121+
/// assignment reference, and
122+
/// 2. A non-assignment reference is present on a line that is:
123+
/// a) At or below the start of the execution branch, and
124+
/// b) Above the next ExitStatement line (if one exists) or the end of the procedure
125+
/// </remarks>
126+
/// <param name="resultCandidate"></param>
127+
/// <param name="finder"></param>
128+
/// <returns></returns>
129+
private static bool IsPotentiallyUsedViaResumeOrGoToExecutionBranch(IdentifierReference resultCandidate, DeclarationFinder finder)
130+
{
131+
if (!resultCandidate.Declaration.References.Any(rf => !rf.IsAssignment)) { return false; }
132+
133+
var labelIdLineNumberPairs = finder.DeclarationsWithType(DeclarationType.LineLabel)
134+
.Where(label => resultCandidate.ParentScoping.Equals(label.ParentDeclaration))
135+
.Select(lbl => (lbl.IdentifierName, lbl.Context.Start.Line));
136+
137+
return GotoExecutionBranchPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs)
138+
|| ResumeExecutionBranchPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
139+
}
140+
141+
private static bool GotoExecutionBranchPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs)
142+
{
143+
var gotoCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.GoToStmtContext>()
144+
.Where(gotoCtxt => gotoCtxt.Start.Line > resultCandidate.Context.Start.Line);
145+
146+
if (!gotoCtxts.Any()) { return false; }
147+
148+
var gotoStmt = GetFirstContextAfterLine(gotoCtxts, resultCandidate.Context.Start.Line);
149+
150+
if (gotoStmt == null) { return false; }
151+
152+
var executionBranchLine = DetermineExecutionBranchLine(gotoStmt.expression().GetText(), labelIdLineNumberPairs);
153+
154+
return IsPotentiallyUsedAssignment(resultCandidate, executionBranchLine);
155+
}
156+
157+
private static bool ResumeExecutionBranchPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs)
158+
{
159+
var resumeStmtCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.ResumeStmtContext>()
160+
.Where(jumpCtxt => jumpCtxt.Start.Line > resultCandidate.Context.Start.Line);
161+
162+
if (!resumeStmtCtxts.Any()) { return false; }
163+
164+
var onErrorGotoStatements = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.OnErrorStmtContext>()
165+
.Where(errorStmtCtxt => !errorStmtCtxt.expression().GetText().Equals("0"))
166+
.ToDictionary(k => k.expression()?.GetText() ?? "0", v => v.Start.Line);
167+
168+
var errorHandlerLabelsAndLines = labelIdLineNumberPairs.Where(pair => onErrorGotoStatements.ContainsKey(pair.IdentifierName));
169+
170+
//If the resultCandidate line preceeds all ErrorHandlers/Resume statements - it is not evaluated
171+
if (errorHandlerLabelsAndLines.All(s => s.Line > resultCandidate.Context.Start.Line))
172+
{
173+
return false;
174+
}
175+
176+
var resumeStmt = GetFirstContextAfterLine(resumeStmtCtxts, resultCandidate.Context.Start.Line);
177+
178+
if (resumeStmt == null) { return false; }
179+
180+
int? executionBranchLine = null;
181+
182+
var expression = resumeStmt.expression()?.GetText();
183+
184+
//For Resume and Resume Next, expression() is null
185+
if (string.IsNullOrEmpty(expression))
186+
{
187+
//Get info for the errorHandlerLabel above the Resume statement
188+
(string IdentifierName, int Line)? errorHandlerLabel = labelIdLineNumberPairs
189+
.Where(pair => resumeStmt.Start.Line > pair.Line)
190+
.OrderBy(pair => resumeStmt.Start.Line - pair.Line)
191+
.FirstOrDefault();
192+
193+
//Since the execution branch line for Resume and Resume Next statements
194+
//is indeterminant by static analysis, the On***GoTo statement
195+
//is used as the execution branch line
196+
if (errorHandlerLabel.HasValue && onErrorGotoStatements.ContainsKey(errorHandlerLabel.Value.IdentifierName))
197+
{
198+
executionBranchLine = onErrorGotoStatements[errorHandlerLabel.Value.IdentifierName];
199+
}
200+
}
201+
else
202+
{
203+
executionBranchLine = DetermineExecutionBranchLine(expression, labelIdLineNumberPairs);
204+
}
205+
206+
return executionBranchLine.HasValue
207+
? IsPotentiallyUsedAssignment(resultCandidate, executionBranchLine.Value)
208+
: false;
209+
}
210+
211+
private static bool IsPotentiallyUsedAssignment(IdentifierReference resultCandidate, int executionBranchLine)
212+
{
213+
if (resultCandidate.Context.Start.Line <= executionBranchLine) { return false; }
214+
215+
var exitStmtCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.ExitStmtContext>()
216+
.Where(exitCtxt => exitCtxt.Start.Line > executionBranchLine
217+
&& exitCtxt.EXIT_DO() == null
218+
&& exitCtxt.EXIT_FOR() == null);
219+
220+
var exitStmtCtxt = GetFirstContextAfterLine(exitStmtCtxts, executionBranchLine);
221+
222+
var nonAssignmentReferences = resultCandidate.Declaration.References
223+
.Where(rf => !rf.IsAssignment);
224+
225+
var possibleUse = exitStmtCtxt != null
226+
? nonAssignmentReferences.Where(rf => rf.Context.Start.Line >= executionBranchLine
227+
&& rf.Context.Start.Line < exitStmtCtxt.Start.Line)
228+
: nonAssignmentReferences.Where(rf => rf.Context.Start.Line >= executionBranchLine);
229+
230+
return possibleUse.Any();
231+
}
232+
233+
private static int DetermineExecutionBranchLine(string expression, IEnumerable<(string IdentifierName, int Line)> IDandLinePairs)
234+
{
235+
if (int.TryParse(expression, out var parsedLineNumber))
236+
{
237+
return parsedLineNumber;
238+
}
239+
(string label, int lineNumber) = IDandLinePairs.Where(v => v.IdentifierName.Equals(expression)).Single();
240+
return lineNumber;
241+
}
242+
243+
private static T GetFirstContextAfterLine<T>(IEnumerable<T> stmtContexts, int targetLine) where T : ParserRuleContext
244+
=> stmtContexts.Where(sc => sc.Start.Line > targetLine)
245+
.OrderBy(sc => sc.Start.Line - targetLine)
246+
.FirstOrDefault();
247+
111248
protected override string ResultDescription(IdentifierReference reference)
112249
{
113250
return Description;

0 commit comments

Comments
 (0)