Skip to content

Commit

Permalink
Add non-undeclared declarations for ReDimed array without dclaration
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Aug 24, 2019
1 parent 9ee0bf9 commit 3a915a4
Show file tree
Hide file tree
Showing 2 changed files with 41 additions and 2 deletions.
14 changes: 12 additions & 2 deletions Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs
Expand Up @@ -974,6 +974,9 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
{
var annotations = FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line)
.Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));

var isReDimVariable = IsContainedInReDimedArrayName(context);

var undeclaredLocal =
new Declaration(
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
Expand All @@ -988,12 +991,12 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
context,
null,
context.GetSelection(),
false,
isReDimVariable,
null,
true,
annotations,
null,
true);
!isReDimVariable);

var hasUndeclared = _newUndeclared.ContainsKey(enclosingProcedure.QualifiedName);
if (hasUndeclared)
Expand All @@ -1017,6 +1020,13 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
return undeclaredLocal;
}

private static bool IsContainedInReDimedArrayName(ParserRuleContext context)
{
var enclosingReDimContext = context.GetAncestor<VBAParser.RedimVariableDeclarationContext>();
return enclosingReDimContext != null
&& enclosingReDimContext.expression().GetSelection().Contains(context.GetSelection());
}


public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressionContext context, IBoundExpression withExpression)
{
Expand Down
29 changes: 29 additions & 0 deletions RubberduckTests/Inspections/UndeclaredVariableInspectionTests.cs
Expand Up @@ -88,6 +88,35 @@ Debug.Print a
}
}

[Test]
[Category("Inspections")]
//ReDim acts as a declaration if the array is not declared already.
//See issue #2522 at https://github.com/rubberduck-vba/Rubberduck/issues/2522
public void UndeclaredVariable_ReturnsNoResultForReDim()
{
const string inputCode =
@"
Sub Test()
Dim bar As Variant
ReDim arr(1 To 42)
bar = arr
End Sub";

var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
.Build();
var vbe = builder.AddProject(project).Build();

using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new UndeclaredVariableInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

Assert.IsFalse(inspectionResults.Any());
}
}

//https://github.com/rubberduck-vba/Rubberduck/issues/2525
[Test]
[Category("Inspections")]
Expand Down

0 comments on commit 3a915a4

Please sign in to comment.