@@ -98,30 +98,30 @@ grammar VBA;
98
98
startRule : module EOF ;
99
99
100
100
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*
108
108
;
109
109
110
110
moduleHeader : VERSION WS DOUBLELITERAL WS CLASS ;
111
111
112
112
moduleConfig :
113
- BEGIN NEWLINE +
113
+ BEGIN endOfLine*
114
114
moduleConfigElement+
115
- END NEWLINE +
115
+ END
116
116
;
117
117
118
118
moduleConfigElement :
119
- ambiguousIdentifier WS ? EQ WS ? literal NEWLINE
119
+ ambiguousIdentifier WS ? EQ WS ? literal endOfLine*
120
120
;
121
121
122
- moduleAttributes : (attributeStmt NEWLINE +)+;
122
+ moduleAttributes : (attributeStmt endOfLine +)+;
123
123
124
- moduleDeclarations : moduleDeclarationsElement (NEWLINE + moduleDeclarationsElement)*;
124
+ moduleDeclarations : moduleDeclarationsElement (endOfLine + moduleDeclarationsElement)*;
125
125
126
126
moduleOption :
127
127
OPTION_BASE WS ? SHORTLITERAL # optionBaseStmt
@@ -131,7 +131,8 @@ moduleOption :
131
131
;
132
132
133
133
moduleDeclarationsElement :
134
- declareStmt
134
+ comment
135
+ | declareStmt
135
136
| enumerationStmt
136
137
| eventStmt
137
138
| constStmt
@@ -144,7 +145,7 @@ moduleDeclarationsElement :
144
145
;
145
146
146
147
moduleBody :
147
- moduleBodyElement (NEWLINE + moduleBodyElement)*;
148
+ moduleBodyElement (endOfStatement moduleBodyElement)* endOfStatement ;
148
149
149
150
moduleBodyElement :
150
151
functionStmt
@@ -161,9 +162,10 @@ moduleBodyElement :
161
162
162
163
attributeStmt : ATTRIBUTE WS implicitCallStmt_InStmt WS ? EQ WS ? literal (WS ? ' ,' WS ? literal)*;
163
164
164
- block : blockStmt WS * ( NEWLINE * WS ? blockStmt)* WS ? NEWLINE * ;
165
+ block : blockStmt (endOfStatement blockStmt)* endOfStatement ;
165
166
166
- blockStmt : lineLabel
167
+ blockStmt :
168
+ lineLabel
167
169
| appactivateStmt
168
170
| attributeStmt
169
171
| beepStmt
@@ -265,28 +267,28 @@ deftypeStmt :
265
267
deleteSettingStmt : DELETESETTING WS valueStmt WS ? ' ,' WS ? valueStmt (WS ? ' ,' WS ? valueStmt)?;
266
268
267
269
doLoopStmt :
268
- DO NEWLINE +
269
- ( block NEWLINE +)?
270
+ DO endOfStatement
271
+ block?
270
272
LOOP
271
273
|
272
- DO WS (WHILE | UNTIL ) WS valueStmt NEWLINE +
273
- ( block NEWLINE +)?
274
+ DO WS (WHILE | UNTIL ) WS valueStmt endOfStatement
275
+ block?
274
276
LOOP
275
277
|
276
- DO NEWLINE +
277
- ( block NEWLINE +)
278
+ DO endOfStatement
279
+ block
278
280
LOOP WS (WHILE | UNTIL ) WS valueStmt
279
281
;
280
282
281
283
endStmt : END ;
282
284
283
285
enumerationStmt :
284
- (visibility WS )? ENUM WS ambiguousIdentifier NEWLINE +
285
- ( enumerationStmt_Constant) *
286
+ (visibility WS )? ENUM WS ambiguousIdentifier endOfStatement
287
+ enumerationStmt_Constant*
286
288
END_ENUM
287
289
;
288
290
289
- enumerationStmt_Constant : ambiguousIdentifier (WS ? EQ WS ? valueStmt)? NEWLINE + ;
291
+ enumerationStmt_Constant : ambiguousIdentifier (WS ? EQ WS ? valueStmt)? endOfStatement ;
290
292
291
293
eraseStmt : ERASE WS valueStmt;
292
294
@@ -299,20 +301,20 @@ exitStmt : EXIT_DO | EXIT_FOR | EXIT_FUNCTION | EXIT_PROPERTY | EXIT_SUB;
299
301
filecopyStmt : FILECOPY WS valueStmt WS ? ' ,' WS ? valueStmt;
300
302
301
303
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?
304
306
NEXT (WS ambiguousIdentifier)?
305
307
;
306
308
307
309
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?
310
312
NEXT (WS ambiguousIdentifier)?
311
313
;
312
314
313
315
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?
316
318
END_FUNCTION
317
319
;
318
320
@@ -328,20 +330,20 @@ ifThenElseStmt :
328
330
;
329
331
330
332
ifBlockStmt :
331
- IF WS ifConditionStmt WS THEN NEWLINE +
332
- ( block NEWLINE +) ?
333
+ IF WS ifConditionStmt WS THEN endOfStatement
334
+ block?
333
335
;
334
336
335
337
ifConditionStmt : valueStmt;
336
338
337
339
ifElseIfBlockStmt :
338
- ELSEIF WS ifConditionStmt WS THEN NEWLINE +
339
- ( block NEWLINE +) ?
340
+ ELSEIF WS ifConditionStmt WS THEN endOfStatement
341
+ block?
340
342
;
341
343
342
344
ifElseBlockStmt :
343
- ELSE NEWLINE +
344
- ( block NEWLINE +) ?
345
+ ELSE endOfStatement
346
+ block?
345
347
;
346
348
347
349
implementsStmt : IMPLEMENTS WS ambiguousIdentifier;
@@ -365,18 +367,18 @@ macroConstStmt : MACRO_CONST WS? ambiguousIdentifier WS? EQ WS? valueStmt;
365
367
macroIfThenElseStmt : macroIfBlockStmt macroElseIfBlockStmt* macroElseBlockStmt? MACRO_END_IF ;
366
368
367
369
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 )*
370
372
;
371
373
372
374
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 )*
375
377
;
376
378
377
379
macroElseBlockStmt :
378
- MACRO_ELSE NEWLINE *
379
- ((moduleDeclarationsElement | moduleBody | block) NEWLINE * )*
380
+ MACRO_ELSE endOfStatement
381
+ ((moduleDeclarationsElement | moduleBody | block) endOfStatement )*
380
382
;
381
383
382
384
midStmt : MID WS ? LPAREN WS ? argsCall WS ? RPAREN ;
@@ -412,20 +414,20 @@ outputList_Expression :
412
414
printStmt : PRINT WS fileNumber WS ? ' ,' (WS ? outputList)?;
413
415
414
416
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?
417
419
END_PROPERTY
418
420
;
419
421
420
422
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?
423
425
END_PROPERTY
424
426
;
425
427
426
428
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?
429
431
END_PROPERTY
430
432
;
431
433
@@ -456,20 +458,20 @@ saveSettingStmt : SAVESETTING WS valueStmt WS? ',' WS? valueStmt WS? ',' WS? val
456
458
seekStmt : SEEK WS fileNumber WS ? ' ,' WS ? valueStmt;
457
459
458
460
selectCaseStmt :
459
- SELECT WS CASE WS valueStmt NEWLINE +
461
+ SELECT WS CASE WS valueStmt endOfStatement
460
462
sC_Case*
461
- WS ? END_SELECT
463
+ END_SELECT
462
464
;
463
465
464
466
sC_Selection :
465
- IS WS ? comparisonOperator WS ? valueStmt # caseCondIs
467
+ IS WS ? comparisonOperator WS ? valueStmt # caseCondIs
466
468
| valueStmt WS TO WS valueStmt # caseCondTo
467
- | valueStmt # caseCondValue
469
+ | valueStmt # caseCondValue
468
470
;
469
471
470
472
sC_Case :
471
- CASE WS sC_Cond WS ? ( ' : ' ? NEWLINE *)
472
- ( block NEWLINE +)*
473
+ CASE WS sC_Cond endOfStatement
474
+ block?
473
475
;
474
476
475
477
// 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;
487
489
stopStmt : STOP ;
488
490
489
491
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?
492
494
END_SUB
493
495
;
494
496
495
497
timeStmt : TIME WS ? EQ WS ? valueStmt;
496
498
497
499
typeStmt :
498
- (visibility WS )? TYPE WS ambiguousIdentifier NEWLINE +
499
- ( typeStmt_Element) *
500
+ (visibility WS )? TYPE WS ambiguousIdentifier endOfStatement
501
+ typeStmt_Element*
500
502
END_TYPE
501
503
;
502
504
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 ;
504
506
505
507
typeOfStmt : TYPEOF WS valueStmt (WS IS WS type)?;
506
508
@@ -553,16 +555,16 @@ variableListStmt : variableSubStmt (WS? ',' WS? variableSubStmt)*;
553
555
variableSubStmt : ambiguousIdentifier (WS ? LPAREN WS ? (subscripts WS ?)? RPAREN WS ?)? typeHint? (WS asTypeClause)?;
554
556
555
557
whileWendStmt :
556
- WHILE WS valueStmt NEWLINE +
557
- ( block NEWLINE )*
558
+ WHILE WS valueStmt endOfStatement
559
+ block?
558
560
WEND
559
561
;
560
562
561
563
widthStmt : WIDTH WS fileNumber WS ? ' ,' WS ? valueStmt;
562
564
563
565
withStmt :
564
- WITH WS (implicitCallStmt_InStmt | (NEW WS type)) NEWLINE +
565
- ( block NEWLINE +) ?
566
+ WITH WS (implicitCallStmt_InStmt | (NEW WS type)) endOfStatement
567
+ block?
566
568
END_WITH
567
569
;
568
570
@@ -675,7 +677,6 @@ typeHint : '&' | '%' | '#' | '!' | '@' | '$';
675
677
676
678
visibility : PRIVATE | PUBLIC | FRIEND | GLOBAL ;
677
679
678
-
679
680
// ambiguous keywords
680
681
ambiguousKeyword :
681
682
ACCESS | ADDRESSOF | ALIAS | AND | ATTRIBUTE | APPACTIVATE | APPEND | AS |
@@ -701,6 +702,14 @@ ambiguousKeyword :
701
702
XOR
702
703
;
703
704
705
+ remComment : REMCOMMENT ;
706
+
707
+ comment : COMMENT ;
708
+
709
+ endOfLine : WS ? (NEWLINE | comment | remComment) WS ?;
710
+
711
+ endOfStatement : (endOfLine | WS ? COLON WS ?)*;
712
+
704
713
705
714
// lexer rules --------------------------------------------------------------------------------
706
715
@@ -928,9 +937,13 @@ fragment TIMESEPARATOR : WS? (':' | '.') WS?;
928
937
fragment AMPM : WS? (A M | P M | A | P);
929
938
930
939
// 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 : ' _' ;
934
947
WS : ([ \t] | LINE_CONTINUATION )+;
935
948
936
949
// identifier
0 commit comments