Skip to content

Commit 97ed7d3

Browse files
authored
Merge branch 'next' into Issue5346_Extract_interface_creates_private_classes
2 parents 864167e + 1bd8b48 commit 97ed7d3

File tree

160 files changed

+7406
-712
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

160 files changed

+7406
-712
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.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs

Lines changed: 70 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using System.Collections.Generic;
12
using System.Linq;
23
using Rubberduck.CodeAnalysis.Inspections.Abstract;
34
using Rubberduck.CodeAnalysis.Inspections.Extensions;
@@ -14,32 +15,92 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1415
/// </summary>
1516
/// <why>
1617
/// Unused procedures are dead code that should probably be removed. Note, a procedure may be effectively "not used" in code, but attached to some
17-
/// Shape object in the host document: in such cases the inspection result should be ignored. An event handler procedure that isn't being
18-
/// resolved as such, may also wrongly trigger this inspection.
18+
/// Shape object in the host document: in such cases the inspection result should be ignored.
1919
/// </why>
2020
/// <remarks>
2121
/// Not all unused procedures can/should be removed: ignore any inspection results for
2222
/// event handler procedures and interface members that Rubberduck isn't recognizing as such.
23+
/// Public procedures of Standard Modules are not flagged by this inspection regardless of
24+
/// the presence or absence of user code references.
2325
/// </remarks>
2426
/// <example hasResult="true">
25-
/// <module name="MyModule" type="Standard Module">
27+
/// <module name="Module1" type="Standard Module">
2628
/// <![CDATA[
2729
/// Option Explicit
2830
///
29-
/// Public Sub DoSomething()
30-
/// ' macro is attached to a worksheet Shape.
31+
/// Private Sub DoSomething()
3132
/// End Sub
3233
/// ]]>
3334
/// </module>
3435
/// </example>
3536
/// <example hasResult="false">
36-
/// <module name="MyModule" type="Standard Module">
37+
/// <module name="Module1" type="Standard Module">
3738
/// <![CDATA[
3839
/// Option Explicit
39-
///
40+
///
4041
/// '@Ignore ProcedureNotUsed
42+
/// Private Sub DoSomething()
43+
/// End Sub
44+
/// ]]>
45+
/// </module>
46+
/// </example>
47+
/// <example hasResult="false">
48+
/// <module name="Macros" type="Standard Module">
49+
/// <![CDATA[
50+
/// Option Explicit
51+
///
52+
/// Public Sub DoSomething()
53+
/// 'a public procedure in a standard module may be a macro
54+
/// 'attached to a worksheet Shape or invoked by means other than user code.
55+
/// End Sub
56+
/// ]]>
57+
/// </module>
58+
/// </example>
59+
/// <example hasResult="true">
60+
/// <module name="Class1" type="Class Module">
61+
/// <![CDATA[
62+
/// Option Explicit
63+
///
64+
/// Public Sub DoSomething()
65+
/// End Sub
66+
///
67+
/// Public Sub DoSomethingElse()
68+
/// End Sub
69+
/// ]]>
70+
/// </module>
71+
/// <module name="Module1" type="Standard Module">
72+
/// <![CDATA[
73+
/// Option Explicit
74+
///
75+
/// Public Sub ReferenceOneClass1Procedure()
76+
/// Dim target As Class1
77+
/// Set target = new Class1
78+
/// target.DoSomething
79+
/// End Sub
80+
/// ]]>
81+
/// </module>
82+
/// </example>
83+
/// <example hasResult="false">
84+
/// <module name="Class1" type="Class Module">
85+
/// <![CDATA[
86+
/// Option Explicit
87+
///
4188
/// Public Sub DoSomething()
42-
/// ' macro is attached to a worksheet Shape.
89+
/// End Sub
90+
///
91+
/// Public Sub DoSomethingElse()
92+
/// End Sub
93+
/// ]]>
94+
/// </module>
95+
/// <module name="Module1" type="Standard Module">
96+
/// <![CDATA[
97+
/// Option Explicit
98+
///
99+
/// Public Sub ReferenceAllClass1Procedures()
100+
/// Dim target As Class1
101+
/// Set target = new Class1
102+
/// target.DoSomething
103+
/// target.DoSomethingElse
43104
/// End Sub
44105
/// ]]>
45106
/// </module>
@@ -78,8 +139,7 @@ public ProcedureNotUsedInspection(IDeclarationFinderProvider declarationFinderPr
78139
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
79140
{
80141
return !declaration.References
81-
.Any(reference => !reference.IsAssignment
82-
&& !reference.ParentScoping.Equals(declaration)) // recursive calls don't count
142+
.Any(reference => !reference.ParentScoping.Equals(declaration)) // ignore recursive/self-referential calls
83143
&& !finder.FindEventHandlers().Contains(declaration)
84144
&& !IsPublicModuleMember(declaration)
85145
&& !IsClassLifeCycleHandler(declaration)

Rubberduck.CodeAnalysis/Inspections/Extensions/DeclarationTypeExtensions.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,9 @@
44

55
namespace Rubberduck.CodeAnalysis.Inspections.Extensions
66
{
7-
internal static class DeclarationTypeExtensions
7+
public static class DeclarationTypeExtensions
88
{
9+
//ToDo: Move this to resources. (This will require moving resource lookups to Core.)
910
public static string ToLocalizedString(this DeclarationType type)
1011
{
1112
return RubberduckUI.ResourceManager.GetString("DeclarationType_" + type, CultureInfo.CurrentUICulture);

0 commit comments

Comments
 (0)