Skip to content

Commit 4b01a60

Browse files
committed
Merge branch 'next' into SuppressHorizontalBringIntoViewInGroupinGrids
2 parents fc8e27b + 669c4d8 commit 4b01a60

File tree

10 files changed

+714
-157
lines changed

10 files changed

+714
-157
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 141 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+
|| IsPotentiallyUsedViaJump(reference, finder));
102105
}
103106

104107
private static bool IsAssignmentOfNothing(IdentifierReference reference)
@@ -108,6 +111,142 @@ 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+
/// Filters Assignment references that meet the following conditions:
120+
/// 1. Precedes 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+
private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate, DeclarationFinder finder)
127+
{
128+
if (!resultCandidate.Declaration.References.Any(rf => !rf.IsAssignment)) { return false; }
129+
130+
var labelIdLineNumberPairs = finder.DeclarationsWithType(DeclarationType.LineLabel)
131+
.Where(label => resultCandidate.ParentScoping.Equals(label.ParentDeclaration))
132+
.Select(lbl => (lbl.IdentifierName, lbl.Context.Start.Line));
133+
134+
return GotoPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs)
135+
|| ResumePotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
136+
}
137+
138+
private static bool GotoPotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs)
139+
{
140+
if (TryGetRelevantJumpContext<VBAParser.GoToStmtContext>(resultCandidate, out var gotoStmt))
141+
{
142+
return IsPotentiallyUsedAssignment(gotoStmt, resultCandidate, labelIdLineNumberPairs);
143+
}
144+
145+
return false;
146+
}
147+
148+
private static bool ResumePotentiallyUsesVariable(IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs)
149+
{
150+
if (TryGetRelevantJumpContext<VBAParser.ResumeStmtContext>(resultCandidate, out var resumeStmt))
151+
{
152+
return IsPotentiallyUsedAssignment(resumeStmt, resultCandidate, labelIdLineNumberPairs);
153+
}
154+
155+
return false;
156+
}
157+
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+
}
169+
170+
private static bool IsPotentiallyUsedAssignment<T>(T jumpContext, IdentifierReference resultCandidate, IEnumerable<(string, int)> labelIdLineNumberPairs) //, int executionBranchLine)
171+
{
172+
int? executionBranchLine = null;
173+
if (jumpContext is VBAParser.GoToStmtContext gotoCtxt)
174+
{
175+
executionBranchLine = DetermineLabeledExecutionBranchLine(gotoCtxt.expression().GetText(), labelIdLineNumberPairs);
176+
}
177+
else
178+
{
179+
executionBranchLine = DetermineResumeStmtExecutionBranchLine(jumpContext as VBAParser.ResumeStmtContext, resultCandidate, labelIdLineNumberPairs);
180+
}
181+
182+
return executionBranchLine.HasValue
183+
? AssignmentIsUsedPriorToExitStmts(resultCandidate, executionBranchLine.Value)
184+
: false;
185+
}
186+
187+
private static bool AssignmentIsUsedPriorToExitStmts(IdentifierReference resultCandidate, int executionBranchLine)
188+
{
189+
if (resultCandidate.Context.Start.Line < executionBranchLine) { return false; }
190+
191+
var procedureExitStmtCtxts = resultCandidate.ParentScoping.Context.GetDescendents<VBAParser.ExitStmtContext>()
192+
.Where(exitCtxt => exitCtxt.EXIT_DO() == null
193+
&& exitCtxt.EXIT_FOR() == null);
194+
195+
var nonAssignmentCtxts = resultCandidate.Declaration.References
196+
.Where(rf => !rf.IsAssignment)
197+
.Select(rf => rf.Context);
198+
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);
203+
204+
return !(sortedContextsAfterBranch.FirstOrDefault() is VBAParser.ExitStmtContext);
205+
}
206+
207+
private static int? DetermineResumeStmtExecutionBranchLine(VBAParser.ResumeStmtContext resumeStmt, IdentifierReference resultCandidate, IEnumerable<(string IdentifierName, int Line)> labelIdLineNumberPairs) //where T: ParserRuleContext
208+
{
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))
220+
{
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];
240+
}
241+
//Resume <label>
242+
return DetermineLabeledExecutionBranchLine(expression, labelIdLineNumberPairs);
243+
}
244+
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;
249+
111250
protected override string ResultDescription(IdentifierReference reference)
112251
{
113252
return Description;

Rubberduck.Core/UI/Command/MenuItems/CommandMenuItemBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ public virtual bool EvaluateCanExecute(RubberduckParserState state)
5454
public virtual bool HiddenWhenDisabled => false;
5555
public virtual bool IsVisible => true;
5656
public virtual bool BeginGroup => false;
57-
public virtual int DisplayOrder => default(int);
57+
public virtual int DisplayOrder => default;
5858
public virtual Image Image => null;
5959
public virtual Image Mask => null;
6060
}

Rubberduck.Core/UI/Command/MenuItems/ParentMenus/ParentMenuItemBase.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ public virtual Func<string> ToolTipText
6262
}
6363

6464
public virtual bool BeginGroup => false;
65-
public virtual int DisplayOrder => default(int);
65+
public virtual int DisplayOrder => default;
6666

6767
public void Localize()
6868
{
@@ -201,8 +201,7 @@ private ICommandBarControl InitializeChildControl(ICommandMenuItem item)
201201

202202
private void child_Click(object sender, CommandBarButtonClickEventArgs e)
203203
{
204-
var item = _items.Select(kvp => kvp.Key).SingleOrDefault(menu => e.Tag.EndsWith(menu.GetType().Name)) as ICommandMenuItem;
205-
if (item == null)
204+
if (!(_items.Select(kvp => kvp.Key).SingleOrDefault(menu => e.Tag.EndsWith(menu.GetType().Name)) is ICommandMenuItem item))
206205
{
207206
return;
208207
}

0 commit comments

Comments
 (0)