Skip to content

Commit c6d3695

Browse files
Andrin Meierretailcoder
authored andcommitted
fix #1668 (#1688)
1 parent 9e4076e commit c6d3695

File tree

2 files changed

+47
-25
lines changed

2 files changed

+47
-25
lines changed

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 23 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -550,44 +550,42 @@ public void Resolve(VBAParser.AsTypeClauseContext context)
550550

551551
public void Resolve(VBAParser.ForNextStmtContext context)
552552
{
553+
// In "For expr1 = expr2" the "expr1 = expr2" part is treated as a single expression.
554+
var assignmentExpr = ((VBAParser.RelationalOpContext)context.expression()[0]);
555+
var lExpr = assignmentExpr.expression()[0];
553556
var firstExpression = _bindingService.ResolveDefault(
554557
_moduleDeclaration,
555558
_currentParent,
556-
context.expression()[0],
559+
lExpr,
557560
GetInnerMostWithExpression(),
558561
StatementResolutionContext.Undefined);
559-
if (firstExpression.Classification == ExpressionClassification.ResolutionFailed)
560-
{
561-
_boundExpressionVisitor.AddIdentifierReferences(
562-
firstExpression,
563-
_qualifiedModuleName,
564-
_currentScope,
565-
_currentParent);
566-
}
567-
else
562+
_boundExpressionVisitor.AddIdentifierReferences(
563+
firstExpression,
564+
_qualifiedModuleName,
565+
_currentScope,
566+
_currentParent);
567+
if (firstExpression.Classification != ExpressionClassification.ResolutionFailed)
568568
{
569-
// In "For expr1 = expr2" the "expr1 = expr2" part is treated as a single expression.
570-
var binOp = (BinaryOpExpression)firstExpression;
571-
var assignmentExpr = binOp.Left;
572-
var fromExpr = binOp.Right;
573569
// each iteration counts as an assignment
574570
_boundExpressionVisitor.AddIdentifierReferences(
575-
assignmentExpr,
571+
firstExpression,
576572
_qualifiedModuleName,
577573
_currentScope,
578574
_currentParent,
579575
true);
580-
_boundExpressionVisitor.AddIdentifierReferences(
581-
assignmentExpr,
582-
_qualifiedModuleName,
583-
_currentScope,
584-
_currentParent);
585-
_boundExpressionVisitor.AddIdentifierReferences(
586-
fromExpr,
587-
_qualifiedModuleName,
588-
_currentScope,
589-
_currentParent);
590576
}
577+
var rExpr = assignmentExpr.expression()[1];
578+
var secondExpression = _bindingService.ResolveDefault(
579+
_moduleDeclaration,
580+
_currentParent,
581+
rExpr,
582+
GetInnerMostWithExpression(),
583+
StatementResolutionContext.Undefined);
584+
_boundExpressionVisitor.AddIdentifierReferences(
585+
secondExpression,
586+
_qualifiedModuleName,
587+
_currentScope,
588+
_currentParent);
591589
for (int exprIndex = 1; exprIndex < context.expression().Count; exprIndex++)
592590
{
593591
ResolveDefault(context.expression()[exprIndex]);

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -752,6 +752,30 @@ End Sub
752752
&& item.IsAssignment));
753753
}
754754

755+
[TestMethod]
756+
public void ForLoop_AddsReferenceEvenIfAssignmentResolutionFailure()
757+
{
758+
// arrange
759+
var code = @"
760+
Public Sub DoSomething()
761+
Dim i As Integer
762+
For i = doesntExist To doesntExistEither
763+
Next
764+
End Sub
765+
";
766+
// act
767+
var state = Resolve(code);
768+
769+
// assert
770+
var declaration = state.AllUserDeclarations.Single(item =>
771+
item.DeclarationType == DeclarationType.Variable && item.IdentifierName == "i");
772+
773+
Assert.IsNotNull(declaration.References.SingleOrDefault(item =>
774+
item.ParentScoping.DeclarationType == DeclarationType.Procedure
775+
&& item.ParentScoping.IdentifierName == "DoSomething"
776+
&& item.IsAssignment));
777+
}
778+
755779
[TestMethod]
756780
public void ForEachLoop_IsReferenceToIteratorDeclaration()
757781
{

0 commit comments

Comments
 (0)