1% Test cases for the parser generator. This all runs in
2% symbolic mode...
3
4
5%
6% This is where (for now) I will put documentation of the syntax I
7% will use when creating a grammer. There is a main function called
8% lalr_construct_parser and that is passed a list that describes
9% a grammar. It is in the form of a sequence of productions, and the first
10% one given is taken to be the top-level target.
11%
12% Each production is in the form
13%     (LHS   ((rhs1.1 rhs1.2 ...) a1.1 a1.2 ...)
14%            ((rhs2.1 rhs2.1 ...) a2.1 a2.2 ...)
15%            ...)
16% which in regular publication style for grammars might be interpreted
17% as meaning
18%      LHS ::= rhs1.1 rhs1.2 ... { a1.1 a1.2 ... }
19%          |   rhs2.1 rhs2.2 ... { a2.1 a2.2 ... }
20%          ...
21%          ;
22%
23% Each LHS is treated as a non-terminal symbol and is specified as a simple
24% name. Note that by default the Reduce parser will be folding characters
25% within names to lower case and so it will be best to choose names for
26% non-terminals that are unambiguous even when case-folded, but I would like
27% to establish a convention that in source code they are written in capitals.
28%
29% The rhs items may be either non-terminals (identified because they are
30% present in the left hand side of some production) or terminals. Terminal
31% symbols can be specified in two different ways.
32% The lexer has built-in recipies that decode certain sequences of characters
33% and return the special markers for !:symbol, !:number, !:string, !:list for
34% commonly used cases. In these cases the variable yylval gets left set
35% to associated data, so for instance in the case of !:symbol it gets set
36% to the particular symbol concerned.
37% The token type :list is used for Lisp or rlisp-like notation where the
38% input contains
39%     'expression
40% or  `expression
41% so for instance the input `(a b c) leads to the lexer returning !:list and
42% yylvel being set to (backquote (a b c)). This treatment is specialised for
43% handling rlisp-like syntax.
44%
45% Other terminals are indicated by writing a string. That may either
46% consist of characters that would otherwise form a symbol (ie a letter
47% followed by letters, digits and underscores) or a sequence of
48% non-alphanumeric characters. In the latter case if a sequence of three or
49% more punctuation marks make up a terminal then all the shorter prefixes
50% of it will also be grouped to form single entities. So if "<-->" is a
51% terminal then '<', '<-' and '<--' will each by parsed as single tokens, and
52% any of them that are not used as terminals will be classified as !:symbol.
53%
54% When the lexer processes input it will return a numeric code that identifies
55% the type of the item seen, so in a production one might write
56%     (!:symbol ":=" EXPRESSION)
57% and as it recognises the first two tokens the lexer will return a numeric
58% code for !:symbol (and set yylval to the actual symbol as seen) and then
59% a numeric code that it allocates for ":=". In the latter case it will
60% also set yylval to the symbol !:!= in case that is useful.
61
62
63symbolic;
64
65
66nil
67
68
69% Before testing parser generation I will demonstrate the lexer..
70% If I was julpy about the exact behaviour of the lexer I could go
71%               on tracelex;
72% to get some more tracing.
73
74lex_cleanup();
75
76
77nil
78
79
80lex_keywords '("begin" "<=>" "<==");
81
82
83nil
84
85
86% The output from this is expected to be
87
88%  Result: (2 symbol)
89%  Result: (4 200)
90%  Result: (4 3.542)
91%  Result: (3 "a string")
92%  Result: (2 nil)
93%  Result: (5 (quote (quoted lisp)))
94%  Result: (5 (backquote (backquoted (!, comma) (!,!@ comma_at))))
95%  Result: (2 !+)
96%  Result: (7 !<!=!>)
97%  Result: (2 !-)
98%  Result: (2 !=)
99%  Result: (2 !>)
100%  Result: (9 !<)
101%  Result: (8 !<!=)
102%  Result: (5 begin)
103%  Result: (2 !;)
104%  Result: (2 !;)
105%  Result: (2 !;)
106%
107%  nil
108
109% The row of "; ; ;" at the end provides some protection so that
110% if faults in the lexer were to cause it to read more or less than it ought
111% to then what is left over is reasonably likely to remain as valid rlisp
112% syntax and so the rest of this test file will be able to continue happily.
113
114
115<< off echo;
116   lex_init();
117   for i := 1:18 do <<
118     tt := yylex();
119     if not zerop posn() then terpri();
120     princ "Result: ";
121     print list(tt, yylval) >>;
122   on echo >>;
123
124Result: (2 symbol)
125Result: (4 200)
126Result: (4 3.542)
127Result: (3 "a string")
128Result: (2 nil)
129Result: (5 (quote (quoted lisp)))
130Result: (5 (backquote (backquoted (!, comma) (!,!@ comma_at))))
131Result: (2 !+)
132Result: (7 !<!=!>)
133Result: (2 !-)
134Result: (2 !=)
135Result: (2 !>)
136Result: (9 !<)
137Result: (8 !<!=)
138Result: (6 begin)
139Result: (2 !;)
140Result: (2 !;)
141Result: (2 !;)
142
143nil
144 ;
145
146
147nil
148
149
150
151on lalr_verbose;
152
153
154nil
155
156
157% Here I set up a sample grammar
158%    S' -> S
159%    S  -> C C        { }
160%    C  -> "c" C      { }
161%        | "d"        { }
162% Example 4.42 from Aho, Sethi and Ullman's Red Dragon book, with
163% some simple semantic actions added. Note that I do not need to insert
164% the production S' -> S for myself since the analysis code will
165% augment my grammar with it for me anyway.
166% Example 4.54 in the more recent Purple book.
167
168% Note that this grammar will introduce "c" and "d" as keywords rather than
169% being general symbols. When I construct a subsequent grammar that will
170% undo that setting. I will omit semantic actions here so that the default
171% action of building a form of tree is used.
172
173% Limitations are
174% (1) I will need a way to specify precedence if this is to be feasibly
175%     useful. I have some planning for this but have not implemented it yet.
176% (2) At present the parser generator will not cope with large grammars
177%     because it does not merge rules promptly enough.
178% (3) The lexer is hand-written and can not readily be reconfigured for
179%     use with languages other than rlisp. For instance it has use of "!"
180%     as a character escape built into it.
181%
182%
183
184
185grammar := '(
186  (S  ((C C)    )   % One production for S, no semantic actions
187  )
188  (C  (("c" C)  )   % First production for C
189      (("d")    )   % Second production for C
190  ));
191
192
193((s ((c c))) (c (("c" c)) (("d"))))
194
195
196lalr_construct_parser grammar;
197
198Terminal symbols are:
199 !:eof:1 !:symbol:2 !:string:3 !:number:4 !:list:5 "d":6 "c":7
200Non-terminal symbols are:
201[0]S'               : S                         { }
202                    ;
203[1]S                : C C                       { }
204                    ;
205[2]C                : "c" C                     { }
206                    | "d"                       { }
207                    ;
208
209Action map:
2100:          nil
2111:          nil
2122:          nil
2133:          nil
214FIRST sets for each non-terminal:
215S':             c d
216S:              c d
217C:              c d
218Merged Items:
219Item number 0
220  S' -> . S  :  $
221  C -> . c C  :  c
222  C -> . c C  :  d
223  C -> . d  :  c
224  C -> . d  :  d
225  S -> . C C  :  $
226          C GOTO state 1
227          S GOTO state 2
228          c GOTO state 4
229          d GOTO state 3
230Item number 1
231  C -> . c C  :  $
232  C -> . d  :  $
233  S -> C . C  :  $
234          C GOTO state 6
235          c GOTO state 4
236          d GOTO state 3
237Item number 2
238  S' -> S .  :  $
239Item number 3
240  C -> d .  :  c
241  C -> d .  :  d
242  C -> d .  :  $
243Item number 4
244  C -> . c C  :  c
245  C -> . c C  :  d
246  C -> . c C  :  $
247  C -> . d  :  c
248  C -> . d  :  d
249  C -> . d  :  $
250  C -> c . C  :  c
251  C -> c . C  :  d
252  C -> c . C  :  $
253          C GOTO state 5
254          c GOTO state 4
255          d GOTO state 3
256Item number 5
257  C -> c C .  :  c
258  C -> c C .  :  d
259  C -> c C .  :  $
260Item number 6
261  S -> C C .  :  $
262End of Merged Items:
263Actions:
2640                   d                   (shift 3)
2650                   c                   (shift 4)
2661                   d                   (shift 3)
2671                   c                   (shift 4)
2682                   $                   accept
2693                   $                   reduce C -> d { 3 }
2703                   d                   reduce C -> d { 3 }
2713                   c                   reduce C -> d { 3 }
2724                   d                   (shift 3)
2734                   c                   (shift 4)
2745                   $                   reduce C -> c C { 2 }
2755                   d                   reduce C -> c C { 2 }
2765                   c                   reduce C -> c C { 2 }
2776                   $                   reduce S -> C C { 1 }
278ACTION_TABLE =
279(0    (6 (shift 3))
280      (7 (shift 4)))
281(1    (6 (shift 3))
282      (7 (shift 4)))
283(2    (0 accept))
284(3    (0 (reduce (c 6) (3)))
285      (6 (reduce (c 6) (3)))
286      (7 (reduce (c 6) (3))))
287(4    (6 (shift 3))
288      (7 (shift 4)))
289(5    (0 (reduce (c 7 c) (2)))
290      (6 (reduce (c 7 c) (2)))
291      (7 (reduce (c 7 c) (2))))
292(6    (0 (reduce (s c c) (1))))
293action_index #V16[0 2 4 5 8 10 13]
294action_terminal #V16[6 -1 6 -1 -1 0 6 -1 6 -1 0 6 -1 -1]
295action_result #V16[3 4 3 4 0 -3 -3 -3 3 4 -2 -2 -2 -1]
296action_fn [nil nil nil]
297action_n #V8[2 2 1]
298action_A #V16[1 2 2]
2990         C GOTO state 1
3001         C GOTO state 6
3014         C GOTO state 5
3020         S GOTO state 2
303goto_index: #V16[0 3 0]
304goto_old_state: #V16[0 1 -1 -1]
305goto_new_state: #V16[1 6 5 2]
306
307nil
308
309
310printc yyparse()$
311
312
313
314c c c d c d ;
315Seems to have finished... ((c (c (c d))) (c d))
316
317
318printc yyparse()$
319
320
321
322d d ;
323Seems to have finished... (d d)
324
325
326
327% Example 4.46 from the Red Dragon (4.61 in Aho, Lam, Sethi and Ullman,
328% "Compilers: principles, techniques and tools", second edition 2007).
329
330% The semantic actions here contain print statements that will
331% print some sort of trace as the parsing progresses.
332
333symbolic procedure neatprintc x;
334 << if not zerop posn() then terpri();
335    printc x >>;
336
337
338neatprintc
339
340
341g4_46 := '((S   ((L "=" R)   (neatprintc "## S => L = R")
342                             (list 'equal !$1 !$3))
343                ((R)         (neatprintc "## S => R")
344                             !$1))
345           (L   (("*" R)     (neatprintc "## L => * R")
346                             (list 'star !$2))
347                ((!:symbol)  (neatprintc "## L => symbol")
348                             !$1))
349           (R   ((L)         (neatprintc "## R => L")
350                             !$1)));
351
352
353((s ((l "=" r) (neatprintc "## S => L = R") (list (quote equal) !$1 !$3)) ((r) (
354neatprintc "## S => R") !$1)) (l (("*" r) (neatprintc "## L => * R") (list (
355quote star) !$2)) ((!:symbol) (neatprintc "## L => symbol") !$1)) (r ((l) (
356neatprintc "## R => L") !$1)))
357
358
359lalr_construct_parser g4_46;
360
361Terminal symbols are:
362 !:eof:1 !:symbol:2 !:string:3 !:number:4 !:list:5 "*":6 "=":7
363Non-terminal symbols are:
364[0]S'               : S                         { }
365                    ;
366[1]S                : L "=" R                   { neatprintc "## S => L = R" }
367                    | R                         { neatprintc "## S => R" }
368                    ;
369[2]L                : "*" R                     { neatprintc "## L => * R" }
370                    | :SYMBOL                   { neatprintc "## L => symbol" }
371                    ;
372[3]R                : L                         { neatprintc "## R => L" }
373                    ;
374
375Action map:
3760:          nil
3771:          ((neatprintc "## S => L = R") (list (quote equal) !$1 !$3))
3782:          ((neatprintc "## S => R") !$1)
3793:          ((neatprintc "## L => * R") (list (quote star) !$2))
3804:          ((neatprintc "## L => symbol") !$1)
3815:          ((neatprintc "## R => L") !$1)
382FIRST sets for each non-terminal:
383S':             !* !:symbol
384S:              !* !:symbol
385L:              !* !:symbol
386R:              !* !:symbol
387Merged Items:
388Item number 0
389  S' -> . S  :  $
390  L -> . !* R  :  !=
391  L -> . !* R  :  $
392  L -> . !:symbol  :  !=
393  L -> . !:symbol  :  $
394  R -> . L  :  $
395  S -> . L != R  :  $
396  S -> . R  :  $
397          L GOTO state 2
398          R GOTO state 1
399          S GOTO state 3
400          !* GOTO state 5
401          !:symbol GOTO state 4
402Item number 1
403  S -> R .  :  $
404Item number 2
405  R -> L .  :  $
406  S -> L . != R  :  $
407          != GOTO state 8
408Item number 3
409  S' -> S .  :  $
410Item number 4
411  L -> !:symbol .  :  !=
412  L -> !:symbol .  :  $
413Item number 5
414  L -> . !* R  :  !=
415  L -> . !* R  :  $
416  L -> . !:symbol  :  !=
417  L -> . !:symbol  :  $
418  L -> !* . R  :  !=
419  L -> !* . R  :  $
420  R -> . L  :  !=
421  R -> . L  :  $
422          L GOTO state 7
423          R GOTO state 6
424          !* GOTO state 5
425          !:symbol GOTO state 4
426Item number 6
427  L -> !* R .  :  !=
428  L -> !* R .  :  $
429Item number 7
430  R -> L .  :  !=
431  R -> L .  :  $
432Item number 8
433  L -> . !* R  :  $
434  L -> . !:symbol  :  $
435  R -> . L  :  $
436  S -> L != . R  :  $
437          L GOTO state 7
438          R GOTO state 9
439          !* GOTO state 5
440          !:symbol GOTO state 4
441Item number 9
442  S -> L != R .  :  $
443End of Merged Items:
444Actions:
4450                   !:symbol            (shift 4)
4460                   !*                  (shift 5)
4471                   $                   reduce S -> R { 2 }
4482                   $                   reduce R -> L { 5 }
4492                   !=                  (shift 8)
4503                   $                   accept
4514                   $                   reduce L -> !:symbol { 4 }
4524                   !=                  reduce L -> !:symbol { 4 }
4535                   !:symbol            (shift 4)
4545                   !*                  (shift 5)
4556                   $                   reduce L -> !* R { 3 }
4566                   !=                  reduce L -> !* R { 3 }
4577                   $                   reduce R -> L { 5 }
4587                   !=                  reduce R -> L { 5 }
4598                   !:symbol            (shift 4)
4608                   !*                  (shift 5)
4619                   $                   reduce S -> L != R { 1 }
462ACTION_TABLE =
463(0    (2 (shift 4))
464      (6 (shift 5)))
465(1    (0 (reduce (s r) (2))))
466(2    (0 (reduce (r l) (5)))
467      (7 (shift 8)))
468(3    (0 accept))
469(4    (0 (reduce (l 2) (4)))
470      (7 (reduce (l 2) (4))))
471(5    (2 (shift 4))
472      (6 (shift 5)))
473(6    (0 (reduce (l 6 r) (3)))
474      (7 (reduce (l 6 r) (3))))
475(7    (0 (reduce (r l) (5)))
476      (7 (reduce (r l) (5))))
477(8    (2 (shift 4))
478      (6 (shift 5)))
479(9    (0 (reduce (s l 7 r) (1))))
480action_index #V16[0 2 3 5 6 8 10 12 14 16]
481action_terminal #V16[2 -1 -1 0 -1 -1 0 -1 2 -1 0 -1 0 -1 2 -1 -1]
482action_result #V16[4 5 -2 -5 8 0 -4 -4 4 5 -3 -3 -5 -5 4 5 -1]
483action_fn [lalr_action_function_9 lalr_action_function_1 lalr_action_function_6
484lalr_action_function_4 lalr_action_function_8]
485action_n #V8[3 1 2 1 1]
486action_A #V16[1 1 2 2 3]
4870         L GOTO state 2
4885         L GOTO state 7
4898         L GOTO state 7
4900         R GOTO state 1
4915         R GOTO state 6
4928         R GOTO state 9
4930         S GOTO state 3
494goto_index: #V16[0 5 0 2]
495goto_old_state: #V16[0 -1 0 5 -1 -1]
496goto_new_state: #V16[2 7 1 6 9 3]
497
498nil
499
500
501printc yyparse()$
502
503
504
505leftsym =
506## L => symbol
507 rightsym ;
508## L => symbol
509## R => L
510## S => L = R
511Seems to have finished... (equal leftsym rightsym)
512
513
514
515printc yyparse()$
516
517
518
519****abc =
520## L => symbol
521## R => L
522## L => * R
523## R => L
524## L => * R
525## R => L
526## L => * R
527## R => L
528## L => * R
529 *def ;
530## L => symbol
531## R => L
532## L => * R
533## R => L
534## S => L = R
535Seems to have finished... (equal (star (star (star (star abc)))) (star def))
536
537
538#if nil  % Skip the rest of this test file...
539
540
541% The next example will not work until I have precedence rules imlemented
542% but is expected to be reasonably representative of natural small grammars.
543
544gtest := '((S  ((P) !$1)
545               ((S op P) (list !$2 !$1 !$3))
546               (("-" P) (list 'minus !$2))
547               (("+" P) !$2))
548           (op (("+") 'plus)
549               (("-") 'difference)
550               (("*") 'times)
551               (("/") 'quotient)
552               (("**") 'expt)
553               (("^") 'expt))
554           (P  (("(" S ")") !$2)
555               ((!:symbol) !$1)
556               ((!:string) !$1)
557               ((!:number) !$1)));
558
559lalr_construct_parser gtest;
560
561printc yyparse()$
562
563a * (b/c + d/e) ^ 2 ^ g - "stringdata" ;
564
565
566% Now a much more complicated grammar - one that recognizes the syntax of
567% RLISP. In order to survive this grammar my paser generator will need to
568% be extended to deal with ambiguous grammars both to cope with the
569% standard problem of "dangling else" clauses and to use precedence
570% declarations to disambiguate the uses of infix operators. Well at
571% present the grammar is written in a grossly bloated form so that
572% operator predcedence is hard wired into it... that too will need changing.
573
574% Note that a naive implementaion of LALR parser table generation via
575% initial construction of a full LR(1) table leads to ridiculous expense
576% when processing a grammar of this scale.
577
578rlisp_grammar := '(
579
580(command         ((  cmnd sep ))
581                 ((  end sep ))
582                 ((  command cmnd sep ))
583                 ((  command end sep ))
584)
585
586
587(sep             ((  ";" ))
588                 ((  "$" ))
589)
590
591
592(proc_type       ((  "symbolic" ))
593                 ((  "algebraic" ))
594)
595
596
597(proc_qual       ((  "expr" ))
598                 ((  "macro" ))
599                 ((  "smacro" ))
600)
601
602
603(sym_list        ((  ")" ))
604                 ((  "," !:symbol sym_list ))
605)
606
607
608(infix           ((  "setq" ))
609                 ((  "or" ))
610                 ((  "and" ))
611                 ((  "member" ))
612                 ((  "memq" ))
613                 ((  "=" ))
614                 ((  "neq" ))
615                 ((  "eq" ))
616                 ((  ">=" ))
617                 ((  ">" ))
618                 ((  "<=" ))
619                 ((  "<" ))
620                 ((  "freeof" ))
621                 ((  "+" ))
622                 ((  "-" ))
623                 ((  "*" ))
624                 ((  "/" ))
625                 ((  "^" ))
626                 ((  "**" ))
627                 ((  "." ))
628)
629
630(prefix          ((  "not" ))
631                 ((  "+" ))
632                 ((  "-" ))
633)
634
635
636(proc_head       ((  !:symbol ))
637                 ((  !:symbol !:symbol ))
638                 ((  !:symbol "(" ")" ))
639                 ((  !:symbol "(" !:symbol sym_list ))
640                 ((  prefix !:symbol ))
641                 ((  !:symbol infix !:symbol ))
642)
643
644
645(proc_def        ((  "procedure" proc_head sep cmnd ))
646                 ((  proc_type "procedure" proc_head sep cmnd ))
647                 ((  proc_qual "procedure" proc_head sep cmnd ))
648                 ((  proc_type proc_qual "procedure" proc_head sep cmnd ))
649)
650
651
652% The type "!:rlistat" is dodgy here... it doe snot (yet) exist!
653
654(rlistat         ((  !:rlistat ))
655                 ((  "in" ))
656                 ((  "on" ))
657)
658
659
660(rltail          ((  expr ))
661                 ((  expr "," rltail ))
662)
663
664
665(cmnd            ((  expr ))
666                 ((  rlistat rltail ))
667)
668
669
670(if_stmt         ((  "if" expr "then" cmnd "else" cmnd ))
671                 ((  "if" expr "then" cmnd ))
672)
673
674
675(for_update      ((  ":" expr ))
676                 ((  "step" expr "until" expr ))
677)
678
679
680(for_action      ((  "do" ))
681                 ((  "sum" ))
682                 ((  "collect" ))
683)
684
685
686(for_inon        ((  "in" ))
687                 ((  "on" ))
688)
689
690
691(for_stmt        ((  "for" !:symbol !:setq expr for_update for_action cmnd ))
692                 ((  "for" "each" !:symbol for_inon expr for_action cmnd ))
693                 ((  "foreach" !:symbol for_inon expr for_action cmnd ))
694)
695
696
697(while_stmt      ((  "while" expr "do" cmnd ))
698)
699
700
701(repeat_stmt     ((  "repeat" cmnd "until" expr ))
702)
703
704
705(return_stmt     ((  "return" ))
706                 ((  "return" expr ))
707)
708
709
710(goto_stmt       ((  "goto" !:symbol ))
711                 ((  "go" !:symbol ))
712                 ((  "go" "to" !:symbol ))
713)
714
715
716(group_tail      ((  ">>" ))
717                 ((  sep ">>" ))
718                 ((  sep cmnd group_tail ))
719)
720
721
722(group_expr      ((  "<<" cmnd group_tail ))
723)
724
725
726(scalar_tail     ((  sep ))
727                 ((  "," !:symbol scalar_tail ))
728                 ((  "," integer scalar_tail ))
729)
730
731
732(scalar_def      ((  "scalar" !:symbol scalar_tail ))
733                 ((  "integer" !:symbol scalar_tail ))
734)
735
736
737(scalar_defs     ((  scalar_def ))
738                 ((  scalar_defs scalar_def ))
739)
740
741
742(block_tail      ((  "end" ))
743                 ((  cmnd "end" ))
744                 ((  !:symbol ":" block_tail ))
745                 ((  cmnd sep block_tail ))
746                 ((  sep block_tail ))
747)
748
749(block_expr      ((  "begin" scalar_defs block_tail ))
750                 ((  "begin" block_tail ))
751)
752
753
754(lambda_vars     ((  sep ))
755                 ((  "," !:symbol lambda_vars ))
756)
757
758
759(lambda_expr     ((  "lambda" !:symbol lambda_vars cmnd ))
760                 ((  "lambda" "(" ")" sep cmnd ))
761                 ((  "lambda" "(" !:symbol sym_list sep cmnd ))
762)
763
764
765(expr            ((  rx0 ))
766                 ((  lx0 ))
767)
768
769
770(rx0             ((  lx0 "where" !:symbol "=" rx1 ))
771                 ((  rx1 ))
772)
773
774
775(lx0             ((  lx0 "where" !:symbol "=" lx1 ))
776                 ((  lx1 ))
777)
778
779
780(rx1             ((  lx2 ":=" rx1 ))
781                 ((  rx2 ))
782)
783
784
785(lx1             ((  lx2 ":=" lx1 ))
786                 ((  lx2 ))
787)
788
789
790(rx2tail         ((  rx3 ))
791                 ((  lx3 "or" rx2tail ))
792)
793
794(rx2             ((  lx3 "or" rx2tail ))
795                 ((  rx3 ))
796)
797
798
799(lx2tail         ((  lx3 ))
800                 ((  lx3 "or" lx2tail ))
801)
802
803(lx2             ((  lx3 "or" lx2tail ))
804                 ((  lx3 ))
805)
806
807
808(rx3tail         ((  rx4 ))
809                 ((  lx4 "and" rx3tail ))
810)
811
812(rx3             ((  lx4 "and" rx3tail ))
813                 ((  rx4 ))
814)
815
816
817(lx3tail         ((  lx4 ))
818                 ((  lx4 "and" lx3tail ))
819)
820
821(lx3             ((  lx4 "and" lx3tail ))
822                 ((  lx4 ))
823)
824
825
826(rx4             ((  "not" rx4 ))
827                 ((  rx5 ))
828)
829
830
831(lx4             ((  "not" lx4 ))
832                 ((  lx5 ))
833)
834
835% The fact that this lists "member" and "memq" (etc) here makes those names
836% keywords, and so possibly disables use as function names as in
837%    member(a, b)
838
839(rx5             ((  lx6 "member" ry6 ))
840                 ((  lx6 "memq" ry6 ))
841                 ((  lx6 "=" ry6 ))
842                 ((  lx6 "neq" ry6 ))
843                 ((  lx6 "eq" ry6 ))
844                 ((  lx6 ">=" ry6 ))
845                 ((  lx6 ">" ry6 ))
846                 ((  lx6 "<=" ry6 ))
847                 ((  lx6 "<" ry6 ))
848                 ((  lx6 "freeof" ry6 ))
849                 ((  rx6 ))
850)
851
852
853(lx5             ((  lx6 "member" ly6 ))
854                 ((  lx6 "memq" ly6 ))
855                 ((  lx6 "=" ly6 ))
856                 ((  lx6 "neq" ly6 ))
857                 ((  lx6 "eq" ly6 ))
858                 ((  lx6 ">=" ly6 ))
859                 ((  lx6 ">" ly6 ))
860                 ((  lx6 "<=" ly6 ))
861                 ((  lx6 "<" ly6 ))
862                 ((  lx6 "freeof" ly6 ))
863                 ((  lx6 ))
864)
865
866
867(ry6             ((  "not" ry6 ))
868                 ((  rx6 ))
869)
870
871
872(ly6             ((  "not" ly6 ))
873                 ((  lx6 ))
874)
875
876
877(rx6tail         ((  ry6a ))
878                 ((  ly6a "+" rx6tail ))
879)
880
881(rx6             ((  lx6a "+" rx6tail ))
882                 ((  rx6a ))
883)
884
885
886(lx6tail         ((  ly6a ))
887                 ((  ly6a "+" lx6tail ))
888)
889
890(lx6             ((  lx6a "+" lx6tail ))
891                 ((  lx6a ))
892)
893
894
895(ry6a            ((  not ry6a ))
896                 ((  rx6a ))
897)
898
899
900(rx6a            ((  lx6a "-" ry7 ))
901                 ((  rx7 ))
902)
903
904
905(ly6a            ((  not ly6a ))
906                 ((  lx6a ))
907)
908
909
910(lx6a            ((  lx6a "-" ly7 ))
911                 ((  lx7 ))
912)
913
914
915(ry7             ((  not ry7 ))
916                 ((  rx7 ))
917)
918
919
920(rx7             ((  "+" ry7 ))
921                 ((  "-" ry7 ))
922                 ((  rx8 ))
923)
924
925
926(ly7             ((  not ly7 ))
927                 ((  lx7 ))
928)
929
930
931(lx7             ((  "+" ly7 ))
932                 ((  "-" ly7 ))
933                 ((  lx8 ))
934)
935
936
937(rx8tail         ((  ry9 ))
938                 ((  ly9 "*" rx8tail ))
939)
940
941(rx8             ((  lx9 "*" rx8tail ))
942                 ((  rx9 ))
943)
944
945
946(lx8tail         ((  ly9 ))
947                 ((  ly9 "*" lx8tail ))
948)
949
950(lx8             ((  lx9 "*" lx8tail ))
951                 ((  lx9 ))
952)
953
954
955(ry9             ((  "not" ry9 ))
956                 ((  "+" ry9 ))
957                 ((  "-" ry9 ))
958                 ((  rx9 ))
959)
960
961
962(rx9             ((  lx9 "/" ry10 ))
963                 ((  rx10 ))
964)
965
966
967(ly9             ((  "not" ly9 ))
968                 ((  "+" ly9 ))
969                 ((  "-" ly9 ))
970                 ((  lx9 ))
971)
972
973
974(lx9             ((  lx9 "/" ly10 ))
975                 ((  lx10 ))
976)
977
978
979(ly10            ((  "not" ly10 ))
980                 ((  "+" ly10 ))
981                 ((  "-" ly10 ))
982                 ((  lx10 ))
983)
984
985
986(lx10            ((  lx11 "^" ly10 ))
987                 ((  lx11 ))
988)
989
990
991(ry10            ((  "not" ry10 ))
992                 ((  "+" ry10 ))
993                 ((  "-" ry10 ))
994                 ((  rx10 ))
995)
996
997
998(rx10            ((  lx11 "^" ry10 ))
999                 ((  rx11 ))
1000)
1001
1002
1003(ry11            ((  "not" ry11 ))
1004                 ((  "+" ry11 ))
1005                 ((  "-" ry11 ))
1006                 ((  rx11 ))
1007)
1008
1009
1010(rx11            ((  x12 "." ry11 ))
1011                 ((  if_stmt ))
1012                 ((  for_stmt ))
1013                 ((  while_stmt ))
1014                 ((  repeat_stmt ))
1015                 ((  return_stmt ))
1016                 ((  goto_stmt ))
1017                 ((  lambda_expr ))
1018                 ((  proc_type ))
1019                 ((  proc_def ))
1020                 ((  endstat ))
1021)
1022
1023
1024(ly11            ((  "not" ly11 ))
1025                 ((  "+" ly11 ))
1026                 ((  "-" ly11 ))
1027                 ((  lx11 ))
1028)
1029
1030
1031(lx11            ((  x12 "." ly11 ))
1032                 ((  x12 ))
1033)
1034
1035
1036(arg_list        ((  expr ")" ))
1037                 ((  expr "," arg_list ))
1038)
1039
1040
1041(x12             ((  x13 "[" expr "]" ))
1042                 ((  x13 "(" ")" ))
1043                 ((  x13 "(" expr "," arg_list ))
1044                 ((  x13 x12 ))
1045                 ((  x13 ))
1046)
1047
1048
1049(x13             ((  !:symbol ))
1050                 ((  !:number ))
1051                 ((  !:string ))
1052                 ((  !:list ))     % Both 'xxx and `xxx here
1053                 ((  group_expr ))
1054                 ((  block_expr ))
1055                 ((  "(" expr ")" ))
1056)
1057)$
1058
1059
1060% lalr_construct_parser rlisp_grammar;
1061
1062#endif
1063
1064end;
1065
1066nil
1067Tested on x86_64-pc-windows CSL
1068Time (counter 1): 0 ms
1069
1070End of Lisp run after 0.00+0.04 seconds
1071real 0.22
1072user 0.01
1073sys 0.03
1074