tagged release 0.6.4
[parrot.git] / languages / cardinal / src / parser / grammar.pg
blobf5b962efa583277a3bcf264d332e69f1e81f7476
1 # $Id$
3 =begin overview
5 This is the grammar for cardinal written as a sequence of Perl 6 rules.
7 Currently taken (partly) from:
8 http://www.math.hokudai.ac.jp/~gotoken/ruby/man/yacc.html
10 and parse.y from the ruby source
12 But adapted here and there; it's not entirely correct, it seems.
14 =end overview
16 grammar cardinal::Grammar is PCT::Grammar;
18 token TOP {
19     <comp_stmt>
20     [ $ || <panic: Syntax error> ]
21     {*}
24 token comp_stmt {
25     {*}                        #= open
26     <stmts>
27     {*}                        #= close
30 rule stmts {
31     <.term>?[ <stmt> [<.term>+ | <.before <end_block>> | $] ]* {*}
34 token term { \n | ';' }
35 token end_block { <.ws> [ 'end' | '}' ] }
37 token basic_stmt {
38     | <alias> {*}           #= alias
39     | <classdef> {*}        #= classdef
40     | <functiondef> {*}     #= functiondef
41     | <if_stmt> {*}         #= if_stmt
42     | <while_stmt> {*}      #= while_stmt
43     | <for_stmt> {*}        #= for_stmt
44     | <unless_stmt> {*}     #= unless_stmt
45     | <module> {*}          #= module
46     | <begin_end> {*}       #= begin_end
47     | <indexed_assignment> {*}      #= indexed_assignment
48     | <assignment> {*}      #= assignment
49     | <return_stmt> {*}     #= return_stmt
50     | <expr> {*}            #= expr
51     | <begin> {*}           #= begin
52     | <end> {*}             #= end
55 token return_stmt {
56     'return' <.ws> <call_args> {*}
59 rule alias {
60     'alias' <fname> <fname>
61     {*}
64 token stmt {
65     <basic_stmt> <.ws> <stmt_mod>*
66     {*}
69 token stmt_mod {
70     $<sym>=[if|while|unless|until] <.ws> <expr>
71     {*}
74 rule expr {
75     $<not>=['not']? <arg> [$<op>=['and'|'or'] <expr>]?
76     {*}
79 rule begin {
80     'BEGIN' '{' <comp_stmt> '}'
81     {*}
84 rule end {
85     'END' '{' <comp_stmt> '}'
86     {*}
89 token indexed_assignment {
90     <basic_primary> '[' <key=arg> ']' <.ws> '=' <.ws> <rhs=arg>
91     {*}
94 rule assignment {
95     <mlhs=lhs> '=' <mrhs=arg>       #XXX need to figure out multiple assignment
96     {*}
99 rule mlhs {
100     | <lhs> {*}               #= lhs
101     | '(' <mlhs> ')' {*}      #= mlhs
104 token lhs {
105     | <basic_primary> {*}            #= basic_primary
108 token indexed {
109     '[' <args>? ']'
110     {*}
113 token member_variable {
114     <primary> '.' <identifier>
115     {*}
118 token methodcall {
119     $<dot>=['.'|'::']
120     <operation> <call_args>? <do_block>?
121     {*}
124 rule do_block {
125     | 'do' <do_args> <.term>? <comp_stmt> 'end' {*}
126     | '{' <do_args> <.term>? <comp_stmt> '}' {*}
129 rule super_call {
130     'super' <call_args>
131     {*}
134 token operation {
135     <.identifier> ('!'|'?')?
138 token call_args {
139     | '()' {*}
140     | <args> {*}
141     | '(' <.ws> <args> <.ws> ')' {*}
144 rule do_args {
145     '|' [ <identifier> [',' <identifier>]*]?'|' {*}
148 token variable {
149     | <varname> {*}      #= varname
150     | 'nil'     {*}      #= nil
151     | 'self'    {*}      #= self
154 token varname {
155     <!reserved_word>
156     [ <global> {*}             #= global
157     | <instance_variable> {*}  #= instance_variable
158     | <local_variable> {*}     #= local_variable
159     | <constant_variable> {*}     #= constant_variable
160     ]
163 token mrhs {
164     <args> {*}
167 rule args {
168     <arg> [',' <arg>]*
169     {*}
172 rule 'arg' is optable { ... }
174 proto 'infix:=' is precedence('1') is pasttype('copy') is lvalue(1)     { ... }
178 token basic_primary {
179     | <literal> {*}                         #= literal
180     | <variable> {*}                        #= variable
181     | <array> {*}                           #= array
182     | <ahash> {*}                           #= ahash
183     | <pcomp_stmt> {*}                      #= pcomp_stmt
184     | <scope_identifier> {*}                #= scope_identifier
187 token primary {
188     <basic_primary> <post_primary_expr>*
189     {*}
192 token post_primary_expr {
193     | <indexed> {*}            #= indexed
194     | <call_args> {*}          #= call_args
195     | <methodcall> {*}         #= methodcall
196     | <scope_identifier> {*}   #= scope_identifier
197     | '[' <args>? ']' {*}      #= args
200 token scope_identifier {
201     '::' <identifier>
202     {*}
205 token pcomp_stmt {
206     '(' <comp_stmt> ')'
207     {*}
211 rule if_stmt {
212     'if' <expr> <.then>
213     <comp_stmt>
214     ['elsif' <expr> <.then>
215     <comp_stmt>]*
216     <else>?
217     'end'
218     {*}
221 token then { ':' | 'then' | <term> ['then']? }
223 rule while_stmt {
224     $<sym>=['while'|'until'] <expr> <.do>
225     <comp_stmt>
226     'end'
227     {*}
230 rule for_stmt {
231     'for' <variable> 'in' <expr> <.do>
232     <comp_stmt>
233     'end'
234     {*}
237 token do { ':' | 'do' | <term> ['do']? }
239 rule unless_stmt {
240     'unless' <expr> <.then> <comp_stmt>
241     <else>?
242     'end'
243     {*}
246 token else {
247     'else' <.ws> <comp_stmt>
248     {*}
251 token ensure {
252     'ensure' <.ws> <comp_stmt>
253     {*}
256 rule rescue {
257     # XXX check <args>
258     ['rescue' <args> <.then> <comp_stmt>]+
259     {*}
262 rule module {
263     'module' <module_identifier>
264     <comp_stmt>
265     'end'
266     {*}
269 rule classdef {
270     'class' <module_identifier> {*}  #= open
271     <comp_stmt>
272     'end'                       {*}  #= block
275 rule functiondef {
276     'def' <fname> <argdecl>
277     <comp_stmt>
278     'end'
279     {*}
282 rule bodystmt {
283     <comp_stmt>
284     <rescue>?
285     <else>?
286     <ensure>?
289 rule argdecl {
290     ['('
291     [ <identifier> [',' <identifier>]* [',' <slurpy_param>]? [',' <block_param>]?
292     | <slurpy_param> [',' <block_param>]?
293     | <block_param>?
294     ]
295     ')']?
296     {*}
299 token slurpy_param {
300     '*' <identifier>
301     {*}
304 token block_param {
305     '&' <identifier>
306     {*}
309 rule begin_end {
310     'begin'
311     <comp_stmt>
312     ['rescue' <args>? <.do> <comp_stmt>]+
313     ['else' <comp_stmt>]?
314     ['ensure' <comp_stmt>]?
315     'end'
316     {*}
319 token fname {
320     <.identifier>
323 rule array {
324     '[' [ <args> [',']? ]? ']'
325     {*}
328 rule ahash {
329     '{' [ [ <args> | <assocs> ] [',']? ]? '}'
330     {*}
333 rule assocs {
334     <assoc> [',' <assoc>]*
335     {*}
338 rule assoc {
339     <arg> '=>' <arg>
340     {*}
343 token identifier {
344     <!reserved_word> <ident> {*}
347 token module_identifier {
348     <.before <[A..Z]>> <ident>
349     {*}
352 token global {
353     '$' <ident>
354     {*}
357 token instance_variable {
358     '@' <ident>
359     {*}
362 token class_variable {
363     '@@' <ident>
364     {*}
367 token local_variable {
368     <before <[a..z_]>> <ident>
369     {*}
372 token constant_variable {
373     <before <[A..Z]>> <ident>
374     {*}
377 token literal {
378     | <float> {*}          #= float
379     | <integer> {*}        #= integer
380     | <string> {*}         #= string
383 token float {
384     \d* '.' \d+
385     {*}
388 token integer {
389     \d+
390     {*}
393 token string {
394     [ \' <string_literal: "'"> \' | \" <string_literal: '"'> \" ]
395     {*}
398 token reserved_word {
399     [alias|and|BEGIN|begin|break|case
400     |class|def|defined|do|else|elsif
401     |END|end|ensure|false|for|if
402     |in|module|next|nil|not|or
403     |redo|rescue|retry|return|self|super
404     |then|true|undef|unless|until|when
405     |while|yield|__FILE__|__LINE__]>>
408 token ws {
409     | '\\' \n                      ## a backslash at end of line
410     | <after [','|'='|'+']> \n     ## a newline after a comma or operator is ignored
411     | \h* ['#' \N* \n*]?
415 proto 'infix:=' is precedence('1') is pasttype('copy') is lvalue(1)     { ... }
417 proto 'prefix:defined?' is looser('infix:=') { ... }
419 proto 'infix:+=' is equiv('infix:=')
420                  is pirop('add')        { ... }
422 proto 'infix:-=' is equiv('infix:=')
423                  is pirop('sub')        { ... }
425 proto 'infix:/=' is equiv('infix:=')
426                  is pirop('div')        { ... }
428 proto 'infix:*=' is equiv('infix:=')
429                  is pirop('mul')        { ... }
431 proto 'infix:%=' is equiv('infix:=')
432                  is pirop('mul')        { ... }
434 proto 'infix:|=' is equiv('infix:=')    { ... }
436 proto 'infix:&=' is equiv('infix:=')    { ... }
438 proto 'infix:~=' is equiv('infix:=')    { ... }
440 proto infix:«>>=» is equiv('infix:=')
441                   is pirop('rsh')       { ... }
443 proto infix:«<<=» is equiv('infix:=')
444                   is pirop('lsh')       { ... }
446 proto 'infix:&&=' is equiv('infix:=')
447                   is pirop('and')       { ... }
449 proto 'infix:**=' is equiv('infix:=')
450                   is pirop('pow')       { ... }
452 proto 'ternary:? :' is tighter('infix:=')
453                     is pirop('if')      { ... }
455 proto 'infix:..' is tighter('ternary:? :')
456                  is pirop('n_add')      { ... }
458 proto 'infix:...' is equiv('infix:...') { ... }
460 proto 'infix:||' is tighter('infix:..')
461                  is past('unless')      { ... }
463 proto 'infix:&&' is tighter('infix:||')
464                  is past('if')          { ... }
467 proto 'infix:=='      is tighter('infix:&&') { ... }
468 proto 'infix:!='      is equiv('infix:==') { ... }
469 proto 'infix:=~'      is equiv('infix:==') { ... }
470 proto 'infix:!~'      is equiv('infix:==') { ... }
471 proto 'infix:==='     is equiv('infix:==') { ... }
472 proto infix:«<=>» is equiv('infix:==') { ... }
475 proto 'infix:«<=»' is tighter('infix:===') { ... }
476 proto infix:«=>» is tighter('infix:===') { ... }
477 proto infix:«>»  is tighter('infix:===') { ... }
478 proto infix:«<»  is tighter('infix:===') { ... }
480 proto 'infix:|' is tighter('infix:«<=»')  { ... }
481 proto 'infix:^' is equiv('infix:|')  { ... }
483 proto 'infix:&' is tighter('infix:|')  { ... }
485 proto infix:«<<»  is tighter('infix:&') { ... }
486 proto infix:«>>»  is equiv(infix:«<<») { ... }
488 proto 'infix:+' is tighter(infix:«<<»)
489                 is pirop('n_add')       { ... }
491 proto 'infix:-' is equiv('infix:+')
492                 is pirop('n_sub')       { ... }
494 proto 'infix:*' is tighter('infix:+')
495                 is pirop('n_mul')       { ... }
497 proto 'infix:/' is equiv('infix:*')
498                 is pirop('n_div')       { ... }
500 proto 'infix:%' is equiv('infix:*')
501                 is pirop('n_mod')       { ... }
503 #proto 'prefix:+' is tighter('infix:*')  { ... }
504 #proto 'prefix:-' is equiv('prefix:+')  { ... }
505 #proto 'prefix:!' is equiv('prefix:+')  { ... }
506 #proto 'prefix:~' is equiv('prefix:+')  { ... }
508 proto 'term:'   is tighter('infix:*')
509                 is parsed(&primary)     { ... }