Skip to content

Commit c8e9543

Browse files
committed
Support same-line statements and jumps
Evaluate content where ":" is used to places labels, statements, and jump statements on the same line.
1 parent 00f6ecb commit c8e9543

File tree

2 files changed

+170
-92
lines changed

2 files changed

+170
-92
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 85 additions & 83 deletions
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ private static List<IdentifierReference> UnusedAssignmentReferences(INode node)
101101
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
102102
{
103103
return !(IsAssignmentOfNothing(reference)
104-
|| IsPotentiallyUsedViaResumeOrGoToExecutionBranch(reference, finder));
104+
|| IsPotentiallyUsedViaJump(reference, finder));
105105
}
106106

107107
private static bool IsAssignmentOfNothing(IdentifierReference reference)
@@ -116,134 +116,136 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
116116
/// An ErrorHandler block that branches execution to a location where the asignment may be used.
117117
/// </summary>
118118
/// <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
119+
/// Filters Assignment references that meet the following conditions:
120+
/// 1. Precedes a GoTo or Resume statement that branches execution to a line before the
121121
/// assignment reference, and
122122
/// 2. A non-assignment reference is present on a line that is:
123123
/// a) At or below the start of the execution branch, and
124124
/// b) Above the next ExitStatement line (if one exists) or the end of the procedure
125125
/// </remarks>
126-
/// <param name="resultCandidate"></param>
127-
/// <param name="finder"></param>
128-
/// <returns></returns>
129-
private static bool IsPotentiallyUsedViaResumeOrGoToExecutionBranch(IdentifierReference resultCandidate, DeclarationFinder finder)
126+
private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate, DeclarationFinder finder)
130127
{
131128
if (!resultCandidate.Declaration.References.Any(rf => !rf.IsAssignment)) { return false; }
132129

133130
var labelIdLineNumberPairs = finder.DeclarationsWithType(DeclarationType.LineLabel)
134131
.Where(label => resultCandidate.ParentScoping.Equals(label.ParentDeclaration))
135132
.Select(lbl => (lbl.IdentifierName, lbl.Context.Start.Line));
136133

137-
return GotoExecutionBranchPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs)
138-
|| ResumeExecutionBranchPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
134+
return GotoPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs)
135+
|| ResumePotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
139136
}
140137

141-
private static bool GotoExecutionBranchPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs)
138+
private static bool GotoPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs)
142139
{
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);
140+
if (TryGetRelevantJumpContext<VBAParser.GoToStmtContext>(resultCandidate, out var gotoStmt))
141+
{
142+
return IsPotentiallyUsedAssignment(gotoStmt, resultCandidate, labelIdLineNumberPairs);
143+
}
153144

154-
return IsPotentiallyUsedAssignment(resultCandidate, executionBranchLine);
145+
return false;
155146
}
156147

157-
private static bool ResumeExecutionBranchPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs)
148+
private static bool ResumePotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs)
158149
{
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))
150+
if (TryGetRelevantJumpContext<VBAParser.ResumeStmtContext>(resultCandidate, out var resumeStmt))
172151
{
173-
return false;
152+
return IsPotentiallyUsedAssignment(resumeStmt, resultCandidate, labelIdLineNumberPairs);
174153
}
175154

176-
var resumeStmt = GetFirstContextAfterLine(resumeStmtCtxts, resultCandidate.Context.Start.Line);
155+
return false;
156+
}
177157

178-
if (resumeStmt == null) { return false; }
158+
private static bool TryGetRelevantJumpContext<T>(IdentifierReference resultCandidate, out T ctxt) where T : ParserRuleContext //, IEnumerable<T> stmtContexts, int targetLine, int? targetColumn = null) where T : ParserRuleContext
159+
{
160+
ctxt = resultCandidate.ParentScoping.Context.GetDescendents<T>()
161+
.Where(sc => sc.Start.Line > resultCandidate.Context.Start.Line
162+
|| (sc.Start.Line == resultCandidate.Context.Start.Line
163+
&& sc.Start.Column > resultCandidate.Context.Start.Column))
164+
.OrderBy(sc => sc.Start.Line - resultCandidate.Context.Start.Line)
165+
.ThenBy(sc => sc.Start.Column - resultCandidate.Context.Start.Column)
166+
.FirstOrDefault();
167+
return ctxt != null;
168+
}
179169

170+
private static bool IsPotentiallyUsedAssignment<T>(T jumpContext, IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs) //, int executionBranchLine)
171+
{
180172
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))
173+
if (jumpContext is VBAParser.GoToStmtContext gotoCtxt)
186174
{
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-
}
175+
executionBranchLine = DetermineLabeledExecutionBranchLine(gotoCtxt.expression().GetText(), labelIdLineNumberPairs);
200176
}
201177
else
202178
{
203-
executionBranchLine = DetermineExecutionBranchLine(expression, labelIdLineNumberPairs);
179+
executionBranchLine = DetermineResumeStmtExecutionBranchLine(jumpContext as VBAParser.ResumeStmtContext, resultCandidate, labelIdLineNumberPairs);
204180
}
205181

206182
return executionBranchLine.HasValue
207-
? IsPotentiallyUsedAssignment(resultCandidate, executionBranchLine.Value)
208-
: false;
183+
? AssignmentIsUsedPriorToExitStmts(resultCandidate, executionBranchLine.Value)
184+
: false;
209185
}
210186

211-
private static bool IsPotentiallyUsedAssignment(IdentifierReference resultCandidate, int executionBranchLine)
187+
private static bool AssignmentIsUsedPriorToExitStmts(IdentifierReference resultCandidate, int executionBranchLine)
212188
{
213-
if (resultCandidate.Context.Start.Line <= executionBranchLine) { return false; }
189+
if (resultCandidate.Context.Start.Line < executionBranchLine) { return false; }
214190

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);
191+
var procedureExitStmtCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.ExitStmtContext>()
192+
.Where(exitCtxt => exitCtxt.EXIT_DO() == null
193+
&& exitCtxt.EXIT_FOR() == null);
219194

220-
var exitStmtCtxt = GetFirstContextAfterLine(exitStmtCtxts, executionBranchLine);
195+
var nonAssignmentCtxts = resultCandidate.Declaration.References
196+
.Where(rf => !rf.IsAssignment)
197+
.Select(rf => rf.Context);
221198

222-
var nonAssignmentReferences = resultCandidate.Declaration.References
223-
.Where(rf => !rf.IsAssignment);
199+
var sortedContextsAfterBranch = nonAssignmentCtxts.Concat(procedureExitStmtCtxts)
200+
.Where(ctxt => ctxt.Start.Line >= executionBranchLine)
201+
.OrderBy(ctxt => ctxt.Start.Line)
202+
.ThenBy(ctxt => ctxt.Start.Column);
224203

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();
204+
return !(sortedContextsAfterBranch.FirstOrDefault() is VBAParser.ExitStmtContext);
231205
}
232206

233-
private static int DetermineExecutionBranchLine(string expression, IEnumerable<(string IdentifierName, int Line)> IDandLinePairs)
207+
private static int? DetermineResumeStmtExecutionBranchLine(VBAParser.ResumeStmtContext resumeStmt, IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs) //where T: ParserRuleContext
234208
{
235-
if (int.TryParse(expression, out var parsedLineNumber))
209+
var onErrorGotoLabelToLineNumber = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.OnErrorStmtContext>()
210+
.Where(errorStmtCtxt => !errorStmtCtxt.expression().GetText().Equals("0"))
211+
.ToDictionary(k => k.expression()?.GetText() ?? "No Label", v => v.Start.Line);
212+
213+
var errorHandlerLabelsAndLines = labelIdLineNumberPairs
214+
.Where(pair => onErrorGotoLabelToLineNumber.ContainsKey(pair.IdentifierName));
215+
216+
//Labels must be located at the start of a line.
217+
//If the resultCandidate line precedes all error handling related labels,
218+
//a Resume statement cannot be invoked (successfully) for the resultCandidate
219+
if (!errorHandlerLabelsAndLines.Any(s => s.Line <= resultCandidate.Context.Start.Line))
236220
{
237-
return parsedLineNumber;
221+
return null;
222+
}
223+
224+
var expression = resumeStmt.expression()?.GetText();
225+
226+
//For Resume and Resume Next, expression() is null
227+
if (string.IsNullOrEmpty(expression))
228+
{
229+
//Get errorHandlerLabel for the Resume statement
230+
string errorHandlerLabel = errorHandlerLabelsAndLines
231+
.Where(pair => resumeStmt.Start.Line >= pair.Line)
232+
.OrderBy(pair => resumeStmt.Start.Line - pair.Line)
233+
.Select(pair => pair.IdentifierName)
234+
.FirstOrDefault();
235+
236+
//Since the execution branch line for Resume and Resume Next statements
237+
//is indeterminant by static analysis, the On***GoTo statement
238+
//is used as the execution branch line
239+
return onErrorGotoLabelToLineNumber[errorHandlerLabel];
238240
}
239-
(string label, int lineNumber) = IDandLinePairs.Where(v => v.IdentifierName.Equals(expression)).Single();
240-
return lineNumber;
241+
//Resume <label>
242+
return DetermineLabeledExecutionBranchLine(expression, labelIdLineNumberPairs);
241243
}
242244

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();
245+
private static int DetermineLabeledExecutionBranchLine(string expression, IEnumerable<(string IdentifierName, int Line)> IDandLinePairs)
246+
=> int.TryParse(expression, out var parsedLineNumber)
247+
? parsedLineNumber
248+
: IDandLinePairs.Single(v => v.IdentifierName.Equals(expression)).Line;
247249

248250
protected override string ResultDescription(IdentifierReference reference)
249251
{

RubberduckTests/Inspections/AssignmentNotUsedInspectionTests.cs

Lines changed: 85 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -262,7 +262,9 @@ Dim foo As Long
262262
//https://github.com/rubberduck-vba/Rubberduck/issues/5456
263263
[TestCase("Resume CleanExit")]
264264
[TestCase("GoTo CleanExit")]
265-
public void IgnoresAssignmentWhereExecutionPathModifiedByJumpStatementCouldIncludeUse_Labels(string statement)
265+
[TestCase("Resume 8")] //Inverse = ratio
266+
[TestCase("GoTo 8")] //Inverse = ratio
267+
public void IgnoresAssignmentWhereUsedByJumpStatement(string statement)
266268
{
267269
string code =
268270
$@"
@@ -275,18 +277,20 @@ On Error Goto ErrorHandler
275277
Inverse = ratio
276278
Exit Function
277279
ErrorHandler:
278-
ratio = -1# 'assigment not used evaluation disqualified by Resume/GoTo - not flagged
280+
'assigment not used evaluation disqualified by Resume/GoTo - not flagged
281+
ratio = -1#
279282
{statement}
280283
End Function
281284
";
282285
var results = InspectionResultsForStandardModule(code);
283286
Assert.AreEqual(1, results.Count());
284287
}
285288

286-
//Inverse = ratio => line 7
287-
[TestCase("Resume 7")]
288-
[TestCase("GoTo 7")]
289-
public void IgnoresAssignmentWhereExecutionPathModifiedByJumpStatementCouldIncludeUse_LineNumbers(string statement)
289+
[TestCase("Resume CleanExit")]
290+
[TestCase("GoTo CleanExit")]
291+
[TestCase("Resume 8")] //Inverse = ratio
292+
[TestCase("GoTo 8")] //Inverse = ratio
293+
public void IgnoresAssignmentWhereUsedByJumpStatement_JumpOnSameLineAsAssignment(string statement)
290294
{
291295
string code =
292296
$@"
@@ -295,18 +299,71 @@ Dim ratio As Double
295299
ratio = 0# 'assigment not used - flagged
296300
On Error Goto ErrorHandler
297301
ratio = 1# / value
302+
CleanExit:
298303
Inverse = ratio
299304
Exit Function
300-
301305
ErrorHandler:
302-
ratio = -1# 'assigment not used evaluation disqualified by Resume/GoTo - not flagged
303-
{statement}
306+
'assigment not used evaluation disqualified by Resume/GoTo - not flagged
307+
ratio = -1#: {statement}
304308
End Function
305309
";
306310
var results = InspectionResultsForStandardModule(code);
307311
Assert.AreEqual(1, results.Count());
308312
}
309313

314+
[TestCase("GoTo")]
315+
[TestCase("Resume")]
316+
public void MultipleSingleLineJumpStmts(string jumpStatement)
317+
{
318+
string code =
319+
$@"
320+
Public Function Fizz(value As Double) As Double
321+
Dim firstVal As Double
322+
Dim anotherVal As Double
323+
Dim yetAnotherVal As Double
324+
On Error GoTo ErrorHandler
325+
Fizz = 1# / value
326+
Exit Function
327+
Exit1:
328+
Fizz = anotherVal
329+
Exit Function
330+
Exit2:
331+
Fizz = firstVal
332+
Exit Function
333+
Exit3:
334+
Fizz = yetAnotherVal
335+
Exit Function
336+
ErrorHandler:
337+
anotherVal = 6#: {jumpStatement} Exit1: firstVal = -1#: {jumpStatement} Exit2: yetAnotherVal = -99#: {jumpStatement} Exit3
338+
End Function
339+
";
340+
var results = InspectionResultsForStandardModule(code);
341+
Assert.AreEqual(0, results.Count());
342+
}
343+
344+
345+
[TestCase("Exit Function: Fizz = firstVal: Exit Function", 1)] //value not read
346+
[TestCase("Fizz = firstVal: Exit Function", 0)] //value is read
347+
public void ExitStmtOnSameLineAsNonAssignments(string exitFunctionLine, int expected)
348+
{
349+
string code =
350+
$@"
351+
Public Function Fizz(value As Double) As Double
352+
Dim firstVal As Double
353+
On Error GoTo ErrorHandler
354+
Fizz = 1# / value
355+
Exit Function
356+
Exit1:
357+
Fizz = 0#
358+
{exitFunctionLine}
359+
ErrorHandler:
360+
firstVal = -1#: GoTo Exit1
361+
End Function
362+
";
363+
var results = InspectionResultsForStandardModule(code);
364+
Assert.AreEqual(expected, results.Count());
365+
}
366+
310367
[Test]
311368
public void IgnoresExitForStmt()
312369
{
@@ -485,6 +542,25 @@ End Function
485542
Assert.AreEqual(1, results.Count());
486543
}
487544

545+
546+
[Test]
547+
public void ResumeStmt_OnSameLineAsLabel()
548+
{
549+
string code =
550+
$@"
551+
Public Function Inverse(value As Double) As Double
552+
Dim ratio As Double
553+
On Error GoTo ErrorHandler:
554+
ratio = 1# / value
555+
Inverse = ratio
556+
Exit Function
557+
ErrorHandler: ratio = 0#: Resume Next
558+
End Function
559+
";
560+
var results = InspectionResultsForStandardModule(code);
561+
Assert.AreEqual(0, results.Count());
562+
}
563+
488564
[Test]
489565
[TestCase("Resume Next", true, 2)]
490566
[TestCase("Resume", true, 2)]

0 commit comments

Comments
 (0)