File Coverage

lib/Parser/LR.pm
Criterion Covered Total %
statement 198 214 92.5
branch 42 58 72.4
condition 3 6 50.0
subroutine 24 26 92.3
pod 11 12 91.6
total 278 316 87.9


line stmt bran cond sub pod time code
1             #!/usr/bin/perl
2             #-------------------------------------------------------------------------------
3             # Parser::LR - Create and use an LR(1) parser.
4             # Philip R Brenan at gmail dot com, Appa Apps Ltd Inc., 2019
5             #-------------------------------------------------------------------------------
6             # podDocumentation
7             package Parser::LR;
8             require v5.26;
9             our $VERSION = 20191121;
10 1     1   868 use warnings FATAL => qw(all);
  1         8  
  1         37  
11 1     1   34 use strict;
  1         2  
  1         36  
12 1     1   5 use Carp;
  1         2  
  1         102  
13 1     1   627 use Data::Dump qw(dump);
  1         7966  
  1         85  
14 1     1   3022 use Data::Table::Text qw(:all);
  1         133265  
  1         3983  
15 1     1   1215 use Data::DFA;
  1         16001  
  1         51  
16 1     1   8 use Data::NFA;
  1         3  
  1         31  
17 1     1   557 use Math::Cartesian::Product;
  1         722  
  1         4609  
18              
19             our $logFile = q(/home/phil/z/z/z/zzz.txt); # Log printed results if developing
20              
21             #D1 Create and use an LR(1) parser. # Construct an LR(1) parser from a set of rules using L; use the parser produced to parse sequences of terminal symbols using L; print the resulting parse tree with L or L.
22              
23             sub printRule($) #P Print a rule
24 0     0 1 0 {my ($rule) = @_; # Rule
25 0         0 my $r = $rule->rule;
26 0         0 my $x = $rule->expandable;
27 0         0 my $e = join ' ', $rule->expansion->@*;
28 0         0 qq($r($e)$x)
29             }
30              
31             sub compileGrammar($%) # Compile a grammar from a set of rules expressed as a string with one rule per line. Returns a L.
32             {my ($rules, %options) = @_; # Rule definitions, options
33              
34             my @lines = map {[split /\s+/]} split /\n/, $rules =~ s(#.*?\n) (\n)gsr; # Words from lines from grammar minus comments
35              
36             my sub newRule(%) # Create a new rule
37             {my (%options) = @_; # Options
38             genHash(q(Parser::LR::Rule), # A parsing rule
39             expandable => undef, # Symbol to expand
40             expansion => undef, # Symbol expansion
41             print => \&printRule, # Rule printer
42             rule => undef, # Rule number
43             %options,
44             );
45             }
46              
47             my @rules; # {symbol}[rule] = a rule to expand symbol
48              
49             for my $line(@lines) # Lines of input
50             {if (my ($expandable, @expansion) = @$line) # Symbol to expand, expansion
51             {push @rules, newRule # A parsing rule
52             (expandable => $expandable, # Symbol to expand
53             expansion => [@expansion], # Symbol expansion
54             print => \&printRule, # Rule printer
55             rule => scalar @rules, # Rule number
56             );
57             }
58             }
59              
60             my $grammar = bless \@rules, q(Parser::LR::Grammar); # {symbol to expand => {expansion=>[]}}
61             my $startSymbol = $$grammar[0]->expandable; # Locate the start symbol as the symbol expanded by the first rule
62              
63             my %expandables; my %terminals; # Find the expandable and terminal symbols
64              
65             for my $rule(@rules) # Expandables
66             {$expandables{$rule->expandable}++;
67             }
68              
69             for my $rule(@rules) # Terminals
70             {$terminals{$_}++ for grep {!$expandables{$_}} $rule->expansion->@*;
71             }
72              
73             my %reducers; # The expandables an expandable can reduce to
74             for my $r(@rules)
75             {my $e = $r->expandable;
76             my @e = $r->expansion->@*;
77             if (@e == 1)
78             {$reducers{$e[0]}{$e}++;
79             }
80             }
81              
82             for my $r (sort keys %reducers) # Propogate reduction of expandables
83             {my $n = 0;
84             for my $r1(sort keys %reducers)
85             {for my $r2(sort keys $reducers{$r1}->%*)
86             {for my $r3(sort keys $reducers{$r2}->%*)
87             {++$n;
88             $reducers{$r1}{$r3}++;
89             }
90             }
91             }
92             }
93              
94             my %recursiveExpandables; # Find self recursive expandables
95             for my $e(sort keys %reducers)
96             {if ($reducers{$e}{$e})
97             {$recursiveExpandables{$e}++
98             }
99             }
100              
101             if (keys %recursiveExpandables) # Check for self recursive expandables
102             {die "Recursive expandables:". dump([sort keys %recursiveExpandables]);
103             }
104              
105             my %optionalExpandables;
106             for my $rule(@rules) # Expandables that have empty expansions
107             {my @e = $rule->expansion->@*;
108             if (!@e)
109             {$optionalExpandables{$rule->expandable}++;
110             }
111             }
112              
113             if (!$options{nosub}) # Substitute rules that do not refer to themselves
114             {my sub appearances($$) # How many times an expandable appears in the expansion of a rule
115             {my ($expandable, $rule) = @_;
116             my $n = 0;
117             for my $e($rule->expansion->@*)
118             {++$n if $e eq $expandable;
119             }
120             $n # Number of times this expandable appears in this rule
121             } # appearances
122              
123             my sub selfRecursive($) # The number of rules the expandable is self recursive in
124             {my ($expandable) = @_;
125             my $n = 0;
126             for my $rule(@rules)
127             {if ($expandable eq $rule->expandable) # A rule expanding this expandable
128             {$n += appearances($expandable, $rule);
129             }
130             }
131             $n # Number of times this expandable appears in this rule
132             } # selfRecursive
133              
134             my sub rulesForExpandable($) # The rules that expand an expandable
135             {my ($expandable) = @_;
136             my @e;
137             for my $rule(@rules) # Terminals that start any rule
138             {if ($rule->expandable eq $expandable)
139             {push @e, $rule;
140             }
141             }
142             @e # Rules for this expandable
143             } # rulesForExpandable
144              
145             my sub addRulesBySubstituting($$$@) # Add rules by substituting the expansions of a non self recursive expandable
146             {my ($expandable, $appearances, $rule, @rules) = @_; # Expandable to substitute, appearances in rule to substitute into, rule to substitute into, rules to substitute from.
147             my @expansions = map {$_->expansion} @rules; # Expansion for each rule of the expandable being substituted
148             my @c; cartesian {push @c, [@_]} map {[@expansions]} 1..$appearances; # Cartesian product of the expansion rules by the number of times it appears in the rule
149             my @n; # New rules
150              
151             for my $c(@c) # Create new rules for each element of the cartesian product
152             {my @f;
153             for my $e($rule->expansion->@*)
154             {if ($expandable eq $e) # Substitute
155             {my $f = shift @$c;
156             push @f, @$f;
157             }
158             else
159             {push @f, $e; # Retain
160             }
161             }
162             push @n, newRule(expandable => $rule->expandable, expansion => [@f]); # Create new rule from substitution
163             }
164             @n # New rules
165             } # addRulesBySubstituting
166              
167             if (1) # Substitute non self recurring expandables to create more rules with fewer expandables
168             {my $changes = 1;
169             for my $a(1..10) # Maximum number of expansion passes
170             {next unless $changes; $changes = 0; # While there were changes made
171             for my $e(sort keys %expandables) # Each expandable
172             {if (!selfRecursive($e)) # Each non self recursive expandable symbol
173             {my @r = rulesForExpandable($e); # Rule set for the expandable being substituted
174             my @n;
175             for my $r(@rules) # Each rule
176             {if (my $n = appearances($e, $r)) # Number of times this expandable is mentioned in this rule - rules where it is the expandable will be ignored because we are only processing non self recursive expandables.
177             {push @n, addRulesBySubstituting($e, $n, $r, @r);
178             ++$changes;
179             }
180             elsif ($r->expandable ne $e) # Retain a rule which has no contact with the expandable being substituted
181             {push @n, $r;
182             }
183             }
184             @rules = @n;
185             }
186             }
187             }
188             }
189             }
190              
191             my %startTerminals;
192             for my $rule(@rules) # Terminals that start any rule
193             {my @e = $rule->expansion->@*;
194             if (my ($e) = $rule->expansion->@*)
195             {if ($terminals{$e})
196             {$startTerminals{$e}++;
197             }
198             }
199             }
200              
201             my $longestRule = 0;
202             for my $rule(@rules) # Longest rule
203             {my $l = $rule->expansion->@*;
204             $longestRule = max($longestRule, $l);
205             }
206              
207             my $nfa = bless {}, q(Data::NFA); # NFA being constructed
208              
209             my $newState = sub # Create a new state in the specified B<$nfa>
210 194     194   244 {my $n = scalar keys %$nfa; # Current NFA size
211 194         296 $$nfa{$n} = Data::NFA::newNfaState; # Create new state
212 194         8186 $n # Number of state created
213             };
214              
215             my $start = &$newState($nfa); # The expansions of each symbol are located from the start state by applying the symbol to be expanded
216              
217             for my $rule(@$grammar) # For each symbol in the expansion
218             {my $expansion = $rule->expansion; # Expansion part of rule
219             my $pos = $start; # Start state for rule
220             for my $e(@$expansion) # Transition to the next state on symbol being consumed
221             {my $p = $pos;
222             my $q = &$newState($nfa);
223             $$nfa{$p}->jumps->{$q}++;
224             $pos = $$nfa{$q}->transitions->{$e} = &$newState($nfa);
225             }
226              
227             $$nfa{$pos}->final = $rule; # Mark the final state with the sub to be called when we reduce by this rule
228             }
229              
230             my $finalState = $$nfa{$start}->transitions->{$startSymbol}=&$newState($nfa); # Transition on start symbol
231              
232             for my $i(sort keys %$nfa) # Add a jump to the symbol jump in state for each expandable symbol
233             {my $state = $$nfa{$i}; # State
234             delete $$state{final} unless defined $$state{final};
235             delete $$state{jumps} unless keys $$state{jumps}->%*;
236             delete $$state{transitions} unless keys $$state{transitions}->%*;
237             }
238              
239             my $dfa = Data::DFA::fromNfa($nfa); # DFA from grammar NFA
240              
241             for my $state(values $dfa->%*) # Remove irrelevant fields from each state
242             {delete @$state{qw(nfaStates pump sequence state)};
243              
244             for(grep {!defined $$state{$_}} qw(final transitions))
245             {delete $$state{$_};
246             }
247             }
248              
249             for my $state(sort keys %$dfa) # Check for multiple reductions
250             {if (my $final = $$dfa{$state}->final)
251             {if (@$final > 1)
252             {lll $dfa->print;
253             die "More than one reduction in state $state";
254             }
255             }
256             }
257              
258             my %expansionStates;
259             for my $state(sort keys %$dfa) # Mark expansions states
260             {for my $symbol(sort keys $$dfa{$state}->transitions->%*)
261             {if ($expandables{$symbol})
262             {$expansionStates{$state}++;
263             }
264             }
265             }
266              
267             for my $i(keys @rules) # Renumber rules
268             {$rules[$i]->rule = $i;
269             }
270              
271             genHash(q(Parser::LR::Grammar), # LR parser produced
272             grammar => $grammar, # Grammar from which the NFA was derived
273             nfa => $nfa, # NFA from grammar
274             dfa => $dfa, # DFA from grammar
275             expandables => \%expandables, # Expandable symbols
276             expansionStates => \%expansionStates, # States we can expand in
277             terminals => \%terminals, # Terminal symbols
278             reducers => \%reducers, # The expandables an expandable can reduce to
279             startSymbol => $startSymbol, # Start symbol
280             finalState => $$dfa{0}->transitions->{$startSymbol}, # Final state at end of parse
281             longestRule => $longestRule, # Longest rule
282             rules => [@rules], # Rules
283             startTerminals => \%startTerminals, # Terminals that start rules
284             optionalExpandables => \%optionalExpandables, # Expandables that can expand to nothing
285             );
286             } # compileGrammar
287              
288             sub longestMatchingRule($@) #P Find the longest rule that completely matches the top of the stack.
289 109     109 1 257 {my ($grammar, @stack) = @_; # Grammar, stack
290 109         1897 my $dfa = $grammar->dfa;
291 109         1907 my $L = $grammar->longestRule;
292 109 100       445 $L = @stack if $L > @stack;
293 109         156 my $N = @stack;
294 109         143 my $S = $N-$L;
295 109         156 my $F = $N-1;
296              
297 109         202 position: for my $i($S..$F) # Scan forward on stack for each possible rule
298 211         220 {my $state = 0;
299 211         284 symbol: for my $j($i..$F) # Scan forward from start in state 0 at selected point
300 367         410 {my $symbol = $stack[$j];
301 367 100       6071 if (my $next = $$dfa{$state}->transitions->{$symbol})
302 264         1043 {$state = $next;
303 264         416 next symbol;
304             }
305 103         435 next position;
306             }
307 108         1692 my $final = $$dfa{$state}->final;
308 108 100       690 return $final->[0] if $final; # Return matching rule
309             }
310             undef
311 12         43 }
312              
313             sub partialMatch($@) #P Check whether we have a partial match with the top of the stack.
314 268     268 1 605 {my ($grammar, @stack) = @_; # Grammar, stack
315 268         4512 my $dfa = $grammar->dfa;
316 268         4680 my $L = $grammar->longestRule;
317 268 100       1049 $L = @stack if $L > @stack;
318 268         325 my $N = @stack;
319              
320 268         507 position: for my $i($N-$L..$N-1) # Scan forward on stack from each possible position
321 727         765 {my $state = 0;
322 727         1042 symbol: for my $j($i..@stack-1) # Scan forward with this rule
323 1237         1409 {my $symbol = $stack[$j];
324 1237 100       19905 if (my $next = $$dfa{$state}->transitions->{$symbol})
325 631         2420 {$state = $next;
326 631         888 next symbol;
327             }
328 606         2507 next position;
329             }
330 121         313 return @stack-$i; # Matches this many characters
331             }
332             0
333 147         332 }
334              
335             sub reduceStackWithRule($$$) #P Reduce by the specified rule and update the stack and parse tree to match.
336 98     98 1 171 {my ($rule, $stack, $tree) = @_; # Rule, stack, parse tree
337 98         1584 my $L = $rule->expansion->@*;
338 98 50       418 if ($L <= @$stack) # Remove expansion
339 98         196 {my @r = splice(@$stack, -$L);
340 98         1781 push @$stack, $rule->expandable;
341 98         1774 my $e = $rule->expansion->@*;
342 98         429 my @s = splice @$tree, -$e;
343 98         1535 push @$tree, bless [$rule->rule, @s], q(Parser::LR::Reduce);
344             }
345             else # Stack too small
346 0         0 {die "Stack too small";
347             }
348             }
349              
350             sub parseWithGrammarAndLog($@) #P Parse, using a compiled B<$grammar>, an array of terminals and return a log of parsing actions taken.
351             {my ($grammar, @terminals) = @_; # Compiled grammar, terminals to parse
352             my $dfa = $grammar->dfa; # Dfa for grammar
353             my @stack;
354             my @log;
355             my @tree;
356              
357             my sub printStack{return join ' ', @stack if @stack; q/(empty)/} # Logging
358             my sub log(@) {my $m = join '', @_; push @log, $m; say STDERR $m}
359             my sub lll(@) {my $m = join '', @_; say STDERR $m}
360              
361             lll join '', "Parse : ", join ' ', @terminals;
362             terminal: while(@terminals) # Parse the terminals
363             {my $terminal = shift @terminals;
364             log "Terminal: $terminal, stack: ", printStack;
365             if (!@stack) # First terminal
366             {push @stack, $terminal;
367             push @tree, $terminal;
368             log " Accept first terminal: $terminal to get stack: ", printStack;
369             }
370             else
371             {my $p = partialMatch($grammar, @stack, $terminal);
372             if (partialMatch($grammar, @stack, $terminal) >= 2) # Fits as is
373             {push @stack, $terminal;
374             push @tree, $terminal;
375             log " Accept $terminal to get stack: ", printStack;
376             }
377             else
378             {if ($grammar->startTerminals->{$terminal}) # Starting terminal = shift now and hope for a later reduction
379             {push @stack, $terminal;
380             push @tree, $terminal;
381             log "Accepted terminal: $terminal as is, stack: ".printStack;
382             next terminal;
383             }
384             else # Not a starting terminal so we will have to reduce to fit now
385             {reduction: for my $r(1..10)
386             {if (my $rule = longestMatchingRule($grammar, @stack))
387             {my $n = $rule->rule;
388             my $e = $rule->expandable;
389             reduceStackWithRule($rule, \@stack, \@tree);
390             log " Reduced by rule $n, expandable: $e, stack: ", printStack;
391             my $P = partialMatch($grammar, @stack, $terminal);
392             if (partialMatch($grammar, @stack, $terminal) >= 2)
393             {push @stack, $terminal;
394             push @tree, $terminal;
395             log " Accept $terminal after $r reductions to get: ", printStack;
396             next terminal;
397             }
398             else
399             {next reduction;
400             }
401             }
402             next terminal;
403             }
404             die "No match after all reductions possible for $terminal on stack "
405             .printStack;
406             }
407             }
408             }
409             }
410              
411             for my $r(1..10) # Final reductions
412             {if (my $rule = longestMatchingRule($grammar, @stack))
413             {my $n = $rule->rule;
414             my $e = $rule->expandable;
415             reduceStackWithRule($rule, \@stack, \@tree);
416             log " Reduced in finals by rule $n, expandable: $e, stack: ", printStack;
417             next;
418             }
419             last;
420             }
421              
422             !@tree and die "No parse tree"; # Check for single parse tree
423             @tree > 1 and die "More than one parse block";
424              
425             log " Parse tree is:\n", &printParseTree($grammar, $tree[0]) if @tree; # Results
426              
427             my $r = join "\n", @log, ''; $r =~ s(\s+\Z) (\n)s; # Remove trailing new lines
428              
429             owf($logFile, $r) if -e $logFile; # Log the result if requested
430             $r
431             } # parseWithGrammarAndLog
432              
433             sub parseWithGrammar($@) # Parse, using a compiled B<$grammar>, an array of terminals and return a parse tree.
434 4     4 1 24 {my ($grammar, @terminals) = @_; # Compiled grammar, terminals to parse
435 4         82 my $dfa = $grammar->dfa; # Dfa for grammar
436 4         26 my @stack;
437             my @log;
438 4         0 my @tree;
439              
440 4         17 terminal: while(@terminals) # Parse the terminals
441 47         71 {my $terminal = shift @terminals;
442 47 100       80 if (!@stack) # First terminal
443 4         9 {push @stack, $terminal;
444 4         11 push @tree, $terminal;
445             }
446             else
447 43         78 {my $p = partialMatch($grammar, @stack, $terminal);
448 43 100       76 if (partialMatch($grammar, @stack, $terminal) >= 2) # Fits as is
449 2         4 {push @stack, $terminal;
450 2         6 push @tree, $terminal;
451             }
452             else
453 41 100       703 {if ($grammar->startTerminals->{$terminal}) # Starting terminal = shift now and hope for a later reduction
454 19         99 {push @stack, $terminal;
455 19         24 push @tree, $terminal;
456 19         45 next terminal;
457             }
458             else # Not a starting terminal so we will have to reduce to fit now
459 22         118 {reduction: for my $r(1..10)
460 50 100       98 {if (my $rule = longestMatchingRule($grammar, @stack))
461 48         759 {my $n = $rule->rule;
462 48         867 my $e = $rule->expandable;
463 48         257 reduceStackWithRule($rule, \@stack, \@tree);
464 48         273 my $P = partialMatch($grammar, @stack, $terminal);
465 48 100       83 if (partialMatch($grammar, @stack, $terminal) >= 2)
466 20         32 {push @stack, $terminal;
467 20         60 push @tree, $terminal;
468 20         51 next terminal;
469             }
470             else
471 28         50 {next reduction;
472             }
473             }
474 2         6 next terminal;
475             }
476 0         0 die "No match after all reductions possible for $terminal on stack "
477             .dump(\@stack). "\n";
478             }
479             }
480             }
481             }
482              
483 4         14 for my $r(1..10) # Final reductions
484 12 100       24 {if (my $rule = longestMatchingRule($grammar, @stack))
485 8         126 {my $n = $rule->rule;
486 8         142 my $e = $rule->expandable;
487 8         39 reduceStackWithRule($rule, \@stack, \@tree);
488 8         47 next;
489             }
490 4         10 last;
491             }
492              
493 4 50       11 !@tree and die "No parse tree"; # Check for single parse tree
494 4 50       14 @tree > 1 and die "More than one parse block";
495              
496 4         69 $tree[0]
497             } # parseWithGrammar
498              
499             sub printGrammar($) # Print a B<$grammar>.
500 1     1 1 4 {my ($grammar) = @_; # Grammar
501 1         2 my @r;
502 1         21 for my $rule($grammar->grammar->@*) # Each rule
503 16         840 {push @r, [$rule->rule, $rule->expandable, $rule->expansion->@*];
504             }
505 1         114 my $r = formatTable([@r], [qw(Rule Expandable Expansion)]);
506 1         1952 $r =~ s(\s+\Z) (\n)gs;
507 1 50       27 owf($logFile, $r) if -e $logFile; # Log the result if requested
508 1         19 $r
509             } # printGrammar
510              
511             sub printSymbolAsXml($) #P Print a symbol in a form acceptable as Xml
512 118     118 1 161 {my ($symbol) = @_; # Symbol
513 118 100       326 $symbol =~ m(\A[0-9a-z]+\Z)i ? $symbol : qq("$symbol");
514             }
515              
516             sub printGrammarAsXml($;$) #P Print a B<$grammar> as XML.
517 1     1 1 3 {my ($grammar, $indent) = @_; # Grammar, indentation level
518 1         3 my @r;
519 1   50     7 my $space = q( )x($indent//0); # Indentation
520              
521 1         21 for my $rule($grammar->grammar->@*) # Create an NFA for each rule as a choice of sequences
522 16         275 {my $r = $rule->rule;
523 16         279 my $s = $rule->expandable;
524 16         58 my $S = printSymbolAsXml($s);
525 16         37 push @r, qq(\n$space <$S>); # Rule
526              
527 16         248 for my $e($rule->expansion->@*) # Expansion
528 50         105 {my $E = printSymbolAsXml($e);
529 50         89 push @r, qq(<$E/>);
530             }
531 16         34 push @r, qq();
532             }
533              
534 1         9 my $r = join "", qq($space), @r, qq(\n$space), "\n"; # Result
535 1         9 $r =~ s(\s+\Z) (\n)gs;
536 1 50       33 owf($logFile, $r) if -e $logFile; # Log the result if requested
537 1         13 $r
538             } # printGrammarAsXml
539              
540             sub printParseTree($$;$) # Print a parse tree.
541 8     8 1 17 {my ($grammar, $tree, $indent) = @_; # Grammar, parse tree, optional indent level
542 8         20 my @r;
543 8         150 my @rules = $grammar->rules->@*;
544              
545 8         49 my $print; $print = sub # Print sub tree
546 145     145   200 {my ($stack, $depth) = @_;
547              
548 145 100       210 if (ref($stack))
549 84 50       171 {if (defined(my ($r) = @$stack))
550 84         95 {my ($rule) = $rules[$r];
551 84         130 my (undef, @exp) = @$stack;
552 84         1427 push @r, [$rule->rule, (q( )x$depth).$rule->expandable];
553 84         1896 for my $s(@exp)
554 137         353 {$print->($s, $depth+1);
555             }
556             }
557             }
558             else
559 61         202 {push @r, [q(), q(), $stack];
560             }
561 8         60 };
562              
563 8 50       21 return q() unless $tree; # Empty tree
564              
565 8   50     51 $print->($tree, $indent//0);
566              
567 8         64 my $r = formatTable([@r], [qw(Rule Expandable Terminal)]);
568 8         11977 $r =~ s(\s+\Z) (\n)gs;
569 8 50       161 owf($logFile, $r) if -e $logFile; # Log the result if requested
570 8         62 $r
571             } # printParseTree
572              
573             sub printParseTreeAsXml($$;$) # Print a parse tree as XML.
574 2     2 1 6 {my ($grammar, $tree, $indent) = @_; # Grammar, parse tree, optional indent level
575 2         5 my @r;
576 2         38 my @rules = $grammar->rules->@*;
577 2         12 my $terminal = 0;
578              
579 2         5 my $print; $print = sub # Print sub tree
580 52     52   73 {my ($stack, $depth) = @_;
581 52         76 my $s = q( ) x $depth;
582              
583 52 100       78 if (ref($stack))
584 27 50       57 {if (defined(my ($r) = @$stack))
585 27         38 {my ($rule) = $rules[$r];
586 27         43 my (undef, @exp) = @$stack;
587 27         462 my $n = $rule->rule;
588 27         503 my $e = $rule->expandable;
589 27         102 my $E = printSymbolAsXml($e);
590 27         76 push @r, qq($s<$E rule="$n">);
591 27         36 for my $s(@exp)
592 50         141 {$print->($s, $depth+1);
593             }
594 27         74 push @r, qq($s);
595             }
596             }
597             else
598 25         32 {my $t = printSymbolAsXml($stack);
599 25         65 push @r, qq($s<$t pos="$terminal"/>);
600 25         41 ++$terminal;
601             }
602 2         17 };
603              
604 2 50       8 return q() unless $tree; # Empty tree
605              
606 2   50     16 $print->($tree, $indent//0);
607              
608 2         17 my $r = join "\n", @r, '';
609 2         33 $r =~ s(\s+\Z) (\n)gs;
610 2 50       43 owf($logFile, $r) if -e $logFile; # Log the result if requested
611 2         18 $r
612             } # printParseTreeAsXml
613              
614             sub printParseTreeAndGrammarAsXml($$) #P Print a parse tree produced from a grammar by L as XML.
615 0     0 1 0 {my ($tree, $grammar) = @_; # Parse tree, grammar
616 0         0 my @r;
617              
618 0         0 push @r, q(), q( );
619 0         0 push @r, printParseTreeAsXml($tree, 2).q( );
620 0         0 push @r, printGrammarAsXml ($grammar, 1).q();
621 0         0 my $r = join "\n", @r, '';
622 0         0 $r =~ s(\s+\Z) (\n)gs;
623 0 0       0 owf($logFile, $r) if -e $logFile; # Log the result if requested
624 0         0 $r
625             }
626              
627             #D0
628             #-------------------------------------------------------------------------------
629             # Export - eeee
630             #-------------------------------------------------------------------------------
631              
632 1     1   10 use Exporter qw(import);
  1         2  
  1         43  
633              
634 1     1   7 use vars qw(@ISA @EXPORT @EXPORT_OK %EXPORT_TAGS);
  1         2  
  1         389  
635              
636             @ISA = qw(Exporter);
637             @EXPORT = qw();
638             @EXPORT_OK = qw();
639              
640             %EXPORT_TAGS = (all=>[@EXPORT, @EXPORT_OK]);
641              
642             #D
643             # podDocumentation
644              
645             =pod
646              
647             =encoding utf-8
648              
649             =head1 Name
650              
651             Parser::LR - Create and use an LR(1) parser.
652              
653             =head1 Synopsis
654              
655             Create an LR grammar from rules expressed one rule per line of a string. Each
656             rule starts with an expandable symbol followed by one possible expansion as a
657             mixture of expandable and terminal symbols:
658              
659             my $grammar = compileGrammar(<
660             A A + B
661             A B
662             B B * C
663             B C
664             C n
665             C ( A )
666             C [ A ]
667             C { A }
668             C ( )
669             C [ ]
670             C { }
671             END
672              
673             Print the grammar with L (substituting non recursive
674             expandables):
675              
676             ok printGrammar($grammar) eq <
677             Rule Symbol Expansion
678             1 0 A A + B
679             2 1 A B
680             3 2 B B * n
681             4 3 B B * ( A )
682             5 4 B B * [ A ]
683             6 5 B B * { A }
684             7 6 B B * ( )
685             8 7 B B * [ ]
686             9 8 B B * { }
687             10 9 B n
688             11 10 B ( A )
689             12 11 B [ A ]
690             13 12 B { A }
691             14 13 B ( )
692             15 14 B [ ]
693             16 15 B { }
694             END
695              
696             Use the grammar so created to parse a string an array of terminal symbols
697             into a parse tree with L:
698              
699             my $tree = parseWithGrammar($grammar, qw/( [ { } ] + [ { n } ] ) * [ n + n ] /);
700              
701             Print the parse tree tree with L:
702              
703             ok printParseTree($grammar, $tree) eq <
704             Rule Expandable Terminal
705             1 1 A
706             2 4 B
707             3 10 B
708             4 (
709             5 0 A
710             6 1 A
711             7 11 B
712             8 [
713             9 1 A
714             10 15 B
715             11 {
716             12 }
717             13 ]
718             14 +
719             15 11 B
720             16 [
721             17 1 A
722             18 12 B
723             19 {
724             20 1 A
725             21 9 B
726             22 n
727             23 }
728             24 ]
729             25 )
730             26 *
731             27 [
732             28 0 A
733             29 1 A
734             30 9 B
735             31 n
736             32 +
737             33 9 B
738             34 n
739             35 ]
740             END
741              
742             Or print the parse tree as XML with: L and apply L to process it
743             further:
744              
745             ok printParseTreeAsXml($grammar, $tree) eq <
746            
747            
748            
749             <"(" pos="0"/>
750            
751            
752            
753             <"[" pos="1"/>
754            
755            
756             <"{" pos="2"/>
757             <"}" pos="3"/>
758            
759            
760             <"]" pos="4"/>
761            
762            
763             <"+" pos="5"/>
764            
765             <"[" pos="6"/>
766            
767            
768             <"{" pos="7"/>
769            
770            
771            
772            
773            
774             <"}" pos="9"/>
775            
776            
777             <"]" pos="10"/>
778            
779            
780             <")" pos="11"/>
781            
782             <"*" pos="12"/>
783             <"[" pos="13"/>
784            
785            
786            
787            
788            
789            
790             <"+" pos="15"/>
791            
792            
793            
794            
795             <"]" pos="17"/>
796            
797            
798             END
799              
800             =head1 Description
801              
802             Create and use an LR(1) parser.
803              
804              
805             Version 20191121.
806              
807              
808             The following sections describe the methods in each functional area of this
809             module. For an alphabetic listing of all methods by name see L.
810              
811              
812              
813             =head1 Create and use an LR(1) parser.
814              
815             Construct an LR(1) parser from a set of rules using L; use the parser produced to parse sequences of terminal symbols using L; print the resulting parse tree with L or L.
816              
817             =head2 compileGrammar($%)
818              
819             Compile a grammar from a set of rules expressed as a string with one rule per line. Returns a L.
820              
821             Parameter Description
822             1 $rules Rule definitions
823             2 %options Options
824              
825             B
826              
827              
828             if (1) {
829             my $grammar = 𝗰𝗼𝗺𝗽𝗶𝗹𝗲𝗚𝗿𝗮𝗺𝗺𝗮𝗿(<
830             A A + B
831             A B
832             B B * C
833             B C
834             C n
835             C ( A )
836             C [ A ]
837             C { A }
838             C ( )
839             C [ ]
840             C { }
841             END
842            
843             ok printGrammar($grammar) eq <
844             Rule Expandable Expansion
845             1 0 A A + B
846             2 1 A B
847             3 2 B B * n
848             4 3 B B * ( A )
849             5 4 B B * [ A ]
850             6 5 B B * { A }
851             7 6 B B * ( )
852             8 7 B B * [ ]
853             9 8 B B * { }
854             10 9 B n
855             11 10 B ( A )
856             12 11 B [ A ]
857             13 12 B { A }
858             14 13 B ( )
859             15 14 B [ ]
860             16 15 B { }
861             END
862            
863             my $tree = parseWithGrammar($grammar, qw/( [ { } ] + [ { n } ] ) * [ n + n ] /);
864            
865             ok printParseTree($grammar, $tree) eq <
866             Rule Expandable Terminal
867             1 1 A
868             2 4 B
869             3 10 B
870             4 (
871             5 0 A
872             6 1 A
873             7 11 B
874             8 [
875             9 1 A
876             10 15 B
877             11 {
878             12 }
879             13 ]
880             14 +
881             15 11 B
882             16 [
883             17 1 A
884             18 12 B
885             19 {
886             20 1 A
887             21 9 B
888             22 n
889             23 }
890             24 ]
891             25 )
892             26 *
893             27 [
894             28 0 A
895             29 1 A
896             30 9 B
897             31 n
898             32 +
899             33 9 B
900             34 n
901             35 ]
902             END
903            
904             ok printParseTreeAsXml($grammar, $tree) eq <
905            
906            
907            
908             <"(" pos="0"/>
909            
910            
911            
912             <"[" pos="1"/>
913            
914            
915             <"{" pos="2"/>
916             <"}" pos="3"/>
917            
918            
919             <"]" pos="4"/>
920            
921            
922             <"+" pos="5"/>
923            
924             <"[" pos="6"/>
925            
926            
927             <"{" pos="7"/>
928            
929            
930            
931            
932            
933             <"}" pos="9"/>
934            
935            
936             <"]" pos="10"/>
937            
938            
939             <")" pos="11"/>
940            
941             <"*" pos="12"/>
942             <"[" pos="13"/>
943            
944            
945            
946            
947            
948            
949             <"+" pos="15"/>
950            
951            
952            
953            
954             <"]" pos="17"/>
955            
956            
957             END
958            
959             ok printGrammarAsXml($grammar) eq <
960            
961             <"+"/>
962            
963             <"*"/>
964             <"*"/><"("/><")"/>
965             <"*"/><"["/><"]"/>
966             <"*"/><"{"/><"}"/>
967             <"*"/><"("/><")"/>
968             <"*"/><"["/><"]"/>
969             <"*"/><"{"/><"}"/>
970            
971             <"("/><")"/>
972             <"["/><"]"/>
973             <"{"/><"}"/>
974             <"("/><")"/>
975             <"["/><"]"/>
976             <"{"/><"}"/>
977            
978             END
979             }
980            
981              
982             =head2 parseWithGrammar($@)
983              
984             Parse, using a compiled B<$grammar>, an array of terminals and return a parse tree.
985              
986             Parameter Description
987             1 $grammar Compiled grammar
988             2 @terminals Terminals to parse
989              
990             B
991              
992              
993             if (1) {
994             my $grammar = compileGrammar(<
995             A A + B
996             A B
997             B B * C
998             B C
999             C n
1000             C ( A )
1001             C [ A ]
1002             C { A }
1003             C ( )
1004             C [ ]
1005             C { }
1006             END
1007            
1008             ok printGrammar($grammar) eq <
1009             Rule Expandable Expansion
1010             1 0 A A + B
1011             2 1 A B
1012             3 2 B B * n
1013             4 3 B B * ( A )
1014             5 4 B B * [ A ]
1015             6 5 B B * { A }
1016             7 6 B B * ( )
1017             8 7 B B * [ ]
1018             9 8 B B * { }
1019             10 9 B n
1020             11 10 B ( A )
1021             12 11 B [ A ]
1022             13 12 B { A }
1023             14 13 B ( )
1024             15 14 B [ ]
1025             16 15 B { }
1026             END
1027            
1028             my $tree = 𝗽𝗮𝗿𝘀𝗲𝗪𝗶𝘁𝗵𝗚𝗿𝗮𝗺𝗺𝗮𝗿($grammar, qw/( [ { } ] + [ { n } ] ) * [ n + n ] /);
1029            
1030             ok printParseTree($grammar, $tree) eq <
1031             Rule Expandable Terminal
1032             1 1 A
1033             2 4 B
1034             3 10 B
1035             4 (
1036             5 0 A
1037             6 1 A
1038             7 11 B
1039             8 [
1040             9 1 A
1041             10 15 B
1042             11 {
1043             12 }
1044             13 ]
1045             14 +
1046             15 11 B
1047             16 [
1048             17 1 A
1049             18 12 B
1050             19 {
1051             20 1 A
1052             21 9 B
1053             22 n
1054             23 }
1055             24 ]
1056             25 )
1057             26 *
1058             27 [
1059             28 0 A
1060             29 1 A
1061             30 9 B
1062             31 n
1063             32 +
1064             33 9 B
1065             34 n
1066             35 ]
1067             END
1068            
1069             ok printParseTreeAsXml($grammar, $tree) eq <
1070            
1071            
1072            
1073             <"(" pos="0"/>
1074            
1075            
1076            
1077             <"[" pos="1"/>
1078            
1079            
1080             <"{" pos="2"/>
1081             <"}" pos="3"/>
1082            
1083            
1084             <"]" pos="4"/>
1085            
1086            
1087             <"+" pos="5"/>
1088            
1089             <"[" pos="6"/>
1090            
1091            
1092             <"{" pos="7"/>
1093            
1094            
1095            
1096            
1097            
1098             <"}" pos="9"/>
1099            
1100            
1101             <"]" pos="10"/>
1102            
1103            
1104             <")" pos="11"/>
1105            
1106             <"*" pos="12"/>
1107             <"[" pos="13"/>
1108            
1109            
1110            
1111            
1112            
1113            
1114             <"+" pos="15"/>
1115            
1116            
1117            
1118            
1119             <"]" pos="17"/>
1120            
1121            
1122             END
1123            
1124             ok printGrammarAsXml($grammar) eq <
1125            
1126             <"+"/>
1127            
1128             <"*"/>
1129             <"*"/><"("/><")"/>
1130             <"*"/><"["/><"]"/>
1131             <"*"/><"{"/><"}"/>
1132             <"*"/><"("/><")"/>
1133             <"*"/><"["/><"]"/>
1134             <"*"/><"{"/><"}"/>
1135            
1136             <"("/><")"/>
1137             <"["/><"]"/>
1138             <"{"/><"}"/>
1139             <"("/><")"/>
1140             <"["/><"]"/>
1141             <"{"/><"}"/>
1142            
1143             END
1144             }
1145            
1146              
1147             =head2 printGrammar($)
1148              
1149             Print a B<$grammar>.
1150              
1151             Parameter Description
1152             1 $grammar Grammar
1153              
1154             B
1155              
1156              
1157             if (1) {
1158             my $grammar = compileGrammar(<
1159             A A + B
1160             A B
1161             B B * C
1162             B C
1163             C n
1164             C ( A )
1165             C [ A ]
1166             C { A }
1167             C ( )
1168             C [ ]
1169             C { }
1170             END
1171            
1172             ok 𝗽𝗿𝗶𝗻𝘁𝗚𝗿𝗮𝗺𝗺𝗮𝗿($grammar) eq <
1173             Rule Expandable Expansion
1174             1 0 A A + B
1175             2 1 A B
1176             3 2 B B * n
1177             4 3 B B * ( A )
1178             5 4 B B * [ A ]
1179             6 5 B B * { A }
1180             7 6 B B * ( )
1181             8 7 B B * [ ]
1182             9 8 B B * { }
1183             10 9 B n
1184             11 10 B ( A )
1185             12 11 B [ A ]
1186             13 12 B { A }
1187             14 13 B ( )
1188             15 14 B [ ]
1189             16 15 B { }
1190             END
1191            
1192             my $tree = parseWithGrammar($grammar, qw/( [ { } ] + [ { n } ] ) * [ n + n ] /);
1193            
1194             ok printParseTree($grammar, $tree) eq <
1195             Rule Expandable Terminal
1196             1 1 A
1197             2 4 B
1198             3 10 B
1199             4 (
1200             5 0 A
1201             6 1 A
1202             7 11 B
1203             8 [
1204             9 1 A
1205             10 15 B
1206             11 {
1207             12 }
1208             13 ]
1209             14 +
1210             15 11 B
1211             16 [
1212             17 1 A
1213             18 12 B
1214             19 {
1215             20 1 A
1216             21 9 B
1217             22 n
1218             23 }
1219             24 ]
1220             25 )
1221             26 *
1222             27 [
1223             28 0 A
1224             29 1 A
1225             30 9 B
1226             31 n
1227             32 +
1228             33 9 B
1229             34 n
1230             35 ]
1231             END
1232            
1233             ok printParseTreeAsXml($grammar, $tree) eq <
1234            
1235            
1236            
1237             <"(" pos="0"/>
1238            
1239            
1240            
1241             <"[" pos="1"/>
1242            
1243            
1244             <"{" pos="2"/>
1245             <"}" pos="3"/>
1246            
1247            
1248             <"]" pos="4"/>
1249            
1250            
1251             <"+" pos="5"/>
1252            
1253             <"[" pos="6"/>
1254            
1255            
1256             <"{" pos="7"/>
1257            
1258            
1259            
1260            
1261            
1262             <"}" pos="9"/>
1263            
1264            
1265             <"]" pos="10"/>
1266            
1267            
1268             <")" pos="11"/>
1269            
1270             <"*" pos="12"/>
1271             <"[" pos="13"/>
1272            
1273            
1274            
1275            
1276            
1277            
1278             <"+" pos="15"/>
1279            
1280            
1281            
1282            
1283             <"]" pos="17"/>
1284            
1285            
1286             END
1287            
1288             ok printGrammarAsXml($grammar) eq <
1289            
1290             <"+"/>
1291            
1292             <"*"/>
1293             <"*"/><"("/><")"/>
1294             <"*"/><"["/><"]"/>
1295             <"*"/><"{"/><"}"/>
1296             <"*"/><"("/><")"/>
1297             <"*"/><"["/><"]"/>
1298             <"*"/><"{"/><"}"/>
1299            
1300             <"("/><")"/>
1301             <"["/><"]"/>
1302             <"{"/><"}"/>
1303             <"("/><")"/>
1304             <"["/><"]"/>
1305             <"{"/><"}"/>
1306            
1307             END
1308             }
1309            
1310              
1311             =head2 printParseTree($$$)
1312              
1313             Print a parse tree.
1314              
1315             Parameter Description
1316             1 $grammar Grammar
1317             2 $tree Parse tree
1318             3 $indent Optional indent level
1319              
1320             B
1321              
1322              
1323             if (1) {
1324             my $grammar = compileGrammar(<
1325             A A + B
1326             A B
1327             B B * C
1328             B C
1329             C n
1330             C ( A )
1331             C [ A ]
1332             C { A }
1333             C ( )
1334             C [ ]
1335             C { }
1336             END
1337            
1338             ok printGrammar($grammar) eq <
1339             Rule Expandable Expansion
1340             1 0 A A + B
1341             2 1 A B
1342             3 2 B B * n
1343             4 3 B B * ( A )
1344             5 4 B B * [ A ]
1345             6 5 B B * { A }
1346             7 6 B B * ( )
1347             8 7 B B * [ ]
1348             9 8 B B * { }
1349             10 9 B n
1350             11 10 B ( A )
1351             12 11 B [ A ]
1352             13 12 B { A }
1353             14 13 B ( )
1354             15 14 B [ ]
1355             16 15 B { }
1356             END
1357            
1358             my $tree = parseWithGrammar($grammar, qw/( [ { } ] + [ { n } ] ) * [ n + n ] /);
1359            
1360             ok 𝗽𝗿𝗶𝗻𝘁𝗣𝗮𝗿𝘀𝗲𝗧𝗿𝗲𝗲($grammar, $tree) eq <
1361             Rule Expandable Terminal
1362             1 1 A
1363             2 4 B
1364             3 10 B
1365             4 (
1366             5 0 A
1367             6 1 A
1368             7 11 B
1369             8 [
1370             9 1 A
1371             10 15 B
1372             11 {
1373             12 }
1374             13 ]
1375             14 +
1376             15 11 B
1377             16 [
1378             17 1 A
1379             18 12 B
1380             19 {
1381             20 1 A
1382             21 9 B
1383             22 n
1384             23 }
1385             24 ]
1386             25 )
1387             26 *
1388             27 [
1389             28 0 A
1390             29 1 A
1391             30 9 B
1392             31 n
1393             32 +
1394             33 9 B
1395             34 n
1396             35 ]
1397             END
1398            
1399             ok printParseTreeAsXml($grammar, $tree) eq <
1400            
1401            
1402            
1403             <"(" pos="0"/>
1404            
1405            
1406            
1407             <"[" pos="1"/>
1408            
1409            
1410             <"{" pos="2"/>
1411             <"}" pos="3"/>
1412            
1413            
1414             <"]" pos="4"/>
1415            
1416            
1417             <"+" pos="5"/>
1418            
1419             <"[" pos="6"/>
1420            
1421            
1422             <"{" pos="7"/>
1423            
1424            
1425            
1426            
1427            
1428             <"}" pos="9"/>
1429            
1430            
1431             <"]" pos="10"/>
1432            
1433            
1434             <")" pos="11"/>
1435            
1436             <"*" pos="12"/>
1437             <"[" pos="13"/>
1438            
1439            
1440            
1441            
1442            
1443            
1444             <"+" pos="15"/>
1445            
1446            
1447            
1448            
1449             <"]" pos="17"/>
1450            
1451            
1452             END
1453            
1454             ok printGrammarAsXml($grammar) eq <
1455            
1456             <"+"/>
1457            
1458             <"*"/>
1459             <"*"/><"("/><")"/>
1460             <"*"/><"["/><"]"/>
1461             <"*"/><"{"/><"}"/>
1462             <"*"/><"("/><")"/>
1463             <"*"/><"["/><"]"/>
1464             <"*"/><"{"/><"}"/>
1465            
1466             <"("/><")"/>
1467             <"["/><"]"/>
1468             <"{"/><"}"/>
1469             <"("/><")"/>
1470             <"["/><"]"/>
1471             <"{"/><"}"/>
1472            
1473             END
1474             }
1475            
1476              
1477             =head2 printParseTreeAsXml($$$)
1478              
1479             Print a parse tree as XML.
1480              
1481             Parameter Description
1482             1 $grammar Grammar
1483             2 $tree Parse tree
1484             3 $indent Optional indent level
1485              
1486             B
1487              
1488              
1489             if (1) {
1490             my $grammar = compileGrammar(<
1491             A A + B
1492             A B
1493             B B * C
1494             B C
1495             C n
1496             C ( A )
1497             C [ A ]
1498             C { A }
1499             C ( )
1500             C [ ]
1501             C { }
1502             END
1503            
1504             ok printGrammar($grammar) eq <
1505             Rule Expandable Expansion
1506             1 0 A A + B
1507             2 1 A B
1508             3 2 B B * n
1509             4 3 B B * ( A )
1510             5 4 B B * [ A ]
1511             6 5 B B * { A }
1512             7 6 B B * ( )
1513             8 7 B B * [ ]
1514             9 8 B B * { }
1515             10 9 B n
1516             11 10 B ( A )
1517             12 11 B [ A ]
1518             13 12 B { A }
1519             14 13 B ( )
1520             15 14 B [ ]
1521             16 15 B { }
1522             END
1523            
1524             my $tree = parseWithGrammar($grammar, qw/( [ { } ] + [ { n } ] ) * [ n + n ] /);
1525            
1526             ok printParseTree($grammar, $tree) eq <
1527             Rule Expandable Terminal
1528             1 1 A
1529             2 4 B
1530             3 10 B
1531             4 (
1532             5 0 A
1533             6 1 A
1534             7 11 B
1535             8 [
1536             9 1 A
1537             10 15 B
1538             11 {
1539             12 }
1540             13 ]
1541             14 +
1542             15 11 B
1543             16 [
1544             17 1 A
1545             18 12 B
1546             19 {
1547             20 1 A
1548             21 9 B
1549             22 n
1550             23 }
1551             24 ]
1552             25 )
1553             26 *
1554             27 [
1555             28 0 A
1556             29 1 A
1557             30 9 B
1558             31 n
1559             32 +
1560             33 9 B
1561             34 n
1562             35 ]
1563             END
1564            
1565             ok 𝗽𝗿𝗶𝗻𝘁𝗣𝗮𝗿𝘀𝗲𝗧𝗿𝗲𝗲𝗔𝘀𝗫𝗺𝗹($grammar, $tree) eq <
1566            
1567            
1568            
1569             <"(" pos="0"/>
1570            
1571            
1572            
1573             <"[" pos="1"/>
1574            
1575            
1576             <"{" pos="2"/>
1577             <"}" pos="3"/>
1578            
1579            
1580             <"]" pos="4"/>
1581            
1582            
1583             <"+" pos="5"/>
1584            
1585             <"[" pos="6"/>
1586            
1587            
1588             <"{" pos="7"/>
1589            
1590            
1591            
1592            
1593            
1594             <"}" pos="9"/>
1595            
1596            
1597             <"]" pos="10"/>
1598            
1599            
1600             <")" pos="11"/>
1601            
1602             <"*" pos="12"/>
1603             <"[" pos="13"/>
1604            
1605            
1606            
1607            
1608            
1609            
1610             <"+" pos="15"/>
1611            
1612            
1613            
1614            
1615             <"]" pos="17"/>
1616            
1617            
1618             END
1619            
1620             ok printGrammarAsXml($grammar) eq <
1621            
1622             <"+"/>
1623            
1624             <"*"/>
1625             <"*"/><"("/><")"/>
1626             <"*"/><"["/><"]"/>
1627             <"*"/><"{"/><"}"/>
1628             <"*"/><"("/><")"/>
1629             <"*"/><"["/><"]"/>
1630             <"*"/><"{"/><"}"/>
1631            
1632             <"("/><")"/>
1633             <"["/><"]"/>
1634             <"{"/><"}"/>
1635             <"("/><")"/>
1636             <"["/><"]"/>
1637             <"{"/><"}"/>
1638            
1639             END
1640             }
1641            
1642              
1643              
1644             =head2 Parser::LR::Grammar Definition
1645              
1646              
1647             LR parser produced
1648              
1649              
1650              
1651              
1652             =head3 Output fields
1653              
1654              
1655             B - DFA from grammar
1656              
1657             B - Expandable symbols
1658              
1659             B - States we can expand in
1660              
1661             B - Final state at end of parse
1662              
1663             B - Grammar from which the NFA was derived
1664              
1665             B - Longest rule
1666              
1667             B - NFA from grammar
1668              
1669             B - Expandables that can expand to nothing
1670              
1671             B - The expandables an expandable can reduce to
1672              
1673             B - Rules
1674              
1675             B - Start symbol
1676              
1677             B - Terminals that start rules
1678              
1679             B - Terminal symbols
1680              
1681              
1682              
1683             =head2 Parser::LR::Rule Definition
1684              
1685              
1686             A parsing rule
1687              
1688              
1689              
1690              
1691             =head3 Output fields
1692              
1693              
1694             B - Symbol to expand
1695              
1696             B - Symbol expansion
1697              
1698             B - Rule printer
1699              
1700             B - Rule number
1701              
1702              
1703              
1704             =head1 Private Methods
1705              
1706             =head2 printRule($)
1707              
1708             Print a rule
1709              
1710             Parameter Description
1711             1 $rule Rule
1712              
1713             =head2 longestMatchingRule($@)
1714              
1715             Find the longest rule that completely matches the top of the stack.
1716              
1717             Parameter Description
1718             1 $grammar Grammar
1719             2 @stack Stack
1720              
1721             =head2 partialMatch($@)
1722              
1723             Check whether we have a partial match with the top of the stack.
1724              
1725             Parameter Description
1726             1 $grammar Grammar
1727             2 @stack Stack
1728              
1729             =head2 reduceStackWithRule($$$)
1730              
1731             Reduce by the specified rule and update the stack and parse tree to match.
1732              
1733             Parameter Description
1734             1 $rule Rule
1735             2 $stack Stack
1736             3 $tree Parse tree
1737              
1738             =head2 parseWithGrammarAndLog($@)
1739              
1740             Parse, using a compiled B<$grammar>, an array of terminals and return a log of parsing actions taken.
1741              
1742             Parameter Description
1743             1 $grammar Compiled grammar
1744             2 @terminals Terminals to parse
1745              
1746             =head2 printSymbolAsXml($)
1747              
1748             Print a symbol in a form acceptable as Xml
1749              
1750             Parameter Description
1751             1 $symbol Symbol
1752              
1753             =head2 printGrammarAsXml($$)
1754              
1755             Print a B<$grammar> as XML.
1756              
1757             Parameter Description
1758             1 $grammar Grammar
1759             2 $indent Indentation level
1760              
1761             =head2 printParseTreeAndGrammarAsXml($$)
1762              
1763             Print a parse tree produced from a grammar by L as XML.
1764              
1765             Parameter Description
1766             1 $tree Parse tree
1767             2 $grammar Grammar
1768              
1769              
1770             =head1 Index
1771              
1772              
1773             1 L - Compile a grammar from a set of rules expressed as a string with one rule per line.
1774              
1775             2 L - Find the longest rule that completely matches the top of the stack.
1776              
1777             3 L - Parse, using a compiled B<$grammar>, an array of terminals and return a parse tree.
1778              
1779             4 L - Parse, using a compiled B<$grammar>, an array of terminals and return a log of parsing actions taken.
1780              
1781             5 L - Check whether we have a partial match with the top of the stack.
1782              
1783             6 L - Print a B<$grammar>.
1784              
1785             7 L - Print a B<$grammar> as XML.
1786              
1787             8 L - Print a parse tree.
1788              
1789             9 L - Print a parse tree produced from a grammar by L as XML.
1790              
1791             10 L - Print a parse tree as XML.
1792              
1793             11 L - Print a rule
1794              
1795             12 L - Print a symbol in a form acceptable as Xml
1796              
1797             13 L - Reduce by the specified rule and update the stack and parse tree to match.
1798              
1799             =head1 Installation
1800              
1801             This module is written in 100% Pure Perl and, thus, it is easy to read,
1802             comprehend, use, modify and install via B:
1803              
1804             sudo cpan install Parser::LR
1805              
1806             =head1 Author
1807              
1808             L
1809              
1810             L
1811              
1812             =head1 Copyright
1813              
1814             Copyright (c) 2016-2019 Philip R Brenan.
1815              
1816             This module is free software. It may be used, redistributed and/or modified
1817             under the same terms as Perl itself.
1818              
1819             =cut
1820              
1821              
1822              
1823             # Tests and documentation
1824              
1825             sub test
1826 1     1 0 12 {my $p = __PACKAGE__;
1827 1         8 binmode($_, ":utf8") for *STDOUT, *STDERR;
1828 1 50       52 return if eval "eof(${p}::DATA)";
1829 1         41 my $s = eval "join('', <${p}::DATA>)";
1830 1 50       9 $@ and die $@;
1831 1     1   678 eval $s;
  1         66282  
  1         10  
  1         59  
1832 1 50       658 $@ and die $@;
1833 1         147 1
1834             }
1835              
1836             test unless caller;
1837              
1838             1;
1839             #podDocumentation
1840             __DATA__