@@ -24,15 +24,15 @@ options { tokenVocab = VBALexer; }
24
24
startRule : module EOF ;
25
25
26
26
module :
27
- endOfStatement
27
+ endOfStatement
28
28
moduleAttributes
29
- moduleHeader?
29
+ moduleHeader?
30
30
moduleAttributes
31
- moduleConfig?
32
- moduleAttributes
33
- moduleDeclarations
31
+ moduleConfig?
34
32
moduleAttributes
35
- moduleBody
33
+ moduleDeclarations
34
+ moduleAttributes
35
+ moduleBody
36
36
moduleAttributes
37
37
// A module can consist of WS as well as line continuations only.
38
38
whiteSpace?
@@ -41,13 +41,13 @@ module :
41
41
moduleHeader : VERSION whiteSpace numberLiteral whiteSpace? CLASS ? endOfStatement;
42
42
43
43
moduleConfig :
44
- BEGIN (whiteSpace GUIDLITERAL whiteSpace unrestrictedIdentifier whiteSpace?)? endOfStatement
45
- moduleConfigElement+
46
- END endOfStatement
44
+ BEGIN (whiteSpace GUIDLITERAL whiteSpace unrestrictedIdentifier whiteSpace?)? endOfStatement
45
+ moduleConfigElement+
46
+ END endOfStatement
47
47
;
48
48
49
49
moduleConfigElement :
50
- unrestrictedIdentifier whiteSpace* EQ whiteSpace* expression (COLON numberLiteral)? endOfStatement
50
+ unrestrictedIdentifier whiteSpace* EQ whiteSpace* expression (COLON numberLiteral)? endOfStatement
51
51
;
52
52
53
53
moduleAttributes : (attributeStmt endOfStatement)*;
@@ -58,71 +58,73 @@ attributeValue : expression;
58
58
moduleDeclarations : (moduleDeclarationsElement endOfStatement)*;
59
59
60
60
moduleOption :
61
- OPTION_BASE whiteSpace numberLiteral # optionBaseStmt
62
- | OPTION_COMPARE whiteSpace (BINARY | TEXT | DATABASE ) # optionCompareStmt
63
- | OPTION_EXPLICIT # optionExplicitStmt
64
- | OPTION_PRIVATE_MODULE # optionPrivateModuleStmt
61
+ OPTION_BASE whiteSpace numberLiteral # optionBaseStmt
62
+ | OPTION_COMPARE whiteSpace (BINARY | TEXT | DATABASE ) # optionCompareStmt
63
+ | OPTION_EXPLICIT # optionExplicitStmt
64
+ | OPTION_PRIVATE_MODULE # optionPrivateModuleStmt
65
65
;
66
66
67
67
moduleDeclarationsElement :
68
- attributeStmt
68
+ whiteSpace?
69
+ (attributeStmt
69
70
| declareStmt
70
71
| defDirective
71
- | enumerationStmt
72
- | eventStmt
73
- | constStmt
74
- | implementsStmt
75
- | variableStmt
76
- | moduleOption
77
- | typeStmt
72
+ | enumerationStmt
73
+ | eventStmt
74
+ | constStmt
75
+ | implementsStmt
76
+ | variableStmt
77
+ | moduleOption
78
+ | typeStmt)
78
79
;
79
80
80
81
moduleBody :
81
- (moduleBodyElement endOfStatement)*;
82
+ whiteSpace?
83
+ (moduleBodyElement endOfStatement)*;
82
84
83
85
moduleBodyElement :
84
- functionStmt
85
- | propertyGetStmt
86
- | propertySetStmt
87
- | propertyLetStmt
88
- | subStmt
86
+ functionStmt
87
+ | propertyGetStmt
88
+ | propertySetStmt
89
+ | propertyLetStmt
90
+ | subStmt
89
91
;
90
92
91
93
block : (blockStmt endOfStatement)*;
92
94
93
95
blockStmt :
94
- statementLabelDefinition
96
+ statementLabelDefinition
95
97
| fileStmt
96
- | attributeStmt
97
- | constStmt
98
- | doLoopStmt
98
+ | attributeStmt
99
+ | constStmt
100
+ | doLoopStmt
99
101
| endStmt
100
- | eraseStmt
101
- | errorStmt
102
+ | eraseStmt
103
+ | errorStmt
102
104
| exitStmt
103
- | forEachStmt
104
- | forNextStmt
105
- | goSubStmt
106
- | goToStmt
107
- | ifStmt
105
+ | forEachStmt
106
+ | forNextStmt
107
+ | goSubStmt
108
+ | goToStmt
109
+ | ifStmt
108
110
| singleLineIfStmt
109
- | implementsStmt
110
- | letStmt
111
- | lsetStmt
112
- | onErrorStmt
113
- | onGoToStmt
114
- | onGoSubStmt
115
- | raiseEventStmt
116
- | redimStmt
117
- | resumeStmt
118
- | returnStmt
119
- | rsetStmt
120
- | selectCaseStmt
121
- | setStmt
111
+ | implementsStmt
112
+ | letStmt
113
+ | lsetStmt
114
+ | onErrorStmt
115
+ | onGoToStmt
116
+ | onGoSubStmt
117
+ | raiseEventStmt
118
+ | redimStmt
119
+ | resumeStmt
120
+ | returnStmt
121
+ | rsetStmt
122
+ | selectCaseStmt
123
+ | setStmt
122
124
| stopStmt
123
- | variableStmt
124
- | whileWendStmt
125
- | withStmt
125
+ | variableStmt
126
+ | whileWendStmt
127
+ | withStmt
126
128
| circleSpecialForm
127
129
| scaleSpecialForm
128
130
| callStmt
@@ -264,9 +266,9 @@ argDefaultValue : EQ whiteSpace? expression;
264
266
// 5.2.2 Implicit Definition Directives
265
267
defDirective : defType whiteSpace letterSpec (whiteSpace? COMMA whiteSpace? letterSpec)*;
266
268
defType :
267
- DEFBOOL | DEFBYTE | DEFINT | DEFLNG | DEFLNGLNG | DEFLNGPTR | DEFCUR |
268
- DEFSNG | DEFDBL | DEFDATE |
269
- DEFSTR | DEFOBJ | DEFVAR
269
+ DEFBOOL | DEFBYTE | DEFINT | DEFLNG | DEFLNGLNG | DEFLNGPTR | DEFCUR |
270
+ DEFSNG | DEFDBL | DEFDATE |
271
+ DEFSTR | DEFOBJ | DEFVAR
270
272
;
271
273
// universalLetterRange must appear before letterRange because they both match the same amount in the case of A-Z but we prefer the universalLetterRange.
272
274
letterSpec : singleLetter | universalLetterRange | letterRange;
@@ -284,23 +286,23 @@ firstLetter : unrestrictedIdentifier;
284
286
lastLetter : unrestrictedIdentifier;
285
287
286
288
doLoopStmt :
287
- DO endOfStatement
288
- block
289
- LOOP
290
- |
291
- DO whiteSpace (WHILE | UNTIL ) whiteSpace expression endOfStatement
292
- block
293
- LOOP
294
- |
295
- DO endOfStatement
296
- block
297
- LOOP whiteSpace (WHILE | UNTIL ) whiteSpace expression
289
+ DO endOfStatement
290
+ block
291
+ LOOP
292
+ |
293
+ DO whiteSpace (WHILE | UNTIL ) whiteSpace expression endOfStatement
294
+ block
295
+ LOOP
296
+ |
297
+ DO endOfStatement
298
+ block
299
+ LOOP whiteSpace (WHILE | UNTIL ) whiteSpace expression
298
300
;
299
301
300
302
enumerationStmt :
301
- (visibility whiteSpace)? ENUM whiteSpace identifier endOfStatement
302
- enumerationStmt_Constant*
303
- END_ENUM
303
+ (visibility whiteSpace)? ENUM whiteSpace identifier endOfStatement
304
+ enumerationStmt_Constant*
305
+ END_ENUM
304
306
;
305
307
306
308
enumerationStmt_Constant : identifier (whiteSpace? EQ whiteSpace? expression)? endOfStatement;
@@ -317,22 +319,22 @@ eventStmt : (visibility whiteSpace)? EVENT whiteSpace identifier whiteSpace? arg
317
319
exitStmt : EXIT_DO | EXIT_FOR | EXIT_FUNCTION | EXIT_PROPERTY | EXIT_SUB ;
318
320
319
321
forEachStmt :
320
- FOR whiteSpace EACH whiteSpace expression whiteSpace IN whiteSpace expression endOfStatement
321
- block
322
- NEXT (whiteSpace expression)?
322
+ FOR whiteSpace EACH whiteSpace expression whiteSpace IN whiteSpace expression endOfStatement
323
+ block
324
+ NEXT (whiteSpace expression)?
323
325
;
324
326
325
327
// expression EQ expression refactored to expression to allow SLL
326
328
forNextStmt :
327
- FOR whiteSpace expression whiteSpace TO whiteSpace expression (whiteSpace STEP whiteSpace expression)? endOfStatement
328
- block
329
- NEXT (whiteSpace expression)?
329
+ FOR whiteSpace expression whiteSpace TO whiteSpace expression (whiteSpace STEP whiteSpace expression)? endOfStatement
330
+ block
331
+ NEXT (whiteSpace expression)?
330
332
;
331
333
332
334
functionStmt :
333
- (visibility whiteSpace)? (STATIC whiteSpace)? FUNCTION whiteSpace? functionName (whiteSpace? argList)? (whiteSpace? asTypeClause)? endOfStatement
334
- block
335
- END_FUNCTION
335
+ (visibility whiteSpace)? (STATIC whiteSpace)? FUNCTION whiteSpace? functionName (whiteSpace? argList)? (whiteSpace? asTypeClause)? endOfStatement
336
+ block
337
+ END_FUNCTION
336
338
;
337
339
functionName : identifier;
338
340
@@ -386,21 +388,21 @@ onGoToStmt : ON whiteSpace expression whiteSpace GOTO whiteSpace expression (whi
386
388
onGoSubStmt : ON whiteSpace expression whiteSpace GOSUB whiteSpace expression (whiteSpace? COMMA whiteSpace? expression)*;
387
389
388
390
propertyGetStmt :
389
- (visibility whiteSpace)? (STATIC whiteSpace)? PROPERTY_GET whiteSpace functionName (whiteSpace? argList)? (whiteSpace asTypeClause)? endOfStatement
390
- block
391
- END_PROPERTY
391
+ (visibility whiteSpace)? (STATIC whiteSpace)? PROPERTY_GET whiteSpace functionName (whiteSpace? argList)? (whiteSpace asTypeClause)? endOfStatement
392
+ block
393
+ END_PROPERTY
392
394
;
393
395
394
396
propertySetStmt :
395
- (visibility whiteSpace)? (STATIC whiteSpace)? PROPERTY_SET whiteSpace subroutineName (whiteSpace? argList)? endOfStatement
396
- block
397
- END_PROPERTY
397
+ (visibility whiteSpace)? (STATIC whiteSpace)? PROPERTY_SET whiteSpace subroutineName (whiteSpace? argList)? endOfStatement
398
+ block
399
+ END_PROPERTY
398
400
;
399
401
400
402
propertyLetStmt :
401
- (visibility whiteSpace)? (STATIC whiteSpace)? PROPERTY_LET whiteSpace subroutineName (whiteSpace? argList)? endOfStatement
402
- block
403
- END_PROPERTY
403
+ (visibility whiteSpace)? (STATIC whiteSpace)? PROPERTY_LET whiteSpace subroutineName (whiteSpace? argList)? endOfStatement
404
+ block
405
+ END_PROPERTY
404
406
;
405
407
406
408
// 5.4.2.20 RaiseEvent Statement
@@ -454,16 +456,16 @@ selectEndValue : expression;
454
456
setStmt : SET whiteSpace lExpression whiteSpace? EQ whiteSpace? expression;
455
457
456
458
subStmt :
457
- (visibility whiteSpace)? (STATIC whiteSpace)? SUB whiteSpace? subroutineName (whiteSpace? argList)? endOfStatement
458
- block
459
- END_SUB
459
+ (visibility whiteSpace)? (STATIC whiteSpace)? SUB whiteSpace? subroutineName (whiteSpace? argList)? endOfStatement
460
+ block
461
+ END_SUB
460
462
;
461
463
subroutineName : identifier;
462
464
463
465
typeStmt :
464
- (visibility whiteSpace)? TYPE whiteSpace identifier endOfStatement
465
- typeStmt_Element*
466
- END_TYPE
466
+ (visibility whiteSpace)? TYPE whiteSpace identifier endOfStatement
467
+ typeStmt_Element*
468
+ END_TYPE
467
469
;
468
470
469
471
typeStmt_Element : identifier (whiteSpace? LPAREN (whiteSpace? subscripts)? whiteSpace? RPAREN )? (whiteSpace asTypeClause)? endOfStatement;
@@ -473,15 +475,15 @@ variableListStmt : variableSubStmt (whiteSpace? COMMA whiteSpace? variableSubStm
473
475
variableSubStmt : identifier (whiteSpace? LPAREN whiteSpace? (subscripts whiteSpace?)? RPAREN whiteSpace?)? (whiteSpace asTypeClause)?;
474
476
475
477
whileWendStmt :
476
- WHILE whiteSpace expression endOfStatement
477
- block
478
- WEND
478
+ WHILE whiteSpace expression endOfStatement
479
+ block
480
+ WEND
479
481
;
480
482
481
483
withStmt :
482
- WITH whiteSpace expression endOfStatement
483
- block
484
- END_WITH
484
+ WITH whiteSpace expression endOfStatement
485
+ block
486
+ END_WITH
485
487
;
486
488
487
489
// Special forms with special syntax, only available in a report.
@@ -533,20 +535,20 @@ expression :
533
535
| LPAREN whiteSpace? expression whiteSpace? RPAREN # parenthesizedExpr
534
536
| TYPEOF whiteSpace expression # typeofexpr // To make the grammar SLL, the type-of-is-expression is actually the child of an IS relational op.
535
537
| NEW whiteSpace expression # newExpr
536
- | expression whiteSpace? POW whiteSpace? expression # powOp
537
- | MINUS whiteSpace? expression # unaryMinusOp
538
- | expression whiteSpace? (MULT | DIV ) whiteSpace? expression # multOp
539
- | expression whiteSpace? INTDIV whiteSpace? expression # intDivOp
540
- | expression whiteSpace? MOD whiteSpace? expression # modOp
541
- | expression whiteSpace? (PLUS | MINUS ) whiteSpace? expression # addOp
542
- | expression whiteSpace? AMPERSAND whiteSpace? expression # concatOp
543
- | expression whiteSpace? (EQ | NEQ | LT | GT | LEQ | GEQ | LIKE | IS ) whiteSpace? expression # relationalOp
544
- | NOT whiteSpace? expression # logicalNotOp
545
- | expression whiteSpace? AND whiteSpace? expression # logicalAndOp
546
- | expression whiteSpace? OR whiteSpace? expression # logicalOrOp
547
- | expression whiteSpace? XOR whiteSpace? expression # logicalXorOp
548
- | expression whiteSpace? EQV whiteSpace? expression # logicalEqvOp
549
- | expression whiteSpace? IMP whiteSpace? expression # logicalImpOp
538
+ | expression whiteSpace? POW whiteSpace? expression # powOp
539
+ | MINUS whiteSpace? expression # unaryMinusOp
540
+ | expression whiteSpace? (MULT | DIV ) whiteSpace? expression # multOp
541
+ | expression whiteSpace? INTDIV whiteSpace? expression # intDivOp
542
+ | expression whiteSpace? MOD whiteSpace? expression # modOp
543
+ | expression whiteSpace? (PLUS | MINUS ) whiteSpace? expression # addOp
544
+ | expression whiteSpace? AMPERSAND whiteSpace? expression # concatOp
545
+ | expression whiteSpace? (EQ | NEQ | LT | GT | LEQ | GEQ | LIKE | IS ) whiteSpace? expression # relationalOp
546
+ | NOT whiteSpace? expression # logicalNotOp
547
+ | expression whiteSpace? AND whiteSpace? expression # logicalAndOp
548
+ | expression whiteSpace? OR whiteSpace? expression # logicalOrOp
549
+ | expression whiteSpace? XOR whiteSpace? expression # logicalXorOp
550
+ | expression whiteSpace? EQV whiteSpace? expression # logicalEqvOp
551
+ | expression whiteSpace? IMP whiteSpace? expression # logicalImpOp
550
552
| HASH expression # markedFileNumberExpr // Added to support special forms such as Input(file1, #file1)
551
553
;
552
554
@@ -815,11 +817,11 @@ annotationList : SINGLEQUOTE (AT annotation whiteSpace?)+;
815
817
annotation : annotationName annotationArgList?;
816
818
annotationName : unrestrictedIdentifier;
817
819
annotationArgList :
818
- whiteSpace annotationArg
819
- | whiteSpace annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+
820
- | whiteSpace? LPAREN whiteSpace? RPAREN
821
- | whiteSpace? LPAREN whiteSpace? annotationArg whiteSpace? RPAREN
822
- | whiteSpace? LPAREN annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+ whiteSpace? RPAREN ;
820
+ whiteSpace annotationArg
821
+ | whiteSpace annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+
822
+ | whiteSpace? LPAREN whiteSpace? RPAREN
823
+ | whiteSpace? LPAREN whiteSpace? annotationArg whiteSpace? RPAREN
824
+ | whiteSpace? LPAREN annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+ whiteSpace? RPAREN ;
823
825
annotationArg : expression;
824
826
825
827
mandatoryLineContinuation : LINE_CONTINUATION WS *;
0 commit comments