diff --git a/Rubberduck.Parsing/Grammar/VBAParser.g4 b/Rubberduck.Parsing/Grammar/VBAParser.g4 index c968dccee9..01c7efa0bb 100644 --- a/Rubberduck.Parsing/Grammar/VBAParser.g4 +++ b/Rubberduck.Parsing/Grammar/VBAParser.g4 @@ -421,7 +421,7 @@ elseBlock : // 5.4.2.9 Single-line If Statement singleLineIfStmt : ifWithNonEmptyThen | ifWithEmptyThen; ifWithNonEmptyThen : IF whiteSpace? booleanExpression whiteSpace? THEN whiteSpace? listOrLabel (whiteSpace singleLineElseClause)?; -ifWithEmptyThen : IF whiteSpace? booleanExpression whiteSpace? THEN whiteSpace? emptyThenStatement? singleLineElseClause?; +ifWithEmptyThen : IF whiteSpace? booleanExpression whiteSpace? THEN whiteSpace? (emptyThenStatement singleLineElseClause? | singleLineElseClause); singleLineElseClause : ELSE whiteSpace? listOrLabel?; // lineNumberLabel should actually be "statement-label" according to MS VBAL but they only allow lineNumberLabels: @@ -543,12 +543,13 @@ subroutineName : identifier; // 5.2.3.3 User Defined Type Declarations // member list includes trailing endOfStatement +// To support actual VBA behaviour, had to change optionalArrayClause to allow a standalone arrayDim without the asTypeClause - see issue #6194 udtDeclaration : (visibility whiteSpace)? TYPE whiteSpace untypedIdentifier endOfStatement udtMemberList END_TYPE; udtMemberList : (udtMember endOfStatement)+; udtMember : reservedNameMemberDeclaration | untypedNameMemberDeclaration; untypedNameMemberDeclaration : untypedIdentifier whiteSpace? optionalArrayClause; reservedNameMemberDeclaration : unrestrictedIdentifier whiteSpace asTypeClause; -optionalArrayClause : (arrayDim whiteSpace)? asTypeClause; +optionalArrayClause : ((arrayDim whiteSpace)? asTypeClause | arrayDim); // 5.2.3.1.3 Array Dimensions and Bounds arrayDim : LPAREN whiteSpace? boundsList? whiteSpace? RPAREN; diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs index 85c822f548..c625cee9a1 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs @@ -321,7 +321,10 @@ public void Resolve(VBAParser.SingleLineIfStmtContext context) if (context.ifWithEmptyThen() != null) { ResolveDefault(context.ifWithEmptyThen().booleanExpression()); - ResolveListOrLabel(context.ifWithEmptyThen().singleLineElseClause().listOrLabel()); + if (context.ifWithEmptyThen().singleLineElseClause() != null) + { + ResolveListOrLabel(context.ifWithEmptyThen().singleLineElseClause().listOrLabel()); + } } else { diff --git a/RubberduckTests/Grammar/VBAParserTests.cs b/RubberduckTests/Grammar/VBAParserTests.cs index 5fb1c2320b..3e12be0ed3 100644 --- a/RubberduckTests/Grammar/VBAParserTests.cs +++ b/RubberduckTests/Grammar/VBAParserTests.cs @@ -4032,6 +4032,32 @@ public void ParserCanDealWithStatementSeparateorsInOneLineIfStatements(string on AssertTree(parseResult.Item1, parseResult.Item2, "//singleLineIfStmt", matches => matches.Count == 1); } + // Adapted from opened issue https://github.com/rubberduck-vba/Rubberduck/issues/6187 + [Test] + public void OneLineIfStatementNotMistakenForIfStatement() + { + string code = @" +Sub Test() + If True Then: A = 1 + If False Then + A = 5 + End If +End Sub"; + var parseResult = Parse(code); + AssertTree(parseResult.Item1, parseResult.Item2, "//singleLineIfStmt", matches => matches.Count == 1); + } + + // Adapted from opened issue https://github.com/rubberduck-vba/Rubberduck/issues/6194 + [Test] + public void UDTMemberCanHaveArrayWithoutType() + { + string code = @" +Type Test + A(0 To 2) +End Type"; + var parseResult = Parse(code); + AssertTree(parseResult.Item1, parseResult.Item2, "//untypedNameMemberDeclaration", matches => matches.Count == 1); + } // Adapted from opened issue https://github.com/rubberduck-vba/Rubberduck/issues/4875 [Test]