tagged release 0.7.1
[parrot.git] / languages / cardinal / src / parser / grammar.pg
blob1643525efc8f72dac5d9f4e53ca102b5aa221bd7
1 # $Id$
3 =begin overview
5 This is the grammar for cardinal written as a sequence of Perl 6 rules.
7 Originally taken (partly) from:
8 http://www.math.hokudai.ac.jp/~gotoken/ruby/man/yacc.html
10 and parse.y from the ruby source
12 =end overview
14 grammar cardinal::Grammar is PCT::Grammar;
16 token TOP {
17     <comp_stmt>
18     [ $ || <panic: Syntax error> ]
19     {*}
22 token comp_stmt {
23     {*}                        #= open
24     <stmts>
25     {*}                        #= close
28 rule stmts {
29     <.term>?[ <stmt> [<.term>+ | <.before <end_block>> | $ | <panic: unterminated statement>] ]* {*}
32 token term { \n | ';' }
33 token end_block { <.ws> [ 'end' | '}' ] }
35 token basic_stmt {
36     | <alias> {*}           #= alias
37     | <classdef> {*}        #= classdef
38     | <functiondef> {*}     #= functiondef
39     | <if_stmt> {*}         #= if_stmt
40     | <while_stmt> {*}      #= while_stmt
41     | <for_stmt> {*}        #= for_stmt
42     | <unless_stmt> {*}     #= unless_stmt
43     | <module> {*}          #= module
44     | <begin_end> {*}       #= begin_end
45     | <indexed_assignment> {*}      #= indexed_assignment
46     | <member_assignment> {*}      #= member_assignment
47     | <assignment> {*}      #= assignment
48     | <return_stmt> {*}     #= return_stmt
49     | <expr> {*}            #= expr
50     | <begin> {*}           #= begin
51     | <end> {*}             #= end
54 token return_stmt {
55     'return' <.ws> <call_args> {*}
58 rule alias {
59     'alias' <fname> <fname>
60     {*}
63 token stmt {
64     <basic_stmt> <.ws> <stmt_mod>*
65     {*}
68 token stmt_mod {
69     $<sym>=[if|while|unless|until] <.ws> <expr>
70     {*}
73 rule expr {
74     [$<not>=['!'|'not']]? <arg> [$<op>=['and'|'or'] <expr>]?
75     {*}
78 rule begin {
79     'BEGIN' '{' <comp_stmt> '}'
80     {*}
83 rule end {
84     'END' '{' <comp_stmt> '}'
85     {*}
88 token indexed_assignment {
89     <basic_primary> '[' <key=arg> ']' <.ws> '=' <.ws> <rhs=arg>
90     {*}
93 token member_assignment {
94     <basic_primary> '.' <key=identifier> <.ws> '=' <.ws> <rhs=arg>
95     {*}
98 rule assignment {
99     <mlhs=lhs> '=' <mrhs=arg>       #XXX need to figure out multiple assignment
100     {*}
103 rule mlhs {
104     | <lhs> {*}               #= lhs
105     | '(' <mlhs> ')' {*}      #= mlhs
108 token lhs {
109     | <basic_primary> {*}            #= basic_primary
112 token indexed {
113     '[' <args>? ']'
114     {*}
117 token member_variable {
118     <primary> '.' <identifier>
119     {*}
122 token methodcall {
123     $<dot>=['.'|'::']
124     <operation> <call_args>? <do_block>?
125     {*}
128 rule do_block {
129     | 'do' <do_args>? <.term>? <.before <stmt>><comp_stmt> 'end' {*}
130     | '{' <do_args>? <.term>? <.before <stmt>><comp_stmt> '}' {*}
133 rule super_call {
134     'super' <call_args>
135     {*}
138 token operation {
139     <.identifier> ('!'|'?')?
142 #XXX UGLY!  Refactor into <args> maybe?
143 token call_args {
144     | '()' [<.ws> <do_block>]? {*}
145     | [ <.after \s|\)> | <.before \s> ] <args> [<.ws> <do_block>]? {*}
146     | '(' <.ws> <args> <.ws> ')' [<.ws> <do_block>]? {*}
149 rule do_args {
150     '|' <block_signature> '|'
153 rule sig_identifier {
154                       #XXX Should this be basic_primary or expr or what?
155     <identifier>[ '=' <default=basic_primary>]? {*}
158 rule block_signature {
159     [
160     | <sig_identifier> [',' <sig_identifier>]* [',' <slurpy_param>]? [',' <block_param>]?
161     | <slurpy_param> [',' <block_param>]?
162     | <block_param>?
163     ] {*}
166 token variable {
167     | <varname> {*}      #= varname
168     | 'nil'     {*}      #= nil
169     | 'self'    {*}      #= self
172 token varname {
173     <!reserved_word>
174     [ <global> {*}             #= global
175     | <class_variable> {*}     #= class_variable
176     | <instance_variable> {*}  #= instance_variable
177     | <local_variable> {*}     #= local_variable
178     | <constant_variable> {*}  #= constant_variable
179     ]
182 token funcall {
183     <!reserved_word> <local_variable> <.before \s|'('> <.before <call_args>> {*}
186 token mrhs {
187     <args> {*}
190 rule args {
191     <arg> [',' <arg>]*
192     {*}
195 rule 'arg' is optable { ... }
197 proto 'infix:=' is precedence('1') is pasttype('copy') is lvalue(1)     { ... }
201 token basic_primary {
202     | <literal> {*}                         #= literal
203     | <funcall> {*}                         #= funcall
204     | <variable> {*}                        #= variable
205     | <ahash> {*}                           #= ahash
206     | <regex> {*}                           #= regex
207     | <do_block> {*}                        #= do_block
208     | <quote_string> {*}                    #= quote_string
209     | <warray> {*}                          #= warray
210     | <array> {*}                           #= array
211     | <pcomp_stmt> {*}                      #= pcomp_stmt
212     | <scope_identifier> {*}                #= scope_identifier
213     | <control_command> {*}                 #= control_command
216 token primary {
217     <basic_primary> <post_primary_expr>*
218     {*}
221 token post_primary_expr {
222     | <indexed> {*}            #= indexed
223     | <call_args> {*}          #= call_args
224     | <methodcall> {*}         #= methodcall
225     | <scope_identifier> {*}   #= scope_identifier
226     | '[' <args>? ']' {*}      #= args
229 token scope_identifier {
230     '::' <identifier>
231     {*}
234 token pcomp_stmt {
235     '(' <comp_stmt> ')'
236     {*}
240 rule if_stmt {
241     'if' <expr> <.then>
242     [<comp_stmt>
243     ['elsif' <expr> <.then>
244     <comp_stmt>]*
245     <else>?
246     'end'
247     |<panic: syntax error in if statement>]
248     {*}
251 token then { ':' | 'then' | <term> ['then']? }
253 rule while_stmt {
254     $<sym>=['while'|'until'] <expr> <.do>
255     <comp_stmt>
256     'end'
257     {*}
260 rule for_stmt {
261     'for' <variable> 'in' <expr> <.do>
262     <comp_stmt>
263     'end'
264     {*}
267 token do { ':' | 'do' | <term> ['do']? }
269 rule unless_stmt {
270     'unless' <expr> <.then> <comp_stmt>
271     <else>?
272     'end'
273     {*}
276 token else {
277     'else' <.ws> <comp_stmt>
278     {*}
281 token ensure {
282     'ensure' <.ws> <comp_stmt>
283     {*}
286 rule rescue {
287     # XXX check <args>
288     ['rescue' <args> <.then> <comp_stmt>]+
289     {*}
292 token control_command {
293     | 'next'  {*}                   #= next
294     | 'break' {*}                   #= break
295     | 'redo'  {*}                   #= redo
298 rule module {
299     'module' <module_identifier>
300     <comp_stmt>
301     'end'
302     {*}
305 rule classdef {
306     'class' <module_identifier> {*}  #= open
307     <comp_stmt>
308     'end'                       {*}  #= block
311 rule functiondef {
312     'def' <fname> <argdecl>
313     <comp_stmt>
314     'end'
315     {*}
318 rule bodystmt {
319     <comp_stmt>
320     <rescue>?
321     <else>?
322     <ensure>?
325 rule argdecl {
326     ['('
327     <block_signature>
328     ')']?
331 token slurpy_param {
332     '*' <identifier>
333     {*}
336 token block_param {
337     '&' <identifier>
338     {*}
341 rule begin_end {
342     'begin'
343     <comp_stmt>
344     ['rescue' <args>? <.do> <comp_stmt>]+
345     ['else' <comp_stmt>]?
346     ['ensure' <comp_stmt>]?
347     'end'
348     {*}
351 token fname {
352     <.identifier> <[=!?]>?
355 token quote_string {
356     ['%q'|'%Q'] <.before <[<[_|({]>> <quote_expression: :qq>
357     {*}
360 token warray {
361     '%w' <.before <[<[({]>> <quote_expression: :w :q>
362     {*}
365 rule array {
366     '[' [ <args> [',']? ]? ']'
367     {*}
370 rule ahash {
371     '{' [ <assocs> [',']? ]? '}'
372     {*}
375 rule assocs {
376     <assoc> [',' <assoc>]*
377     {*}
380 rule assoc {
381     <arg> '=>' <arg>
382     {*}
385 token identifier {
386     <!reserved_word> <ident> {*}
389 token module_identifier {
390     <.before <[A..Z]>> <ident>
391     {*}
394 token global {
395     '$' <ident>
396     {*}
399 token instance_variable {
400     '@' <ident>
401     {*}
404 token class_variable {
405     '@@' <ident>
406     {*}
409 token local_variable {
410     <before <[a..z_]>> <ident>
411     {*}
414 token constant_variable {
415     <before <[A..Z]>> <ident>
416     {*}
419 token literal {
420     | <float> {*}          #= float
421     | <integer> {*}        #= integer
422     | <string> {*}         #= string
425 token float {
426     '-'? \d* '.' \d+
427     {*}
430 token integer {
431     '-'? \d+
432     {*}
435 token string {
436     [ \' <string_literal: "'"> \' | \" <string_literal: '"'> \" ]
437     {*}
440 token regex {
441     <.before '/'> [<quote_expression: :regex> $<modifiers>=[<alpha>]*
442                   |<panic: problem parsing regex>]
443     {*}
446 token reserved_word {
447     [alias|and|BEGIN|begin|break|case
448     |class|def|defined|do|else|elsif
449     |END|end|ensure|false|for|if
450     |in|module|next|nil|not|or
451     |redo|rescue|retry|return|self|super
452     |then|true|undef|unless|until|when
453     |while|yield|__FILE__|__LINE__]>>
456 token ws {
457     | '\\' \n                      ## a backslash at end of line
458     | <after [','|'='|'+']> \n     ## a newline after a comma or operator is ignored
459     | \h* ['#' \N* \n*]?
463 proto 'infix:=' is precedence('1') is pasttype('copy') is lvalue(1)     { ... }
465 proto 'prefix:defined?' is looser('infix:=') { ... }
467 proto 'infix:+=' is equiv('infix:=')
468                  { ... }
470 proto 'infix:-=' is equiv('infix:=')
471                  is pirop('sub')        { ... }
473 proto 'infix:/=' is equiv('infix:=')
474                  is pirop('div')        { ... }
476 proto 'infix:*=' is equiv('infix:=')
477                  is pirop('mul')        { ... }
479 proto 'infix:%=' is equiv('infix:=')
480                  is pirop('mul')        { ... }
482 proto 'infix:|=' is equiv('infix:=')    { ... }
484 proto 'infix:&=' is equiv('infix:=')    { ... }
486 proto 'infix:~=' is equiv('infix:=')    { ... }
488 proto infix:«>>=» is equiv('infix:=')
489                   is pirop('rsh')       { ... }
491 proto infix:«<<=» is equiv('infix:=')
492                   is pirop('lsh')       { ... }
494 proto 'infix:&&=' is equiv('infix:=')
495                   is pirop('and')       { ... }
497 proto 'infix:**=' is equiv('infix:=')
498                   is pirop('pow')       { ... }
500 proto 'ternary:? :' is tighter('infix:=')
501                     is pirop('if')      { ... }
503 proto 'infix:..' is tighter('ternary:? :') 
504                 is parsed(&primary)     { ... }
505                  #is pirop('n_add')      { ... }
507 proto 'infix:...' is equiv('infix:...') { ... }
509 proto 'infix:||' is tighter('infix:..')
510                  is past('unless')      { ... }
512 proto 'infix:&&' is tighter('infix:||')
513                  is past('if')          { ... }
516 proto 'infix:=='      is tighter('infix:&&') { ... }
517 proto 'infix:!='      is equiv('infix:==') { ... }
518 proto 'infix:=~'      is equiv('infix:==') { ... }
519 proto 'infix:!~'      is equiv('infix:==') { ... }
520 proto 'infix:==='     is equiv('infix:==') { ... }
521 proto infix:«<=>» is equiv('infix:==') { ... }
524 proto infix:«>»  is tighter('infix:===') { ... }
525 proto infix:«<»  is tighter('infix:===') { ... }
526 proto infix:«<=»  is tighter('infix:===') { ... }
527 proto infix:«>=» is tighter('infix:===') { ... }
529 proto 'infix:|' is tighter('infix:<=')  { ... }
530 proto 'infix:^' is equiv('infix:|')  { ... }
532 proto 'infix:&' is tighter('infix:|')  { ... }
534 proto infix:«<<»  is tighter('infix:&') { ... }
535 proto infix:«>>»  is equiv(infix:«<<») { ... }
537 proto 'infix:+' is tighter(infix:«<<»)  { ... }
539 proto 'infix:-' is equiv('infix:+') { ... }
540                 #is pirop('n_sub')       { ... }
542 proto 'infix:*' is tighter('infix:+') { ... }
543                 #is pirop('n_mul')       { ... }
545 proto 'infix:/' is equiv('infix:*')  { ... }
546                 #is pirop('n_div')       { ... }
548 proto 'infix:%' is equiv('infix:*')
549                 is pirop('n_mod')       { ... }
551 #proto 'prefix:+' is tighter('infix:*')  { ... }
552 #proto 'prefix:-' is equiv('prefix:+')  { ... }
553 #proto 'prefix:!' is equiv('prefix:+')  { ... }
554 #proto 'prefix:~' is equiv('prefix:+')  { ... }
556 proto 'term:'   is tighter('infix:*')
557                 is parsed(&primary)     { ... }