Skip to content

Commit

Permalink
Merge pull request #6048 from MDoerner/FixConstantNotUsedForArrayBounds
Browse files Browse the repository at this point in the history
Fix constant not used for array bounds
  • Loading branch information
retailcoder committed Nov 4, 2022
2 parents 4b2f10c + dceed09 commit 97b0b54
Show file tree
Hide file tree
Showing 5 changed files with 37 additions and 10 deletions.
6 changes: 1 addition & 5 deletions Rubberduck.Parsing/Grammar/VBAParser.g4
Original file line number Diff line number Diff line change
Expand Up @@ -561,7 +561,7 @@ constantExpression : expression;

variableStmt : (DIM | STATIC | visibility) whiteSpace variableListStmt;
variableListStmt : variableSubStmt (whiteSpace? COMMA whiteSpace? variableSubStmt)*;
variableSubStmt : (WITHEVENTS whiteSpace)? identifier (whiteSpace? LPAREN whiteSpace? (subscripts whiteSpace?)? RPAREN)? (whiteSpace asTypeClause)?;
variableSubStmt : (WITHEVENTS whiteSpace)? identifier (whiteSpace? arrayDim)? (whiteSpace asTypeClause)?;

whileWendStmt :
WHILE whiteSpace expression endOfStatement
Expand Down Expand Up @@ -589,10 +589,6 @@ pSetSpecialForm : (expression whiteSpace? DOT whiteSpace?)? PSET (whiteSpace STE
tuple : LPAREN whiteSpace? expression whiteSpace? COMMA whiteSpace? expression whiteSpace? RPAREN;
lineSpecialFormOption : {EqualsStringIgnoringCase(TextOf(TokenAtRelativePosition(1)),"b","bf")}? unrestrictedIdentifier;

subscripts : subscript (whiteSpace? COMMA whiteSpace? subscript)*;

subscript : (expression whiteSpace TO whiteSpace)? expression;

unrestrictedIdentifier : identifier | statementKeyword | markerKeyword;
legalLabelIdentifier : { !IsTokenType(TokenTypeAtRelativePosition(1),DOEVENTS,END,CLOSE,ELSE,LOOP,NEXT,RANDOMIZE,REM,RESUME,RETURN,STOP,WEND)}? identifier | markerKeyword;
//The predicate in the following rule has been introduced to lessen the problem that VBA uses the same characters used as type hints in other syntactical constructs,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -688,7 +688,7 @@ public override void EnterVariableSubStmt(VBAParser.VariableSubStmtContext conte
: SymbolList.TypeHintToTypeName[typeHint];
var withEvents = context.WITHEVENTS() != null;
var isAutoObject = asTypeClause != null && asTypeClause.NEW() != null;
bool isArray = context.LPAREN() != null;
bool isArray = context.arrayDim() != null;
AddDeclaration(
CreateDeclaration(
name,
Expand Down
6 changes: 3 additions & 3 deletions Rubberduck.Refactorings/Common/CodeBuilder.cs
Original file line number Diff line number Diff line change
Expand Up @@ -390,9 +390,9 @@ private static string BuildUDTMemberDeclaration(string udtMemberIdentifier, Decl

if (prototype.IsArray)
{
var identifierExpression = prototype.Context.TryGetChildContext<VBAParser.SubscriptsContext>(out var ctxt)
? $"{udtMemberIdentifier}({ctxt.GetText()})"
: $"{udtMemberIdentifier}()";
var identifierExpression = prototype.Context.TryGetChildContext<VBAParser.ArrayDimContext>(out var ctxt)
? $"{udtMemberIdentifier}{ctxt.GetText()}"
: $"{udtMemberIdentifier}()"; // This should never happen.

return $"{identifierExpression} {Tokens.As} {asTypeName}";
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ protected override void Refactor(MoveCloserToUsageModel model, IRewriteSession r

private void InsertNewDeclaration(VariableDeclaration target, IRewriteSession rewriteSession, string DeclarationStatement)
{
var subscripts = target.Context.GetDescendent<VBAParser.SubscriptsContext>()?.GetText() ?? string.Empty;
var subscripts = target.Context.GetDescendent<VBAParser.BoundsListContext>()?.GetText() ?? string.Empty;
var identifier = target.IsArray ? $"{target.IdentifierName}({subscripts})" : target.IdentifierName;

var newVariable = target.AsTypeContext is null
Expand Down
31 changes: 31 additions & 0 deletions RubberduckTests/Inspections/ConstantNotUsedInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,37 @@ End Sub
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
// See issue #6042 at https://github.com/rubberduck-vba/Rubberduck/issues/6042
public void ConstantNotUsed_DoesNotReturnResult_UsedOnlyInArrayUpperBound()
{
var inputCode =
$@"
Sub Test1()
Const MY_CONST As Byte = 5
Dim tmpArr(1 To MY_CONST) As Variant
Dim tmpArr(1 To MY_CONST)
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void ConstantNotUsed_DoesNotReturnResult_UsedOnlyInArrayLowerBound()
{
var inputCode =
$@"
Sub Test1()
Const MY_CONST As Byte = 5
Dim tmpArr(MY_CONST To 1) As Variant
Dim tmpArr(MY_CONST To 1)
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
//See issue #4994 at https://github.com/rubberduck-vba/Rubberduck/issues/4994
Expand Down

0 comments on commit 97b0b54

Please sign in to comment.