Skip to content

Commit 9c881e1

Browse files
authored
Merge pull request #3791 from Vogel612/comment-parsing
Enforce ending NEWLINE on commentBody
2 parents 9002f7e + 7ea8323 commit 9c881e1

File tree

2 files changed

+28
-7
lines changed

2 files changed

+28
-7
lines changed

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -502,8 +502,9 @@ subroutineName : identifier;
502502
// 5.2.3.3 User Defined Type Declarations
503503
publicTypeDeclaration : ((GLOBAL | PUBLIC) whiteSpace)? udtDeclaration;
504504
privateTypeDeclaration : PRIVATE whiteSpace udtDeclaration;
505-
udtDeclaration : TYPE whiteSpace untypedIdentifier endOfStatement udtMemberList endOfStatement END_TYPE;
506-
udtMemberList : udtMember (endOfStatement udtMember)*;
505+
// member list includes trailing endOfStatement
506+
udtDeclaration : TYPE whiteSpace untypedIdentifier endOfStatement udtMemberList END_TYPE;
507+
udtMemberList : (udtMember endOfStatement)+;
507508
udtMember : reservedNameMemberDeclaration | untypedNameMemberDeclaration;
508509
untypedNameMemberDeclaration : untypedIdentifier whiteSpace? optionalArrayClause;
509510
reservedNameMemberDeclaration : unrestrictedIdentifier whiteSpace asTypeClause;
@@ -864,21 +865,24 @@ endOfLine :
864865
| whiteSpace? commentOrAnnotation
865866
;
866867

868+
// we expect endOfStatement to consume all trailing whitespace
867869
endOfStatement :
868-
(endOfLine | (whiteSpace? COLON whiteSpace?))+
870+
(endOfLine whiteSpace? | (whiteSpace? COLON whiteSpace?))+
869871
| whiteSpace? EOF
870872
;
871873

872874
// Annotations must come before comments because of precedence. ANTLR4 matches as much as possible then chooses the one that comes first.
873875
commentOrAnnotation :
874-
annotationList
876+
(annotationList
875877
| remComment
876-
| comment
878+
| comment)
879+
// all comments must end with a logical line. See VBA Language Spec 3.3.1
880+
(NEWLINE | EOF)
877881
;
878882
remComment : REM whiteSpace? commentBody;
879883
comment : SINGLEQUOTE commentBody;
880-
commentBody : (LINE_CONTINUATION | ~NEWLINE)*;
881-
annotationList : SINGLEQUOTE (AT annotation whiteSpace?)+ (whiteSpace? COLON commentBody)?;
884+
commentBody : (~NEWLINE)*;
885+
annotationList : SINGLEQUOTE (AT annotation whiteSpace?)+ (COLON commentBody)?;
882886
annotation : annotationName annotationArgList?;
883887
annotationName : unrestrictedIdentifier;
884888
annotationArgList :

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2180,6 +2180,23 @@ End Sub
21802180
AssertTree(parseResult.Item1, parseResult.Item2, "//variableSubStmt", matches => matches.Count == 1);
21812181
}
21822182

2183+
[Category("Parser")]
2184+
[Test]
2185+
public void UserDefinedType_TreatsFinalCommentAsComment()
2186+
{
2187+
// See Issue #3789
2188+
const string code = @"
2189+
Private Type tX
2190+
foo As String
2191+
bar As Long
2192+
'foobar as shouldNotBeVisible
2193+
End Type
2194+
";
2195+
var parseResult = Parse(code);
2196+
AssertTree(parseResult.Item1, parseResult.Item2, "//udtMember", matches => matches.Count == 2);
2197+
AssertTree(parseResult.Item1, parseResult.Item2, "//commentOrAnnotation", matches => matches.Count == 1);
2198+
}
2199+
21832200
private Tuple<VBAParser, ParserRuleContext> Parse(string code, PredictionMode predictionMode = null)
21842201
{
21852202
var stream = new AntlrInputStream(code);

0 commit comments

Comments
 (0)