Skip to content

Commit 242a112

Browse files
authored
Merge pull request #6023 from MDoerner/FixUnassignedVariableUsageOnRedimmedVariantArray
Make UnassignedVariableUsageInspection aware of redimmed variant arrays
2 parents 12f50e5 + 4e0a0a0 commit 242a112

File tree

2 files changed

+248
-1
lines changed

2 files changed

+248
-1
lines changed

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
}

RubberduckTests/Inspections/UnassignedVariableUsageInspectionTests.cs

Lines changed: 165 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,171 @@ End Sub
9696
Assert.AreEqual(1, InspectionResultsForStandardModule(code).Count());
9797
}
9898

99+
[Test]
100+
[Category("Inspections")]
101+
public void IgnoresReDimDefinedArrays()
102+
{
103+
const string code = @"
104+
Sub Foo()
105+
ReDim bar(2) As String
106+
bar(1) = ""value""
107+
End Sub
108+
";
109+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
110+
}
111+
112+
[Test]
113+
[Category("Inspections")]
114+
public void IgnoresArrayReDimAfterRedim()
115+
{
116+
const string code = @"
117+
Sub Foo()
118+
Dim bar As Variant
119+
ReDim bar(1 To 10)
120+
ReDim bar(11 To 1220)
121+
End Sub
122+
";
123+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
124+
}
125+
126+
[Test]
127+
[Category("Inspections")]
128+
public void IgnoresArrayReDimOnRedimDefinedArray()
129+
{
130+
const string code = @"
131+
Sub Foo()
132+
ReDim bar(1 To 10)
133+
ReDim bar(11 To 1220)
134+
End Sub
135+
";
136+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
137+
}
138+
139+
[Test]
140+
[Category("Inspections")]
141+
// ref issue #5990
142+
public void IgnoresUsageOfArrayInBoundsAfterRedim()
143+
{
144+
const string code = @"
145+
Sub TEST()
146+
Dim i, arr
147+
ReDim arr(2)
148+
arr(0) = Array(""aaa"", ""bbbb"")
149+
arr(1) = Array(""ccc"", ""dddd"")
150+
arr(2) = Array(""eee"", ""ffff"")
151+
For i = LBound(arr) To UBound(arr) ' I get two ""Variable 'arr' is used but not assigned."" here
152+
'...
153+
Next
154+
End Sub
155+
";
156+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(code, out _, referenceStdLibs: true).Object;
157+
Assert.AreEqual(0, InspectionResults(vbe).Count());
158+
}
159+
160+
[Test]
161+
[Category("Inspections")]
162+
public void IgnoresUsageOfArrayInBounds()
163+
{
164+
const string code = @"
165+
Sub TEST()
166+
Dim i, arr(2)
167+
arr(0) = Array(""aaa"", ""bbbb"")
168+
arr(1) = Array(""ccc"", ""dddd"")
169+
arr(2) = Array(""eee"", ""ffff"")
170+
For i = LBound(arr) To UBound(arr)
171+
'...
172+
Next
173+
End Sub
174+
";
175+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(code, out _, referenceStdLibs: true).Object;
176+
Assert.AreEqual(0, InspectionResults(vbe).Count());
177+
}
178+
179+
[Test]
180+
[Category("Inspections")]
181+
public void IgnoresUsageOfReDimDefinedArrayInBounds()
182+
{
183+
const string code = @"
184+
Sub TEST()
185+
Dim i
186+
ReDim arr(2)
187+
arr(0) = Array(""aaa"", ""bbbb"")
188+
arr(1) = Array(""ccc"", ""dddd"")
189+
arr(2) = Array(""eee"", ""ffff"")
190+
For i = LBound(arr) To UBound(arr)
191+
'...
192+
Next
193+
End Sub
194+
";
195+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(code, out _, referenceStdLibs: true).Object;
196+
Assert.AreEqual(0, InspectionResults(vbe).Count());
197+
}
198+
199+
[Test]
200+
[Category("Inspections")]
201+
public void IgnoresUsageOfVariantArrayAsFunctionArgumentAfterRedim()
202+
{
203+
const string code = @"
204+
Private Function Foo(arg As Variant) As Variant
205+
Foo = arg
206+
End Function
207+
208+
Sub Baz()
209+
Dim bar
210+
ReDim bar(2)
211+
bar(0) = 1
212+
bar(1) = 2
213+
bar(2) = 3
214+
Dim fooBar As Variant
215+
fooBar = Foo(bar)
216+
End Sub
217+
";
218+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
219+
}
220+
221+
[Test]
222+
[Category("Inspections")]
223+
public void IgnoresUsageOfArrayAsFunctionArgument()
224+
{
225+
const string code = @"
226+
Private Function Foo(arg As Variant) As Variant
227+
Foo = arg
228+
End Function
229+
230+
Sub Baz()
231+
Dim bar(2)
232+
bar(0) = 1
233+
bar(1) = 2
234+
bar(2) = 3
235+
Dim fooBar As Variant
236+
fooBar = Foo(bar)
237+
End Sub
238+
";
239+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
240+
}
241+
242+
[Test]
243+
[Category("Inspections")]
244+
public void ResultForUsageOfVariantArrayAsFunctionArgumentBeforeRedim()
245+
{
246+
const string code = @"
247+
Private Function Foo(arg As Variant) As Variant
248+
Foo = arg
249+
End Function
250+
251+
Sub Baz()
252+
Dim bar
253+
Dim fooBar As Variant
254+
fooBar = Foo(bar)
255+
ReDim bar(2)
256+
bar(0) = 1
257+
bar(1) = 2
258+
bar(2) = 3
259+
End Sub
260+
";
261+
Assert.AreEqual(1, InspectionResultsForStandardModule(code).Count());
262+
}
263+
99264
[Test]
100265
[Category("Inspections")]
101266
public void DoNotIgnoreIndexedPropertyAccess_Let()

0 commit comments

Comments
 (0)