Skip to content

Commit

Permalink
Merge branch 'rubberduck-vba/next' into ConflictDetectionSession
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Jul 11, 2020
2 parents 392fea1 + e498d95 commit 8db77b7
Show file tree
Hide file tree
Showing 290 changed files with 11,074 additions and 1,549 deletions.
@@ -1,10 +1,12 @@
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Inspections.CodePathAnalysis;
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
using Rubberduck.Inspections.CodePathAnalysis.Nodes;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
Expand Down Expand Up @@ -67,7 +69,7 @@ private IEnumerable<IdentifierReference> UnusedAssignments(Declaration localVari
return UnusedAssignmentReferences(tree);
}

public static List<IdentifierReference> UnusedAssignmentReferences(INode node)
private static List<IdentifierReference> UnusedAssignmentReferences(INode node)
{
var nodes = new List<IdentifierReference>();

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

protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
return !IsAssignmentOfNothing(reference);
return !(IsAssignmentOfNothing(reference)
|| IsPotentiallyUsedViaJump(reference, finder));
}

private static bool IsAssignmentOfNothing(IdentifierReference reference)
Expand All @@ -108,6 +111,142 @@ private static bool IsAssignmentOfNothing(IdentifierReference reference)
&& setStmtContext.expression().GetText().Equals(Tokens.Nothing);
}

/// <summary>
/// Filters false positive result references due to GoTo and Resume statements. e.g.,
/// An ErrorHandler block that branches execution to a location where the asignment may be used.
/// </summary>
/// <remarks>
/// 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
/// 2. A non-assignment reference is present on a line that is:
/// 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
/// </remarks>
private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate, DeclarationFinder finder)
{
if (!resultCandidate.Declaration.References.Any(rf => !rf.IsAssignment)) { return false; }

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

return GotoPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs)
|| ResumePotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
}

private static bool GotoPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs)
{
if (TryGetRelevantJumpContext<VBAParser.GoToStmtContext>(resultCandidate, out var gotoStmt))
{
return IsPotentiallyUsedAssignment(gotoStmt, resultCandidate, labelIdLineNumberPairs);
}

return false;
}

private static bool ResumePotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs)
{
if (TryGetRelevantJumpContext<VBAParser.ResumeStmtContext>(resultCandidate, out var resumeStmt))
{
return IsPotentiallyUsedAssignment(resumeStmt, resultCandidate, labelIdLineNumberPairs);
}

return false;
}

private static bool TryGetRelevantJumpContext<T>(IdentifierReference resultCandidate, out T ctxt) where T : ParserRuleContext //, IEnumerable<T> stmtContexts, int targetLine, int? targetColumn = null) where T : ParserRuleContext
{
ctxt = resultCandidate.ParentScoping.Context.GetDescendents<T>()
.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)
.FirstOrDefault();
return ctxt != null;
}

private static bool IsPotentiallyUsedAssignment<T>(T jumpContext, IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs) //, int executionBranchLine)
{
int? executionBranchLine = null;
if (jumpContext is VBAParser.GoToStmtContext gotoCtxt)
{
executionBranchLine = DetermineLabeledExecutionBranchLine(gotoCtxt.expression().GetText(), labelIdLineNumberPairs);
}
else
{
executionBranchLine = DetermineResumeStmtExecutionBranchLine(jumpContext as VBAParser.ResumeStmtContext, resultCandidate, labelIdLineNumberPairs);
}

return executionBranchLine.HasValue
? AssignmentIsUsedPriorToExitStmts(resultCandidate, executionBranchLine.Value)
: false;
}

private static bool AssignmentIsUsedPriorToExitStmts(IdentifierReference resultCandidate, int executionBranchLine)
{
if (resultCandidate.Context.Start.Line < executionBranchLine) { return false; }

var procedureExitStmtCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.ExitStmtContext>()
.Where(exitCtxt => exitCtxt.EXIT_DO() == null
&& exitCtxt.EXIT_FOR() == null);

var nonAssignmentCtxts = resultCandidate.Declaration.References
.Where(rf => !rf.IsAssignment)
.Select(rf => rf.Context);

var sortedContextsAfterBranch = nonAssignmentCtxts.Concat(procedureExitStmtCtxts)
.Where(ctxt => ctxt.Start.Line >= executionBranchLine)
.OrderBy(ctxt => ctxt.Start.Line)
.ThenBy(ctxt => ctxt.Start.Column);

return !(sortedContextsAfterBranch.FirstOrDefault() is VBAParser.ExitStmtContext);
}

private static int? DetermineResumeStmtExecutionBranchLine(VBAParser.ResumeStmtContext resumeStmt, IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs) //where T: ParserRuleContext
{
var onErrorGotoLabelToLineNumber = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.OnErrorStmtContext>()
.Where(errorStmtCtxt => !errorStmtCtxt.expression().GetText().Equals("0"))
.ToDictionary(k => k.expression()?.GetText() ?? "No Label", v => v.Start.Line);

var errorHandlerLabelsAndLines = labelIdLineNumberPairs
.Where(pair => onErrorGotoLabelToLineNumber.ContainsKey(pair.IdentifierName));

//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))
{
return null;
}

var expression = resumeStmt.expression()?.GetText();

//For Resume and Resume Next, expression() is null
if (string.IsNullOrEmpty(expression))
{
//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)
.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];
}
//Resume <label>
return DetermineLabeledExecutionBranchLine(expression, labelIdLineNumberPairs);
}

private static int DetermineLabeledExecutionBranchLine(string expression, IEnumerable<(string IdentifierName, int Line)> IDandLinePairs)
=> int.TryParse(expression, out var parsedLineNumber)
? parsedLineNumber
: IDandLinePairs.Single(v => v.IdentifierName.Equals(expression)).Line;

protected override string ResultDescription(IdentifierReference reference)
{
return Description;
Expand Down
Expand Up @@ -53,11 +53,12 @@ public FunctionReturnValueDiscardedInspection(IDeclarationFinderProvider declara
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
return reference?.Declaration != null
&& !reference.IsAssignment
&& !reference.IsArrayAccess
&& !reference.IsInnerRecursiveDefaultMemberAccess
&& reference.Declaration.DeclarationType == DeclarationType.Function
&& IsCalledAsProcedure(reference.Context);
&& reference.Declaration.IsUserDefined
&& !reference.IsAssignment
&& !reference.IsArrayAccess
&& !reference.IsInnerRecursiveDefaultMemberAccess
&& reference.Declaration.DeclarationType == DeclarationType.Function
&& IsCalledAsProcedure(reference.Context);
}

private static bool IsCalledAsProcedure(ParserRuleContext context)
Expand Down
@@ -1,3 +1,4 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
Expand All @@ -14,32 +15,92 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// </summary>
/// <why>
/// Unused procedures are dead code that should probably be removed. Note, a procedure may be effectively "not used" in code, but attached to some
/// Shape object in the host document: in such cases the inspection result should be ignored. An event handler procedure that isn't being
/// resolved as such, may also wrongly trigger this inspection.
/// Shape object in the host document: in such cases the inspection result should be ignored.
/// </why>
/// <remarks>
/// Not all unused procedures can/should be removed: ignore any inspection results for
/// event handler procedures and interface members that Rubberduck isn't recognizing as such.
/// Public procedures of Standard Modules are not flagged by this inspection regardless of
/// the presence or absence of user code references.
/// </remarks>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// ' macro is attached to a worksheet Shape.
/// Private Sub DoSomething()
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
///
/// '@Ignore ProcedureNotUsed
/// Private Sub DoSomething()
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="Macros" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// 'a public procedure in a standard module may be a macro
/// 'attached to a worksheet Shape or invoked by means other than user code.
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="true">
/// <module name="Class1" type="Class Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// End Sub
///
/// Public Sub DoSomethingElse()
/// End Sub
/// ]]>
/// </module>
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub ReferenceOneClass1Procedure()
/// Dim target As Class1
/// Set target = new Class1
/// target.DoSomething
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="Class1" type="Class Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// ' macro is attached to a worksheet Shape.
/// End Sub
///
/// Public Sub DoSomethingElse()
/// End Sub
/// ]]>
/// </module>
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub ReferenceAllClass1Procedures()
/// Dim target As Class1
/// Set target = new Class1
/// target.DoSomething
/// target.DoSomethingElse
/// End Sub
/// ]]>
/// </module>
Expand Down Expand Up @@ -78,8 +139,7 @@ public ProcedureNotUsedInspection(IDeclarationFinderProvider declarationFinderPr
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
return !declaration.References
.Any(reference => !reference.IsAssignment
&& !reference.ParentScoping.Equals(declaration)) // recursive calls don't count
.Any(reference => !reference.ParentScoping.Equals(declaration)) // ignore recursive/self-referential calls
&& !finder.FindEventHandlers().Contains(declaration)
&& !IsPublicModuleMember(declaration)
&& !IsClassLifeCycleHandler(declaration)
Expand Down
Expand Up @@ -4,8 +4,9 @@

namespace Rubberduck.CodeAnalysis.Inspections.Extensions
{
internal static class DeclarationTypeExtensions
public static class DeclarationTypeExtensions
{
//ToDo: Move this to resources. (This will require moving resource lookups to Core.)
public static string ToLocalizedString(this DeclarationType type)
{
return RubberduckUI.ResourceManager.GetString("DeclarationType_" + type, CultureInfo.CurrentUICulture);
Expand Down

0 comments on commit 8db77b7

Please sign in to comment.