1 {
2 {-# LANGUAGE BangPatterns #-}
3 module Language.JavaScript.Parser.Grammar7
4     ( parseProgram
5     , parseModule
6     , parseStatement
7     , parseExpression
8     , parseLiteral
9     ) where
10 
11 import Data.Char
12 import Data.Functor (($>))
13 import Language.JavaScript.Parser.Lexer
14 import Language.JavaScript.Parser.ParserMonad
15 import Language.JavaScript.Parser.SrcLocation
16 import Language.JavaScript.Parser.Token
17 import qualified Language.JavaScript.Parser.AST as AST
18 
19 }
20 
21 -- The name of the generated function to be exported from the module
22 %name parseProgram           Program
23 %name parseModule            Module
24 %name parseLiteral           LiteralMain
25 %name parseExpression        ExpressionMain
26 %name parseStatement         StatementMain
27 
28 %tokentype { Token }
29 %error { parseError }
30 %monad { Alex } { >>= } { return }
31 %lexer { lexCont } { EOFToken {} }
32 
33 
34 %token
35 
36      ';'    { SemiColonToken {} }
37      ','    { CommaToken {} }
38      '?'    { HookToken {} }
39      ':'    { ColonToken {} }
40      '||'   { OrToken {} }
41      '&&'   { AndToken {} }
42      '|'    { BitwiseOrToken {} }
43      '^'    { BitwiseXorToken {} }
44      '&'    { BitwiseAndToken {} }
45      '=>'   { ArrowToken {} }
46      '==='  { StrictEqToken {} }
47      '=='   { EqToken {} }
48      '*='   { TimesAssignToken {} }
49      '/='   { DivideAssignToken {} }
50      '%='   { ModAssignToken {} }
51      '+='   { PlusAssignToken {} }
52      '-='   { MinusAssignToken {} }
53      '<<='  { LshAssignToken {} }
54      '>>='  { RshAssignToken {} }
55      '>>>=' { UrshAssignToken {} }
56      '&='   { AndAssignToken {} }
57      '^='   { XorAssignToken {} }
58      '|='   { OrAssignToken {} }
59      '='    { SimpleAssignToken {} }
60      '!=='  { StrictNeToken {} }
61      '!='   { NeToken {} }
62      '<<'   { LshToken {} }
63      '<='   { LeToken {} }
64      '<'    { LtToken {} }
65      '>>>'  { UrshToken {} }
66      '>>'   { RshToken {} }
67      '>='   { GeToken {} }
68      '>'    { GtToken {} }
69      '++'   { IncrementToken {} }
70      '--'   { DecrementToken {} }
71      '+'    { PlusToken {} }
72      '-'    { MinusToken {} }
73      '*'    { MulToken {} }
74      '/'    { DivToken {} }
75      '%'    { ModToken {} }
76      '!'    { NotToken {} }
77      '~'    { BitwiseNotToken {} }
78      '...'  { SpreadToken {} }
79      '.'    { DotToken {} }
80      '['    { LeftBracketToken {} }
81      ']'    { RightBracketToken {} }
82      '{'    { LeftCurlyToken {} }
83      '}'    { RightCurlyToken {} }
84      '('    { LeftParenToken {} }
85      ')'    { RightParenToken {} }
86 
87      'as'         { AsToken {} }
88      'autosemi'   { AutoSemiToken {} }
89      'async'      { AsyncToken {} }
90      'await'      { AwaitToken {} }
91      'break'      { BreakToken {} }
92      'case'       { CaseToken {} }
93      'catch'      { CatchToken {} }
94      'class'      { ClassToken {} }
95      'const'      { ConstToken {} }
96      'continue'   { ContinueToken {} }
97      'debugger'   { DebuggerToken {} }
98      'default'    { DefaultToken {} }
99      'delete'     { DeleteToken {} }
100      'do'         { DoToken {} }
101      'else'       { ElseToken {} }
102      'enum'       { EnumToken {} }
103      'export'     { ExportToken {} }
104      'extends'    { ExtendsToken {} }
105      'false'      { FalseToken {} }
106      'finally'    { FinallyToken {} }
107      'for'        { ForToken {} }
108      'function'   { FunctionToken {} }
109      'from'       { FromToken {} }
110      'get'        { GetToken {} }
111      'if'         { IfToken {} }
112      'import'     { ImportToken {} }
113      'in'         { InToken {} }
114      'instanceof' { InstanceofToken {} }
115      'let'        { LetToken {} }
116      'new'        { NewToken {} }
117      'null'       { NullToken {} }
118      'of'         { OfToken {} }
119      'return'     { ReturnToken {} }
120      'set'        { SetToken {} }
121      'static'     { StaticToken {} }
122      'super'      { SuperToken {} }
123      'switch'     { SwitchToken {} }
124      'this'       { ThisToken {} }
125      'throw'      { ThrowToken {} }
126      'true'       { TrueToken {} }
127      'try'        { TryToken {} }
128      'typeof'     { TypeofToken {} }
129      'var'        { VarToken {} }
130      'void'       { VoidToken {} }
131      'while'      { WhileToken {} }
132      'with'       { WithToken {} }
133      'yield'      { YieldToken {} }
134 
135 
136      'ident'      { IdentifierToken {} }
137      'decimal'    { DecimalToken {} }
138      'hexinteger' { HexIntegerToken {} }
139      'octal'      { OctalToken {} }
140      'string'     { StringToken {} }
141      'regex'      { RegExToken {} }
142      'tmplnosub'  { NoSubstitutionTemplateToken {} }
143      'tmplhead'   { TemplateHeadToken {} }
144      'tmplmiddle' { TemplateMiddleToken {} }
145      'tmpltail'   { TemplateTailToken {} }
146 
147      'future'     { FutureToken {} }
148 
149      'tail'       { TailToken {} }
150 
151 
152 %%
153 
154 -- ---------------------------------------------------------------------
155 -- Sort out automatically inserted semi-colons.
156 -- A MaybeSemi is an actual semi-colon or nothing.
157 -- An AutoSemu is either an actual semi-colon or 'virtual' semi-colon inserted
158 -- by the Alex lexer or nothing.
159 
160 MaybeSemi :: { AST.JSSemi }
161 MaybeSemi : ';' { AST.JSSemi (mkJSAnnot $1) }
162          |      { AST.JSSemiAuto }
163 
164 AutoSemi :: { AST.JSSemi }
165 AutoSemi : ';'         { AST.JSSemi (mkJSAnnot $1) }
166          | 'autosemi'  { AST.JSSemiAuto }
167          |             { AST.JSSemiAuto }
168 
169 -- ---------------------------------------------------------------------
170 
171 -- Helpers
172 
173 LParen :: { AST.JSAnnot }
174 LParen : '(' { mkJSAnnot $1 }
175 
176 RParen :: { AST.JSAnnot }
177 RParen : ')' { mkJSAnnot $1 }
178 
179 LBrace :: { AST.JSAnnot }
180 LBrace : '{' { mkJSAnnot $1 }
181 
182 RBrace :: { AST.JSAnnot }
183 RBrace : '}' { mkJSAnnot $1 }
184 
185 LSquare :: { AST.JSAnnot }
186 LSquare : '[' { mkJSAnnot $1 }
187 
188 RSquare :: { AST.JSAnnot }
189 RSquare : ']' { mkJSAnnot $1 }
190 
191 Comma :: { AST.JSAnnot }
192 Comma : ',' { mkJSAnnot $1 }
193 
194 Colon :: { AST.JSAnnot }
195 Colon : ':' { mkJSAnnot $1 }
196 
197 Semi :: { AST.JSAnnot }
198 Semi : ';' { mkJSAnnot $1 }
199 
200 Arrow :: { AST.JSAnnot }
201 Arrow : '=>' { mkJSAnnot $1 }
202 
203 Spread :: { AST.JSAnnot }
204 Spread : '...' { mkJSAnnot $1 }
205 
206 Dot :: { AST.JSAnnot }
207 Dot : '.' { mkJSAnnot $1 }
208 
209 As :: { AST.JSAnnot }
210 As : 'as' { mkJSAnnot $1 }
211 
212 Increment :: { AST.JSUnaryOp }
213 Increment : '++' { AST.JSUnaryOpIncr (mkJSAnnot $1) }
214 
215 Decrement :: { AST.JSUnaryOp }
216 Decrement : '--' { AST.JSUnaryOpDecr (mkJSAnnot $1) }
217 
218 Delete :: { AST.JSUnaryOp }
219 Delete : 'delete' { AST.JSUnaryOpDelete (mkJSAnnot $1) }
220 
221 Void :: { AST.JSUnaryOp }
222 Void : 'void' { AST.JSUnaryOpVoid (mkJSAnnot $1) }
223 
224 Typeof :: { AST.JSUnaryOp }
225 Typeof : 'typeof' { AST.JSUnaryOpTypeof (mkJSAnnot $1) }
226 
227 Plus :: { AST.JSBinOp }
228 Plus : '+' { AST.JSBinOpPlus (mkJSAnnot $1) }
229 
230 Minus :: { AST.JSBinOp }
231 Minus : '-' { AST.JSBinOpMinus (mkJSAnnot $1) }
232 
233 Tilde :: { AST.JSUnaryOp }
234 Tilde : '~' { AST.JSUnaryOpTilde (mkJSAnnot $1) }
235 
236 Not :: { AST.JSUnaryOp }
237 Not : '!' { AST.JSUnaryOpNot (mkJSAnnot $1) }
238 
239 Mul :: { AST.JSBinOp }
240 Mul : '*' { AST.JSBinOpTimes (mkJSAnnot $1) }
241 
242 Div :: { AST.JSBinOp }
243 Div : '/' { AST.JSBinOpDivide (mkJSAnnot $1) }
244 
245 Mod :: { AST.JSBinOp }
246 Mod : '%' { AST.JSBinOpMod (mkJSAnnot $1) }
247 
248 Lsh :: { AST.JSBinOp }
249 Lsh : '<<' { AST.JSBinOpLsh (mkJSAnnot $1) }
250 
251 Rsh :: { AST.JSBinOp }
252 Rsh : '>>' { AST.JSBinOpRsh (mkJSAnnot $1) }
253 
254 Ursh :: { AST.JSBinOp }
255 Ursh : '>>>' { AST.JSBinOpUrsh (mkJSAnnot $1) }
256 
257 Le :: { AST.JSBinOp }
258 Le : '<=' { AST.JSBinOpLe (mkJSAnnot $1) }
259 
260 Lt :: { AST.JSBinOp }
261 Lt : '<' { AST.JSBinOpLt (mkJSAnnot $1) }
262 
263 Ge :: { AST.JSBinOp }
264 Ge : '>=' { AST.JSBinOpGe (mkJSAnnot $1) }
265 
266 Gt :: { AST.JSBinOp }
267 Gt : '>' { AST.JSBinOpGt (mkJSAnnot $1) }
268 
269 In :: { AST.JSBinOp }
270 In : 'in' { AST.JSBinOpIn (mkJSAnnot $1) }
271 
272 Instanceof :: { AST.JSBinOp }
273 Instanceof : 'instanceof' { AST.JSBinOpInstanceOf (mkJSAnnot $1) }
274 
275 StrictEq :: { AST.JSBinOp }
276 StrictEq : '===' { AST.JSBinOpStrictEq (mkJSAnnot $1) }
277 
278 Equal :: { AST.JSBinOp }
279 Equal : '==' { AST.JSBinOpEq (mkJSAnnot $1) }
280 
281 StrictNe :: { AST.JSBinOp }
282 StrictNe : '!==' { AST.JSBinOpStrictNeq (mkJSAnnot $1) }
283 
284 Ne :: { AST.JSBinOp }
285 Ne : '!=' { AST.JSBinOpNeq (mkJSAnnot $1)}
286 
287 Of :: { AST.JSBinOp }
288 Of : 'of' { AST.JSBinOpOf (mkJSAnnot $1) }
289 
290 Or :: { AST.JSBinOp }
291 Or : '||' { AST.JSBinOpOr (mkJSAnnot $1) }
292 
293 And :: { AST.JSBinOp }
294 And : '&&' { AST.JSBinOpAnd (mkJSAnnot $1) }
295 
296 BitOr :: { AST.JSBinOp }
297 BitOr : '|' { AST.JSBinOpBitOr (mkJSAnnot $1) }
298 
299 BitAnd :: { AST.JSBinOp }
300 BitAnd : '&' { AST.JSBinOpBitAnd (mkJSAnnot $1) }
301 
302 BitXor :: { AST.JSBinOp }
303 BitXor : '^' { AST.JSBinOpBitXor (mkJSAnnot $1)}
304 
305 Hook :: { AST.JSAnnot }
306 Hook : '?' { mkJSAnnot $1 }
307 
308 SimpleAssign :: { AST.JSAnnot }
309 SimpleAssign : '=' { mkJSAnnot $1 }
310 
311 OpAssign :: { AST.JSAssignOp }
312 OpAssign : '*='     { AST.JSTimesAssign  (mkJSAnnot $1) }
313          | '/='     { AST.JSDivideAssign (mkJSAnnot $1) }
314          | '%='     { AST.JSModAssign    (mkJSAnnot $1) }
315          | '+='     { AST.JSPlusAssign   (mkJSAnnot $1) }
316          | '-='     { AST.JSMinusAssign  (mkJSAnnot $1) }
317          | '<<='    { AST.JSLshAssign    (mkJSAnnot $1) }
318          | '>>='    { AST.JSRshAssign    (mkJSAnnot $1) }
319          | '>>>='   { AST.JSUrshAssign   (mkJSAnnot $1) }
320          | '&='     { AST.JSBwAndAssign  (mkJSAnnot $1) }
321          | '^='     { AST.JSBwXorAssign  (mkJSAnnot $1) }
322          | '|='     { AST.JSBwOrAssign   (mkJSAnnot $1) }
323 
324 -- IdentifierName ::                                                        See 7.6
325 --         IdentifierStart
326 --         IdentifierName IdentifierPart
327 -- Note: This production needs to precede the productions for all keyword
328 -- statements and PrimaryExpression. Contra the Happy documentation, in the
329 -- case of a reduce/reduce conflict, the *later* rule takes precedence, and
330 -- the ambiguity of, for example, `{break}` needs to resolve in favor of
331 -- `break` as a keyword and not as an identifier in property shorthand
332 -- syntax.
333 -- TODO: make this include any reserved word too, including future ones
334 IdentifierName :: { AST.JSExpression }
335 IdentifierName : Identifier {$1}
336              | 'async'      { AST.JSIdentifier (mkJSAnnot $1) "async" }
337              | 'await'      { AST.JSIdentifier (mkJSAnnot $1) "await" }
338              | 'break'      { AST.JSIdentifier (mkJSAnnot $1) "break" }
339              | 'case'       { AST.JSIdentifier (mkJSAnnot $1) "case" }
340              | 'catch'      { AST.JSIdentifier (mkJSAnnot $1) "catch" }
341              | 'class'      { AST.JSIdentifier (mkJSAnnot $1) "class" }
342              | 'const'      { AST.JSIdentifier (mkJSAnnot $1) "const" }
343              | 'continue'   { AST.JSIdentifier (mkJSAnnot $1) "continue" }
344              | 'debugger'   { AST.JSIdentifier (mkJSAnnot $1) "debugger" }
345              | 'default'    { AST.JSIdentifier (mkJSAnnot $1) "default" }
346              | 'delete'     { AST.JSIdentifier (mkJSAnnot $1) "delete" }
347              | 'do'         { AST.JSIdentifier (mkJSAnnot $1) "do" }
348              | 'else'       { AST.JSIdentifier (mkJSAnnot $1) "else" }
349              | 'enum'       { AST.JSIdentifier (mkJSAnnot $1) "enum" }
350              | 'export'     { AST.JSIdentifier (mkJSAnnot $1) "export" }
351              | 'extends'    { AST.JSIdentifier (mkJSAnnot $1) "extends" }
352              | 'false'      { AST.JSIdentifier (mkJSAnnot $1) "false" }
353              | 'finally'    { AST.JSIdentifier (mkJSAnnot $1) "finally" }
354              | 'for'        { AST.JSIdentifier (mkJSAnnot $1) "for" }
355              | 'function'   { AST.JSIdentifier (mkJSAnnot $1) "function" }
356              | 'if'         { AST.JSIdentifier (mkJSAnnot $1) "if" }
357              | 'in'         { AST.JSIdentifier (mkJSAnnot $1) "in" }
358              | 'instanceof' { AST.JSIdentifier (mkJSAnnot $1) "instanceof" }
359              | 'let'        { AST.JSIdentifier (mkJSAnnot $1) "let" }
360              | 'new'        { AST.JSIdentifier (mkJSAnnot $1) "new" }
361              | 'null'       { AST.JSIdentifier (mkJSAnnot $1) "null" }
362              | 'of'         { AST.JSIdentifier (mkJSAnnot $1) "of" }
363              | 'return'     { AST.JSIdentifier (mkJSAnnot $1) "return" }
364              | 'static'     { AST.JSIdentifier (mkJSAnnot $1) "static" }
365              | 'super'      { AST.JSIdentifier (mkJSAnnot $1) "super" }
366              | 'switch'     { AST.JSIdentifier (mkJSAnnot $1) "switch" }
367              | 'this'       { AST.JSIdentifier (mkJSAnnot $1) "this" }
368              | 'throw'      { AST.JSIdentifier (mkJSAnnot $1) "throw" }
369              | 'true'       { AST.JSIdentifier (mkJSAnnot $1) "true" }
370              | 'try'        { AST.JSIdentifier (mkJSAnnot $1) "try" }
371              | 'typeof'     { AST.JSIdentifier (mkJSAnnot $1) "typeof" }
372              | 'var'        { AST.JSIdentifier (mkJSAnnot $1) "var" }
373              | 'void'       { AST.JSIdentifier (mkJSAnnot $1) "void" }
374              | 'while'      { AST.JSIdentifier (mkJSAnnot $1) "while" }
375              | 'with'       { AST.JSIdentifier (mkJSAnnot $1) "with" }
376              | 'future'     { AST.JSIdentifier (mkJSAnnot $1) (tokenLiteral $1) }
377 
378 Var :: { AST.JSAnnot }
379 Var : 'var' { mkJSAnnot $1 }
380 
381 Let :: { AST.JSAnnot }
382 Let : 'let' { mkJSAnnot $1 }
383 
384 Const :: { AST.JSAnnot }
385 Const : 'const' { mkJSAnnot $1 }
386 
387 Import :: { AST.JSAnnot }
388 Import : 'import' { mkJSAnnot $1 }
389 
390 From :: { AST.JSAnnot }
391 From : 'from' { mkJSAnnot $1 }
392 
393 Export :: { AST.JSAnnot }
394 Export : 'export' { mkJSAnnot $1 }
395 
396 If :: { AST.JSAnnot }
397 If : 'if' { mkJSAnnot $1 }
398 
399 Else :: { AST.JSAnnot }
400 Else : 'else' { mkJSAnnot $1 }
401 
402 Do :: { AST.JSAnnot }
403 Do : 'do' { mkJSAnnot $1 }
404 
405 While :: { AST.JSAnnot }
406 While : 'while' { mkJSAnnot $1 }
407 
408 For :: { AST.JSAnnot }
409 For : 'for' { mkJSAnnot $1 }
410 
411 Continue :: { AST.JSAnnot }
412 Continue : 'continue' { mkJSAnnot $1 }
413 
414 Async :: { AST.JSAnnot }
415 Async : 'async' { mkJSAnnot $1 }
416 
417 Await :: { AST.JSAnnot }
418 Await : 'await' { mkJSAnnot $1 }
419 
420 Break :: { AST.JSAnnot }
421 Break : 'break' { mkJSAnnot $1 }
422 
423 Return :: { AST.JSAnnot }
424 Return : 'return' { mkJSAnnot $1 }
425 
426 With :: { AST.JSAnnot }
427 With : 'with' { mkJSAnnot $1 }
428 
429 Switch :: { AST.JSAnnot }
430 Switch : 'switch' { mkJSAnnot $1 }
431 
432 Case :: { AST.JSAnnot }
433 Case : 'case' { mkJSAnnot $1 }
434 
435 Default :: { AST.JSAnnot }
436 Default : 'default' { mkJSAnnot $1 }
437 
438 Throw :: { AST.JSAnnot }
439 Throw : 'throw' { mkJSAnnot $1 {- 'Throw' -} }
440 
441 Try :: { AST.JSAnnot }
442 Try : 'try' { mkJSAnnot $1 }
443 
444 CatchL :: { AST.JSAnnot }
445 CatchL : 'catch' { mkJSAnnot $1 }
446 
447 FinallyL :: { AST.JSAnnot }
448 FinallyL : 'finally' { mkJSAnnot $1 }
449 
450 Function :: { AST.JSAnnot }
451 Function : 'function' { mkJSAnnot $1 {- 'Function' -} }
452 
453 New :: { AST.JSAnnot }
454 New : 'new' { mkJSAnnot $1 }
455 
456 Class :: { AST.JSAnnot }
457 Class : 'class' { mkJSAnnot $1 }
458 
459 Extends :: { AST.JSAnnot }
460 Extends : 'extends' { mkJSAnnot $1 }
461 
462 Static :: { AST.JSAnnot }
463 Static : 'static' { mkJSAnnot $1 }
464 
465 Super :: { AST.JSExpression }
466 Super : 'super' { AST.JSLiteral (mkJSAnnot $1) "super" }
467 
468 
469 Eof :: { AST.JSAnnot }
470 Eof : 'tail' { mkJSAnnot $1 {- 'Eof' -} }
471 
472 -- Literal ::                                                                See 7.8
473 --         NullLiteral
474 --         BooleanLiteral
475 --         NumericLiteral
476 --         StringLiteral
477 Literal :: { AST.JSExpression }
478 Literal : NullLiteral     { $1 }
479         | BooleanLiteral  { $1 }
480         | NumericLiteral  { $1 }
481         | StringLiteral   { $1 }
482         | RegularExpressionLiteral { $1 }
483 
484 NullLiteral :: { AST.JSExpression }
485 NullLiteral : 'null' { AST.JSLiteral (mkJSAnnot $1) "null" }
486 
487 BooleanLiteral :: { AST.JSExpression }
488 BooleanLiteral : 'true'  { AST.JSLiteral (mkJSAnnot $1) "true" }
489                | 'false' { AST.JSLiteral (mkJSAnnot $1) "false" }
490 
491 -- <Numeric Literal> ::= DecimalLiteral
492 --                     | HexIntegerLiteral
493 --                     | OctalLiteral
494 NumericLiteral :: { AST.JSExpression }
495 NumericLiteral : 'decimal'    { AST.JSDecimal (mkJSAnnot $1) (tokenLiteral $1) }
496                | 'hexinteger' { AST.JSHexInteger (mkJSAnnot $1) (tokenLiteral $1) }
497                | 'octal'      { AST.JSOctal (mkJSAnnot $1) (tokenLiteral $1) }
498 
499 StringLiteral :: { AST.JSExpression }
500 StringLiteral : 'string'  { AST.JSStringLiteral (mkJSAnnot $1) (tokenLiteral $1) }
501 
502 -- <Regular Expression Literal> ::= RegExp
503 RegularExpressionLiteral :: { AST.JSExpression }
504 RegularExpressionLiteral : 'regex' { AST.JSRegEx (mkJSAnnot $1) (tokenLiteral $1) }
505 
506 -- PrimaryExpression :                                                   See 11.1
507 --        this
508 --        Identifier
509 --        Literal
510 --        ArrayLiteral
511 --        ObjectLiteral
512 --        ( Expression )
513 PrimaryExpression :: { AST.JSExpression }
514 PrimaryExpression : 'this'                   { AST.JSLiteral (mkJSAnnot $1) "this" }
515                   | Identifier               { $1 {- 'PrimaryExpression1' -} }
516                   | Literal                  { $1 {- 'PrimaryExpression2' -} }
517                   | ArrayLiteral             { $1 {- 'PrimaryExpression3' -} }
518                   | ObjectLiteral            { $1 {- 'PrimaryExpression4' -} }
519                   | ClassExpression          { $1 }
520                   | GeneratorExpression      { $1 }
521                   | TemplateLiteral          { mkJSTemplateLiteral Nothing $1 {- 'PrimaryExpression6' -} }
522                   | LParen Expression RParen { AST.JSExpressionParen $1 $2 $3 }
523 
524 -- Identifier ::                                                            See 7.6
525 --         IdentifierName but not ReservedWord
526 Identifier :: { AST.JSExpression }
527 Identifier : 'ident' { AST.JSIdentifier (mkJSAnnot $1) (tokenLiteral $1) }
528            | 'as'    { AST.JSIdentifier (mkJSAnnot $1) "as" }
529            | 'get'   { AST.JSIdentifier (mkJSAnnot $1) "get" }
530            | 'set'   { AST.JSIdentifier (mkJSAnnot $1) "set" }
531            | 'from'  { AST.JSIdentifier (mkJSAnnot $1) "from" }
532            | 'yield' { AST.JSIdentifier (mkJSAnnot $1) "yield" }
533 
534 -- Must follow Identifier; when ambiguous, `yield` as a keyword should take
535 -- precedence over `yield` as an identifier name.
536 Yield :: { AST.JSAnnot }
537 Yield : 'yield' { mkJSAnnot $1 }
538 
539 
540 SpreadExpression :: { AST.JSExpression }
541 SpreadExpression : Spread AssignmentExpression  { AST.JSSpreadExpression $1 $2 {- 'SpreadExpression' -} }
542 
543 TemplateLiteral :: { JSUntaggedTemplate }
544 TemplateLiteral : 'tmplnosub'              { JSUntaggedTemplate (mkJSAnnot $1) (tokenLiteral $1) [] }
545                 | 'tmplhead' TemplateParts { JSUntaggedTemplate (mkJSAnnot $1) (tokenLiteral $1) $2 }
546 
547 TemplateParts :: { [AST.JSTemplatePart] }
548 TemplateParts : TemplateExpression RBrace 'tmplmiddle' TemplateParts { AST.JSTemplatePart $1 $2 ('}' : tokenLiteral $3) : $4 }
549               | TemplateExpression RBrace 'tmpltail'                 { AST.JSTemplatePart $1 $2 ('}' : tokenLiteral $3) : [] }
550 
551 -- This production only exists to ensure that inTemplate is set to True before
552 -- a tmplmiddle or tmpltail token is lexed. Since the lexer is always one token
553 -- ahead of the parser, setInTemplate needs to be called during a reduction
554 -- that is *two* tokens behind tmplmiddle/tmpltail. Accordingly,
555 -- TemplateExpression is always followed by an RBrace, which is lexed normally.
556 TemplateExpression :: { AST.JSExpression }
557 TemplateExpression : Expression {% setInTemplate True \$> $1 }
558 
559 -- ArrayLiteral :                                                        See 11.1.4
560 --        [ Elisionopt ]
561 --        [ ElementList ]
562 --        [ ElementList , Elisionopt ]
563 ArrayLiteral :: { AST.JSExpression }
564 ArrayLiteral : LSquare RSquare                          { AST.JSArrayLiteral $1 [] $2           {- 'ArrayLiteral11' -} }
565              | LSquare Elision RSquare                  { AST.JSArrayLiteral $1 $2 $3           {- 'ArrayLiteral12' -}  }
566              | LSquare ElementList RSquare              { AST.JSArrayLiteral $1 $2 $3           {- 'ArrayLiteral13' -}  }
567              | LSquare ElementList Elision RSquare      { AST.JSArrayLiteral $1 ($2 ++ $3) $4   {- 'ArrayLiteral14' -} }
568 
569 
570 -- ElementList :                                                         See 11.1.4
571 --        Elisionopt AssignmentExpression
572 --        ElementList , Elisionopt AssignmentExpression
573 ElementList :: { [AST.JSArrayElement] }
574 ElementList : Elision AssignmentExpression              { $1 ++ [AST.JSArrayElement $2]             {- 'ElementList1' -} }
575             | AssignmentExpression                      { [AST.JSArrayElement $1]                   {- 'ElementList2' -} }
576             | ElementList Elision AssignmentExpression  { (($1)++($2 ++ [AST.JSArrayElement $3]))   {- 'ElementList3' -} }
577 
578 
579 -- Elision :                                                             See 11.1.4
580 --        ,
581 --        Elision ,
582 Elision :: { [AST.JSArrayElement] }
583 Elision : Comma             { [AST.JSArrayComma $1]     {- 'Elision1' -} }
584         | Comma Elision     { (AST.JSArrayComma $1):$2  {- 'Elision2' -} }
585 
586 -- ObjectLiteral :                                                       See 11.1.5
587 --        { }
588 --        { PropertyNameAndValueList }
589 --        { PropertyNameAndValueList , }
590 ObjectLiteral :: { AST.JSExpression }
591 ObjectLiteral : LBrace RBrace                                { AST.JSObjectLiteral $1 (AST.JSCTLNone AST.JSLNil) $2     {- 'ObjectLiteral1' -} }
592               | LBrace PropertyNameandValueList RBrace       { AST.JSObjectLiteral $1 (AST.JSCTLNone $2) $3             {- 'ObjectLiteral2' -} }
593               | LBrace PropertyNameandValueList Comma RBrace { AST.JSObjectLiteral $1 (AST.JSCTLComma $2 $3) $4         {- 'ObjectLiteral3' -} }
594 
595 -- <Property Name and Value List> ::= <Property Name> ':' <Assignment Expression>
596 --                                  | <Property Name and Value List> ',' <Property Name> ':' <Assignment Expression>
597 
598 -- Seems we can have function declarations in the value part too
599 -- PropertyNameAndValueList :                                            See 11.1.5
600 --        PropertyAssignment
601 --        PropertyNameAndValueList , PropertyAssignment
602 PropertyNameandValueList :: { AST.JSCommaList AST.JSObjectProperty }
603 PropertyNameandValueList : PropertyAssignment                                { AST.JSLOne $1        {- 'PropertyNameandValueList1' -} }
604                          | PropertyNameandValueList Comma PropertyAssignment { AST.JSLCons $1 $2 $3 {- 'PropertyNameandValueList2' -} }
605 
606 -- PropertyAssignment :                                                  See 11.1.5
607 --        PropertyName : AssignmentExpression
608 --        get PropertyName() { FunctionBody }
609 --        set PropertyName( PropertySetParameterList ) { FunctionBody }
610 PropertyAssignment :: { AST.JSObjectProperty }
611 PropertyAssignment : PropertyName Colon AssignmentExpression { AST.JSPropertyNameandValue $1 $2 [$3] }
612                    | IdentifierName { identifierToProperty $1 }
613                    | MethodDefinition { AST.JSObjectMethod $1 }
614 
615 -- TODO: not clear if get/set are keywords, or just used in a specific context. Puzzling.
616 MethodDefinition :: { AST.JSMethodDefinition }
617 MethodDefinition : PropertyName LParen RParen FunctionBody
618                      { AST.JSMethodDefinition $1 $2 AST.JSLNil $3 $4 }
619                  | PropertyName LParen FormalParameterList RParen FunctionBody
620                      { AST.JSMethodDefinition $1 $2 $3 $4 $5 }
621                  | '*' PropertyName LParen RParen FunctionBody
622                      { AST.JSGeneratorMethodDefinition (mkJSAnnot $1) $2 $3 AST.JSLNil $4 $5 }
623                  | '*' PropertyName LParen FormalParameterList RParen FunctionBody
624                      { AST.JSGeneratorMethodDefinition (mkJSAnnot $1) $2 $3 $4 $5 $6 }
625                  -- Should be "get" in next, but is not a Token
626                  | 'get' PropertyName LParen RParen FunctionBody
627                      { AST.JSPropertyAccessor (AST.JSAccessorGet (mkJSAnnot $1)) $2 $3 AST.JSLNil $4 $5 }
628                  -- Should be "set" in next, but is not a Token
629                  | 'set' PropertyName LParen PropertySetParameterList RParen FunctionBody
630                      { AST.JSPropertyAccessor (AST.JSAccessorSet (mkJSAnnot $1)) $2 $3 (AST.JSLOne $4) $5 $6 }
631 
632 -- PropertyName :                                                        See 11.1.5
633 --        IdentifierName
634 --        StringLiteral
635 --        NumericLiteral
636 PropertyName :: { AST.JSPropertyName }
637 PropertyName : IdentifierName { propName $1 {- 'PropertyName1' -} }
638              | StringLiteral  { propName $1 {- 'PropertyName2' -} }
639              | NumericLiteral { propName $1 {- 'PropertyName3' -} }
640              | LSquare AssignmentExpression RSquare { AST.JSPropertyComputed $1 $2 $3 {- 'PropertyName4' -} }
641 
642 -- PropertySetParameterList :                                            See 11.1.5
643 --        Identifier
644 PropertySetParameterList :: { AST.JSExpression }
645 PropertySetParameterList : AssignmentExpression { $1 {- 'PropertySetParameterList' -} }
646 
647 -- MemberExpression :                                           See 11.2
648 --        PrimaryExpression
649 --        FunctionExpression
650 --        MemberExpression [ Expression ]
651 --        MemberExpression . IdentifierName
652 --        new MemberExpression Arguments
653 MemberExpression :: { AST.JSExpression }
654 MemberExpression : PrimaryExpression   { $1 {- 'MemberExpression1' -} }
655                  | FunctionExpression  { $1 {- 'MemberExpression2' -} }
656                  | MemberExpression LSquare Expression RSquare { AST.JSMemberSquare $1 $2 $3 $4 {- 'MemberExpression3' -} }
657                  | MemberExpression Dot IdentifierName         { AST.JSMemberDot $1 $2 $3       {- 'MemberExpression4' -} }
658                  | MemberExpression TemplateLiteral            { mkJSTemplateLiteral (Just $1) $2 }
659                  | Super LSquare Expression RSquare            { AST.JSMemberSquare $1 $2 $3 $4 }
660                  | Super Dot IdentifierName                    { AST.JSMemberDot $1 $2 $3 }
661                  | New MemberExpression Arguments              { mkJSMemberNew $1 $2 $3         {- 'MemberExpression5' -} }
662 
663 -- NewExpression :                                              See 11.2
664 --        MemberExpression
665 --        new NewExpression
666 NewExpression :: { AST.JSExpression }
667 NewExpression : MemberExpression    { $1                        {- 'NewExpression1' -} }
668               | New NewExpression   { AST.JSNewExpression $1 $2 {- 'NewExpression2' -} }
669 
670 AwaitExpression :: { AST.JSExpression }
671 AwaitExpression
672   : Await Expression { AST.JSAwaitExpression $1 $2 }
673 
674 -- CallExpression :                                             See 11.2
675 --        MemberExpression Arguments
676 --        CallExpression Arguments
677 --        CallExpression [ Expression ]
678 --        CallExpression . IdentifierName
679 CallExpression :: { AST.JSExpression }
680 CallExpression : MemberExpression Arguments
681                     { mkJSMemberExpression $1 $2 {- 'CallExpression1' -} }
682                | Super Arguments
683                     { mkJSCallExpression $1 $2 }
684                | CallExpression Arguments
685                     { mkJSCallExpression $1 $2 {- 'CallExpression2' -} }
686                | CallExpression LSquare Expression RSquare
687                     { AST.JSCallExpressionSquare $1 $2 $3 $4 {- 'CallExpression3' -} }
688                | CallExpression Dot IdentifierName
689                     { AST.JSCallExpressionDot $1 $2 $3 {- 'CallExpression4' -} }
690                | CallExpression TemplateLiteral
691                     { mkJSTemplateLiteral (Just $1) $2 {- 'CallExpression5' -} }
692 
693 -- Arguments :                                                  See 11.2
694 --        ()
695 --        ( ArgumentList )
696 Arguments :: { JSArguments }
697 Arguments : LParen RParen               { JSArguments $1 AST.JSLNil $2  {- 'Arguments1' -} }
698           | LParen ArgumentList RParen  { JSArguments $1 $2 $3			{- 'Arguments2' -} }
699 
700 -- ArgumentList :                                               See 11.2
701 --        AssignmentExpression
702 --        ArgumentList , AssignmentExpression
703 ArgumentList :: { AST.JSCommaList AST.JSExpression }
704 ArgumentList : AssignmentExpression                    { AST.JSLOne $1          {- 'ArgumentList1' -} }
705              | ArgumentList Comma AssignmentExpression { AST.JSLCons $1 $2 $3   {- 'ArgumentList2' -} }
706 
707 -- LeftHandSideExpression :                                     See 11.2
708 --        NewExpression
709 --        CallExpression
710 LeftHandSideExpression :: { AST.JSExpression }
711 LeftHandSideExpression : NewExpression  { $1 {- 'LeftHandSideExpression1' -} }
712                        | CallExpression { $1 {- 'LeftHandSideExpression12' -} }
713                        | AwaitExpression { $1 {- 'LeftHandSideExpression13' -} }
714 
715 -- PostfixExpression :                                          See 11.3
716 --        LeftHandSideExpression
717 --                                  [no LineTerminator here]
718 --        LeftHandSideExpression                             ++
719 --                                  [no LineTerminator here]
720 --        LeftHandSideExpression                             --
721 PostfixExpression :: { AST.JSExpression }
722 PostfixExpression : LeftHandSideExpression { $1 {- 'PostfixExpression' -} }
723                   | PostfixExpression Increment { AST.JSExpressionPostfix $1 $2 }
724                   | PostfixExpression Decrement { AST.JSExpressionPostfix $1 $2 }
725 
726 -- UnaryExpression :                                            See 11.4
727 --        PostfixExpression
728 --        delete UnaryExpression
729 --        void UnaryExpression
730 --        typeof UnaryExpression
731 --        ++ UnaryExpression
732 --        -- UnaryExpression
733 --        + UnaryExpression
734 --        - UnaryExpression
735 --        ~ UnaryExpression
736 --        ! UnaryExpression
737 UnaryExpression :: { AST.JSExpression }
738 UnaryExpression : PostfixExpression         { $1 {- 'UnaryExpression' -} }
739                 | Delete    UnaryExpression { AST.JSUnaryExpression $1 $2 }
740                 | Void      UnaryExpression { AST.JSUnaryExpression $1 $2 }
741                 | Typeof    UnaryExpression { AST.JSUnaryExpression $1 $2 }
742                 | Increment UnaryExpression { AST.JSUnaryExpression $1 $2 }
743                 | Decrement UnaryExpression { AST.JSUnaryExpression $1 $2 }
744                 | Plus      UnaryExpression { AST.JSUnaryExpression (mkUnary $1) $2 }
745                 | Minus     UnaryExpression { AST.JSUnaryExpression (mkUnary $1) $2 }
746                 | Tilde     UnaryExpression { AST.JSUnaryExpression $1 $2 }
747                 | Not       UnaryExpression { AST.JSUnaryExpression $1 $2 }
748 
749 -- MultiplicativeExpression :                                   See 11.5
750 --        UnaryExpression
751 --        MultiplicativeExpression * UnaryExpression
752 --        MultiplicativeExpression / UnaryExpression
753 --        MultiplicativeExpression % UnaryExpression
754 MultiplicativeExpression :: { AST.JSExpression }
755 MultiplicativeExpression : UnaryExpression                              { $1 {- 'MultiplicativeExpression' -} }
756                          | MultiplicativeExpression Mul UnaryExpression { AST.JSExpressionBinary {- '*' -} $1 $2 $3 }
757                          | MultiplicativeExpression Div UnaryExpression { AST.JSExpressionBinary {- '/' -} $1 $2 $3 }
758                          | MultiplicativeExpression Mod UnaryExpression { AST.JSExpressionBinary {- '%' -} $1 $2 $3 }
759 
760 -- AdditiveExpression :                                        See 11.6
761 --        MultiplicativeExpression
762 --        AdditiveExpression + MultiplicativeExpression
763 --        AdditiveExpression - MultiplicativeExpression
764 AdditiveExpression :: { AST.JSExpression }
765 AdditiveExpression : AdditiveExpression Plus  MultiplicativeExpression  { AST.JSExpressionBinary {- '+' -} $1 $2 $3 }
766                    | AdditiveExpression Minus MultiplicativeExpression  { AST.JSExpressionBinary {- '-' -} $1 $2 $3 }
767                    | MultiplicativeExpression                           { $1 {- 'AdditiveExpression' -} }
768 
769 -- ShiftExpression :                                           See 11.7
770 --        AdditiveExpression
771 --        ShiftExpression << AdditiveExpression
772 --        ShiftExpression >> AdditiveExpression
773 --        ShiftExpression >>> AdditiveExpression
774 ShiftExpression :: { AST.JSExpression }
775 ShiftExpression : ShiftExpression Lsh  AdditiveExpression   { AST.JSExpressionBinary {- '<<' -}  $1 $2 $3 }
776                 | ShiftExpression Rsh  AdditiveExpression   { AST.JSExpressionBinary {- '>>' -}  $1 $2 $3 }
777                 | ShiftExpression Ursh AdditiveExpression   { AST.JSExpressionBinary {- '>>>' -} $1 $2 $3 }
778                 | AdditiveExpression                        { $1 {- 'ShiftExpression' -} }
779 
780 -- RelationalExpression :                                      See 11.8
781 --        ShiftExpression
782 --        RelationalExpression < ShiftExpression
783 --        RelationalExpression > ShiftExpression
784 --        RelationalExpression <= ShiftExpression
785 --        RelationalExpression >= ShiftExpression
786 --        RelationalExpression instanceof ShiftExpression
787 --        RelationalExpression in ShiftExpression
788 RelationalExpression :: { AST.JSExpression }
789 RelationalExpression : ShiftExpression { $1 {- 'RelationalExpression' -} }
790                      | RelationalExpression Lt  ShiftExpression { AST.JSExpressionBinary {- '<' -}  $1 $2 $3 }
791                      | RelationalExpression Gt  ShiftExpression { AST.JSExpressionBinary {- '>' -}  $1 $2 $3 }
792                      | RelationalExpression Le  ShiftExpression { AST.JSExpressionBinary {- '<=' -} $1 $2 $3 }
793                      | RelationalExpression Ge  ShiftExpression { AST.JSExpressionBinary {- '>=' -} $1 $2 $3 }
794                      | RelationalExpression Instanceof ShiftExpression { AST.JSExpressionBinary {- ' instanceof' -} $1 $2 $3 }
795                      | RelationalExpression In         ShiftExpression { AST.JSExpressionBinary {- ' in        ' -} $1 $2 $3 }
796 
797 -- RelationalExpressionNoIn :                                  See 11.8
798 --        ShiftExpression
799 --        RelationalExpressionNoIn < ShiftExpression
800 --        RelationalExpressionNoIn > ShiftExpression
801 --        RelationalExpressionNoIn <= ShiftExpression
802 --        RelationalExpressionNoIn >= ShiftExpression
803 --        RelationalExpressionNoIn instanceof ShiftExpression
804 RelationalExpressionNoIn :: { AST.JSExpression }
805 RelationalExpressionNoIn : ShiftExpression { $1 {- 'RelationalExpressionNoIn' -} }
806                      | RelationalExpressionNoIn Lt  ShiftExpression { AST.JSExpressionBinary {- '<' -}  $1 $2 $3 }
807                      | RelationalExpressionNoIn Gt  ShiftExpression { AST.JSExpressionBinary {- '>' -}  $1 $2 $3 }
808                      | RelationalExpressionNoIn Le  ShiftExpression { AST.JSExpressionBinary {- '<=' -} $1 $2 $3 }
809                      | RelationalExpressionNoIn Ge  ShiftExpression { AST.JSExpressionBinary {- '>=' -} $1 $2 $3 }
810                      | RelationalExpressionNoIn Instanceof ShiftExpression { AST.JSExpressionBinary {- ' instanceof ' -} $1 $2 $3 }
811 
812 -- EqualityExpression :                                        See 11.9
813 --        RelationalExpression
814 --        EqualityExpression == RelationalExpression
815 --        EqualityExpression != RelationalExpression
816 --        EqualityExpression === RelationalExpression
817 --        EqualityExpression !== RelationalExpression
818 EqualityExpression :: { AST.JSExpression }
819 EqualityExpression : RelationalExpression { $1 {- 'EqualityExpression' -} }
820                    | EqualityExpression Equal    RelationalExpression { AST.JSExpressionBinary {- '==' -}  $1 $2 $3 }
821                    | EqualityExpression Ne       RelationalExpression { AST.JSExpressionBinary {- '!=' -}  $1 $2 $3 }
822                    | EqualityExpression StrictEq RelationalExpression { AST.JSExpressionBinary {- '===' -} $1 $2 $3 }
823                    | EqualityExpression StrictNe RelationalExpression { AST.JSExpressionBinary {- '!==' -} $1 $2 $3 }
824 
825 -- EqualityExpressionNoIn :                                    See 11.9
826 --        RelationalExpressionNoIn
827 --        EqualityExpressionNoIn == RelationalExpressionNoIn
828 --        EqualityExpressionNoIn != RelationalExpressionNoIn
829 --        EqualityExpressionNoIn === RelationalExpressionNoIn
830 --        EqualityExpressionNoIn !== RelationalExpressionNoIn
831 EqualityExpressionNoIn :: { AST.JSExpression }
832 EqualityExpressionNoIn : RelationalExpressionNoIn { $1 {- 'EqualityExpressionNoIn' -} }
833                        | EqualityExpressionNoIn Equal    RelationalExpression { AST.JSExpressionBinary {- '==' -}  $1 $2 $3 }
834                        | EqualityExpressionNoIn Ne       RelationalExpression { AST.JSExpressionBinary {- '!=' -}  $1 $2 $3 }
835                        | EqualityExpressionNoIn StrictEq RelationalExpression { AST.JSExpressionBinary {- '===' -} $1 $2 $3 }
836                        | EqualityExpressionNoIn StrictNe RelationalExpression { AST.JSExpressionBinary {- '!==' -} $1 $2 $3 }
837 
838 -- BitwiseANDExpression :                                      See 11.10
839 --        EqualityExpression
840 --        BitwiseANDExpression & EqualityExpression
841 BitwiseAndExpression :: { AST.JSExpression }
842 BitwiseAndExpression : EqualityExpression { $1 {- 'BitwiseAndExpression' -} }
843                      | BitwiseAndExpression BitAnd EqualityExpression { AST.JSExpressionBinary {- '&' -} $1 $2 $3 }
844 
845 -- BitwiseANDExpressionNoIn :                                  See 11.10
846 --        EqualityExpressionNoIn
847 --        BitwiseANDExpressionNoIn & EqualityExpressionNoIn
848 BitwiseAndExpressionNoIn :: { AST.JSExpression }
849 BitwiseAndExpressionNoIn : EqualityExpressionNoIn { $1 {- 'BitwiseAndExpression' -} }
850                      | BitwiseAndExpressionNoIn BitAnd EqualityExpressionNoIn { AST.JSExpressionBinary {- '&' -} $1 $2 $3 }
851 
852 -- BitwiseXORExpression :                                                                See 11.10
853 --        BitwiseANDExpression
854 --        BitwiseXORExpression ^ BitwiseANDExpression
855 BitwiseXOrExpression :: { AST.JSExpression }
856 BitwiseXOrExpression : BitwiseAndExpression { $1 {- 'BitwiseXOrExpression' -} }
857                      | BitwiseXOrExpression BitXor BitwiseAndExpression { AST.JSExpressionBinary {- '^' -} $1 $2 $3 }
858 
859 -- BitwiseXORExpressionNoIn :                                                            See 11.10
860 --        BitwiseANDExpressionNoIn
861 --        BitwiseXORExpressionNoIn ^ BitwiseANDExpressionNoIn
862 BitwiseXOrExpressionNoIn :: { AST.JSExpression }
863 BitwiseXOrExpressionNoIn : BitwiseAndExpressionNoIn { $1 {- 'BitwiseXOrExpression' -} }
864                          | BitwiseXOrExpressionNoIn BitXor BitwiseAndExpressionNoIn { AST.JSExpressionBinary {- '^' -} $1 $2 $3 }
865 
866 -- BitwiseORExpression :                                                                 See 11.10
867 --        BitwiseXORExpression
868 --        BitwiseORExpression | BitwiseXORExpression
869 BitwiseOrExpression :: { AST.JSExpression }
870 BitwiseOrExpression : BitwiseXOrExpression { $1 {- 'BitwiseOrExpression' -} }
871                     | BitwiseOrExpression BitOr BitwiseXOrExpression { AST.JSExpressionBinary {- '|' -} $1 $2 $3 }
872 
873 -- BitwiseORExpressionNoIn :                                                             See 11.10
874 --        BitwiseXORExpressionNoIn
875 --        BitwiseORExpressionNoIn | BitwiseXORExpressionNoIn
876 BitwiseOrExpressionNoIn :: { AST.JSExpression }
877 BitwiseOrExpressionNoIn : BitwiseXOrExpressionNoIn { $1 {- 'BitwiseOrExpression' -} }
878                         | BitwiseOrExpressionNoIn BitOr BitwiseXOrExpressionNoIn { AST.JSExpressionBinary {- '|' -} $1 $2 $3 }
879 
880 -- LogicalANDExpression :                                                                See 11.11
881 --        BitwiseORExpression
882 --        LogicalANDExpression && BitwiseORExpression
883 LogicalAndExpression :: { AST.JSExpression }
884 LogicalAndExpression : BitwiseOrExpression { $1 {- 'LogicalAndExpression' -} }
885                      | LogicalAndExpression And BitwiseOrExpression { AST.JSExpressionBinary {- '&&' -} $1 $2 $3 }
886 
887 -- LogicalANDExpressionNoIn :                                                            See 11.11
888 --        BitwiseORExpressionNoIn
889 --        LogicalANDExpressionNoIn && BitwiseORExpressionNoIn
890 LogicalAndExpressionNoIn :: { AST.JSExpression }
891 LogicalAndExpressionNoIn : BitwiseOrExpressionNoIn { $1 {- 'LogicalAndExpression' -} }
892                          | LogicalAndExpressionNoIn And BitwiseOrExpressionNoIn { AST.JSExpressionBinary {- '&&' -} $1 $2 $3 }
893 
894 -- LogicalORExpression :                                                                 See 11.11
895 --        LogicalANDExpression
896 --        LogicalORExpression || LogicalANDExpression
897 LogicalOrExpression :: { AST.JSExpression }
898 LogicalOrExpression : LogicalAndExpression { $1 {- 'LogicalOrExpression' -} }
899                     | LogicalOrExpression Or LogicalAndExpression { AST.JSExpressionBinary {- '||' -} $1 $2 $3 }
900 
901 -- LogicalORExpressionNoIn :                                                             See 11.11
902 --        LogicalANDExpressionNoIn
903 --        LogicalORExpressionNoIn || LogicalANDExpressionNoIn
904 LogicalOrExpressionNoIn :: { AST.JSExpression }
905 LogicalOrExpressionNoIn : LogicalAndExpressionNoIn { $1 {- 'LogicalOrExpression' -} }
906                         | LogicalOrExpressionNoIn Or LogicalAndExpressionNoIn { AST.JSExpressionBinary {- '||' -} $1 $2 $3 }
907 
908 -- ConditionalExpression :                                                               See 11.12
909 --        LogicalORExpression
910 --        LogicalORExpression ? AssignmentExpression : AssignmentExpression
911 ConditionalExpression :: { AST.JSExpression }
912 ConditionalExpression : LogicalOrExpression { $1 {- 'ConditionalExpression1' -} }
913                       | LogicalOrExpression Hook AssignmentExpression Colon AssignmentExpression
914                         { AST.JSExpressionTernary $1 $2 $3 $4 $5 {- 'ConditionalExpression2' -}  }
915 
916 -- ConditionalExpressionNoIn :                                                           See 11.12
917 --        LogicalORExpressionNoIn
918 --        LogicalORExpressionNoIn ? AssignmentExpressionNoIn : AssignmentExpressionNoIn
919 ConditionalExpressionNoIn :: { AST.JSExpression }
920 ConditionalExpressionNoIn : LogicalOrExpressionNoIn { $1 {- 'ConditionalExpressionNoIn1' -} }
921                           | LogicalOrExpressionNoIn Hook AssignmentExpressionNoIn Colon AssignmentExpressionNoIn
922                             { AST.JSExpressionTernary $1 $2 $3 $4 $5 {- 'ConditionalExpressionNoIn2' -} }
923 
924 -- AssignmentExpression :                                                                See 11.13
925 --        ConditionalExpression
926 --        LeftHandSideExpression AssignmentOperator AssignmentExpression
927 AssignmentExpression :: { AST.JSExpression }
928 AssignmentExpression : ConditionalExpression { $1 {- 'AssignmentExpression1' -} }
929                      | YieldExpression { $1 }
930                      | LeftHandSideExpression AssignmentOperator AssignmentExpression
931                        { AST.JSAssignExpression $1 $2 $3 {- 'AssignmentExpression2' -} }
932                      | SpreadExpression { $1 }
933 
934 -- AssignmentExpressionNoIn :                                                            See 11.13
935 --        ConditionalExpressionNoIn
936 --        LeftHandSideExpression AssignmentOperator AssignmentExpressionNoIn
937 AssignmentExpressionNoIn :: { AST.JSExpression }
938 AssignmentExpressionNoIn : ConditionalExpressionNoIn { $1 {- 'AssignmentExpressionNoIn1' -} }
939                          | YieldExpression { $1 }
940                          | LeftHandSideExpression AssignmentOperator AssignmentExpressionNoIn
941                            { AST.JSAssignExpression $1 $2 $3 {- 'AssignmentExpressionNoIn1' -} }
942 
943 -- AssignmentOperator : one of                                                           See 11.13
944 --     '=' | '*=' | '/=' | '%=' | '+=' | '-=' | '<<=' | '>>=' | '>>>=' | '&=' | '^=' | '|='
945 AssignmentOperator :: { AST.JSAssignOp }
946 AssignmentOperator : OpAssign     { $1 }
947                    | SimpleAssign { AST.JSAssign $1 {- 'SimpleAssign' -} }
948 
949 -- Expression :                                                   See 11.14
950 --         AssignmentExpression
951 --         Expression , AssignmentExpression
952 Expression :: { AST.JSExpression }
953 Expression : AssignmentExpression { $1 {- 'Expression' -} }
954            | Expression Comma AssignmentExpression  { AST.JSCommaExpression $1 $2 $3    {- 'Expression2' -} }
955 
956 -- ExpressionNoIn :                                               See 11.14
957 --         AssignmentExpressionNoIn
958 --         ExpressionNoIn , AssignmentExpressionNoIn
959 ExpressionNoIn :: { AST.JSExpression }
960 ExpressionNoIn : AssignmentExpressionNoIn { $1 {- 'ExpressionNoIn' -} }
961                | ExpressionNoIn Comma AssignmentExpressionNoIn  { AST.JSCommaExpression $1 $2 $3 {- 'ExpressionNoIn2' -} }
962 
963 -- TODO: still required?
964 ExpressionOpt :: { AST.JSCommaList AST.JSExpression }
965 ExpressionOpt : Expression { AST.JSLOne $1  {- 'ExpressionOpt1' -} }
966               |            { AST.JSLNil     {- 'ExpressionOpt2' -} }
967 
968 ExpressionNoInOpt :: { AST.JSCommaList AST.JSExpression }
969 ExpressionNoInOpt : ExpressionNoIn { AST.JSLOne $1  {- 'ExpressionOpt1' -} }
970                   |                { AST.JSLNil     {- 'ExpressionOpt2' -} }
971 
972 
973 -- Statement :                                                    See clause 12
974 --         Block
975 --         VariableStatement
976 --         EmptyStatement
977 --         ExpressionStatement
978 --         IfStatement
979 --         IterationStatement
980 --         ContinueStatement
981 --         BreakStatement
982 --         ReturnStatement
983 --         WithStatement
984 --         LabelledStatement
985 --         SwitchStatement
986 --         ThrowStatement
987 --         TryStatement
988 --         DebuggerStatement
989 Statement :: { AST.JSStatement }
990 Statement : StatementNoEmpty   { $1 {- 'Statement1' -} }
991           | EmptyStatement     { $1 {- 'Statement2' -} }
992 
993 StatementNoEmpty :: { AST.JSStatement }
994 StatementNoEmpty
995   : IfStatement             { $1 {- 'StatementNoEmpty5' -} }
996   | ContinueStatement       { $1 {- 'StatementNoEmpty7' -} }
997   | BreakStatement          { $1 {- 'StatementNoEmpty8' -} }
998   | ReturnStatement         { $1 {- 'StatementNoEmpty9' -} }
999   | WithStatement           { $1 {- 'StatementNoEmpty10' -} }
1000   | LabelledStatement       { $1 {- 'StatementNoEmpty11' -} }
1001   | SwitchStatement         { $1 {- 'StatementNoEmpty12' -} }
1002   | ThrowStatement          { $1 {- 'StatementNoEmpty13' -} }
1003   | TryStatement            { $1 {- 'StatementNoEmpty14' -} }
1004   | StatementBlock          { $1 {- 'StatementNoEmpty1' -} }
1005   | VariableStatement       { $1 {- 'StatementNoEmpty2' -} }
1006   | IterationStatement      { $1 {- 'StatementNoEmpty6' -} }
1007   | ExpressionStatement     { $1 {- 'StatementNoEmpty4' -} }
1008   | AsyncFunctionStatement  { $1 {- 'StatementNoEmpty15' -} }
1009   | DebuggerStatement       { $1 {- 'StatementNoEmpty15' -} }
1010 
1011 
1012 
1013 StatementBlock :: { AST.JSStatement }
1014 StatementBlock : Block MaybeSemi       { blockToStatement $1 $2 {- 'StatementBlock1' -} }
1015 
1016 
1017 -- Block :                                                        See 12.1
1018 --         { StatementListopt }
1019 Block :: { AST.JSBlock }
1020 Block : LBrace RBrace               { AST.JSBlock $1 [] $2 {- 'Block1' -} }
1021       | LBrace StatementList RBrace { AST.JSBlock $1 $2 $3 {- 'Block2' -} }
1022 
1023 -- StatementList :                                                See 12.1
1024 --         Statement
1025 --         StatementList Statement
1026 StatementList :: { [AST.JSStatement] }
1027 StatementList : Statement               { [$1]       {- 'StatementList1' -} }
1028               | StatementList Statement { ($1++[$2]) {- 'StatementList2' -} }
1029 
1030 -- VariableStatement :                                            See 12.2
1031 --         var VariableDeclarationList ;
1032 VariableStatement :: { AST.JSStatement }
1033 VariableStatement : Var   VariableDeclarationList MaybeSemi { AST.JSVariable $1 $2 $3 {- 'VariableStatement1' -} }
1034                   | Let   VariableDeclarationList MaybeSemi { AST.JSLet      $1 $2 $3 {- 'VariableStatement2' -} }
1035                   | Const VariableDeclarationList MaybeSemi { AST.JSConstant $1 $2 $3 {- 'VariableStatement3' -} }
1036 
1037 -- VariableDeclarationList :                                      See 12.2
1038 --         VariableDeclaration
1039 --         VariableDeclarationList , VariableDeclaration
1040 VariableDeclarationList :: { AST.JSCommaList AST.JSExpression }
1041 VariableDeclarationList : VariableDeclaration                               { AST.JSLOne $1         {- 'VariableDeclarationList1' -} }
1042                         | VariableDeclarationList Comma VariableDeclaration { AST.JSLCons $1 $2 $3  {- 'VariableDeclarationList2' -} }
1043 
1044 -- VariableDeclarationListNoIn :                                  See 12.2
1045 --         VariableDeclarationNoIn
1046 --         VariableDeclarationListNoIn , VariableDeclarationNoIn
1047 VariableDeclarationListNoIn :: { AST.JSCommaList AST.JSExpression }
1048 VariableDeclarationListNoIn : VariableDeclarationNoIn                                   { AST.JSLOne $1         {- 'VariableDeclarationListNoIn1' -} }
1049                             | VariableDeclarationListNoIn Comma VariableDeclarationNoIn { AST.JSLCons $1 $2 $3  {- 'VariableDeclarationListNoIn2' -} }
1050 
1051 -- VariableDeclaration :                                          See 12.2
1052 --         Identifier Initialiseropt
1053 VariableDeclaration :: { AST.JSExpression }
1054 VariableDeclaration : PrimaryExpression SimpleAssign AssignmentExpression { AST.JSVarInitExpression $1 (AST.JSVarInit $2 $3) {- 'JSVarInitExpression1' -} }
1055                     | Identifier                                          { AST.JSVarInitExpression $1 AST.JSVarInitNone     {- 'JSVarInitExpression2' -} }
1056 
1057 -- VariableDeclarationNoIn :                                      See 12.2
1058 --         Identifier InitialiserNoInopt
1059 VariableDeclarationNoIn :: { AST.JSExpression }
1060 VariableDeclarationNoIn : PrimaryExpression SimpleAssign AssignmentExpression { AST.JSVarInitExpression $1 (AST.JSVarInit $2 $3) {- 'JSVarInitExpressionInit2' -} }
1061                         | Identifier                                          { AST.JSVarInitExpression $1 AST.JSVarInitNone     {- 'JSVarInitExpression2' -} }
1062 
1063 -- EmptyStatement :                                                                         See 12.3
1064 --         ;
1065 EmptyStatement :: { AST.JSStatement }
1066 EmptyStatement : Semi { AST.JSEmptyStatement $1 {- 'EmptyStatement' -} }
1067 
1068 -- ExpressionStatement :                                                                    See 12.4
1069 --         [lookahead not in {{, function}] Expression  ;
1070 -- TODO: Sort out lookahead issue. Maybe by just putting production lower to set reduce/reduce conflict
1071 --       According to http://sideshowbarker.github.com/es5-spec/#x12.4, the ambiguity is with
1072 --       Block or FunctionDeclaration
1073 ExpressionStatement :: { AST.JSStatement }
1074 ExpressionStatement : Expression MaybeSemi { expressionToStatement $1 $2 {- 'ExpressionStatement' -} }
1075 
1076 
1077 -- IfStatement :                                                                            See 12.5
1078 --         if ( Expression ) Statement else Statement
1079 --         if ( Expression ) Statement
1080 IfStatement :: { AST.JSStatement } -- +++XXXX++
1081 IfStatement : If LParen Expression RParen EmptyStatement
1082                   { AST.JSIf $1 $2 $3 $4 $5                            {- 'IfStatement1' -} }
1083             | If LParen Expression RParen StatementNoEmpty Else Statement
1084                   {  AST.JSIfElse $1 $2 $3 $4 $5 $6 $7                 {- 'IfStatement3' -} }
1085             | If LParen Expression RParen StatementNoEmpty
1086                   { AST.JSIf $1 $2 $3 $4 $5                            {- 'IfStatement3' -} }
1087             | If LParen Expression RParen EmptyStatement Else Statement
1088                   {  AST.JSIfElse $1 $2 $3 $4 $5 $6 $7                 {- 'IfStatement4' -} }
1089 
1090 -- IterationStatement :                                                                     See 12.6
1091 --         do Statement while ( Expression );
1092 --         while ( Expression ) Statement
1093 --         for (ExpressionNoInopt; Expressionopt ; Expressionopt ) Statement
1094 --         for ( var VariableDeclarationListNoIn; Expressionopt ; Expressionopt ) Statement
1095 --         for ( LeftHandSideExpression in Expression ) Statement
1096 --         for ( var VariableDeclarationNoIn in Expression ) Statement
1097 IterationStatement :: { AST.JSStatement }
1098 IterationStatement : Do StatementNoEmpty While LParen Expression RParen MaybeSemi
1099                      { AST.JSDoWhile $1 $2 $3 $4 $5 $6 $7 {- 'IterationStatement1' -} }
1100                    | While LParen Expression RParen Statement
1101                      { AST.JSWhile $1 $2 $3 $4 $5 {- 'IterationStatement2' -} }
1102                    | For LParen ExpressionNoInOpt Semi ExpressionOpt Semi ExpressionOpt RParen Statement
1103                      { AST.JSFor $1 $2 $3 $4 $5 $6 $7 $8 $9 {- 'IterationStatement3' -} }
1104                    | For LParen Var VariableDeclarationListNoIn Semi ExpressionOpt Semi ExpressionOpt RParen Statement
1105                      { AST.JSForVar $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 {- 'IterationStatement4' -} }
1106                    | For LParen LeftHandSideExpression In Expression RParen Statement
1107                      { AST.JSForIn $1 $2 $3 $4 $5 $6 $7 {- 'IterationStatement 5' -} }
1108                    | For LParen Var VariableDeclarationNoIn In Expression RParen Statement
1109                      { AST.JSForVarIn $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement6' -} }
1110                    | For LParen Let VariableDeclarationListNoIn Semi ExpressionOpt Semi ExpressionOpt RParen Statement
1111                      { AST.JSForLet $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 {- 'IterationStatement 7' -} }
1112                    | For LParen Let VariableDeclarationNoIn In Expression RParen Statement
1113                      { AST.JSForLetIn $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 8' -} }
1114                    | For LParen Let VariableDeclarationNoIn Of Expression RParen Statement
1115                      { AST.JSForLetOf $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 9' -} }
1116                    | For LParen LeftHandSideExpression Of Expression RParen Statement
1117                      { AST.JSForOf $1 $2 $3 $4 $5 $6 $7 {- 'IterationStatement 10'-} }
1118                    | For LParen Var VariableDeclarationNoIn Of Expression RParen Statement
1119                      { AST.JSForVarOf $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 11' -} }
1120                    | For LParen Const VariableDeclarationListNoIn Semi ExpressionOpt Semi ExpressionOpt RParen Statement
1121                      { AST.JSForConst $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 {- 'IterationStatement 12' -} }
1122                    | For LParen Const VariableDeclarationNoIn In Expression RParen Statement
1123                      { AST.JSForConstIn $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 13' -} }
1124                    | For LParen Const VariableDeclarationNoIn Of Expression RParen Statement
1125                      { AST.JSForConstOf $1 $2 $3 $4 $5 $6 $7 $8 {- 'IterationStatement 14' -} }
1126 
1127 -- ContinueStatement :                                                                      See 12.7
1128 --         continue [no LineTerminator here] Identifieropt ;
1129 ContinueStatement :: { AST.JSStatement }
1130 ContinueStatement : Continue AutoSemi              { AST.JSContinue $1 AST.JSIdentNone $2  {- 'ContinueStatement1' -} }
1131                   | Continue Identifier MaybeSemi  { AST.JSContinue $1 (identName $2) $3   {- 'ContinueStatement2' -} }
1132 
1133 -- BreakStatement :                                                                         See 12.8
1134 --         break [no LineTerminator here] Identifieropt ;
1135 BreakStatement :: { AST.JSStatement }
1136 BreakStatement : Break AutoSemi              { AST.JSBreak $1 AST.JSIdentNone $2 {- 'BreakStatement1' -} }
1137                | Break Identifier MaybeSemi  { AST.JSBreak $1 (identName $2) $3  {- 'BreakStatement2' -} }
1138 
1139 -- ReturnStatement :                                                                        See 12.9
1140 --         return [no LineTerminator here] Expressionopt ;
1141 ReturnStatement :: { AST.JSStatement }
1142 ReturnStatement : Return AutoSemi              { AST.JSReturn $1 Nothing $2 }
1143                 | Return Expression MaybeSemi  { AST.JSReturn $1 (Just $2) $3 }
1144 
1145 -- WithStatement :                                                                          See 12.10
1146 --         with ( Expression ) Statement
1147 WithStatement :: { AST.JSStatement }
1148 WithStatement : With LParen Expression RParen Statement MaybeSemi  { AST.JSWith $1 $2 $3 $4 $5 $6 }
1149 
1150 -- SwitchStatement :                                                                        See 12.11
1151 --         switch ( Expression ) CaseBlock
1152 SwitchStatement :: { AST.JSStatement }
1153 SwitchStatement : Switch LParen Expression RParen LBrace CaseBlock RBrace MaybeSemi { AST.JSSwitch $1 $2 $3 $4 $5 $6 $7 $8 }
1154 
1155 -- CaseBlock :                                                                              See 12.11
1156 --         { CaseClausesopt }
1157 --         { CaseClausesopt DefaultClause CaseClausesopt }
1158 CaseBlock :: { [AST.JSSwitchParts] }
1159 CaseBlock : CaseClausesOpt                              { $1           {- 'CaseBlock1' -} }
1160           | CaseClausesOpt DefaultClause CaseClausesOpt { $1++[$2]++$3 {- 'CaseBlock2' -} }
1161 
1162 -- CaseClauses :                                                                            See 12.11
1163 --         CaseClause
1164 --         CaseClauses CaseClause
1165 CaseClausesOpt :: { [AST.JSSwitchParts] }
1166 CaseClausesOpt : CaseClause                { [$1]       {- 'CaseClausesOpt1' -} }
1167                | CaseClausesOpt CaseClause { ($1++[$2]) {- 'CaseClausesOpt2' -} }
1168                |                           { []         {- 'CaseClausesOpt3' -} }
1169 
1170 -- CaseClause :                                                               See 12.11
1171 --        case Expression : StatementListopt
1172 CaseClause :: { AST.JSSwitchParts }
1173 CaseClause : Case Expression Colon StatementList  { AST.JSCase $1 $2 $3 $4 {- 'CaseClause1' -} }
1174            | Case Expression Colon                { AST.JSCase $1 $2 $3 [] {- 'CaseClause2' -} }
1175 
1176 -- DefaultClause :                                                            See 12.11
1177 --        default : StatementListopt
1178 DefaultClause :: { AST.JSSwitchParts }
1179 DefaultClause : Default Colon                { AST.JSDefault $1 $2 [] {- 'DefaultClause1' -} }
1180               | Default Colon StatementList  { AST.JSDefault $1 $2 $3 {- 'DefaultClause2' -} }
1181 
1182 -- LabelledStatement :                                                        See 12.12
1183 --        Identifier : Statement
1184 LabelledStatement :: { AST.JSStatement }
1185 LabelledStatement : Identifier Colon Statement { AST.JSLabelled (identName $1) $2 $3 {- 'LabelledStatement' -} }
1186 
1187 -- ThrowStatement :                                                           See 12.13
1188 --        throw [no LineTerminator here] Expression ;
1189 ThrowStatement :: { AST.JSStatement }
1190 ThrowStatement : Throw Expression MaybeSemi { AST.JSThrow $1 $2 $3 {- 'ThrowStatement' -} }
1191 
1192 -- Note: worked in updated syntax as per https://developer.mozilla.org/en/JavaScript/Reference/Statements/try...catch
1193 --   i.e., 0 or more catches, then an optional finally
1194 -- TryStatement :                                                             See 12.14
1195 --        try Block Catch
1196 --        try Block Finally
1197 --        try Block Catch Finally
1198 TryStatement :: { AST.JSStatement }
1199 TryStatement : Try Block Catches         { AST.JSTry $1 $2 $3 AST.JSNoFinally {- 'TryStatement1' -} }
1200              | Try Block Finally         { AST.JSTry $1 $2 [] $3              {- 'TryStatement2' -} }
1201              | Try Block Catches Finally { AST.JSTry $1 $2 $3 $4              {- 'TryStatement3' -} }
1202 
1203 Catches :: { [AST.JSTryCatch] }
1204 Catches : Catch         { [$1]       {- 'Catches1' -} }
1205         | Catches Catch { ($1++[$2]) {- 'Catches2' -} }
1206 
1207 -- Note: worked in updated syntax as per https://developer.mozilla.org/en/JavaScript/Reference/Statements/try...catch
1208 -- <Catch> ::= 'catch' '(' Identifier ')' <Block>
1209 --   becomes
1210 -- <Catch> ::= 'catch' '(' Identifier ')' <Block>
1211 --           | 'catch' '(' Identifier 'if' ConditionalExpression ')' <Block>
1212 Catch :: { AST.JSTryCatch }
1213 Catch : CatchL LParen Identifier                          RParen Block { AST.JSCatch $1 $2 $3 $4 $5 {- 'Catch1' -} }
1214       | CatchL LParen Identifier If ConditionalExpression RParen Block { AST.JSCatchIf $1 $2 $3 $4 $5 $6 $7 {- 'Catch2' -} }
1215 
1216 -- Finally :                                                                  See 12.14
1217 --        finally Block
1218 Finally :: { AST.JSTryFinally }
1219 Finally : FinallyL Block { AST.JSFinally $1 $2 {- 'Finally' -} }
1220 
1221 -- DebuggerStatement :                                                        See 12.15
1222 --        debugger ;
1223 DebuggerStatement :: { AST.JSStatement }
1224 DebuggerStatement : 'debugger' MaybeSemi { AST.JSExpressionStatement (AST.JSLiteral (mkJSAnnot $1) "debugger") $2 {- 'DebuggerStatement' -} }
1225 
1226 -- FunctionDeclaration :                                                      See clause 13
1227 --        function Identifier ( FormalParameterListopt ) { FunctionBody }
1228 FunctionDeclaration :: { AST.JSStatement }
1229 FunctionDeclaration : NamedFunctionExpression MaybeSemi { expressionToStatement $1 $2                {- 'FunctionDeclaration1' -} }
1230 
1231 AsyncFunctionStatement :: { AST.JSStatement }
1232 AsyncFunctionStatement : Async NamedFunctionExpression MaybeSemi {  expressionToAsyncFunction $1 $2 $3  {- 'AsyncFunctionStatement1' -} }
1233 
1234 -- FunctionExpression :                                                       See clause 13
1235 --        function Identifieropt ( FormalParameterListopt ) { FunctionBody }
1236 FunctionExpression :: { AST.JSExpression }
1237 FunctionExpression : ArrowFunctionExpression     { $1 {- 'ArrowFunctionExpression' -} }
1238                    | LambdaExpression            { $1 {- 'FunctionExpression1' -} }
1239                    | NamedFunctionExpression     { $1 {- 'FunctionExpression2' -} }
1240 
1241 ArrowFunctionExpression :: { AST.JSExpression }
1242 ArrowFunctionExpression : ArrowParameterList Arrow StatementOrBlock
1243                            { AST.JSArrowExpression $1 $2 $3 }
1244 
1245 ArrowParameterList :: { AST.JSArrowParameterList }
1246 ArrowParameterList : PrimaryExpression {%^ toArrowParameterList $1 }
1247                    | LParen RParen
1248                       { AST.JSParenthesizedArrowParameterList $1 AST.JSLNil $2 }
1249 
1250 StatementOrBlock :: { AST.JSStatement }
1251 StatementOrBlock : Block MaybeSemi		{ blockToStatement $1 $2 }
1252                  | Expression MaybeSemi { expressionToStatement $1 $2 }
1253 
1254 -- StatementListItem :
1255 --        Statement
1256 --        Declaration
1257 StatementListItem :: { AST.JSStatement }
1258 StatementListItem : Statement           { $1 }
1259 
1260 NamedFunctionExpression :: { AST.JSExpression }
1261 NamedFunctionExpression : Function Identifier LParen RParen FunctionBody
1262                             { AST.JSFunctionExpression $1 (identName $2) $3 AST.JSLNil $4 $5    {- 'NamedFunctionExpression1' -} }
1263                         | Function Identifier LParen FormalParameterList RParen FunctionBody
1264                             { AST.JSFunctionExpression $1 (identName $2) $3 $4 $5 $6            {- 'NamedFunctionExpression2' -} }
1265 
1266 LambdaExpression :: { AST.JSExpression }
1267 LambdaExpression : Function LParen RParen FunctionBody
1268                     { AST.JSFunctionExpression $1 AST.JSIdentNone $2 AST.JSLNil $3 $4	{- 'LambdaExpression1' -} }
1269                  | Function LParen FormalParameterList RParen FunctionBody
1270                     { AST.JSFunctionExpression $1 AST.JSIdentNone $2 $3 $4 $5           {- 'LambdaExpression2' -} }
1271 
1272 -- GeneratorDeclaration :
1273 --         function * BindingIdentifier ( FormalParameters ) { GeneratorBody }
1274 --         function * ( FormalParameters ) { GeneratorBody }
1275 GeneratorDeclaration :: { AST.JSStatement }
1276 GeneratorDeclaration : NamedGeneratorExpression MaybeSemi  { expressionToStatement $1 $2 }
1277 
1278 -- GeneratorExpression :
1279 --         function * BindingIdentifieropt ( FormalParameters ) { GeneratorBody }
1280 -- GeneratorBody :
1281 --         FunctionBody
1282 GeneratorExpression :: { AST.JSExpression }
1283 GeneratorExpression : NamedGeneratorExpression { $1 }
1284                     | Function '*' LParen RParen FunctionBody
1285                         { AST.JSGeneratorExpression $1 (mkJSAnnot $2) AST.JSIdentNone $3 AST.JSLNil $4 $5 }
1286                     | Function '*' LParen FormalParameterList RParen FunctionBody
1287                         { AST.JSGeneratorExpression $1 (mkJSAnnot $2) AST.JSIdentNone $3 $4 $5 $6 }
1288 
1289 NamedGeneratorExpression :: { AST.JSExpression }
1290 NamedGeneratorExpression : Function '*' Identifier LParen RParen FunctionBody
1291                              { AST.JSGeneratorExpression $1 (mkJSAnnot $2) (identName $3) $4 AST.JSLNil $5 $6 }
1292                          | Function '*' Identifier LParen FormalParameterList RParen FunctionBody
1293                              { AST.JSGeneratorExpression $1 (mkJSAnnot $2) (identName $3) $4 $5 $6 $7 }
1294 
1295 -- YieldExpression :
1296 --         yield
1297 --         yield [no LineTerminator here] AssignmentExpression
1298 --         yield [no LineTerminator here] * AssignmentExpression
1299 YieldExpression :: { AST.JSExpression }
1300 YieldExpression : Yield { AST.JSYieldExpression $1 Nothing }
1301                 | Yield AssignmentExpression { AST.JSYieldExpression $1 (Just $2) }
1302                 | Yield '*' AssignmentExpression { AST.JSYieldFromExpression $1 (mkJSAnnot $2) $3 }
1303 
1304 
1305 IdentifierOpt :: { AST.JSIdent }
1306 IdentifierOpt : Identifier { identName $1     {- 'IdentifierOpt1' -} }
1307               |            { AST.JSIdentNone  {- 'IdentifierOpt2' -} }
1308 
1309 -- FormalParameterList :                                                      See clause 13
1310 --        Identifier
1311 --        FormalParameterList , Identifier
1312 FormalParameterList :: { AST.JSCommaList AST.JSExpression }
1313 FormalParameterList : AssignmentExpression                           { AST.JSLOne $1         {- 'FormalParameterList1' -} }
1314                     | FormalParameterList Comma AssignmentExpression { AST.JSLCons $1 $2 $3  {- 'FormalParameterList2' -} }
1315 
1316 -- FunctionBody :                                                             See clause 13
1317 --        SourceElementsopt
1318 FunctionBody :: { AST.JSBlock }
1319 FunctionBody : Block                    { $1    {- 'FunctionBody1' -} }
1320 
1321 -- ClassDeclaration :
1322 --         class BindingIdentifier ClassTail
1323 --         class ClassTail
1324 -- ClassExpression :
1325 --         class BindingIdentifieropt ClassTail
1326 -- ClassTail :
1327 --         ClassHeritageopt { ClassBodyopt }
1328 ClassDeclaration :: { AST.JSStatement }
1329 ClassDeclaration : Class Identifier ClassHeritage LBrace ClassBody RBrace { AST.JSClass $1 (identName $2) $3 $4 $5 $6 AST.JSSemiAuto }
1330 
1331 ClassExpression :: { AST.JSExpression }
1332 ClassExpression : Class Identifier ClassHeritage LBrace ClassBody RBrace { AST.JSClassExpression $1 (identName $2)  $3 $4 $5 $6 }
1333                 | Class            ClassHeritage LBrace ClassBody RBrace { AST.JSClassExpression $1 AST.JSIdentNone $2 $3 $4 $5 }
1334 
1335 -- ClassHeritage :
1336 --         extends LeftHandSideExpression
1337 ClassHeritage :: { AST.JSClassHeritage }
1338 ClassHeritage : Extends LeftHandSideExpression { AST.JSExtends $1 $2 }
1339               |                                { AST.JSExtendsNone }
1340 
1341 -- ClassBody :
1342 --         ClassElementList
1343 -- ClassElementList :
1344 --         ClassElement
1345 --         ClassElementList ClassElement
1346 ClassBody :: { [AST.JSClassElement] }
1347 ClassBody :                        { [] }
1348           | ClassBody ClassElement { $1 ++ [$2] }
1349 
1350 -- ClassElement :
1351 --         MethodDefinition
1352 --         static MethodDefinition
1353 --         ;
1354 ClassElement :: { AST.JSClassElement }
1355 ClassElement : MethodDefinition        { AST.JSClassInstanceMethod $1 }
1356              | Static MethodDefinition { AST.JSClassStaticMethod $1 $2 }
1357              | Semi                    { AST.JSClassSemi $1 }
1358 
1359 -- Program :                                                                  See clause 14
1360 --        SourceElementsopt
1361 
1362 Program :: { AST.JSAST }
1363 Program : StatementList Eof     	{ AST.JSAstProgram $1 $2   	{- 'Program1' -} }
1364         | Eof                   	{ AST.JSAstProgram [] $1 	{- 'Program2' -} }
1365 
1366 -- Module :                                                                   See 15.2
1367 --        ModuleBody[opt]
1368 --
1369 -- ModuleBody :
1370 --        ModuleItemList
1371 Module :: { AST.JSAST }
1372 Module : ModuleItemList Eof     	{ AST.JSAstModule $1 $2   	{- 'Module1' -} }
1373         | Eof                   	{ AST.JSAstModule [] $1 	{- 'Module2' -} }
1374 
1375 -- ModuleItemList :
1376 --         ModuleItem
1377 --         ModuleItemList ModuleItem
1378 ModuleItemList :: { [AST.JSModuleItem] }
1379 ModuleItemList : ModuleItem                  { [$1]         {- 'ModuleItemList1' -} }
1380                | ModuleItemList ModuleItem   { ($1++[$2])   {- 'ModuleItemList2' -} }
1381 
1382 -- ModuleItem :
1383 --        ImportDeclaration
1384 --        ExportDeclaration
1385 --        StatementListItem
1386 ModuleItem :: { AST.JSModuleItem }
1387 ModuleItem : Import ImportDeclaration
1388                     { AST.JSModuleImportDeclaration $1 $2   {- 'ModuleItem1' -} }
1389            | Export ExportDeclaration
1390                     { AST.JSModuleExportDeclaration $1 $2   {- 'ModuleItem1' -} }
1391            | StatementListItem
1392                     { AST.JSModuleStatementListItem $1      {- 'ModuleItem2' -} }
1393 
1394 ImportDeclaration :: { AST.JSImportDeclaration }
1395 ImportDeclaration : ImportClause FromClause AutoSemi
1396                           { AST.JSImportDeclaration $1 $2 $3 }
1397                   | 'string' AutoSemi
1398                           { AST.JSImportDeclarationBare (mkJSAnnot $1) (tokenLiteral $1) $2 }
1399 
1400 ImportClause :: { AST.JSImportClause }
1401 ImportClause : IdentifierName
1402                      { AST.JSImportClauseDefault (identName $1) }
1403              | NameSpaceImport
1404                      { AST.JSImportClauseNameSpace $1 }
1405              | NamedImports
1406                      { AST.JSImportClauseNamed $1 }
1407              | IdentifierName ',' NameSpaceImport
1408                      { AST.JSImportClauseDefaultNameSpace (identName $1) (mkJSAnnot $2) $3 }
1409              | IdentifierName ',' NamedImports
1410                      { AST.JSImportClauseDefaultNamed (identName $1) (mkJSAnnot $2) $3 }
1411 
1412 FromClause :: { AST.JSFromClause }
1413 FromClause : From 'string'
1414                   { AST.JSFromClause $1 (mkJSAnnot $2) (tokenLiteral $2) }
1415 
1416 NameSpaceImport :: { AST.JSImportNameSpace }
1417 NameSpaceImport : Mul As IdentifierName
1418                         { AST.JSImportNameSpace $1 $2 (identName $3) }
1419 
1420 NamedImports :: { AST.JSImportsNamed }
1421 NamedImports : LBrace ImportsList RBrace
1422                       { AST.JSImportsNamed $1 $2 $3 }
1423 
1424 ImportsList :: { AST.JSCommaList AST.JSImportSpecifier }
1425 ImportsList : ImportSpecifier
1426                     { AST.JSLOne $1 }
1427             | ImportsList Comma ImportSpecifier
1428                     { AST.JSLCons $1 $2 $3 }
1429 
1430 ImportSpecifier :: { AST.JSImportSpecifier }
1431 ImportSpecifier : IdentifierName
1432                     { AST.JSImportSpecifier (identName $1) }
1433                 | IdentifierName As IdentifierName
1434                     { AST.JSImportSpecifierAs (identName $1) $2 (identName $3) }
1435 
1436 -- ExportDeclaration :                                                        See 15.2.3
1437 -- [ ]    export * FromClause ;
1438 -- [x]    export ExportClause FromClause ;
1439 -- [x]    export ExportClause ;
1440 -- [x]    export VariableStatement
1441 -- [ ]    export Declaration
1442 -- [ ]    Declaration :
1443 -- [ ]       HoistableDeclaration
1444 -- [x]       ClassDeclaration
1445 -- [x]       LexicalDeclaration
1446 -- [ ]    HoistableDeclaration :
1447 -- [x]       FunctionDeclaration
1448 -- [x]       GeneratorDeclaration
1449 -- [ ]       AsyncFunctionDeclaration
1450 -- [ ]       AsyncGeneratorDeclaration
1451 -- [ ]    export default HoistableDeclaration[Default]
1452 -- [ ]    export default ClassDeclaration[Default]
1453 -- [ ]    export default [lookahead ∉ { function, class }] AssignmentExpression[In] ;
1454 ExportDeclaration :: { AST.JSExportDeclaration }
1455 ExportDeclaration : ExportClause FromClause AutoSemi
1456                          { AST.JSExportFrom $1 $2 $3  {- 'ExportDeclaration1' -} }
1457                   | ExportClause AutoSemi
1458                          { AST.JSExportLocals $1 $2   {- 'ExportDeclaration2' -} }
1459                   | VariableStatement AutoSemi
1460                          { AST.JSExport $1 $2         {- 'ExportDeclaration3' -} }
1461                   | FunctionDeclaration AutoSemi
1462                          { AST.JSExport $1 $2         {- 'ExportDeclaration4' -} }
1463                   | GeneratorDeclaration AutoSemi
1464                          { AST.JSExport $1 $2         {- 'ExportDeclaration5' -} }
1465                   | ClassDeclaration AutoSemi
1466                          { AST.JSExport $1 $2         {- 'ExportDeclaration6' -} }
1467 
1468 -- ExportClause :
1469 --           { }
1470 --           { ExportsList }
1471 --           { ExportsList , }
1472 ExportClause :: { AST.JSExportClause }
1473 ExportClause : LBrace RBrace
1474                     { AST.JSExportClause $1 AST.JSLNil $2     {- 'ExportClause1' -} }
1475              | LBrace ExportsList RBrace
1476                     { AST.JSExportClause $1 $2 $3             {- 'ExportClause2' -} }
1477 
1478 -- ExportsList :
1479 --           ExportSpecifier
1480 --           ExportsList , ExportSpecifier
1481 ExportsList :: { AST.JSCommaList AST.JSExportSpecifier }
1482 ExportsList : ExportSpecifier
1483                     { AST.JSLOne $1          {- 'ExportsList1' -} }
1484             | ExportsList Comma ExportSpecifier
1485                     { AST.JSLCons $1 $2 $3   {- 'ExportsList2' -} }
1486 
1487 -- ExportSpecifier :
1488 --           IdentifierName
1489 --           IdentifierName as IdentifierName
1490 ExportSpecifier :: { AST.JSExportSpecifier }
1491 ExportSpecifier : IdentifierName
1492                     { AST.JSExportSpecifier (identName $1)                      {- 'ExportSpecifier1' -} }
1493                 | IdentifierName As IdentifierName
1494                     { AST.JSExportSpecifierAs (identName $1) $2 (identName $3)  {- 'ExportSpecifier2' -} }
1495 
1496 -- For debugging/other entry points
1497 LiteralMain :: { AST.JSAST }
1498 LiteralMain : Literal Eof			{ AST.JSAstLiteral $1 $2	{- 'LiteralMain' -} }
1499 
1500 ExpressionMain :: { AST.JSAST }
1501 ExpressionMain : Expression Eof					{ AST.JSAstExpression $1 $2 {- 'ExpressionMain' -} }
1502 
1503 StatementMain :: { AST.JSAST }
1504 StatementMain : StatementNoEmpty Eof	{ AST.JSAstStatement $1 $2   	{- 'StatementMain' -} }
1505 
1506 {
1507 
1508 -- Need this type while build the AST, but is not actually part of the AST.
1509 data JSArguments = JSArguments AST.JSAnnot (AST.JSCommaList AST.JSExpression) AST.JSAnnot    -- ^lb, args, rb
1510 data JSUntaggedTemplate = JSUntaggedTemplate !AST.JSAnnot !String ![AST.JSTemplatePart] -- lquot, head, parts
1511 
1512 blockToStatement :: AST.JSBlock -> AST.JSSemi -> AST.JSStatement
1513 blockToStatement (AST.JSBlock a b c) s = AST.JSStatementBlock a b c s
1514 
1515 expressionToStatement :: AST.JSExpression -> AST.JSSemi -> AST.JSStatement
1516 expressionToStatement (AST.JSFunctionExpression a b@(AST.JSIdentName{}) c d e f) s = AST.JSFunction a b c d e f s
1517 expressionToStatement (AST.JSGeneratorExpression a b c@(AST.JSIdentName{}) d e f g) s = AST.JSGenerator a b c d e f g s
1518 expressionToStatement (AST.JSAssignExpression lhs op rhs) s = AST.JSAssignStatement lhs op rhs s
1519 expressionToStatement (AST.JSMemberExpression e l a r) s = AST.JSMethodCall e l a r s
1520 expressionToStatement (AST.JSClassExpression a b@(AST.JSIdentName{}) c d e f) s = AST.JSClass a b c d e f s
1521 expressionToStatement exp s = AST.JSExpressionStatement exp s
1522 
1523 expressionToAsyncFunction :: AST.JSAnnot -> AST.JSExpression -> AST.JSSemi -> AST.JSStatement
1524 expressionToAsyncFunction aa (AST.JSFunctionExpression a b@(AST.JSIdentName{}) c d e f) s = AST.JSAsyncFunction aa a b c d e f s
1525 expressionToAsyncFunction _aa _exp _s = error "Bad async function."
1526 
1527 mkJSCallExpression :: AST.JSExpression -> JSArguments -> AST.JSExpression
1528 mkJSCallExpression e (JSArguments l arglist r) = AST.JSCallExpression e l arglist r
1529 
1530 mkJSMemberExpression :: AST.JSExpression -> JSArguments -> AST.JSExpression
1531 mkJSMemberExpression e (JSArguments l arglist r) = AST.JSMemberExpression e l arglist r
1532 
1533 mkJSMemberNew :: AST.JSAnnot -> AST.JSExpression -> JSArguments -> AST.JSExpression
1534 mkJSMemberNew a e (JSArguments l arglist r) = AST.JSMemberNew a e l arglist r
1535 
1536 parseError :: Token -> Alex a
1537 parseError = alexError . show
1538 
1539 mkJSAnnot :: Token -> AST.JSAnnot
1540 mkJSAnnot a = AST.JSAnnot (tokenSpan a) (tokenComment a)
1541 
1542 mkJSTemplateLiteral :: Maybe AST.JSExpression -> JSUntaggedTemplate -> AST.JSExpression
1543 mkJSTemplateLiteral tag (JSUntaggedTemplate a h ps) = AST.JSTemplateLiteral tag a h ps
1544 
1545 -- ---------------------------------------------------------------------
1546 -- | mkUnary : The parser detects '+' and '-' as the binary version of these
1547 -- operator. This function converts from the binary version to the unary
1548 -- version.
1549 mkUnary :: AST.JSBinOp -> AST.JSUnaryOp
1550 mkUnary (AST.JSBinOpMinus annot) = AST.JSUnaryOpMinus annot
1551 mkUnary (AST.JSBinOpPlus  annot) = AST.JSUnaryOpPlus  annot
1552 
1553 mkUnary x = error $ "Invalid unary op : " ++ show x
1554 
1555 identName :: AST.JSExpression -> AST.JSIdent
1556 identName (AST.JSIdentifier a s) = AST.JSIdentName a s
1557 identName x = error $ "Cannot convert '" ++ show x ++ "' to a JSIdentName."
1558 
1559 propName :: AST.JSExpression ->  AST.JSPropertyName
1560 propName (AST.JSIdentifier a s) = AST.JSPropertyIdent a s
1561 propName (AST.JSDecimal a s) = AST.JSPropertyNumber a s
1562 propName (AST.JSHexInteger a s) = AST.JSPropertyNumber a s
1563 propName (AST.JSOctal a s) = AST.JSPropertyNumber a s
1564 propName (AST.JSStringLiteral a s) = AST.JSPropertyString a s
1565 propName x = error $ "Cannot convert '" ++ show x ++ "' to a JSPropertyName."
1566 
1567 identifierToProperty :: AST.JSExpression -> AST.JSObjectProperty
1568 identifierToProperty (AST.JSIdentifier a s) = AST.JSPropertyIdentRef a s
1569 identifierToProperty x = error $ "Cannot convert '" ++ show x ++ "' to a JSObjectProperty."
1570 
1571 toArrowParameterList :: AST.JSExpression -> Token -> Alex AST.JSArrowParameterList
1572 toArrowParameterList (AST.JSIdentifier a s)          = const . return $ AST.JSUnparenthesizedArrowParameter (AST.JSIdentName a s)
1573 toArrowParameterList (AST.JSExpressionParen lb x rb) = const . return $ AST.JSParenthesizedArrowParameterList lb (commasToCommaList x) rb
1574 toArrowParameterList _                               = parseError
1575 
1576 commasToCommaList :: AST.JSExpression -> AST.JSCommaList AST.JSExpression
1577 commasToCommaList (AST.JSCommaExpression l c r) = AST.JSLCons (commasToCommaList l) c r
1578 commasToCommaList x = AST.JSLOne x
1579 
1580 }
1581