Skip to content

Commit

Permalink
Merge d2dff52 into fbfff3c
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Sep 30, 2021
2 parents fbfff3c + d2dff52 commit 287f1db
Show file tree
Hide file tree
Showing 6 changed files with 67 additions and 13 deletions.
Expand Up @@ -51,7 +51,9 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
&& !declaration.IsWithEvents
&& !declaration.IsSelfAssigned
&& !HasUdtType(declaration, finder) // UDT variables don't need to be assigned
&& !declaration.References.Any(reference => reference.IsAssignment || IsAssignedByRefArgument(reference.ParentScoping, reference, finder));
&& !declaration.References.Any(reference => reference.IsAssignment
|| reference.IsReDim //Ignores Variants used as arrays without assignment of an existing one.
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder));
}

private static bool HasUdtType(Declaration declaration, DeclarationFinder finder)
Expand Down
6 changes: 4 additions & 2 deletions Rubberduck.Parsing/Symbols/Declaration.cs
Expand Up @@ -382,7 +382,8 @@ private bool IsObjectOrObjectArray
bool isArrayAccess = false,
bool isProcedureCoercion = false,
bool isInnerRecursiveDefaultMemberAccess = false,
IdentifierReference qualifyingReference = null
IdentifierReference qualifyingReference = null,
bool isReDim = false
)
{
var oldReference = _references.FirstOrDefault(r =>
Expand Down Expand Up @@ -416,7 +417,8 @@ private bool IsObjectOrObjectArray
isArrayAccess,
isProcedureCoercion,
isInnerRecursiveDefaultMemberAccess,
qualifyingReference);
qualifyingReference,
isReDim);
_references.AddOrUpdate(newReference, 1, (key, value) => 1);
return newReference;
}
Expand Down
5 changes: 4 additions & 1 deletion Rubberduck.Parsing/Symbols/IdentifierReference.cs
Expand Up @@ -31,7 +31,8 @@ public class IdentifierReference : IEquatable<IdentifierReference>
bool isArrayAccess = false,
bool isProcedureCoercion = false,
bool isInnerRecursiveDefaultMemberAccess = false,
IdentifierReference qualifyingReference = null)
IdentifierReference qualifyingReference = null,
bool isReDim = false)
{
ParentScoping = parentScopingDeclaration;
ParentNonScoping = parentNonScopingDeclaration;
Expand All @@ -50,6 +51,7 @@ public class IdentifierReference : IEquatable<IdentifierReference>
Annotations = annotations ?? new List<IParseTreeAnnotation>();
IsInnerRecursiveDefaultMemberAccess = isInnerRecursiveDefaultMemberAccess;
QualifyingReference = qualifyingReference;
IsReDim = isReDim;
}

public QualifiedSelection QualifiedSelection { get; }
Expand Down Expand Up @@ -84,6 +86,7 @@ public class IdentifierReference : IEquatable<IdentifierReference>
public int DefaultMemberRecursionDepth { get; }

public bool IsArrayAccess { get; }
public bool IsReDim { get; }

public ParserRuleContext Context { get; }

Expand Down
Expand Up @@ -24,9 +24,10 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder)
Declaration parent,
bool isAssignmentTarget = false,
bool hasExplicitLetStatement = false,
bool isSetAssignment = false)
bool isSetAssignment = false,
bool isReDim = false)
{
Visit(boundExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
Visit(boundExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment, isReDim: isReDim);
}

/// <summary>
Expand All @@ -50,12 +51,13 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder)
bool isAssignmentTarget = false,
bool hasExplicitLetStatement = false,
bool isSetAssignment = false,
bool hasArrayAccess = false)
bool hasArrayAccess = false,
bool isReDim = false)
{
switch (boundExpression)
{
case SimpleNameExpression simpleNameExpression:
return Visit(simpleNameExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
return Visit(simpleNameExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment, isReDim);
case MemberAccessExpression memberAccessExpression:
return Visit(memberAccessExpression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
case IndexExpression indexExpression:
Expand Down Expand Up @@ -119,7 +121,8 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder)
Declaration parent,
bool isAssignmentTarget,
bool hasExplicitLetStatement,
bool isSetAssignment)
bool isSetAssignment,
bool isReDim)
{
var callSiteContext = expression.Context;
var callee = expression.ReferencedDeclaration;
Expand All @@ -136,7 +139,8 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder)
FindIdentifierAnnotations(module, selection.StartLine),
isAssignmentTarget,
hasExplicitLetStatement,
isSetAssignment);
isSetAssignment,
isReDim: isReDim);
}

private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedModuleName module, int line)
Expand Down
Expand Up @@ -169,7 +169,8 @@ private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedMod
StatementResolutionContext statementContext = StatementResolutionContext.Undefined,
bool isAssignmentTarget = false,
bool hasExplicitLetStatement = false,
bool isSetAssignment = false)
bool isSetAssignment = false,
bool isReDim = false)
{
var withExpression = GetInnerMostWithExpression();
var boundExpression = _bindingService.ResolveDefault(
Expand All @@ -190,7 +191,8 @@ private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedMod
_currentParent,
isAssignmentTarget,
hasExplicitLetStatement,
isSetAssignment);
isSetAssignment,
isReDim);
}

private void ResolveType(ParserRuleContext expression)
Expand Down Expand Up @@ -258,7 +260,7 @@ public void Resolve(VBAParser.RedimStmtContext context)
// The indexedExpression is the array that is being resized.
// We can't treat it as a normal index expression because the semantics are different.
// It's not actually a function call but a special statement.
ResolveDefault(indexedExpression, false);
ResolveDefault(indexedExpression, false, isReDim: true);
if (argumentList.argument() != null)
{
foreach (var positionalArgument in argumentList.argument())
Expand Down
41 changes: 41 additions & 0 deletions RubberduckTests/Inspections/VariableNotAssignedInspectionTests.cs
Expand Up @@ -379,6 +379,47 @@ End Sub
).Count());
}

[Test]
[Category("Inspections")]
public void VariableNotAssigned_ArrayWithElementAssignment_DoesNotReturnResult()
{
const string inputCode = @"
Public Sub Foo()
Dim arr(0 To 0) As Variant
arr(0) = 42
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void VariableNotAssigned_ReDimDeclaredArrayWithElementAssignment_DoesNotReturnResult()
{
const string inputCode = @"
Public Sub Foo()
ReDim arr(0 To 0) As Variant
arr(0) = 42
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
//See issue #5845 at https://github.com/rubberduck-vba/Rubberduck/issues/5845
public void VariableNotAssigned_VariantUsedAsArrayWithElementAssignment_DoesNotReturnResult()
{
const string inputCode = @"
Public Sub Foo()
Dim arr As Variant
ReDim arr(0 To 0) As Variant
arr(0) = 42
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void VariableNotAssigned_Ignored_DoesNotReturnResult()
Expand Down

0 comments on commit 287f1db

Please sign in to comment.