From 521146ed5378d74d3a11ec248731ce58206823f5 Mon Sep 17 00:00:00 2001 From: Brian Zenger Date: Sun, 9 Aug 2020 15:09:53 -0700 Subject: [PATCH] Address PR comments Corrects GoTo LineNumber label handling. --- .../Concrete/AssignmentNotUsedInspection.cs | 113 +++++++++--------- .../AssignmentNotUsedInspectionTests.cs | 10 +- 2 files changed, 61 insertions(+), 62 deletions(-) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs index 999ef326c8..a944cf3f6d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs @@ -106,25 +106,28 @@ private static IEnumerable FindUnusedAssignmentReferences(D var tree = walker.GenerateTree(localVariable.ParentScopeDeclaration.Context, localVariable); var allAssignmentsAndReferences = tree.Nodes(new[] { typeof(AssignmentNode), typeof(ReferenceNode) }) - .Where(node => localVariable.References.Contains(node.Reference)); + .Where(node => localVariable.References.Contains(node.Reference)) + .ToList(); var unusedAssignmentNodes = allAssignmentsAndReferences.Any(n => n is ReferenceNode) ? FindUnusedAssignmentNodes(tree, localVariable, allAssignmentsAndReferences) : allAssignmentsAndReferences.OfType(); - return unusedAssignmentNodes.Except(FindDescendantsOfNeverFlagNodeTypes(unusedAssignmentNodes)) + return unusedAssignmentNodes.Where(n => !IsDescendentOfNeverFlagNode(n)) .Select(n => n.Reference); } private static IEnumerable FindUnusedAssignmentNodes(INode node, Declaration localVariable, IEnumerable allAssignmentsAndReferences) { var assignmentExprNodes = node.Nodes(new[] { typeof(AssignmentExpressionNode) }) - .Where(n => localVariable.References.Contains(n.Children.FirstOrDefault()?.Reference)); + .Where(n => localVariable.References.Contains(n.Children.FirstOrDefault()?.Reference)) + .ToList(); var usedAssignments = new List(); foreach (var refNode in allAssignmentsAndReferences.OfType().Reverse()) { - var assignmentExprNodesWithReference = assignmentExprNodes.Where(n => n.Nodes(new[] { typeof(ReferenceNode) }) + var assignmentExprNodesWithReference = assignmentExprNodes + .Where(n => n.Nodes(new[] { typeof(ReferenceNode) }) .Contains(refNode)); var assignmentsPrecedingReference = assignmentExprNodesWithReference.Any() @@ -144,30 +147,14 @@ private static IEnumerable FindUnusedAssignmentNodes(INode node, .Except(usedAssignments); } - private static IEnumerable FindDescendantsOfNeverFlagNodeTypes(IEnumerable flaggedAssignments) + private static bool IsDescendentOfNeverFlagNode(AssignmentNode assignment) { - var filteredResults = new List(); - - foreach (var assignment in flaggedAssignments) - { - if (assignment.TryGetAncestorNode(out _)) - { - filteredResults.Add(assignment); - } - if (assignment.TryGetAncestorNode(out _)) - { - filteredResults.Add(assignment); - } - } - return filteredResults; + return assignment.TryGetAncestorNode(out _) + || assignment.TryGetAncestorNode(out _); } private static bool IsAssignmentOfNothing(IdentifierReference reference) { - if (reference.Context.Parent is VBAParser.SetStmtContext setStmtContext2) - { - var test = setStmtContext2.expression(); - } return reference.IsSetAssignment && reference.Context.Parent is VBAParser.SetStmtContext setStmtContext && setStmtContext.expression().GetText().Equals(Tokens.Nothing); @@ -179,25 +166,25 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference) /// /// /// Filters Assignment references that meet the following conditions: - /// 1. Precedes a GoTo or Resume statement that branches execution to a line before the - /// assignment reference, and + /// 1. Reference precedes a GoTo or Resume statement that branches execution to a line before the + /// assignment reference, AND /// 2. A non-assignment reference is present on a line that is: - /// a) At or below the start of the execution branch, and + /// a) At or below the start of the execution branch, AND /// b) Above the next ExitStatement line (if one exists) or the end of the procedure /// private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate, DeclarationFinder finder) { if (!resultCandidate.Declaration.References.Any(rf => !rf.IsAssignment)) { return false; } - var labelIdLineNumberPairs = finder.DeclarationsWithType(DeclarationType.LineLabel) + var labelIdLineNumberPairs = finder.Members(resultCandidate.QualifiedModuleName, DeclarationType.LineLabel) .Where(label => resultCandidate.ParentScoping.Equals(label.ParentDeclaration)) - .Select(lbl => (lbl.IdentifierName, lbl.Context.Start.Line)); + .ToDictionary(key => key.IdentifierName, v => v.Context.Start.Line); return JumpStmtPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs) || JumpStmtPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs); } - private static bool JumpStmtPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs) where T : ParserRuleContext + private static bool JumpStmtPotentiallyUsesVariable(IdentifierReference resultCandidate, Dictionary labelIdLineNumberPairs) where T: ParserRuleContext { if (TryGetRelevantJumpContext(resultCandidate, out var jumpStmt)) { @@ -210,25 +197,27 @@ private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate private static bool TryGetRelevantJumpContext(IdentifierReference resultCandidate, out T ctxt) where T : ParserRuleContext { ctxt = resultCandidate.ParentScoping.Context.GetDescendents() - .Where(sc => sc.Start.Line > resultCandidate.Context.Start.Line - || (sc.Start.Line == resultCandidate.Context.Start.Line - && sc.Start.Column > resultCandidate.Context.Start.Column)) - .OrderBy(sc => sc.Start.Line - resultCandidate.Context.Start.Line) - .ThenBy(sc => sc.Start.Column - resultCandidate.Context.Start.Column) + .Where(descendent => descendent.GetSelection() > resultCandidate.Selection) + .OrderBy(descendent => descendent.GetSelection()) .FirstOrDefault(); return ctxt != null; } - private static bool IsPotentiallyUsedAssignment(T jumpContext, IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs) + private static bool IsPotentiallyUsedAssignment(T jumpContext, IdentifierReference resultCandidate, Dictionary labelIdLineNumberPairs) where T : ParserRuleContext { int? executionBranchLine = null; - if (jumpContext is VBAParser.GoToStmtContext gotoCtxt) - { - executionBranchLine = DetermineLabeledExecutionBranchLine(gotoCtxt.expression().GetText(), labelIdLineNumberPairs); - } - else + + switch (jumpContext) { - executionBranchLine = DetermineResumeStmtExecutionBranchLine(jumpContext as VBAParser.ResumeStmtContext, resultCandidate, labelIdLineNumberPairs); + case VBAParser.GoToStmtContext gotoStmt: + executionBranchLine = labelIdLineNumberPairs[gotoStmt.expression().GetText()]; + break; + case VBAParser.ResumeStmtContext resume: + executionBranchLine = DetermineResumeStmtExecutionBranchLine(resume, resultCandidate, labelIdLineNumberPairs); + break; + default: + executionBranchLine = null; + break; } return executionBranchLine.HasValue @@ -256,49 +245,57 @@ private static bool AssignmentIsUsedPriorToExitStmts(IdentifierReference resultC return !(sortedContextsAfterBranch.FirstOrDefault() is VBAParser.ExitStmtContext); } - private static int? DetermineResumeStmtExecutionBranchLine(VBAParser.ResumeStmtContext resumeStmt, IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs) + private static int? DetermineResumeStmtExecutionBranchLine(VBAParser.ResumeStmtContext resumeStmt, IdentifierReference resultCandidate, Dictionary labelIdLineNumberPairs) { var onErrorGotoLabelToLineNumber = resultCandidate.ParentScoping.Context.GetDescendents() - .Where(errorStmtCtxt => !errorStmtCtxt.expression().GetText().Equals("0")) + .Where(errorStmtCtxt => IsBranchingOnErrorGoToLabel(errorStmtCtxt)) .ToDictionary(k => k.expression()?.GetText() ?? "No Label", v => v.Start.Line); var errorHandlerLabelsAndLines = labelIdLineNumberPairs - .Where(pair => onErrorGotoLabelToLineNumber.ContainsKey(pair.IdentifierName)); + .Where(pair => onErrorGotoLabelToLineNumber.ContainsKey(pair.Key)); //Labels must be located at the start of a line. //If the resultCandidate line precedes all error handling related labels, //a Resume statement cannot be invoked (successfully) for the resultCandidate - if (!errorHandlerLabelsAndLines.Any(s => s.Line <= resultCandidate.Context.Start.Line)) + if (!errorHandlerLabelsAndLines.Any(kvp => kvp.Value <= resultCandidate.Context.Start.Line)) { return null; } - var expression = resumeStmt.expression()?.GetText(); + var resumeStmtExpression = resumeStmt.expression()?.GetText(); //For Resume and Resume Next, expression() is null - if (string.IsNullOrEmpty(expression)) + if (string.IsNullOrEmpty(resumeStmtExpression)) { - //Get errorHandlerLabel for the Resume statement - string errorHandlerLabel = errorHandlerLabelsAndLines - .Where(pair => resumeStmt.Start.Line >= pair.Line) - .OrderBy(pair => resumeStmt.Start.Line - pair.Line) - .Select(pair => pair.IdentifierName) + var errorHandlerLabelForTheResumeStatement = errorHandlerLabelsAndLines + .Where(kvp => resumeStmt.Start.Line >= kvp.Value) + .OrderBy(kvp => resumeStmt.Start.Line - kvp.Value) + .Select(kvp => kvp.Key) .FirstOrDefault(); //Since the execution branch line for Resume and Resume Next statements //is indeterminant by static analysis, the On***GoTo statement //is used as the execution branch line - return onErrorGotoLabelToLineNumber[errorHandlerLabel]; + return onErrorGotoLabelToLineNumber[errorHandlerLabelForTheResumeStatement]; } //Resume