Skip to content

Commit 2039bbf

Browse files
authored
Merge pull request #5860 from MDoerner/FixVariableNotAssignedForVariantsUsedAsArrays
Fix VariableNotAssigned for Variants used as arrays
2 parents 1a1069d + d2dff52 commit 2039bbf

File tree

6 files changed

+67
-13
lines changed

6 files changed

+67
-13
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,9 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
5151
&& !declaration.IsWithEvents
5252
&& !declaration.IsSelfAssigned
5353
&& !HasUdtType(declaration, finder) // UDT variables don't need to be assigned
54-
&& !declaration.References.Any(reference => reference.IsAssignment || IsAssignedByRefArgument(reference.ParentScoping, reference, finder));
54+
&& !declaration.References.Any(reference => reference.IsAssignment
55+
|| reference.IsReDim //Ignores Variants used as arrays without assignment of an existing one.
56+
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder));
5557
}
5658

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

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -382,7 +382,8 @@ public IdentifierReference AddReference(
382382
bool isArrayAccess = false,
383383
bool isProcedureCoercion = false,
384384
bool isInnerRecursiveDefaultMemberAccess = false,
385-
IdentifierReference qualifyingReference = null
385+
IdentifierReference qualifyingReference = null,
386+
bool isReDim = false
386387
)
387388
{
388389
var oldReference = _references.FirstOrDefault(r =>
@@ -416,7 +417,8 @@ public IdentifierReference AddReference(
416417
isArrayAccess,
417418
isProcedureCoercion,
418419
isInnerRecursiveDefaultMemberAccess,
419-
qualifyingReference);
420+
qualifyingReference,
421+
isReDim);
420422
_references.AddOrUpdate(newReference, 1, (key, value) => 1);
421423
return newReference;
422424
}

Rubberduck.Parsing/Symbols/IdentifierReference.cs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,8 @@ internal IdentifierReference(
3131
bool isArrayAccess = false,
3232
bool isProcedureCoercion = false,
3333
bool isInnerRecursiveDefaultMemberAccess = false,
34-
IdentifierReference qualifyingReference = null)
34+
IdentifierReference qualifyingReference = null,
35+
bool isReDim = false)
3536
{
3637
ParentScoping = parentScopingDeclaration;
3738
ParentNonScoping = parentNonScopingDeclaration;
@@ -50,6 +51,7 @@ internal IdentifierReference(
5051
Annotations = annotations ?? new List<IParseTreeAnnotation>();
5152
IsInnerRecursiveDefaultMemberAccess = isInnerRecursiveDefaultMemberAccess;
5253
QualifyingReference = qualifyingReference;
54+
IsReDim = isReDim;
5355
}
5456

5557
public QualifiedSelection QualifiedSelection { get; }
@@ -84,6 +86,7 @@ internal IdentifierReference(
8486
public int DefaultMemberRecursionDepth { get; }
8587

8688
public bool IsArrayAccess { get; }
89+
public bool IsReDim { get; }
8790

8891
public ParserRuleContext Context { get; }
8992

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -24,9 +24,10 @@ public void AddIdentifierReferences(
2424
Declaration parent,
2525
bool isAssignmentTarget = false,
2626
bool hasExplicitLetStatement = false,
27-
bool isSetAssignment = false)
27+
bool isSetAssignment = false,
28+
bool isReDim = false)
2829
{
29-
Visit(boundExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
30+
Visit(boundExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment, isReDim: isReDim);
3031
}
3132

3233
/// <summary>
@@ -50,12 +51,13 @@ private IdentifierReference Visit(
5051
bool isAssignmentTarget = false,
5152
bool hasExplicitLetStatement = false,
5253
bool isSetAssignment = false,
53-
bool hasArrayAccess = false)
54+
bool hasArrayAccess = false,
55+
bool isReDim = false)
5456
{
5557
switch (boundExpression)
5658
{
5759
case SimpleNameExpression simpleNameExpression:
58-
return Visit(simpleNameExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
60+
return Visit(simpleNameExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment, isReDim);
5961
case MemberAccessExpression memberAccessExpression:
6062
return Visit(memberAccessExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
6163
case IndexExpression indexExpression:
@@ -119,7 +121,8 @@ private IdentifierReference Visit(
119121
Declaration parent,
120122
bool isAssignmentTarget,
121123
bool hasExplicitLetStatement,
122-
bool isSetAssignment)
124+
bool isSetAssignment,
125+
bool isReDim)
123126
{
124127
var callSiteContext = expression.Context;
125128
var callee = expression.ReferencedDeclaration;
@@ -136,7 +139,8 @@ private IdentifierReference Visit(
136139
FindIdentifierAnnotations(module, selection.StartLine),
137140
isAssignmentTarget,
138141
hasExplicitLetStatement,
139-
isSetAssignment);
142+
isSetAssignment,
143+
isReDim: isReDim);
140144
}
141145

142146
private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedModuleName module, int line)

Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,8 @@ private void ResolveDefault(
169169
StatementResolutionContext statementContext = StatementResolutionContext.Undefined,
170170
bool isAssignmentTarget = false,
171171
bool hasExplicitLetStatement = false,
172-
bool isSetAssignment = false)
172+
bool isSetAssignment = false,
173+
bool isReDim = false)
173174
{
174175
var withExpression = GetInnerMostWithExpression();
175176
var boundExpression = _bindingService.ResolveDefault(
@@ -190,7 +191,8 @@ private void ResolveDefault(
190191
_currentParent,
191192
isAssignmentTarget,
192193
hasExplicitLetStatement,
193-
isSetAssignment);
194+
isSetAssignment,
195+
isReDim);
194196
}
195197

196198
private void ResolveType(ParserRuleContext expression)
@@ -258,7 +260,7 @@ public void Resolve(VBAParser.RedimStmtContext context)
258260
// The indexedExpression is the array that is being resized.
259261
// We can't treat it as a normal index expression because the semantics are different.
260262
// It's not actually a function call but a special statement.
261-
ResolveDefault(indexedExpression, false);
263+
ResolveDefault(indexedExpression, false, isReDim: true);
262264
if (argumentList.argument() != null)
263265
{
264266
foreach (var positionalArgument in argumentList.argument())

RubberduckTests/Inspections/VariableNotAssignedInspectionTests.cs

Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -379,6 +379,47 @@ End Sub
379379
).Count());
380380
}
381381

382+
[Test]
383+
[Category("Inspections")]
384+
public void VariableNotAssigned_ArrayWithElementAssignment_DoesNotReturnResult()
385+
{
386+
const string inputCode = @"
387+
Public Sub Foo()
388+
Dim arr(0 To 0) As Variant
389+
arr(0) = 42
390+
End Sub
391+
";
392+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
393+
}
394+
395+
[Test]
396+
[Category("Inspections")]
397+
public void VariableNotAssigned_ReDimDeclaredArrayWithElementAssignment_DoesNotReturnResult()
398+
{
399+
const string inputCode = @"
400+
Public Sub Foo()
401+
ReDim arr(0 To 0) As Variant
402+
arr(0) = 42
403+
End Sub
404+
";
405+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
406+
}
407+
408+
[Test]
409+
[Category("Inspections")]
410+
//See issue #5845 at https://github.com/rubberduck-vba/Rubberduck/issues/5845
411+
public void VariableNotAssigned_VariantUsedAsArrayWithElementAssignment_DoesNotReturnResult()
412+
{
413+
const string inputCode = @"
414+
Public Sub Foo()
415+
Dim arr As Variant
416+
ReDim arr(0 To 0) As Variant
417+
arr(0) = 42
418+
End Sub
419+
";
420+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
421+
}
422+
382423
[Test]
383424
[Category("Inspections")]
384425
public void VariableNotAssigned_Ignored_DoesNotReturnResult()

0 commit comments

Comments
 (0)