Initial Commit
[packages] / xemacs-packages / semantic / wisent / wisent-python.wy
1 ;;; wisent-python.wy -- LALR grammar for Python
2 ;;
3 ;; Copyright (C) 2002, 2003, 2004, 2007 Richard Kim
4 ;;
5 ;; Author: Richard Kim <ryk@dspwiz.com>
6 ;; Maintainer: Richard Kim <ryk@dspwiz.com>
7 ;; Created: June 2002
8 ;; Keywords: syntax
9 ;; X-RCS: $Id: wisent-python.wy,v 1.1 2007-11-26 15:12:35 michaels Exp $
10 ;;
11 ;; This file is not part of GNU Emacs.
12 ;;
13 ;; This program is free software; you can redistribute it and/or
14 ;; modify it under the terms of the GNU General Public License as
15 ;; published by the Free Software Foundation; either version 2, or (at
16 ;; your option) any later version.
17 ;;
18 ;; This software is distributed in the hope that it will be useful,
19 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
20 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 ;; General Public License for more details.
22 ;;
23 ;; You should have received a copy of the GNU General Public License
24 ;; along with GNU Emacs; see the file COPYING.  If not, write to the
25 ;; Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
26 ;; Boston, MA 02110-1301, USA.
27
28 ;;; Commentary:
29 ;;
30 ;; This is an LALR python parser that follows the official python
31 ;; grammar closely with very few exceptions.
32 ;;
33 ;;; To do:
34 ;;
35 ;; * Verify that semantic-lex-python-number regexp is correct.
36
37 ;; --------
38 ;; Settings
39 ;; --------
40
41 ;;%package wisent-python-wy
42
43 %languagemode python-mode
44
45 ;; The default start symbol
46 %start goal
47 ;; Alternate entry points
48 ;;    - Needed by partial re-parse
49 %start function_parameter
50 %start paren_class
51 %start indented_block
52 ;;    - Needed by EXPANDFULL clauses
53 %start function_parameters
54 %start paren_classes
55 %start indented_block_body
56
57 ;; -------------------------------
58 ;; Misc. Python specific terminals
59 ;; -------------------------------
60 ;; The value of these tokens are for documentation only, they are not
61 ;; used by the lexer.
62 %token <charquote>   BACKSLASH    "\\"
63 %token <newline>     NEWLINE      "\n"
64 %token <indentation> INDENT       "^\\s-+"
65 %token <indentation> DEDENT       "[^:INDENT:]" 
66 %token <indentation> INDENT_BLOCK "(INDENT DEDENT)"
67
68 ;; -----------------------------
69 ;; Block & Parenthesis terminals
70 ;; -----------------------------
71 %type  <block>       ;;syntax "\\s(\\|\\s)" matchdatatype block
72
73 %token <block>       PAREN_BLOCK "(LPAREN RPAREN)"
74 %token <block>       BRACE_BLOCK "(LBRACE RBRACE)"
75 %token <block>       BRACK_BLOCK "(LBRACK RBRACK)"
76
77 %token <open-paren>  LPAREN      "("
78 %token <close-paren> RPAREN      ")"
79 %token <open-paren>  LBRACE      "{"
80 %token <close-paren> RBRACE      "}"
81 %token <open-paren>  LBRACK      "["
82 %token <close-paren> RBRACK      "]"
83
84 ;; ------------------
85 ;; Operator terminals
86 ;; ------------------
87 %type  <punctuation> ;;syntax "\\(\\s.\\|\\s$\\|\\s'\\)+" matchdatatype string
88
89 %token <punctuation> LTLTEQ     "<<="
90 %token <punctuation> GTGTEQ     ">>="
91 %token <punctuation> EXPEQ      "**="
92 %token <punctuation> DIVDIVEQ   "//="
93 %token <punctuation> DIVDIV     "//"
94 %token <punctuation> LTLT       "<<"
95 %token <punctuation> GTGT       ">>"
96 %token <punctuation> EXPONENT   "**"
97 %token <punctuation> EQ         "=="
98 %token <punctuation> GE         ">="
99 %token <punctuation> LE         "<="
100 %token <punctuation> PLUSEQ     "+="
101 %token <punctuation> MINUSEQ    "-="
102 %token <punctuation> MULTEQ     "*="
103 %token <punctuation> DIVEQ      "/="
104 %token <punctuation> MODEQ      "%="
105 %token <punctuation> AMPEQ      "&="
106 %token <punctuation> OREQ       "|="
107 %token <punctuation> HATEQ      "^="
108 %token <punctuation> LTGT       "<>"
109 %token <punctuation> NE         "!="
110 %token <punctuation> HAT        "^"
111 %token <punctuation> LT         "<"
112 %token <punctuation> GT         ">"
113 %token <punctuation> AMP        "&"
114 %token <punctuation> MULT       "*"
115 %token <punctuation> DIV        "/"
116 %token <punctuation> MOD        "%"
117 %token <punctuation> PLUS       "+"
118 %token <punctuation> MINUS      "-"
119 %token <punctuation> PERIOD     "."
120 %token <punctuation> TILDE      "~"
121 %token <punctuation> BAR        "|"
122 %token <punctuation> COLON      ":"
123 %token <punctuation> SEMICOLON  ";"
124 %token <punctuation> COMMA      ","
125 %token <punctuation> ASSIGN     "="
126 %token <punctuation> BACKQUOTE  "`"
127
128
129 ;; -----------------
130 ;; Literal terminals
131 ;; -----------------
132 %token <string>      STRING_LITERAL
133
134 %type  <number>      ;;syntax semantic-lex-number-expression
135 %token <number>      NUMBER_LITERAL
136
137 %type  <symbol>      ;;syntax "\\(\\sw\\|\\s_\\)+"
138 %token <symbol>      NAME
139
140 ;; -----------------
141 ;; Keyword terminals
142 ;; -----------------
143 %type  <keyword> ;;syntax "\\(\\sw\\|\\s_\\)+" matchdatatype keyword
144
145 %keyword AND         "and"
146 %put     AND summary
147 "Logical AND binary operator ... "
148
149 %keyword ASSERT      "assert"
150 %put     ASSERT summary
151 "Raise AssertionError exception if <expr> is false"
152
153 %keyword BREAK       "break"
154 %put     BREAK summary
155 "Terminate 'for' or 'while loop"
156
157 %keyword CLASS       "class"
158 %put     CLASS summary
159 "Define a new class"
160
161 %keyword CONTINUE            "continue"
162 %put     CONTINUE summary
163 "Skip to the next interation of enclosing for or whilte loop"
164
165 %keyword DEF         "def"
166 %put     DEF summary
167 "Define a new function"
168
169 %keyword DEL         "del"
170 %put     DEL summary
171 "Delete specified objects, i.e., undo what assignment did"
172
173 %keyword ELIF        "elif"
174 %put     ELIF summary
175 "Shorthand for 'else if' following an 'if' statement"
176
177 %keyword ELSE        "else"
178 %put     ELSE summary
179 "Start the 'else' clause following an 'if' statement"
180
181 %keyword EXCEPT      "except"
182 %put     EXCEPT summary
183 "Specify exception handlers along with 'try' keyword"
184
185 %keyword EXEC        "exec"
186 %put     EXEC summary
187 "Dynamically execute python code"
188
189 %keyword FINALLY             "finally"
190 %put     FINALLY summary
191 "Specify code to be executed after 'try' statements whether or not an exception occured"
192
193 %keyword FOR         "for"
194 %put     FOR summary
195 "Start a 'for' loop"
196
197 %keyword FROM        "from"
198 %put     FROM summary
199 "Modify behavior of 'import' statement"
200
201 %keyword GLOBAL      "global"
202 %put     GLOBAL summary
203 "Declare one or more symbols as global symbols"
204
205 %keyword IF          "if"
206 %put     IF summary
207 "Start 'if' conditional statement"
208
209 %keyword IMPORT      "import"
210 %put     IMPORT summary
211 "Load specified modules"
212
213 %keyword IN          "in"
214 %put     IN summary
215 "Part of 'for' statement "
216
217 %keyword IS          "is"
218 %put     IS summary
219 "Binary operator that tests for object equality"
220
221 %keyword LAMBDA      "lambda"
222 %put     LAMDA summary
223 "Create anonymous function"
224
225 %keyword NOT         "not"
226 %put     NOT summary
227 "Unary boolean negation operator"
228
229 %keyword OR          "or"
230 %put     OR summary
231 "Binary logical 'or' operator"
232
233 %keyword PASS        "pass"
234 %put     PASS summary
235 "Statement that does nothing"
236
237 %keyword PRINT       "print"
238 %put     PRINT summary
239 "Print each argument to standard output"
240
241 %keyword RAISE       "raise"
242 %put     RAISE summary
243 "Raise an exception"
244
245 %keyword RETURN      "return"
246 %put     RETURN summary
247 "Return from a function"
248
249 %keyword TRY         "try"
250 %put     TRY summary
251 "Start of statements protected by exception handlers"
252
253 %keyword WHILE       "while"
254 %put     WHILE summary
255 "Start a 'while' loop"
256
257 %keyword YIELD       "yield"
258 %put     YIELD summary
259 "Create a generator function"
260
261 %%
262
263 ;;;****************************************************************************
264 ;;;@ goal
265 ;;;****************************************************************************
266
267 ;; simple_stmt are statements that do not involve INDENT tokens
268 ;; compound_stmt are statements that involve INDENT tokens
269 goal
270   : NEWLINE
271   | simple_stmt
272   | compound_stmt
273   ;
274
275 ;;;****************************************************************************
276 ;;;@ simple_stmt
277 ;;;****************************************************************************
278
279 ;; simple_stmt: small_stmt (';' small_stmt)* [';'] NEWLINE
280 simple_stmt
281   : small_stmt_list semicolon_opt NEWLINE
282   ;
283
284 ;; small_stmt (';' small_stmt)*
285 small_stmt_list
286   : small_stmt
287   | small_stmt_list SEMICOLON small_stmt
288   ;
289
290 small_stmt
291   : expr_stmt
292   | print_stmt
293   | del_stmt
294   | pass_stmt
295   | flow_stmt
296   | import_stmt
297   | global_stmt
298   | exec_stmt
299   | assert_stmt
300   ;
301
302 ;;;============================================================================
303 ;;;@@ print_stmt
304 ;;;============================================================================
305
306 ;; print_stmt: 'print' [ test (',' test)* [','] ]
307 ;;           | '>>' test [ (',' test)+ [','] ]
308 print_stmt
309   : PRINT print_stmt_trailer
310     (CODE-TAG $1 nil)
311   ;
312
313 ;; [ test (',' test)* [','] ] | '>>' test [ (',' test)+ [','] ]
314 print_stmt_trailer
315   : test_list_opt
316     ()
317   | GTGT test trailing_test_list_with_opt_comma_opt
318     ()
319   ;
320
321 ;; [ (',' test)+ [','] ]
322 trailing_test_list_with_opt_comma_opt
323   : ;;EMPTY
324   | trailing_test_list comma_opt
325     ()
326   ;
327
328 ;; (',' test)+
329 trailing_test_list
330   : COMMA test
331     ()
332   | trailing_test_list COMMA test
333     ()
334   ;
335
336 ;;;============================================================================
337 ;;;@@ expr_stmt
338 ;;;============================================================================
339
340 ;; expr_stmt: testlist (augassign testlist | ('=' testlist)*)
341 expr_stmt
342   : testlist expr_stmt_trailer
343     (if (and $2 (stringp $1) (string-match "^\\(\\sw\\|\\s_\\)+$" $1))
344         ;; If this is an assignment statement and left side is a symbol,
345         ;; then generate a 'variable token, else return 'code token.
346         (VARIABLE-TAG $1 nil nil)
347       (CODE-TAG $1 nil))
348   ;
349
350 ;; Could be EMPTY because of eq_testlist_zom.
351 ;; (augassign testlist | ('=' testlist)*)
352 expr_stmt_trailer
353   : augassign testlist
354   | eq_testlist_zom
355   ;
356
357 ;; Could be EMPTY!
358 ;; ('=' testlist)*
359 eq_testlist_zom
360   : ;;EMPTY
361   | eq_testlist_zom ASSIGN testlist
362     (identity $3)
363   ;
364
365 ;; augassign: '+=' | '-=' | '*=' | '/=' | '%=' | '&=' | '|=' | '^='
366 ;;          | '<<=' | '>>=' | '**=' | '//='
367 augassign
368   : PLUSEQ | MINUSEQ | MULTEQ | DIVEQ | MODEQ
369   | AMPEQ  | OREQ    | HATEQ  | LTLTEQ
370   | GTGTEQ | EXPEQ   | DIVDIVEQ
371   ;
372
373 ;;;============================================================================
374 ;;;@@ del_stmt
375 ;;;============================================================================
376
377 ;; del_stmt: 'del' exprlist
378 del_stmt
379   : DEL exprlist
380     (CODE-TAG $1 nil)
381   ;
382
383 ;; exprlist: expr (',' expr)* [',']
384 exprlist
385   : expr_list comma_opt
386     ()
387   ;
388
389 ;; expr (',' expr)*
390 expr_list
391   : expr
392     ()
393   | expr_list COMMA expr
394     ()
395   ;
396
397 ;;;============================================================================
398 ;;;@@ pass_stmt
399 ;;;============================================================================
400
401 ;; pass_stmt: 'pass'
402 pass_stmt
403   : PASS
404     (CODE-TAG $1 nil)
405   ;
406
407 ;;;============================================================================
408 ;;;@@ flow_stmt
409 ;;;============================================================================
410
411 flow_stmt
412   : break_stmt
413   | continue_stmt
414   | return_stmt
415   | raise_stmt
416   | yield_stmt
417   ;
418
419 ;; break_stmt: 'break'
420 break_stmt
421   : BREAK
422     (CODE-TAG $1 nil)
423   ;
424
425 ;; continue_stmt: 'continue'
426 continue_stmt
427   : CONTINUE
428     (CODE-TAG $1 nil)
429   ;
430
431 ;; return_stmt: 'return' [testlist]
432 return_stmt
433   : RETURN testlist_opt
434     (CODE-TAG $1 nil)
435   ;
436
437 ;; [testlist]
438 testlist_opt
439   : ;;EMPTY
440   | testlist
441     ()
442   ;
443
444 ;; yield_stmt: 'yield' testlist
445 yield_stmt
446   : YIELD testlist
447     (CODE-TAG $1 nil)
448   ;
449
450 ;; raise_stmt: 'raise' [test [',' test [',' test]]]
451 raise_stmt
452   : RAISE zero_one_two_or_three_tests
453     (CODE-TAG $1 nil)
454   ;
455
456 ;; [test [',' test [',' test]]]
457 zero_one_two_or_three_tests
458   : ;;EMPTY
459   | test zero_one_or_two_tests
460     ()
461   ;
462
463 ;; [',' test [',' test]]
464 zero_one_or_two_tests
465   : ;;EMPTY
466   | COMMA test zero_or_one_comma_test
467     ()
468   ;
469
470 ;; [',' test]
471 zero_or_one_comma_test
472   : ;;EMPTY
473   | COMMA test
474     ()
475   ;
476
477 ;;;============================================================================
478 ;;;@@ import_stmt
479 ;;;============================================================================
480
481 ;; import_stmt : 'import' dotted_as_name (',' dotted_as_name)*
482 ;;             | 'from' dotted_name 'import'
483 ;;               ('*' | import_as_name (',' import_as_name)*)
484 import_stmt
485   : IMPORT dotted_as_name_list
486     (INCLUDE-TAG $2 nil)
487   | FROM dotted_name IMPORT star_or_import_as_name_list
488     (INCLUDE-TAG $2 nil)
489   ;
490
491 ;; dotted_as_name (',' dotted_as_name)*
492 dotted_as_name_list
493   : dotted_as_name
494   | dotted_as_name_list COMMA dotted_as_name
495   ;
496
497 ;; ('*' | import_as_name (',' import_as_name)*)
498 star_or_import_as_name_list
499   : MULT
500     ()
501   | import_as_name_list
502     ()
503   ;
504
505 ;; import_as_name (',' import_as_name)*
506 import_as_name_list
507   : import_as_name
508     ()
509   | import_as_name_list COMMA import_as_name
510     ()
511   ;
512
513 ;; import_as_name: NAME [NAME NAME]
514 import_as_name
515   : NAME name_name_opt
516     ()
517   ;
518
519 ;; dotted_as_name: dotted_name [NAME NAME]
520 dotted_as_name
521   : dotted_name name_name_opt
522   ;
523
524 ;; [NAME NAME]
525 name_name_opt
526   : ;;EMPTY
527   | NAME NAME
528     ()
529   ;
530
531 ;; dotted_name: NAME ('.' NAME)*
532 dotted_name
533   : NAME
534   | dotted_name PERIOD NAME
535     (format "%s.%s" $1 $3)
536   ;
537
538 ;;;============================================================================
539 ;;;@@ global_stmt
540 ;;;============================================================================
541
542 ;; global_stmt: 'global' NAME (',' NAME)*
543 global_stmt
544   : GLOBAL comma_sep_name_list
545     (CODE-TAG $1 nil)
546   ;
547
548 ;; NAME (',' NAME)*
549 comma_sep_name_list
550   : NAME
551   | comma_sep_name_list COMMA NAME
552   ;
553
554 ;;;============================================================================
555 ;;;@@ exec_stmt
556 ;;;============================================================================
557
558 ;; exec_stmt: 'exec' expr ['in' test [',' test]]
559 exec_stmt
560   : EXEC expr exec_trailer
561     (CODE-TAG $1 nil)
562   ;
563
564 ;; ['in' test [',' test]]
565 exec_trailer
566   : ;;EMPTY
567   | IN test comma_test_opt
568     ()
569   ;
570
571 ;; [',' test]
572 comma_test_opt
573   : ;;EMPTY
574   | COMMA test
575     ()
576   ;
577
578 ;;;============================================================================
579 ;;;@@ assert_stmt
580 ;;;============================================================================
581
582 ;; assert_stmt: 'assert' test [',' test]
583 assert_stmt
584   : ASSERT test comma_test_opt
585     (CODE-TAG $1 nil)
586   ;
587
588 ;;;****************************************************************************
589 ;;;@ compound_stmt
590 ;;;****************************************************************************
591
592 compound_stmt
593   : if_stmt
594   | while_stmt
595   | for_stmt
596   | try_stmt
597   | funcdef
598   | class_declaration
599   ;
600
601 ;;;============================================================================
602 ;;;@@ if_stmt
603 ;;;============================================================================
604
605 ;; if_stmt: 'if' test ':' suite ('elif' test ':' suite)* ['else' ':' suite]
606 if_stmt
607   : IF test COLON suite elif_suite_pair_list else_suite_pair_opt
608     (CODE-TAG $1 nil)
609   ;
610
611 ;; ('elif' test ':' suite)*
612 elif_suite_pair_list
613   : ;;EMPTY
614   | elif_suite_pair_list ELIF test COLON suite
615     ()
616   ;
617
618 ;; ['else' ':' suite]
619 else_suite_pair_opt
620   : ;;EMPTY
621   | ELSE COLON suite
622     ()
623   ;
624
625 ;; This NT follows the COLON token for most compound statements.
626 ;; suite: simple_stmt | NEWLINE INDENT stmt+ DEDENT
627 suite
628   : simple_stmt
629     (list $1)
630   | NEWLINE indented_block
631     (progn $2)
632   ;
633
634 indented_block
635   : INDENT_BLOCK
636     (EXPANDFULL $1 indented_block_body)
637   ;
638
639 indented_block_body
640   : INDENT
641     ()
642   | DEDENT
643     ()
644   | simple_stmt
645   | compound_stmt
646   ;
647
648 ;;;============================================================================
649 ;;;@@ while_stmt
650 ;;;============================================================================
651
652 ;; while_stmt: 'while' test ':' suite ['else' ':' suite]
653 while_stmt
654   : WHILE test COLON suite else_suite_pair_opt
655     (CODE-TAG $1 nil)
656   ;
657
658 ;;;============================================================================
659 ;;;@@ for_stmt
660 ;;;============================================================================
661
662 ;; for_stmt: 'for' exprlist 'in' testlist ':' suite ['else' ':' suite]
663 for_stmt
664   : FOR exprlist IN testlist COLON suite else_suite_pair_opt
665     (CODE-TAG $1 nil)
666   ;
667
668 ;;;============================================================================
669 ;;;@@ try_stmt
670 ;;;============================================================================
671
672 ;; try_stmt: ('try' ':' suite (except_clause ':' suite)+ #diagram:break
673 ;;            ['else' ':' suite] | 'try' ':' suite 'finally' ':' suite)
674 try_stmt
675   : TRY COLON suite except_clause_suite_pair_list else_suite_pair_opt
676     (CODE-TAG $1 nil)
677   | TRY COLON suite FINALLY COLON suite
678     (CODE-TAG $1 nil)
679   ;
680
681 ;; (except_clause ':' suite)+
682 except_clause_suite_pair_list
683   : except_clause COLON suite
684     ()
685   | except_clause_suite_pair_list except_clause COLON suite
686     ()
687   ;
688
689 ;; # NB compile.c makes sure that the default except clause is last
690 ;; except_clause: 'except' [test [',' test]]
691 except_clause
692   : EXCEPT zero_one_or_two_test
693     ()
694   ;
695
696 ;; [test [',' test]]
697 zero_one_or_two_test
698   : ;;EMPTY
699   | test zero_or_one_comma_test
700     ()
701   ;
702
703 ;;;============================================================================
704 ;;;@@ funcdef
705 ;;;============================================================================
706
707 ;; funcdef: 'def' NAME parameters ':' suite
708 funcdef
709   : DEF NAME function_parameter_list COLON suite
710     (FUNCTION-TAG $2 nil $3)
711   ;
712
713 function_parameter_list
714   : PAREN_BLOCK
715     (let ((wisent-python-EXPANDING-block t))
716       (EXPANDFULL $1 function_parameters))
717   ;
718
719 ;; parameters: '(' [varargslist] ')'
720 function_parameters
721   : LPAREN
722     ()
723   | RPAREN
724     ()
725   | function_parameter COMMA
726   | function_parameter RPAREN
727   ;
728
729 function_parameter
730   : fpdef_opt_test
731  ;;  : NAME
732  ;;    (VARIABLE-TAG $1 nil nil)
733   | MULT NAME
734     (VARIABLE-TAG $2 nil nil)
735   | EXPONENT NAME
736     (VARIABLE-TAG $2 nil nil)
737   ;
738
739 ;;;============================================================================
740 ;;;@@ class_declaration
741 ;;;============================================================================
742
743 ;; classdef: 'class' NAME ['(' testlist ')'] ':' suite
744 class_declaration
745   : CLASS NAME paren_class_list_opt COLON suite
746     (TYPE-TAG $2 $1             ;; Name "class"
747               $5                ;; Members
748               (cons $3 nil)     ;; (SUPERCLASSES . INTERFACES)
749               )
750   ;
751
752 ;; ['(' testlist ')']
753 paren_class_list_opt
754   : ;;EMPTY
755   | paren_class_list
756   ;
757
758 paren_class_list
759   : PAREN_BLOCK
760     (let ((wisent-python-EXPANDING-block t))
761       (mapcar 'semantic-tag-name (EXPANDFULL $1 paren_classes)))
762   ;
763
764 ;; parameters: '(' [varargslist] ')'
765 paren_classes
766   : LPAREN
767     ()
768   | RPAREN
769     ()
770   | paren_class COMMA
771     (VARIABLE-TAG $1 nil nil)
772   | paren_class RPAREN
773     (VARIABLE-TAG $1 nil nil)
774   ;
775
776 ;; In general, the base class can be specified by a general expression
777 ;; which evalue to a class object, i.e., base classes are not just names!
778 ;; However base classes are names in most cases.  Thus the
779 ;; non-terminals below work only with simple names.  Even if the
780 ;; parser can parse general expressions, I don't see much benefit in
781 ;; generating a string of expression as base class "name".
782 paren_class
783   : dotted_name
784   ;
785
786 ;;;****************************************************************************
787 ;;;@ test
788 ;;;****************************************************************************
789
790 ;; test: and_test ('or' and_test)* | lambdef
791 test
792   : test_test
793   | lambdef
794   ;
795
796 ;; and_test ('or' and_test)*
797 test_test
798   : and_test
799   | test_test OR and_test
800     ()
801   ;
802
803 ;; and_test: not_test ('and' not_test)*
804 and_test
805   : not_test
806   | and_test AND not_test
807     ()
808   ;
809
810 ;; not_test: 'not' not_test | comparison
811 not_test
812   : NOT not_test
813     ()
814   | comparison
815   ;
816
817 ;; comparison: expr (comp_op expr)*
818 comparison
819   : expr
820   | comparison comp_op expr
821     ()
822   ;
823
824 ;; comp_op: '<'|'>'|'=='|'>='|'<='|'<>'|'!='|'in'|'not' 'in'|'is'|'is' 'not'
825 comp_op
826   : LT | GT | EQ | GE | LE | LTGT | NE | IN | NOT IN | IS | IS NOT
827   ;
828
829 ;; expr: xor_expr ('|' xor_expr)*
830 expr
831   : xor_expr
832   | expr BAR xor_expr
833     ()
834   ;
835
836 ;; xor_expr: and_expr ('^' and_expr)*
837 xor_expr
838   : and_expr
839   | xor_expr HAT and_expr
840     ()
841   ;
842
843 ;; and_expr: shift_expr ('&' shift_expr)*
844 and_expr
845   : shift_expr
846   | and_expr AMP shift_expr
847     ()
848   ;
849
850 ;; shift_expr: arith_expr (('<<'|'>>') arith_expr)*
851 shift_expr
852   : arith_expr
853   | shift_expr shift_expr_operators arith_expr
854     ()
855   ;
856
857 ;; ('<<'|'>>')
858 shift_expr_operators
859   : LTLT
860   | GTGT
861   ;
862
863 ;; arith_expr: term (('+'|'-') term)*
864 arith_expr
865   : term
866   | arith_expr plus_or_minus term
867     ()
868   ;
869
870 ;; ('+'|'-')
871 plus_or_minus
872   : PLUS
873   | MINUS
874   ;
875
876 ;; term: factor (('*'|'/'|'%'|'//') factor)*
877 term
878   : factor
879   | term term_operator factor
880     ()
881   ;
882
883 term_operator
884   : MULT
885   | DIV
886   | MOD
887   | DIVDIV
888   ;
889
890 ;; factor: ('+'|'-'|'~') factor | power
891 factor
892   : prefix_operators factor
893     ()
894   | power
895   ;
896
897 ;; ('+'|'-'|'~')
898 prefix_operators
899   : PLUS
900   | MINUS
901   | TILDE
902   ;
903
904 ;; power: atom trailer* ('**' factor)*
905 power
906   : atom trailer_zom exponent_zom
907     (concat $1
908             (if $2 (concat " " $2 " ") "")
909             (if $3 (concat " " $3) "")
910             )
911   ;
912
913 trailer_zom
914   : ;;EMPTY
915   | trailer_zom trailer
916     ()
917   ;
918
919 exponent_zom
920   : ;;EMPTY
921   | exponent_zom EXPONENT factor
922     ()
923   ;
924
925 ;; trailer: '(' [arglist] ')' | '[' subscriptlist ']' | '.' NAME
926 trailer
927   : PAREN_BLOCK
928     ()
929   | BRACK_BLOCK
930     ()
931   | PERIOD NAME
932     ()
933   ;
934
935 ;; atom: '(' [testlist] ')' | '[' [listmaker] ']' | '{' [dictmaker] '}'
936 ;;     | '`' testlist '`'   | NAME | NUMBER | STRING+
937 atom
938   : PAREN_BLOCK
939     ()
940   | BRACK_BLOCK
941     ()
942   | BRACE_BLOCK
943     ()
944   | BACKQUOTE testlist BACKQUOTE
945     ()
946   | NAME
947   | NUMBER_LITERAL
948   | one_or_more_string
949   ;
950
951 test_list_opt
952   : ;;EMPTY
953   | testlist
954     ()
955   ;
956
957 ;; testlist: test (',' test)* [',']
958 testlist
959   : comma_sep_test_list comma_opt
960   ;
961
962 ;; test (',' test)*
963 comma_sep_test_list
964   : test
965   | comma_sep_test_list COMMA test
966     (format "%s, %s" $1 $3)
967   ;
968
969 ;; (read $1) and (read $2) were done before to peel away the double quotes.
970 ;; However that does not work for single quotes, so it was taken out.
971 one_or_more_string
972   : STRING_LITERAL
973   | one_or_more_string STRING_LITERAL
974     (concat $1 $2)
975   ;
976
977 ;;;****************************************************************************
978 ;;;@ lambdef
979 ;;;****************************************************************************
980
981 ;; lambdef: 'lambda' [varargslist] ':' test
982 lambdef
983   : LAMBDA varargslist_opt COLON test
984     (format "%s %s" $1 (or $2 ""))
985   ;
986
987 ;; [varargslist]
988 varargslist_opt
989   : ;;EMPTY
990   | varargslist
991   ;
992
993 ;; varargslist: (fpdef ['=' test] ',')* ('*' NAME [',' '**' NAME] | '**' NAME)
994 ;;             | fpdef ['=' test] (',' fpdef ['=' test])* [',']
995 varargslist
996   : fpdef_opt_test_list_comma_zom rest_args
997     (nconc $2 $1)
998   | fpdef_opt_test_list comma_opt
999   ;
1000
1001 ;; ('*' NAME [',' '**' NAME] | '**' NAME)
1002 rest_args
1003   : MULT NAME multmult_name_opt
1004     () ;;(VARIABLE-TAG $2 nil nil)
1005   | EXPONENT NAME
1006     () ;;(VARIABLE-TAG $2 nil nil)
1007   ;
1008
1009 ;; [',' '**' NAME]
1010 multmult_name_opt
1011   : ;;EMPTY
1012   | COMMA EXPONENT NAME
1013     (VARIABLE-TAG $3 nil nil)
1014   ;
1015
1016 fpdef_opt_test_list_comma_zom
1017   : ;;EMPTY
1018   | fpdef_opt_test_list_comma_zom fpdef_opt_test COMMA
1019     (nconc $2 $1)
1020   ;
1021
1022 ;; fpdef ['=' test] (',' fpdef ['=' test])*
1023 fpdef_opt_test_list
1024   : fpdef_opt_test
1025   | fpdef_opt_test_list COMMA fpdef_opt_test
1026     (nconc $3 $1)
1027   ;
1028
1029 ;; fpdef ['=' test]
1030 fpdef_opt_test
1031   : fpdef eq_test_opt
1032   ;
1033
1034 ;; fpdef: NAME | '(' fplist ')'
1035 fpdef
1036   : NAME
1037     (VARIABLE-TAG $1 nil nil)
1038  ;; Below breaks the parser.  Don't know why, but my guess is that
1039  ;; LPAREN/RPAREN clashes with the ones in function_parameters.
1040  ;;  | LPAREN fplist RPAREN
1041  ;;    (identity $2)
1042   ;
1043
1044 ;; fplist: fpdef (',' fpdef)* [',']
1045 fplist
1046   : fpdef_list comma_opt
1047   ;
1048
1049 ;; fpdef (',' fpdef)*
1050 fpdef_list
1051   : fpdef
1052   | fpdef_list COMMA fpdef
1053   ;
1054
1055 ;; ['=' test]
1056 eq_test_opt
1057   : ;;EMPTY
1058   | ASSIGN test
1059     ()
1060   ;
1061
1062 ;;;****************************************************************************
1063 ;;;@ Misc
1064 ;;;****************************************************************************
1065
1066 ;; [',']
1067 comma_opt
1068   : ;;EMPTY
1069   | COMMA
1070   ;
1071
1072 ;; [';']
1073 semicolon_opt
1074   : ;;EMPTY
1075   | SEMICOLON
1076   ;
1077
1078 ;;; wisent-python.wy ends here