Skip to content

Commit 43221db

Browse files
author
Andrin Meier
committed
add comments to parse tree
1 parent 62e8bd0 commit 43221db

File tree

10 files changed

+28764
-26514
lines changed

10 files changed

+28764
-26514
lines changed

Rubberduck.Parsing/Grammar/VBA.g4

Lines changed: 81 additions & 68 deletions
Original file line numberDiff line numberDiff line change
@@ -98,30 +98,30 @@ grammar VBA;
9898
startRule : module EOF;
9999

100100
module :
101-
WS? NEWLINE*
102-
(moduleHeader NEWLINE+)?
103-
moduleConfig? NEWLINE*
104-
moduleAttributes? NEWLINE*
105-
moduleDeclarations? NEWLINE*
106-
moduleBody? NEWLINE*
107-
WS?
101+
endOfLine*
102+
(moduleHeader endOfLine*)?
103+
moduleConfig? endOfLine*
104+
moduleAttributes? endOfLine*
105+
moduleDeclarations? endOfLine*
106+
moduleBody? endOfLine*
107+
endOfLine*
108108
;
109109

110110
moduleHeader : VERSION WS DOUBLELITERAL WS CLASS;
111111

112112
moduleConfig :
113-
BEGIN NEWLINE+
113+
BEGIN endOfLine*
114114
moduleConfigElement+
115-
END NEWLINE+
115+
END
116116
;
117117

118118
moduleConfigElement :
119-
ambiguousIdentifier WS? EQ WS? literal NEWLINE
119+
ambiguousIdentifier WS? EQ WS? literal endOfLine*
120120
;
121121

122-
moduleAttributes : (attributeStmt NEWLINE+)+;
122+
moduleAttributes : (attributeStmt endOfLine+)+;
123123

124-
moduleDeclarations : moduleDeclarationsElement (NEWLINE+ moduleDeclarationsElement)*;
124+
moduleDeclarations : moduleDeclarationsElement (endOfLine+ moduleDeclarationsElement)*;
125125

126126
moduleOption :
127127
OPTION_BASE WS? SHORTLITERAL # optionBaseStmt
@@ -131,7 +131,8 @@ moduleOption :
131131
;
132132

133133
moduleDeclarationsElement :
134-
declareStmt
134+
comment
135+
| declareStmt
135136
| enumerationStmt
136137
| eventStmt
137138
| constStmt
@@ -144,7 +145,7 @@ moduleDeclarationsElement :
144145
;
145146

146147
moduleBody :
147-
moduleBodyElement (NEWLINE+ moduleBodyElement)*;
148+
moduleBodyElement (endOfStatement moduleBodyElement)* endOfStatement;
148149

149150
moduleBodyElement :
150151
functionStmt
@@ -161,9 +162,10 @@ moduleBodyElement :
161162

162163
attributeStmt : ATTRIBUTE WS implicitCallStmt_InStmt WS? EQ WS? literal (WS? ',' WS? literal)*;
163164

164-
block : blockStmt WS* (NEWLINE* WS? blockStmt)* WS? NEWLINE*;
165+
block : blockStmt (endOfStatement blockStmt)* endOfStatement;
165166

166-
blockStmt : lineLabel
167+
blockStmt :
168+
lineLabel
167169
| appactivateStmt
168170
| attributeStmt
169171
| beepStmt
@@ -265,28 +267,28 @@ deftypeStmt :
265267
deleteSettingStmt : DELETESETTING WS valueStmt WS? ',' WS? valueStmt (WS? ',' WS? valueStmt)?;
266268

267269
doLoopStmt :
268-
DO NEWLINE+
269-
(block NEWLINE+)?
270+
DO endOfStatement
271+
block?
270272
LOOP
271273
|
272-
DO WS (WHILE | UNTIL) WS valueStmt NEWLINE+
273-
(block NEWLINE+)?
274+
DO WS (WHILE | UNTIL) WS valueStmt endOfStatement
275+
block?
274276
LOOP
275277
|
276-
DO NEWLINE+
277-
(block NEWLINE+)
278+
DO endOfStatement
279+
block
278280
LOOP WS (WHILE | UNTIL) WS valueStmt
279281
;
280282

281283
endStmt : END;
282284

283285
enumerationStmt:
284-
(visibility WS)? ENUM WS ambiguousIdentifier NEWLINE+
285-
(enumerationStmt_Constant)*
286+
(visibility WS)? ENUM WS ambiguousIdentifier endOfStatement
287+
enumerationStmt_Constant*
286288
END_ENUM
287289
;
288290

289-
enumerationStmt_Constant : ambiguousIdentifier (WS? EQ WS? valueStmt)? NEWLINE+;
291+
enumerationStmt_Constant : ambiguousIdentifier (WS? EQ WS? valueStmt)? endOfStatement;
290292

291293
eraseStmt : ERASE WS valueStmt;
292294

@@ -299,20 +301,20 @@ exitStmt : EXIT_DO | EXIT_FOR | EXIT_FUNCTION | EXIT_PROPERTY | EXIT_SUB;
299301
filecopyStmt : FILECOPY WS valueStmt WS? ',' WS? valueStmt;
300302

301303
forEachStmt :
302-
FOR WS EACH WS ambiguousIdentifier typeHint? WS IN WS valueStmt NEWLINE+
303-
(block NEWLINE+)?
304+
FOR WS EACH WS ambiguousIdentifier typeHint? WS IN WS valueStmt endOfStatement
305+
block?
304306
NEXT (WS ambiguousIdentifier)?
305307
;
306308

307309
forNextStmt :
308-
FOR WS ambiguousIdentifier typeHint? (WS asTypeClause)? WS? EQ WS? valueStmt WS TO WS valueStmt (WS STEP WS valueStmt)? NEWLINE+
309-
(block NEWLINE+)?
310+
FOR WS ambiguousIdentifier typeHint? (WS asTypeClause)? WS? EQ WS? valueStmt WS TO WS valueStmt (WS STEP WS valueStmt)? endOfStatement
311+
block?
310312
NEXT (WS ambiguousIdentifier)?
311313
;
312314

313315
functionStmt :
314-
(visibility WS)? (STATIC WS)? FUNCTION WS? ambiguousIdentifier typeHint? (WS? argList)? (WS? asTypeClause)? NEWLINE+
315-
(block NEWLINE+)?
316+
(visibility WS)? (STATIC WS)? FUNCTION WS? ambiguousIdentifier typeHint? (WS? argList)? (WS? asTypeClause)? endOfStatement
317+
block?
316318
END_FUNCTION
317319
;
318320

@@ -328,20 +330,20 @@ ifThenElseStmt :
328330
;
329331

330332
ifBlockStmt :
331-
IF WS ifConditionStmt WS THEN NEWLINE+
332-
(block NEWLINE+)?
333+
IF WS ifConditionStmt WS THEN endOfStatement
334+
block?
333335
;
334336

335337
ifConditionStmt : valueStmt;
336338

337339
ifElseIfBlockStmt :
338-
ELSEIF WS ifConditionStmt WS THEN NEWLINE+
339-
(block NEWLINE+)?
340+
ELSEIF WS ifConditionStmt WS THEN endOfStatement
341+
block?
340342
;
341343

342344
ifElseBlockStmt :
343-
ELSE NEWLINE+
344-
(block NEWLINE+)?
345+
ELSE endOfStatement
346+
block?
345347
;
346348

347349
implementsStmt : IMPLEMENTS WS ambiguousIdentifier;
@@ -365,18 +367,18 @@ macroConstStmt : MACRO_CONST WS? ambiguousIdentifier WS? EQ WS? valueStmt;
365367
macroIfThenElseStmt : macroIfBlockStmt macroElseIfBlockStmt* macroElseBlockStmt? MACRO_END_IF;
366368

367369
macroIfBlockStmt :
368-
MACRO_IF WS? ifConditionStmt WS THEN NEWLINE*
369-
((moduleDeclarationsElement | moduleBody | block) NEWLINE*)*
370+
MACRO_IF WS? ifConditionStmt WS THEN endOfStatement
371+
((moduleDeclarationsElement | moduleBody | block) endOfStatement)*
370372
;
371373

372374
macroElseIfBlockStmt :
373-
MACRO_ELSEIF WS? ifConditionStmt WS THEN NEWLINE*
374-
((moduleDeclarationsElement | moduleBody | block) NEWLINE*)*
375+
MACRO_ELSEIF WS? ifConditionStmt WS THEN endOfStatement
376+
((moduleDeclarationsElement | moduleBody | block) endOfStatement)*
375377
;
376378

377379
macroElseBlockStmt :
378-
MACRO_ELSE NEWLINE*
379-
((moduleDeclarationsElement | moduleBody | block) NEWLINE*)*
380+
MACRO_ELSE endOfStatement
381+
((moduleDeclarationsElement | moduleBody | block) endOfStatement)*
380382
;
381383

382384
midStmt : MID WS? LPAREN WS? argsCall WS? RPAREN;
@@ -412,20 +414,20 @@ outputList_Expression :
412414
printStmt : PRINT WS fileNumber WS? ',' (WS? outputList)?;
413415

414416
propertyGetStmt :
415-
(visibility WS)? (STATIC WS)? PROPERTY_GET WS ambiguousIdentifier typeHint? (WS? argList)? (WS asTypeClause)? NEWLINE+
416-
(block NEWLINE+)?
417+
(visibility WS)? (STATIC WS)? PROPERTY_GET WS ambiguousIdentifier typeHint? (WS? argList)? (WS asTypeClause)? endOfStatement
418+
block?
417419
END_PROPERTY
418420
;
419421

420422
propertySetStmt :
421-
(visibility WS)? (STATIC WS)? PROPERTY_SET WS ambiguousIdentifier (WS? argList)? NEWLINE+
422-
(block NEWLINE+)?
423+
(visibility WS)? (STATIC WS)? PROPERTY_SET WS ambiguousIdentifier (WS? argList)? endOfStatement
424+
block?
423425
END_PROPERTY
424426
;
425427

426428
propertyLetStmt :
427-
(visibility WS)? (STATIC WS)? PROPERTY_LET WS ambiguousIdentifier (WS? argList)? NEWLINE+
428-
(block NEWLINE+)?
429+
(visibility WS)? (STATIC WS)? PROPERTY_LET WS ambiguousIdentifier (WS? argList)? endOfStatement
430+
block?
429431
END_PROPERTY
430432
;
431433

@@ -456,20 +458,20 @@ saveSettingStmt : SAVESETTING WS valueStmt WS? ',' WS? valueStmt WS? ',' WS? val
456458
seekStmt : SEEK WS fileNumber WS? ',' WS? valueStmt;
457459

458460
selectCaseStmt :
459-
SELECT WS CASE WS valueStmt NEWLINE+
461+
SELECT WS CASE WS valueStmt endOfStatement
460462
sC_Case*
461-
WS? END_SELECT
463+
END_SELECT
462464
;
463465

464466
sC_Selection :
465-
IS WS? comparisonOperator WS? valueStmt # caseCondIs
467+
IS WS? comparisonOperator WS? valueStmt # caseCondIs
466468
| valueStmt WS TO WS valueStmt # caseCondTo
467-
| valueStmt # caseCondValue
469+
| valueStmt # caseCondValue
468470
;
469471

470472
sC_Case :
471-
CASE WS sC_Cond WS? (':'? NEWLINE*)
472-
(block NEWLINE+)*
473+
CASE WS sC_Cond endOfStatement
474+
block?
473475
;
474476

475477
// ELSE first, so that it is not interpreted as a variable call
@@ -487,20 +489,20 @@ setStmt : SET WS implicitCallStmt_InStmt WS? EQ WS? valueStmt;
487489
stopStmt : STOP;
488490

489491
subStmt :
490-
(visibility WS)? (STATIC WS)? SUB WS? ambiguousIdentifier (WS? argList)? NEWLINE+
491-
(block NEWLINE+)?
492+
(visibility WS)? (STATIC WS)? SUB WS? ambiguousIdentifier (WS? argList)? endOfStatement
493+
block?
492494
END_SUB
493495
;
494496

495497
timeStmt : TIME WS? EQ WS? valueStmt;
496498

497499
typeStmt :
498-
(visibility WS)? TYPE WS ambiguousIdentifier NEWLINE+
499-
(typeStmt_Element)*
500+
(visibility WS)? TYPE WS ambiguousIdentifier endOfStatement
501+
typeStmt_Element*
500502
END_TYPE
501503
;
502504

503-
typeStmt_Element : ambiguousIdentifier (WS? LPAREN (WS? subscripts)? WS? RPAREN)? (WS asTypeClause)? NEWLINE+;
505+
typeStmt_Element : ambiguousIdentifier (WS? LPAREN (WS? subscripts)? WS? RPAREN)? (WS asTypeClause)? endOfStatement;
504506

505507
typeOfStmt : TYPEOF WS valueStmt (WS IS WS type)?;
506508

@@ -553,16 +555,16 @@ variableListStmt : variableSubStmt (WS? ',' WS? variableSubStmt)*;
553555
variableSubStmt : ambiguousIdentifier (WS? LPAREN WS? (subscripts WS?)? RPAREN WS?)? typeHint? (WS asTypeClause)?;
554556

555557
whileWendStmt :
556-
WHILE WS valueStmt NEWLINE+
557-
(block NEWLINE)*
558+
WHILE WS valueStmt endOfStatement
559+
block?
558560
WEND
559561
;
560562

561563
widthStmt : WIDTH WS fileNumber WS? ',' WS? valueStmt;
562564

563565
withStmt :
564-
WITH WS (implicitCallStmt_InStmt | (NEW WS type)) NEWLINE+
565-
(block NEWLINE+)?
566+
WITH WS (implicitCallStmt_InStmt | (NEW WS type)) endOfStatement
567+
block?
566568
END_WITH
567569
;
568570

@@ -675,7 +677,6 @@ typeHint : '&' | '%' | '#' | '!' | '@' | '$';
675677

676678
visibility : PRIVATE | PUBLIC | FRIEND | GLOBAL;
677679

678-
679680
// ambiguous keywords
680681
ambiguousKeyword :
681682
ACCESS | ADDRESSOF | ALIAS | AND | ATTRIBUTE | APPACTIVATE | APPEND | AS |
@@ -701,6 +702,14 @@ ambiguousKeyword :
701702
XOR
702703
;
703704

705+
remComment : REMCOMMENT;
706+
707+
comment : COMMENT;
708+
709+
endOfLine : WS? (NEWLINE | comment | remComment) WS?;
710+
711+
endOfStatement : (endOfLine | WS? COLON WS?)*;
712+
704713

705714
// lexer rules --------------------------------------------------------------------------------
706715

@@ -928,9 +937,13 @@ fragment TIMESEPARATOR : WS? (':' | '.') WS?;
928937
fragment AMPM : WS? (A M | P M | A | P);
929938
930939
// whitespace, line breaks, comments, ...
931-
LINE_CONTINUATION : [ \t]+ '_' '\r'? '\n' -> skip;
932-
NEWLINE : (':' WS?) | (WS? ('\r'? '\n') WS?);
933-
COMMENT : WS? ('\'' | ':'? REM WS) (LINE_CONTINUATION | ~('\n' | '\r'))* -> skip;
940+
LINE_CONTINUATION : [ \t]+ UNDERSCORE '\r'? '\n' -> skip;
941+
NEWLINE : [\r\n\u2028\u2029]+;
942+
REMCOMMENT : COLON? REM WS (LINE_CONTINUATION | ~[\r\n\u2028\u2029])*;
943+
COMMENT : SINGLEQUOTE (LINE_CONTINUATION | ~[\r\n\u2028\u2029])*;
944+
SINGLEQUOTE : '\'';
945+
COLON : ':';
946+
UNDERSCORE : '_';
934947
WS : ([ \t] | LINE_CONTINUATION)+;
935948

936949
// identifier

0 commit comments

Comments
 (0)