* lisp/emacs-lisp/trace.el: Rewrite, use nadvice and lexical-binding.
[emacs.git] / admin / grammars / js.wy
blob7b55f5c38341504183f0f804cdf70cecd8882664
1 ;;; javascript-jv.wy -- LALR grammar for Javascript
3 ;; Copyright (C) 2005-2012 Free Software Foundation, Inc.
4 ;; Copyright (C) 1998-2011 Ecma International.
6 ;; Author: Joakim Verona
8 ;; This file is part of GNU Emacs.
10 ;; GNU Emacs is free software: you can redistribute it and/or modify
11 ;; it under the terms of the GNU General Public License as published by
12 ;; the Free Software Foundation, either version 3 of the License, or
13 ;; (at your option) any later version.
15 ;; GNU Emacs is distributed in the hope that it will be useful,
16 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
17 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18 ;; GNU General Public License for more details.
20 ;; You should have received a copy of the GNU General Public License
21 ;; along with GNU Emacs.  If not, see <http://www.gnu.org/licenses/>.
23 ;;; Commentary:
25 ;; The grammar itself is transcribed from the ECMAScript Language
26 ;; Specification published at
28 ;; http://www.ecma-international.org/publications/standards/Ecma-262.htm
30 ;; and redistributed under the following license:
32 ;; Redistribution and use in source and binary forms, with or without
33 ;; modification, are permitted provided that the following conditions
34 ;; are met:
36 ;; 1. Redistributions of source code must retain the above copyright
37 ;; notice, this list of conditions and the following disclaimer.
39 ;; 2. Redistributions in binary form must reproduce the above
40 ;; copyright notice, this list of conditions and the following
41 ;; disclaimer in the documentation and/or other materials provided
42 ;; with the distribution.
44 ;; 3. Neither the name of the authors nor Ecma International may be
45 ;; used to endorse or promote products derived from this software
46 ;; without specific prior written permission.  THIS SOFTWARE IS
47 ;; PROVIDED BY THE ECMA INTERNATIONAL "AS IS" AND ANY EXPRESS OR
48 ;; IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
49 ;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
50 ;; ARE DISCLAIMED. IN NO EVENT SHALL ECMA INTERNATIONAL BE LIABLE FOR
51 ;; ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
52 ;; CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT
53 ;; OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR
54 ;; BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
55 ;; LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
56 ;; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE
57 ;; USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
58 ;; DAMAGE.
60 %package wisent-javascript-jv-wy
61 %provide semantic/wisent/js-wy
62 ;; JAVE I prefere ecmascript-mode
63 %languagemode ecmascript-mode javascript-mode
65 ;; The default goal
66 %start Program
67 ;; Other Goals
68 %start FormalParameterList
70 ;; with the terminals stuff, I used the javascript.y names,
71 ;; but the semantic/wisent/java-tags.wy types
72 ;; when possible
73 ;; ------------------
74 ;; Operator terminals
75 ;; ------------------
77 ;;define-lex-string-type-analyzer gets called with the "syntax" comment
78 %type <punctuation> ;;syntax "\\(\\s.\\|\\s$\\|\\s'\\)+" matchdatatype string
80 %token <punctuation> ASSIGN_SYMBOL            "="
81 %token <punctuation> BITWISE_AND              "&"
82 %token <punctuation> BITWISE_AND_EQUALS       "&="
83 %token <punctuation> BITWISE_EXCLUSIVE_OR     "^"
84 %token <punctuation> BITWISE_EXCLUSIVE_OR_EQUALS "^="
85 %token <punctuation> BITWISE_OR               "|"
86 %token <punctuation> BITWISE_OR_EQUALS        "|="
87 %token <punctuation> BITWISE_SHIFT_LEFT       "<<"
88 %token <punctuation> BITWISE_SHIFT_LEFT_EQUALS "<<="
89 %token <punctuation> BITWISE_SHIFT_RIGHT      ">>"
90 %token <punctuation> BITWISE_SHIFT_RIGHT_EQUALS ">>="
91 %token <punctuation> BITWISE_SHIFT_RIGHT_ZERO_FILL ">>>"
92 %token <punctuation> BITWISE_SHIFT_RIGHT_ZERO_FILL_EQUALS ">>>="
93 %token <punctuation> NOT_EQUAL "!="
94 %token <punctuation> DIV_EQUALS "/="
95 %token <punctuation> EQUALS "=="
96 %token <punctuation> GREATER_THAN ">"
97 %token <punctuation> GT_EQUAL ">="
98 %token <punctuation> LOGICAL_AND "&&"
99 %token <punctuation> LOGICAL_OR "||"
100 %token <punctuation> LOGICAL_NOT "!!"
101 %token <punctuation> LS_EQUAL "<="
102 %token <punctuation> MINUS "-"
103 %token <punctuation> MINUS_EQUALS "-="
104 %token <punctuation> MOD "%"
105 %token <punctuation> MOD_EQUALS "%="
106 %token <punctuation> MULTIPLY "*"
107 %token <punctuation> MULTIPLY_EQUALS "*="
108 %token <punctuation> PLUS "+"
109 %token <punctuation> PLUS_EQUALS "+="
110 %token <punctuation> INCREMENT "++"
111 %token <punctuation> DECREMENT "--"
112 %token <punctuation> DIV "/"
113 %token <punctuation> COLON ":"
114 %token <punctuation> COMMA ","
115 %token <punctuation> DOT "."
116 %token <punctuation> LESS_THAN "<"
117 %token <punctuation> LINE_TERMINATOR "\n"
118 %token <punctuation> SEMICOLON ";"
119 %token <punctuation> ONES_COMPLIMENT "~"
122 ;; -----------------------------
123 ;; Block & Parenthesis terminals
124 ;; -----------------------------
125 %type  <block>       ;;syntax "\\s(\\|\\s)" matchdatatype block
126 %token <block>       PAREN_BLOCK "(OPEN_PARENTHESIS CLOSE_PARENTHESIS)"
127 %token <block>       BRACE_BLOCK "(START_BLOCK END_BLOCK)"
128 %token <block>       BRACK_BLOCK "(OPEN_SQ_BRACKETS CLOSE_SQ_BRACKETS)"
130 %token <open-paren>  OPEN_PARENTHESIS  "("
131 %token <close-paren>  CLOSE_PARENTHESIS ")"
133 %token <open-paren>  START_BLOCK       "{"
134 %token <close-paren>  END_BLOCK         "}"
136 %token <open-paren>  OPEN_SQ_BRACKETS  "["
137 %token <close-paren>  CLOSE_SQ_BRACKETS "]"
140 ;; -----------------
141 ;; Keyword terminals
142 ;; -----------------
144 ;; Generate a keyword analyzer
145 %type  <keyword> ;;syntax "\\(\\sw\\|\\s_\\)+" matchdatatype keyword
147 %keyword IF           "if"
148 %put     IF summary
149 "if (<expr>) <stmt> [else <stmt>] (jv)"
151 %keyword BREAK        "break"
152 %put     BREAK summary
153 "break [<label>] ;"
155 %keyword CONTINUE     "continue"
156 %put     CONTINUE summary
157 "continue [<label>] ;"
159 %keyword ELSE         "else"
160 %put     ELSE summary
161 "if (<expr>) <stmt> else <stmt>"
164 %keyword FOR          "for"
165 %put     FOR summary
166 "for ([<init-expr>]; [<expr>]; [<update-expr>]) <stmt>"
169 %keyword FUNCTION  "function"
170 %put     FUNCTION summary
171 "function declaration blah blah"
173 %keyword THIS         "this"
174 %put THIS summary
175 "this"
178 %keyword RETURN       "return"
179 %put     RETURN summary
180 "return [<expr>] ;"
182 %keyword WHILE        "while"
183 %put     WHILE summary
184 "while (<expr>) <stmt> | do <stmt> while (<expr>);"
186 %keyword VOID_SYMBOL         "void"
187 %put     VOID_SYMBOL summary
188 "Method return type: void <name> ..."
192 %keyword NEW          "new"
193 %put NEW summary
194 "new <objecttype> - Creates a new object."
196 %keyword DELETE "delete"
197 %put DELETE summary
198 "delete(<objectreference>) - Deletes the object."
200 %keyword VAR "var"
201 %put VAR  summary
202 "var <variablename> [= value];"
204 %keyword WITH "with"
205 %put WITH summary
206 "with "
208 %keyword TYPEOF "typeof"
209 %put TYPEOF summary
210 "typeof "
212 %keyword IN "in"
213 %put IN  summary
214 "in something"
217 ;; -----------------
218 ;; Literal terminals
219 ;; -----------------
221 ;;the .y file uses VARIABLE as IDENTIFIER, which seems a bit evil
222 ;; it think the normal .wy convention is better than this
223 %type  <symbol>      ;;syntax "\\(\\sw\\|\\s_\\)+"
224 %token <symbol>      VARIABLE
226 %type  <string>      ;;syntax "\\s\"" matchdatatype sexp
227 %token <string>      STRING
229 %type  <number>      ;;syntax semantic-lex-number-expression
230 %token <number>      NUMBER
233 %token FALSE
234 %token TRUE
235 %token QUERY
238 %token NULL_TOKEN
240 ;;%token UNDEFINED_TOKEN
241 ;;%token INFINITY
243 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
244 ;; associativity and stuff
245 %left PLUS MINUS
246 %left MULTIPLY DIV MOD
248 %nonassoc FALSE
249 %nonassoc HIGHER_THAN_FALSE
250 %nonassoc ELSE
251 %nonassoc LOWER_THAN_CLOSE_PARENTHESIS
252 %nonassoc CLOSE_PARENTHESIS
256 Program : SourceElement
257         ;
259 SourceElement : Statement
260               | FunctionDeclaration
261               ;
263 Statement : Block
264           | VariableStatement
265           | EmptyStatement
266           | ExpressionStatement
267           | IfStatement
268           | IterationExpression
269           | ContinueStatement
270           | BreakStatement
271           | ReturnStatement
272           | WithStatement
273           ;   
274       
275 FunctionDeclaration : FUNCTION VARIABLE FormalParameterListBlock Block
276                       (FUNCTION-TAG $2 nil $3)
277                     ;
279 FormalParameterListBlock : PAREN_BLOCK
280                            (EXPANDFULL $1 FormalParameterList)
281                         ;
283 FormalParameterList: OPEN_PARENTHESIS
284                      ()
285                    | VARIABLE
286                      (VARIABLE-TAG $1 nil nil)
287                    | CLOSE_PARENTHESIS
288                      ()
289                    | COMMA
290                      ()
291                    ;
293 StatementList : Statement
294               | StatementList Statement
295               ;
297 Block : BRACE_BLOCK
298      ;; If you want to parse the body of the function
299      ;; ( EXPANDFULL $1 BlockExpand )
300       ;
302 BlockExpand: START_BLOCK StatementList END_BLOCK
303            | START_BLOCK END_BLOCK
304            ;
306 VariableStatement : VAR VariableDeclarationList SEMICOLON
307                     (VARIABLE-TAG $2 nil nil)
308                   ;
310 VariableDeclarationList : VariableDeclaration
311                           (list $1)
312                         | VariableDeclarationList COMMA VariableDeclaration
313                           (append $1 (list $3))
314                         ;
316 VariableDeclaration : VARIABLE
317                       (append (list $1 nil) $region)
318                     | VARIABLE Initializer
319                       (append (cons $1 $2) $region)
320                     ;
322 Initializer : ASSIGN_SYMBOL AssignmentExpression
323               (list $2)
324             ;
326 EmptyStatement : SEMICOLON
327                ;
329 ExpressionStatement : Expression SEMICOLON
330                     ;
332 IfStatement : IF OPEN_PARENTHESIS Expression CLOSE_PARENTHESIS Statement  %prec HIGHER_THAN_FALSE
333             | IF OPEN_PARENTHESIS Expression CLOSE_PARENTHESIS Statement ELSE Statement
334             | IF OPEN_PARENTHESIS FALSE CLOSE_PARENTHESIS Statement
335             | IF OPEN_PARENTHESIS LeftHandSideExpression AssignmentOperator AssignmentExpression CLOSE_PARENTHESIS Statement
336             ;
338 IterationExpression : WHILE OPEN_PARENTHESIS Expression CLOSE_PARENTHESIS Statement %prec HIGHER_THAN_FALSE
339                     | WHILE OPEN_PARENTHESIS FALSE CLOSE_PARENTHESIS Statement
340                     | WHILE OPEN_PARENTHESIS LeftHandSideExpression AssignmentOperator AssignmentExpression CLOSE_PARENTHESIS Statement
341                     | FOR OPEN_PARENTHESIS OptionalExpression SEMICOLON OptionalExpression SEMICOLON OptionalExpression CLOSE_PARENTHESIS Statement
342                     | FOR OPEN_PARENTHESIS VAR VariableDeclarationList SEMICOLON OptionalExpression SEMICOLON OptionalExpression CLOSE_PARENTHESIS Statement
343                     | FOR OPEN_PARENTHESIS LeftHandSideExpression IN Expression CLOSE_PARENTHESIS Statement
344                     | FOR OPEN_PARENTHESIS VAR VARIABLE OptionalInitializer IN Expression CLOSE_PARENTHESIS Statement
345                     ;
347 ContinueStatement : CONTINUE SEMICOLON
348                   ;
350 ;;JAVE break needs labels 
351 BreakStatement : BREAK SEMICOLON
352               ;;               | BREAK identifier SEMICOLON
353                ;
355 ReturnStatement : RETURN Expression SEMICOLON
356                 | RETURN SEMICOLON
357                 ;
359 WithStatement : WITH OPEN_PARENTHESIS Expression CLOSE_PARENTHESIS   Statement
360               ;
362 OptionalInitializer : Initializer
363                     |
364                     ;
366 PrimaryExpression : THIS
367                   | VARIABLE
368                   | NUMBER
369                   | STRING
370                   | NULL_TOKEN
371                   | TRUE
372                   | FALSE
373                   | OPEN_PARENTHESIS Expression CLOSE_PARENTHESIS
374                   ;
376 MemberExpression : PrimaryExpression
377                  | MemberExpression OPEN_SQ_BRACKETS Expression  CLOSE_SQ_BRACKETS
378                  | MemberExpression DOT VARIABLE
379                  | NEW MemberExpression Arguments
380                  ;
382 NewExpression : MemberExpression
383               | NEW NewExpression
384               ;
386 CallExpression : MemberExpression Arguments
387                | CallExpression Arguments
388                | CallExpression OPEN_SQ_BRACKETS Expression  CLOSE_SQ_BRACKETS
389                | CallExpression DOT VARIABLE
390                ;
392 Arguments : OPEN_PARENTHESIS CLOSE_PARENTHESIS
393           | OPEN_PARENTHESIS ArgumentList CLOSE_PARENTHESIS
394           ;
396 ArgumentList : AssignmentExpression
397              | ArgumentList COMMA AssignmentExpression
398              ;
400 LeftHandSideExpression : NewExpression
401                        | CallExpression
402                        ;
404 PostfixExpression : LeftHandSideExpression
405                   | LeftHandSideExpression INCREMENT
406                   | LeftHandSideExpression DECREMENT
407                   ;
409 UnaryExpression : PostfixExpression
410                 | DELETE UnaryExpression
411                 | VOID_SYMBOL UnaryExpression
412                 | TYPEOF UnaryExpression
413                 | INCREMENT UnaryExpression
414                 | DECREMENT UnaryExpression
415                 | PLUS UnaryExpression
416                 | MINUS UnaryExpression
417                 | ONES_COMPLIMENT UnaryExpression
418                 | LOGICAL_NOT UnaryExpression
419                 ;
421 MultiplicativeExpression : UnaryExpression
422                          | MultiplicativeExpression MULTIPLY UnaryExpression
423                          | MultiplicativeExpression DIV UnaryExpression
424                          | MultiplicativeExpression MOD UnaryExpression
425                          ;
427 AdditiveExpression : MultiplicativeExpression
428                    | AdditiveExpression PLUS MultiplicativeExpression
429                    | AdditiveExpression MINUS MultiplicativeExpression
430                    ;
432 ShiftExpression : AdditiveExpression
433                 | ShiftExpression BITWISE_SHIFT_LEFT AdditiveExpression
434                 | ShiftExpression BITWISE_SHIFT_RIGHT AdditiveExpression
435                 | ShiftExpression BITWISE_SHIFT_RIGHT_ZERO_FILL  AdditiveExpression
436                 ;
438 RelationalExpression : ShiftExpression
439                      | RelationalExpression LESS_THAN ShiftExpression
440                      | RelationalExpression GREATER_THAN ShiftExpression
441                      | RelationalExpression LS_EQUAL ShiftExpression
442                      | RelationalExpression GT_EQUAL ShiftExpression
443                      ;
445 EqualityExpression : RelationalExpression
446                    | EqualityExpression EQUALS RelationalExpression
447                    | EqualityExpression NOT_EQUAL RelationalExpression
448                    ;
450 BitwiseANDExpression : EqualityExpression
451                      | BitwiseANDExpression BITWISE_AND EqualityExpression
452                      ;
454 BitwiseXORExpression : BitwiseANDExpression
455                      | BitwiseXORExpression BITWISE_EXCLUSIVE_OR     BitwiseANDExpression
456                      ;
458 BitwiseORExpression : BitwiseXORExpression
459                     | BitwiseORExpression BITWISE_OR BitwiseXORExpression
460                     ;
462 LogicalANDExpression : BitwiseORExpression
463                      | LogicalANDExpression LOGICAL_AND BitwiseORExpression
464                      ;
466 LogicalORExpression : LogicalANDExpression
467                     | LogicalORExpression LOGICAL_OR LogicalANDExpression
468                     ;
470 ConditionalExpression : LogicalORExpression
471                       | LogicalORExpression QUERY AssignmentExpression COLON    AssignmentExpression
472                       ;
474 AssignmentExpression : ConditionalExpression
475                      | LeftHandSideExpression AssignmentOperator  AssignmentExpression %prec LOWER_THAN_CLOSE_PARENTHESIS
476                      ;
478 AssignmentOperator : ASSIGN_SYMBOL
479                    | MULTIPLY_EQUALS
480                    | DIV_EQUALS
481                    | MOD_EQUALS
482                    | PLUS_EQUALS
483                    | MINUS_EQUALS
484                    | BITWISE_SHIFT_LEFT_EQUALS
485                    | BITWISE_SHIFT_RIGHT_EQUALS
486                    | BITWISE_SHIFT_RIGHT_ZERO_FILL_EQUALS
487                    | BITWISE_AND_EQUALS
488                    | BITWISE_EXCLUSIVE_OR_EQUALS
489                    | BITWISE_OR_EQUALS
490                    ;
492 Expression : AssignmentExpression
493            | Expression COMMA AssignmentExpression
494            ;
496 OptionalExpression : Expression
497                    |
498                    ;
502 ;;here something like:
503 ;;(define-lex wisent-java-tags-lexer
504 ;; should go
505 (define-lex javascript-lexer-jv
506 "javascript thingy"
507 ;;std stuff
508   semantic-lex-ignore-whitespace
509   semantic-lex-ignore-newline
510   semantic-lex-ignore-comments
512   ;;stuff generated from the wy file(one for each "type" declaration)
513   wisent-javascript-jv-wy--<number>-regexp-analyzer
514   wisent-javascript-jv-wy--<string>-sexp-analyzer
516   wisent-javascript-jv-wy--<keyword>-keyword-analyzer
518   wisent-javascript-jv-wy--<symbol>-regexp-analyzer
519   wisent-javascript-jv-wy--<punctuation>-string-analyzer
520   wisent-javascript-jv-wy--<block>-block-analyzer
523   ;;;;more std stuff
524   semantic-lex-default-action
525   )
527 ;;; javascript-jv.wy ends here