Skip to content

Commit dc812cf

Browse files
committed
Merge branch '5456_AssignNotUsed_Jumps' into UnusedAssignment_FalsePositives
2 parents 3d4a5cb + c8e9543 commit dc812cf

File tree

2 files changed

+478
-2
lines changed

2 files changed

+478
-2
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 140 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Collections.Generic;
22
using System.IO;
33
using System.Linq;
4+
using Antlr4.Runtime;
45
using Rubberduck.CodeAnalysis.Inspections.Abstract;
56
using Rubberduck.CodeAnalysis.Inspections.Extensions;
67
using Rubberduck.Inspections.CodePathAnalysis;
@@ -79,7 +80,7 @@ private IEnumerable<IdentifierReference> UnusedAssignments(Declaration localVari
7980
return UnusedAssignmentReferences(tree);
8081
}
8182

82-
public static List<IdentifierReference> UnusedAssignmentReferences(INode node)
83+
private static List<IdentifierReference> UnusedAssignmentReferences(INode node)
8384
{
8485
var nodes = new List<IdentifierReference>();
8586

@@ -298,7 +299,8 @@ private static bool TryFindAssigmentUsedBySubsequentAssignment(ReferenceNode ref
298299

299300
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
300301
{
301-
return !IsAssignmentOfNothing(reference);
302+
return !(IsAssignmentOfNothing(reference)
303+
|| IsPotentiallyUsedViaJump(reference, finder));
302304
}
303305

304306
private static bool IsAssignmentOfNothing(IdentifierReference reference)
@@ -308,6 +310,142 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
308310
&& setStmtContext.expression().GetText().Equals(Tokens.Nothing);
309311
}
310312

313+
/// <summary>
314+
/// Filters false positive result references due to GoTo and Resume statements. e.g.,
315+
/// An ErrorHandler block that branches execution to a location where the asignment may be used.
316+
/// </summary>
317+
/// <remarks>
318+
/// Filters Assignment references that meet the following conditions:
319+
/// 1. Precedes a GoTo or Resume statement that branches execution to a line before the
320+
/// assignment reference, and
321+
/// 2. A non-assignment reference is present on a line that is:
322+
/// a) At or below the start of the execution branch, and
323+
/// b) Above the next ExitStatement line (if one exists) or the end of the procedure
324+
/// </remarks>
325+
private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate, DeclarationFinder finder)
326+
{
327+
if (!resultCandidate.Declaration.References.Any(rf => !rf.IsAssignment)) { return false; }
328+
329+
var labelIdLineNumberPairs = finder.DeclarationsWithType(DeclarationType.LineLabel)
330+
.Where(label => resultCandidate.ParentScoping.Equals(label.ParentDeclaration))
331+
.Select(lbl => (lbl.IdentifierName, lbl.Context.Start.Line));
332+
333+
return GotoPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs)
334+
|| ResumePotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
335+
}
336+
337+
private static bool GotoPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs)
338+
{
339+
if (TryGetRelevantJumpContext<VBAParser.GoToStmtContext>(resultCandidate, out var gotoStmt))
340+
{
341+
return IsPotentiallyUsedAssignment(gotoStmt, resultCandidate, labelIdLineNumberPairs);
342+
}
343+
344+
return false;
345+
}
346+
347+
private static bool ResumePotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs)
348+
{
349+
if (TryGetRelevantJumpContext<VBAParser.ResumeStmtContext>(resultCandidate, out var resumeStmt))
350+
{
351+
return IsPotentiallyUsedAssignment(resumeStmt, resultCandidate, labelIdLineNumberPairs);
352+
}
353+
354+
return false;
355+
}
356+
357+
private static bool TryGetRelevantJumpContext<T>(IdentifierReference resultCandidate, out T ctxt) where T : ParserRuleContext //, IEnumerable<T> stmtContexts, int targetLine, int? targetColumn = null) where T : ParserRuleContext
358+
{
359+
ctxt = resultCandidate.ParentScoping.Context.GetDescendents<T>()
360+
.Where(sc => sc.Start.Line > resultCandidate.Context.Start.Line
361+
|| (sc.Start.Line == resultCandidate.Context.Start.Line
362+
&& sc.Start.Column > resultCandidate.Context.Start.Column))
363+
.OrderBy(sc => sc.Start.Line - resultCandidate.Context.Start.Line)
364+
.ThenBy(sc => sc.Start.Column - resultCandidate.Context.Start.Column)
365+
.FirstOrDefault();
366+
return ctxt != null;
367+
}
368+
369+
private static bool IsPotentiallyUsedAssignment<T>(T jumpContext, IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs) //, int executionBranchLine)
370+
{
371+
int? executionBranchLine = null;
372+
if (jumpContext is VBAParser.GoToStmtContext gotoCtxt)
373+
{
374+
executionBranchLine = DetermineLabeledExecutionBranchLine(gotoCtxt.expression().GetText(), labelIdLineNumberPairs);
375+
}
376+
else
377+
{
378+
executionBranchLine = DetermineResumeStmtExecutionBranchLine(jumpContext as VBAParser.ResumeStmtContext, resultCandidate, labelIdLineNumberPairs);
379+
}
380+
381+
return executionBranchLine.HasValue
382+
? AssignmentIsUsedPriorToExitStmts(resultCandidate, executionBranchLine.Value)
383+
: false;
384+
}
385+
386+
private static bool AssignmentIsUsedPriorToExitStmts(IdentifierReference resultCandidate, int executionBranchLine)
387+
{
388+
if (resultCandidate.Context.Start.Line < executionBranchLine) { return false; }
389+
390+
var procedureExitStmtCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.ExitStmtContext>()
391+
.Where(exitCtxt => exitCtxt.EXIT_DO() == null
392+
&& exitCtxt.EXIT_FOR() == null);
393+
394+
var nonAssignmentCtxts = resultCandidate.Declaration.References
395+
.Where(rf => !rf.IsAssignment)
396+
.Select(rf => rf.Context);
397+
398+
var sortedContextsAfterBranch = nonAssignmentCtxts.Concat(procedureExitStmtCtxts)
399+
.Where(ctxt => ctxt.Start.Line >= executionBranchLine)
400+
.OrderBy(ctxt => ctxt.Start.Line)
401+
.ThenBy(ctxt => ctxt.Start.Column);
402+
403+
return !(sortedContextsAfterBranch.FirstOrDefault() is VBAParser.ExitStmtContext);
404+
}
405+
406+
private static int? DetermineResumeStmtExecutionBranchLine(VBAParser.ResumeStmtContext resumeStmt, IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs) //where T: ParserRuleContext
407+
{
408+
var onErrorGotoLabelToLineNumber = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.OnErrorStmtContext>()
409+
.Where(errorStmtCtxt => !errorStmtCtxt.expression().GetText().Equals("0"))
410+
.ToDictionary(k => k.expression()?.GetText() ?? "No Label", v => v.Start.Line);
411+
412+
var errorHandlerLabelsAndLines = labelIdLineNumberPairs
413+
.Where(pair => onErrorGotoLabelToLineNumber.ContainsKey(pair.IdentifierName));
414+
415+
//Labels must be located at the start of a line.
416+
//If the resultCandidate line precedes all error handling related labels,
417+
//a Resume statement cannot be invoked (successfully) for the resultCandidate
418+
if (!errorHandlerLabelsAndLines.Any(s => s.Line <= resultCandidate.Context.Start.Line))
419+
{
420+
return null;
421+
}
422+
423+
var expression = resumeStmt.expression()?.GetText();
424+
425+
//For Resume and Resume Next, expression() is null
426+
if (string.IsNullOrEmpty(expression))
427+
{
428+
//Get errorHandlerLabel for the Resume statement
429+
string errorHandlerLabel = errorHandlerLabelsAndLines
430+
.Where(pair => resumeStmt.Start.Line >= pair.Line)
431+
.OrderBy(pair => resumeStmt.Start.Line - pair.Line)
432+
.Select(pair => pair.IdentifierName)
433+
.FirstOrDefault();
434+
435+
//Since the execution branch line for Resume and Resume Next statements
436+
//is indeterminant by static analysis, the On***GoTo statement
437+
//is used as the execution branch line
438+
return onErrorGotoLabelToLineNumber[errorHandlerLabel];
439+
}
440+
//Resume <label>
441+
return DetermineLabeledExecutionBranchLine(expression, labelIdLineNumberPairs);
442+
}
443+
444+
private static int DetermineLabeledExecutionBranchLine(string expression, IEnumerable<(string IdentifierName, int Line)> IDandLinePairs)
445+
=> int.TryParse(expression, out var parsedLineNumber)
446+
? parsedLineNumber
447+
: IDandLinePairs.Single(v => v.IdentifierName.Equals(expression)).Line;
448+
311449
protected override string ResultDescription(IdentifierReference reference)
312450
{
313451
return Description;

0 commit comments

Comments
 (0)