Skip to content

Commit 54dd27b

Browse files
committed
Merge branch 'next' into 5907HandleConcatOpContext
2 parents 542e8e6 + 1bb58c3 commit 54dd27b

14 files changed

+802
-35
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,24 @@ public ConstantNotUsedInspection(IDeclarationFinderProvider declarationFinderPro
4545
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4646
{
4747
return declaration?.Context != null
48-
&& !declaration.References.Any();
48+
&& !declaration.References.Any()
49+
&& !IsPublicInExposedClass(declaration);
50+
}
51+
52+
private static bool IsPublicInExposedClass(Declaration procedure)
53+
{
54+
if (!(procedure.Accessibility == Accessibility.Public
55+
|| procedure.Accessibility == Accessibility.Global))
56+
{
57+
return false;
58+
}
59+
60+
if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
61+
{
62+
return false;
63+
}
64+
65+
return classParent.IsExposed;
4966
}
5067

5168
protected override string ResultDescription(Declaration declaration)

Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs

Lines changed: 38 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System.Linq;
2+
using Antlr4.Runtime.Tree;
23
using Rubberduck.CodeAnalysis.Inspections.Abstract;
34
using Rubberduck.Parsing;
45
using Rubberduck.Parsing.Grammar;
@@ -122,31 +123,58 @@ protected override string ResultDescription(Declaration declaration)
122123
private class FunctionReturnValueAssignmentLocator : VBAParserBaseVisitor<bool>
123124
{
124125
private readonly string _name;
125-
private bool _result;
126+
private bool _inFunctionReturnWithExpression;
126127

127128
public FunctionReturnValueAssignmentLocator(string name)
128129
{
129130
_name = name;
131+
_inFunctionReturnWithExpression = false;
130132
}
131133

132-
public override bool VisitBlock(VBAParser.BlockContext context)
134+
protected override bool DefaultResult => false;
135+
136+
protected override bool ShouldVisitNextChild(IRuleNode node, bool currentResult)
137+
{
138+
return !currentResult;
139+
}
140+
141+
//This is actually the default implementation, but for explicities sake stated here.
142+
protected override bool AggregateResult(bool aggregate, bool nextResult)
143+
{
144+
return nextResult;
145+
}
146+
147+
public override bool VisitWithStmt(VBAParser.WithStmtContext context)
133148
{
134-
base.VisitBlock(context);
135-
return _result;
149+
var oldInFunctionReturnWithExpression = _inFunctionReturnWithExpression;
150+
_inFunctionReturnWithExpression = context.expression().GetText() == _name;
151+
var result = base.VisitWithStmt(context);
152+
_inFunctionReturnWithExpression = oldInFunctionReturnWithExpression;
153+
return result;
136154
}
137155

138156
public override bool VisitLetStmt(VBAParser.LetStmtContext context)
139157
{
140-
var leftmost = context.lExpression().GetChild(0).GetText();
141-
_result = _result || leftmost == _name;
142-
return _result;
158+
var LHS = context.lExpression();
159+
if (_inFunctionReturnWithExpression
160+
&& LHS is VBAParser.WithMemberAccessExprContext)
161+
{
162+
return true;
163+
}
164+
var leftmost = LHS.GetChild(0).GetText();
165+
return leftmost == _name;
143166
}
144167

145168
public override bool VisitSetStmt(VBAParser.SetStmtContext context)
146169
{
147-
var leftmost = context.lExpression().GetChild(0).GetText();
148-
_result = _result || leftmost == _name;
149-
return _result;
170+
var LHS = context.lExpression();
171+
if (_inFunctionReturnWithExpression
172+
&& LHS is VBAParser.WithMemberAccessExprContext)
173+
{
174+
return true;
175+
}
176+
var leftmost = LHS.GetChild(0).GetText();
177+
return leftmost == _name;
150178
}
151179
}
152180
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs

Lines changed: 21 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -19,9 +19,9 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1919
/// Shape object in the host document: in such cases the inspection result should be ignored.
2020
/// </why>
2121
/// <remarks>
22-
/// Not all unused procedures can/should be removed: ignore any inspection results for
23-
/// event handler procedures and interface members that Rubberduck isn't recognizing as such, or annotate them with @EntryPoint.
22+
/// Not all unused procedures can/should be removed: ignore any inspection results for event handler procedures or annotate them with @EntryPoint.
2423
/// Members that are annotated with @EntryPoint (or @ExcelHotkey) are not flagged by this inspection, regardless of the presence or absence of user code references.
24+
/// Moreover, unused public members of exposed class modules will not be reported.
2525
/// </remarks>
2626
/// <example hasResult="true">
2727
/// <module name="Module1" type="Standard Module">
@@ -144,12 +144,28 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
144144
&& !finder.FindEventHandlers().Contains(declaration)
145145
&& !IsClassLifeCycleHandler(declaration)
146146
&& !(declaration is ModuleBodyElementDeclaration member
147-
&& (member.IsInterfaceMember
148-
|| member.IsInterfaceImplementation))
147+
&& member.IsInterfaceImplementation)
149148
&& !declaration.Annotations
150149
.Any(pta => pta.Annotation is ITestAnnotation)
151150
&& !IsDocumentEventHandler(declaration)
152-
&& !IsEntryPoint(declaration);
151+
&& !IsEntryPoint(declaration)
152+
&& !IsPublicInExposedClass(declaration);
153+
}
154+
155+
private static bool IsPublicInExposedClass(Declaration procedure)
156+
{
157+
if(!(procedure.Accessibility == Accessibility.Public
158+
|| procedure.Accessibility == Accessibility.Global))
159+
{
160+
return false;
161+
}
162+
163+
if(!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
164+
{
165+
return false;
166+
}
167+
168+
return classParent.IsExposed;
153169
}
154170

155171
private static bool IsEntryPoint(Declaration procedure) =>

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 83 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Collections.Generic;
22
using System.Diagnostics.CodeAnalysis;
33
using System.Linq;
4+
using Antlr4.Runtime.Misc;
45
using Rubberduck.CodeAnalysis.Inspections.Abstract;
56
using Rubberduck.InternalApi.Extensions;
67
using Rubberduck.Parsing;
@@ -81,7 +82,8 @@ protected override IEnumerable<IdentifierReference> ObjectionableReferences(Decl
8182
.ToHashSet();
8283

8384
return base.ObjectionableReferences(finder)
84-
.Where(reference => !excludedReferenceSelections.Contains(reference.QualifiedSelection));
85+
.Where(reference => !excludedReferenceSelections.Contains(reference.QualifiedSelection)
86+
&& !IsRedimedVariantArrayReference(reference));
8587
}
8688

8789
private IEnumerable<ModuleBodyElementDeclaration> DeclarationsWithExcludedArgumentUsage(DeclarationFinder finder)
@@ -204,5 +206,85 @@ private static bool IsArrayReDim(IdentifierReference reference)
204206

205207
return reDimVariableStmt is VBAParser.RedimVariableDeclarationContext;
206208
}
209+
210+
// This function works under the assumption that there are no assignments to the referenced variable.
211+
private bool IsRedimedVariantArrayReference(IdentifierReference reference)
212+
{
213+
if (reference.Declaration.AsTypeName != "Variant")
214+
{
215+
return false;
216+
}
217+
218+
if(!reference.Context.TryGetAncestor<VBAParser.ModuleBodyElementContext>(out var containingMember))
219+
{
220+
return false;
221+
}
222+
223+
var referenceSelection = reference.Selection;
224+
var referencedDeclarationName = reference.Declaration.IdentifierName;
225+
var reDimLocator = new PriorReDimLocator(referencedDeclarationName, referenceSelection);
226+
227+
return reDimLocator.Visit(containingMember);
228+
}
229+
230+
/// <summary>
231+
/// A visitor that visits a member's body and returns <c>true</c> if any <c>ReDim</c> statement for the variable called <c>name</c> is present before the <c>selection</c>.
232+
/// </summary>
233+
private class PriorReDimLocator : VBAParserBaseVisitor<bool>
234+
{
235+
private readonly string _name;
236+
private readonly Selection _selection;
237+
238+
public PriorReDimLocator(string name, Selection selection)
239+
{
240+
_name = name;
241+
_selection = selection;
242+
}
243+
244+
protected override bool DefaultResult => false;
245+
246+
protected override bool ShouldVisitNextChild(Antlr4.Runtime.Tree.IRuleNode node, bool currentResult)
247+
{
248+
return !currentResult;
249+
}
250+
251+
//This is actually the default implementation, but for explicities sake stated here.
252+
protected override bool AggregateResult(bool aggregate, bool nextResult)
253+
{
254+
return nextResult;
255+
}
256+
257+
public override bool VisitRedimVariableDeclaration([NotNull] VBAParser.RedimVariableDeclarationContext context)
258+
{
259+
var reDimedVariableName = RedimedVariableName(context);
260+
if (reDimedVariableName != _name)
261+
{
262+
return false;
263+
}
264+
265+
var reDimSelection = context.GetSelection();
266+
267+
return reDimSelection <= _selection;
268+
}
269+
270+
private string RedimedVariableName([NotNull] VBAParser.RedimVariableDeclarationContext context)
271+
{
272+
if (!(context.expression() is VBAParser.LExprContext reDimmedVariablelExpr))
273+
{
274+
//This is not syntactically correct VBA.
275+
return null;
276+
}
277+
278+
switch (reDimmedVariablelExpr.lExpression())
279+
{
280+
case VBAParser.IndexExprContext indexExpr:
281+
return indexExpr.lExpression().GetText();
282+
case VBAParser.WhitespaceIndexExprContext whiteSpaceIndexExpr:
283+
return whiteSpaceIndexExpr.lExpression().GetText();
284+
default: //This should not be possible in syntactically correct VBA.
285+
return null;
286+
}
287+
}
288+
}
207289
}
208290
}

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,24 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
5353
&& !HasUdtType(declaration, finder) // UDT variables don't need to be assigned
5454
&& !declaration.References.Any(reference => reference.IsAssignment
5555
|| reference.IsReDim //Ignores Variants used as arrays without assignment of an existing one.
56-
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder));
56+
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder))
57+
&& !IsPublicInExposedClass(declaration);
58+
}
59+
60+
private static bool IsPublicInExposedClass(Declaration procedure)
61+
{
62+
if (!(procedure.Accessibility == Accessibility.Public
63+
|| procedure.Accessibility == Accessibility.Global))
64+
{
65+
return false;
66+
}
67+
68+
if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
69+
{
70+
return false;
71+
}
72+
73+
return classParent.IsExposed;
5774
}
5875

5976
private static bool HasUdtType(Declaration declaration, DeclarationFinder finder)

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -54,9 +54,27 @@ public VariableNotUsedInspection(IDeclarationFinderProvider declarationFinderPro
5454
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
5555
{
5656
// exclude undeclared, see #5439
57-
return !declaration.IsWithEvents && !declaration.IsUndeclared
57+
return !declaration.IsWithEvents
58+
&& !declaration.IsUndeclared
5859
&& declaration.References.All(reference => reference.IsAssignment)
59-
&& !declaration.References.Any(IsForLoopAssignment);
60+
&& !declaration.References.Any(IsForLoopAssignment)
61+
&& !IsPublicInExposedClass(declaration);
62+
}
63+
64+
private static bool IsPublicInExposedClass(Declaration procedure)
65+
{
66+
if (!(procedure.Accessibility == Accessibility.Public
67+
|| procedure.Accessibility == Accessibility.Global))
68+
{
69+
return false;
70+
}
71+
72+
if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
73+
{
74+
return false;
75+
}
76+
77+
return classParent.IsExposed;
6078
}
6179

6280
private bool IsForLoopAssignment(IdentifierReference reference)

Rubberduck.Core/UI/Converters/SearchResultToXamlConverter.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,10 +33,12 @@ public object Convert(object value, Type targetType, object parameter, CultureIn
3333
textBlock.TextWrapping = TextWrapping.Wrap;
3434

3535
var input = item.ResultText.Replace(' ', nonBreakingSpace);
36-
if (item.HighlightIndex.HasValue)
36+
if (item.HighlightIndex.HasValue
37+
&& item.HighlightIndex.Value.EndColumn < input.Length // if we do not check this, any inconsistent input will crash the host.
38+
&& item.HighlightIndex.Value.StartColumn < input.Length)
3739
{
3840
var highlight = item.HighlightIndex.Value;
39-
if (highlight.StartColumn > 0)
41+
if (highlight.StartColumn > 0)
4042
{
4143
var preRun = new Run(input.Substring(0, highlight.StartColumn))
4244
{

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -529,7 +529,7 @@ internal set
529529
{
530530
_asTypeDeclaration = value;
531531
IsSelfAssigned = IsSelfAssigned || (DeclarationType == DeclarationType.Variable &&
532-
AsTypeDeclaration.DeclarationType == DeclarationType.UserDefinedType);
532+
AsTypeDeclaration?.DeclarationType == DeclarationType.UserDefinedType);
533533
}
534534
}
535535

0 commit comments

Comments
 (0)