Giter Site home page Giter Site logo

parser-gen's Introduction

parser-gen

A Lua parser generator that makes it possible to describe grammars in a PEG syntax. The tool will parse a given input using a provided grammar and if the matching is successful produce an AST as an output with the captured values using Lpeg. If the matching fails, labelled errors can be used in the grammar to indicate failure position, and recovery grammars are generated to continue parsing the input using LpegLabel. The tool can also automatically generate error labels and recovery grammars for LL(1) grammars.

parser-gen is a GSoC 2017 project, and was completed with the help of my mentor @sqmedeiros from LabLua. A blog documenting the progress of the project can be found here.


Table of contents

Requirements

lua >= 5.1
lpeglabel >= 1.2.0

Syntax

compile

This function generates a PEG parser from the grammar description.

local pg = require "parser-gen"
grammar = pg.compile(input,definitions [, errorgen, noast])

Arguments:

input - A string containing a PEG grammar description. For complete PEG syntax see the grammar section of this document.

definitions - table of custom functions and definitions used inside the grammar, for example {equals=equals}, where equals is a function.

errorgen - EXPERIMENTAL optional boolean parameter(default:false), when enabled generates error labels automatically. Works well only on LL(1) grammars. Custom error labels have precedence over automatically generated ones.

noast - optional boolean parameter(default:false), when enabled does not generate an AST for the parse.

Output:

grammar - a compiled grammar on success, throws error on failure.

setlabels

If custom error labels are used, the function setlabels allows setting their description (and custom recovery pattern):

pg.setlabels(t)

Example table of a simple error and one with a custom recovery expression:

-- grammar rule: " ifexp <- 'if' exp 'then'^missingThen stmt 'end'^missingEnd "
local t = {
	missingEnd = "Missing 'end' in if expression",
	missingThen = {"Missing 'then' in if expression", " (!stmt .)* "} -- a custom recovery pattern
}
pg.setlabels(t)

If the recovery pattern is not set, then the one specified by the rule SYNC will be used. It is by default set to:

SKIP <- %s / %nl -- a space ' ' or newline '\n' character
SYNC <- .? (!SKIP .)*

Learn more about special rules in the grammar section.

parse

This operation attempts to match a grammar to the given input.

result, errors = pg.parse(input, grammar [, errorfunction])

Arguments:

input - an input string that the tool will attempt to parse.

grammar - a compiled grammar.

errorfunction - an optional function that will be called if an error is encountered, with the arguments desc for the error description set using setlabels(); location indicators line and col; the remaining string before failure sfail and a custom recovery expression trec if available. Example:

local errs = 0
local function printerror(desc,line,col,sfail,trec)
	errs = errs+1
	print("Error #"..errs..": "..desc.." before '"..sfail.."' on line "..line.."(col "..col..")")
end

result, errors = pg.parse(input,grammar,printerror)

Output:

If the parse is succesful, the function returns an abstract syntax tree containing the captures result and a table of any encountered errors. If the parse was unsuccessful, result is going to be nil. Also, if the noast option is enabled when compiling the grammar, the function will then produce the longest match length or any custom captures used.

calcline

Calculates line and column information regarding position i of the subject (exported from the relabel module).

line, col = pg.calcline(subject, position)

Arguments:

subject - subject string

position - position inside the string, for example, the one given by automatic AST generation.

usenodes

When AST generation is enabled, this function will enable the "node" mode, where only rules tagged with a node prefix will generate AST entries. Must be used before compiling the grammar.

pg.usenodes(value)

Arguments:

value - a boolean value that enables or disables this function

Grammar Syntax

The grammar used for this tool is described using a PEG-like syntax, that is identical to the one provided by the re module, with an extension of labelled failures provided by relabel module (except numbered labels). That is, all grammars that work with relabel should work with parser-gen as long as numbered error labels are not used, as they are not supported by parser-gen.

Since a parser generated with parser-gen automatically consumes space characters, builds ASTs and generates errors, additional extensions have been added based on the ANTLR syntax.

Basic syntax

The syntax of parser-gen grammars is somewhat similar to regex syntax. The next table summarizes the tools syntax. A p represents an arbitrary pattern; num represents a number ([0-9]+); name represents an identifier ([a-zA-Z][a-zA-Z0-9_]*).defs is the definitions table provided when compiling the grammar. Note that error names must be set using setlabels() before compiling the grammar. Constructions are listed in order of decreasing precedence.

SyntaxDescription
( p ) grouping
'string' literal string
"string" literal string
[class] character class
. any character
%name pattern defs[name] or a pre-defined pattern
namenon terminal
<name>non terminal
%{name} error label
{} position capture
{ p } simple capture
{: p :} anonymous group capture
{:name: p :} named group capture
{~ p ~} substitution capture
{| p |} table capture
=name back reference
p ? optional match
p * zero or more repetitions
p + one or more repetitions
p^num exactly n repetitions
p^+num at least n repetitions
p^-num at most n repetitions
p^name match p or throw error label name.
p -> 'string' string capture
p -> "string" string capture
p -> num numbered capture
p -> name function/query/string capture equivalent to p / defs[name]
p => name match-time capture equivalent to lpeg.Cmt(p, defs[name])
& p and predicate
! p not predicate
p1 p2 concatenation
p1 //{name [, name, ...]} p2 specifies recovery pattern p2 for p1 when one of the labels is thrown
p1 / p2 ordered choice
(name <- p)+ grammar

The grammar below is used to match balanced parenthesis

balanced <- "(" ([^()] / balanced)* ")" 

For more examples check out the re page, see the Tiny parser below or the Lua parser writen with this tool.

Error labels

Error labels are provided by the relabel function %{errorname} (errorname must follow [A-Za-z][A-Za-z0-9_]* format). Usually we use error labels in a syntax like 'a' ('b' / %{errB}) 'c', which throws an error label if 'b' is not matched. This syntax is quite complicated so an additional syntax is allowed 'a' 'b'^errB 'c', which allows cleaner description of grammars. Note: all errors must be defined in a table using parser-gen.setlabels() before compiling and parsing the grammar.

Tokens

Non-terminals with names in all capital letters, i.e. [A-Z]+, are considered tokens and are treated as a single object in parsing. That is, the whole string matched by a token is captured in a single AST entry and space characters are not consumed. Consider two examples:

-- a token non-terminal
grammar = pg.compile [[
	WORD <- [A-Z]+
]]
res, _ = pg.parse("AA A", grammar) -- outputs {rule="WORD", "AA"}
-- a non-token non-terminal
grammar = pg.compile [[
	word <- [A-Z]+
]]
res, _ = pg.parse("AA A", grammar) -- outputs {rule="word", "A", "A", "A"}

Fragments

If a token definition is followed by a fragment keyword, then the parser does not build an AST entry for that token. Essentially, these rules are used to simplify grammars without building unnecessarily complicated ASTS. Example of fragment usage:

grammar = pg.compile [[
	WORD <- LETTER+
	fragment LETTER <- [A-Z]
]]
res, _ = pg.parse("AA A", grammar) -- outputs {rule="WORD", "AA"}

Without using fragment:

grammar = pg.compile [[
	WORD <- LETTER+
	LETTER <- [A-Z]
]]
res, _ = pg.parse("AA A", grammar) -- outputs {rule="WORD", {rule="LETTER", "A"}, {rule="LETTER", "A"}}

Nodes

When node mode is enabled using pg.usenodes(true) only rules prefixed with a node keyword will generate AST entries:

grammar = pg.compile [[
	node WORD <- LETTER+
	LETTER <- [A-Z]
]]
res, _ = pg.parse("AA A", grammar) -- outputs {rule="WORD", "AA"}

Special rules

There are two special rules used by the grammar:

SKIP

The SKIP rule identifies which characters to skip in a grammar. For example, most programming languages do not take into acount any space or newline characters. By default, SKIP is set to:

SKIP <- %s / %nl

This rule can be extended to contain semicolons ';', comments, or any other patterns that the parser can safely ignore.

Character skipping can be disabled by using:

SKIP <- ''

SYNC

This rule specifies the general recovery expression both for custom errors and automatically generated ones. By default:

SYNC <- .? (!SKIP .)*

The default SYNC rule consumes any characters until the next character matched by SKIP, usually a space or a newline. That means, if some statement in a program is invalid, the parser will continue parsing after a space or a newline character.

For some programming languages it might be useful to skip to a semicolon or a keyword, since they usually indicate the end of a statement, so SYNC could be something like:

HELPER <- ';' / 'end' / SKIP -- etc
SYNC <- (!HELPER .)* SKIP* -- we can consume the spaces after syncing with them as well

Recovery grammars can be disabled by using:

SYNC <- ''

Example: Tiny parser

Below is the full code from parsers/tiny-parser.lua:

local pg = require "parser-gen"
local peg = require "peg-parser"
local errs = {errMissingThen = "Missing Then"} -- one custom error
pg.setlabels(errs)

--warning: experimental error generation function is enabled. If the grammar isn't LL(1), set errorgen to false
local errorgen = true

local grammar = pg.compile([[

	program			<- stmtsequence !. 
	stmtsequence		<- statement (';' statement)* 
	statement 		<- ifstmt / repeatstmt / assignstmt / readstmt / writestmt
	ifstmt 			<- 'if' exp 'then'^errMissingThen stmtsequence elsestmt? 'end' 
	elsestmt		<- ('else' stmtsequence)
	repeatstmt		<- 'repeat' stmtsequence 'until' exp 
	assignstmt		<- IDENTIFIER ':=' exp 
	readstmt		<- 'read'  IDENTIFIER 
	writestmt		<- 'write' exp 
	exp 			<- simpleexp (COMPARISONOP simpleexp)*
	COMPARISONOP		<- '<' / '='
	simpleexp		<- term (ADDOP term)* 
	ADDOP			<- [+-]
	term			<- factor (MULOP factor)*
	MULOP			<- [*/]
	factor			<- '(' exp ')' / NUMBER / IDENTIFIER

	NUMBER			<- '-'? [0-9]+
	KEYWORDS		<- 'if' / 'repeat' / 'read' / 'write' / 'then' / 'else' / 'end' / 'until' 
	RESERVED		<- KEYWORDS ![a-zA-Z]
	IDENTIFIER		<- !RESERVED [a-zA-Z]+
	HELPER			<- ';' / %nl / %s / KEYWORDS / !.
	SYNC			<- (!HELPER .)*

]], _, errorgen)

local errors = 0
local function printerror(desc,line,col,sfail,trec)
	errors = errors+1
	print("Error #"..errors..": "..desc.." on line "..line.."(col "..col..")")
end


local function parse(input)
	errors = 0
	result, errors = pg.parse(input,grammar,printerror)
	return result, errors
end

if arg[1] then	
	-- argument must be in quotes if it contains spaces
	res, errs = parse(arg[1])
	peg.print_t(res)
	peg.print_r(errs)
end
local ret = {parse=parse}
return ret

For input: lua tiny-parser-nocap.lua "if a b:=1" we get:

Error #1: Missing Then on line 1(col 6)
Error #2: Expected stmtsequence on line 1(col 9)
Error #3: Expected 'end' on line 1(col 9)
-- ast:
rule='program',
pos=1,
{
         rule='stmtsequence',
         pos=1,
         {
                  rule='statement',
                  pos=1,
                  {
                           rule='ifstmt',
                           pos=1,
                           'if',
                           {
                                    rule='exp',
                                    pos=4,
                                    {
                                             rule='simpleexp',
                                             pos=4,
                                             {
                                                      rule='term',
                                                      pos=4,
                                                      {
                                                               rule='factor',
                                                               pos=4,
                                                               {
                                                                        rule='IDENTIFIER',
                                                                        pos=4,
                                                                        'a',
                                                               },
                                                      },
                                             },
                                    },
                           },
                  },
         },
},
-- error table:
[1] => {
         [msg] => 'Missing Then' -- custom error is used over the automatically generated one
         [line] => '1'
         [col] => '6'
         [label] => 'errMissingThen'
       }
[2] => {
         [msg] => 'Expected stmtsequence' -- automatically generated errors
         [line] => '1'
         [col] => '9'
         [label] => 'errorgen6'
       }
[3] => {
         [msg] => 'Expected 'end''
         [line] => '1'
         [col] => '9'
         [label] => 'errorgen4'
       }

parser-gen's People

Contributors

andremm avatar hishamhm avatar vsbenas avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar

parser-gen's Issues

The AST generated by lua-parser seems to have some issue with operators associativity and priority

I was testing lua-parser.lua example and found the following issue with the generated AST: while evaluating the expression 2^3+1 I got 16 as the result when in fact it should be 9.

I used the following dummy code to reproduce this behavior:

local m = require 'lua-parser'

local t = m.parse("return 2^3+1")

local function eval (exp)
  if exp.rule == "exp" then
    if exp[1] then
      local exp1 = eval(exp[1])
      if exp[2] then
         local exp2 = eval(exp[2][2])
         if exp[2][1][1] == '+' then
           return exp1 + exp2
         elseif exp[2][1][1] == '*' then
           return exp1 * exp2
         elseif exp[2][1][1] == '^' then
           return exp1 ^ exp2
         end
      else
        return exp1
      end
    end
  elseif exp.rule == "expTokens" then
    return eval(exp[1])
  elseif exp.rule == "number" then
    return eval(exp[1])
  elseif exp.rule == "INT" then
    return tonumber(exp[1])
  end
end

-- throws away the return statement and only evaluates its expression
print(eval(t[1][1][2][1]))

Am I missing something in the AST or is it a bug?

Generate error labels automatically

Currently the tool can only identify error label locations correctly for LL(1) grammars, probably not all of them as well.
We would like to implement an approach that would identify LL(1) parts of all grammars and generate error labels only where appropriate. For example, in a grammar like

[[
rule <- 'a' 'b' / 'a' 'c' 'e'
]]

we should be able to identify 'c' 'e' and add an error label on e like 'e'^error1. This can be formalized by p1 p2 => p1 p2^error IFF FOLLOW(p1) โŠ† FIRST(p2)
Now the approach that errogen.lua takes is quite primitive and builds a semi-follow set that has key (rulename, value) where value can be both non-terminals(nt_name) or terminals (t_name) but this approach will not extend well as it does not take into account that two non-terminals can have the same FIRST set.

My mentor suggested this approach:

You should also calculate the FIRST and FOLLOW for every
choice p1 / p2 to make sure the grammar is LL(1). I think you will
need to give a name for each choice that is not associated with
a grammar nonterminal. For example:
A -> B (C / D) / E
You should give a name for (C / D).
This is somewhat similar to rewriting the grammar for an EBNF form,
but without doing this explicitly. See whether this strategy fits or
if it is better to rewrite the grammar as you suggested.

To decide if a grammar is LL(1) you should check that for each
choice p1 / p2 the following applies:

  1. FIRST(p1) intersection FIRST(p2) is empty
    In case p2 matches the empty string, assuming that A -> p1 / p2,
    you must also check that:
  2. FIRST(p1) intersection FOLLOW(A) is empty

The tricky part, of course, is finding FIRST/FOLLOW sets of a PEG grammar without transforming it. Would anyone like to attempt this challenge? Transforming it to EBNF or any other form is also an acceptable option.

AST structure produced by peg-parser.lua is in the following format:

--[[
Example input: 	"

	Program <- stmt* / SPACE
	stmt <- ('a' / 'b')+
	SPACE <- ''
		
"

Example output: {
	{rulename = "Program",	rule = {action = "or", op1 = {action = "*", op1 = {nt = "stmt"}}, op2 = {nt = "SPACE", token="1"}}},
	{rulename = "stmt", 	rule = {action = "+", op1 = {action="or", op1 = {t = "a"}, op2 = {t = "b"}}}},
	{rulename = "SPACE",	rule = {t=""}, token=1},
}
]]

Generated parser with simple rule

Hello,

I'm using parser-gen and I found an odd behaviour. I was able to reduce the problem to this simple grammar:

top <- foo 'bar' !.
foo <- 'foo' 'foo' / 'foo'

The generated parser is not able to parse the string "foo bar", it expects another foo, even though it isn't necessary.
I'm able to work around this issue by inlining the rule:

top <- ('foo' 'foo' / 'foo') 'bar' !.

The full code snipet to reproduce the issue:

local pg = require 'parser-gen'
local peg = require 'peg-parser'

local grammar = pg.compile([[

    top     <- foo 'bar' !.

    foo     <- (('foo' 'foo') / 'foo')

]], _, true)

local function printerror(desc, line, col, sfail, trec)
    print('Error: ' .. desc .. ' on line ' .. line ..
          ' (col ' .. col .. ')')
end

local input = [[
foo bar
]]

local result = pg.parse(input, grammar, printerror)
peg.print_t(result)

Regards,
Gabriel

How can we get position info inside the AST?

We are using parser-gen to write the parser of the Titan language, but we do not know how we can insert position info inside the nodes of the generated AST.

For instance, when I run your example tiny-parser.lua with the following code

if a then
  b := 1
end

I get the following AST without position info

rule='program',
{
         rule='stmtsequence',
         {
                  rule='statement',
                  {
                           rule='ifstmt',
                           'if',
                           {
                                    rule='exp',
                                    {
                                             rule='simpleexp',
                                             {
                                                      rule='term',
                                                      {
                                                               rule='factor',
                                                               {
                                                                        rule='IDENTIFIER',
                                                                        'a',
                                                               },
                                                      },
                                             },
                                    },
                           },
                           'then',
                           {
                                    rule='stmtsequence',
                                    {
                                             rule='statement',
                                             {
                                                      rule='assignstmt',
                                                      {
                                                               rule='IDENTIFIER',
                                                               'b',
                                                      },
                                                      ':=',
                                                      {
                                                               rule='exp',
                                                               {
                                                                        rule='simpleexp',
                                                                        {
                                                                                 rule='term',
                                                                                 {
                                                                                          rule='factor',
                                                                                          {
                                                                                                   rule='NUMBER',
                                                                                                   '1',
                                                                                          },
                                                                                 },
                                                                        },
                                                               },
                                                      },
                                             },
                                    },
                           },
                           'end',
                  },
         },
},

How can we use parser-gen to decorate the AST with position info? I mean, how can we generate the following AST?

rule='program',
{
         pos = 1,
         rule='stmtsequence',
         {
                  pos = 1,
                  rule='statement',
                  {
                           pos = 1,
                           rule='ifstmt',
                           'if',
                           {
                                    pos = 1,
                                    rule='exp',
                                    {
                                             pos = 4,
                                             rule='simpleexp',
                                             {
                                                      pos = 4,
                                                      rule='term',
                                                      {
                                                               pos = 4,
                                                               rule='factor',
                                                               {
                                                                        pos = 4,
                                                                        rule='IDENTIFIER',
                                                                        'a',
                                                               },
                                                      },
                                             },
                                    },
                           },
                           'then',
                           {
                                    pos = 12, 
                                    rule='stmtsequence',
                                    {
                                             pos = 12,
                                             rule='statement',
                                             {
                                                      pos = 12,
                                                      rule='assignstmt',
                                                      {
                                                               pos = 12,
                                                               rule='IDENTIFIER',
                                                               'b',
                                                      },
                                                      ':=',
                                                      {
                                                               pos = 17,
                                                               rule='exp',
                                                               {
                                                                        pos = 17,
                                                                        rule='simpleexp',
                                                                        {
                                                                                 pos = 17,
                                                                                 rule='term',
                                                                                 {
                                                                                          pos = 17,
                                                                                          rule='factor',
                                                                                          {
                                                                                                   pos = 17,
                                                                                                   rule='NUMBER',
                                                                                                   '1',
                                                                                          },
                                                                                 },
                                                                        },
                                                               },
                                                      },
                                             },
                                    },
                           },
                           'end',
                  },
         },
},

Or even better, can we generate an AST that has line and column info like the one below?

rule='program',
{
         line = 1,
         col = 1,
         rule='stmtsequence',
         {
                  line = 1,
                  col = 1,
                  rule='statement',
                  {
                           line = 1,
                           col = 1,
                           rule='ifstmt',
                           'if',
                           {
                                    line = 1,
                                    col = 1,
                                    rule='exp',
                                    {
                                             line = 1,
                                             col = 4,
                                             rule='simpleexp',
                                             {
                                                      line = 1,
                                                      col = 4,
                                                      rule='term',
                                                      {
                                                               line = 1,
                                                               col = 4,
                                                               rule='factor',
                                                               {
                                                                        line = 1,
                                                                        col = 4
                                                                        rule='IDENTIFIER',
                                                                        'a',
                                                               },
                                                      },
                                             },
                                    },
                           },
                           'then',
                           {
                                    line = 2,
                                    col = 3 
                                    rule='stmtsequence',
                                    {
                                             line = 2,
                                             col = 3,
                                             rule='statement',
                                             {
                                                      line = 2,
                                                      col = 3,
                                                      rule='assignstmt',
                                                      {
                                                               line = 2,
                                                               col = 3,
                                                               rule='IDENTIFIER',
                                                               'b',
                                                      },
                                                      ':=',
                                                      {
                                                               line = 2,
                                                               col = 8,
                                                               rule='exp',
                                                               {
                                                                        line = 2,
                                                                        col = 8,
                                                                        rule='simpleexp',
                                                                        {
                                                                                 line = 2,
                                                                                 col = 8,
                                                                                 rule='term',
                                                                                 {
                                                                                          line = 2,
                                                                                          col = 8,
                                                                                          rule='factor',
                                                                                          {
                                                                                                   line = 2,
                                                                                                   col = 8,
                                                                                                   rule='NUMBER',
                                                                                                   '1',
                                                                                          },
                                                                                 },
                                                                        },
                                                               },
                                                      },
                                             },
                                    },
                           },
                           'end',
                  },
         },
},

Feature request: a mode for explicit node creation in ASTs

Currently, parser-gen generates an AST where it produces a node for each rule, unless told so via fragment. This produces a lot of intermediate nodes in ASTs (e.g. statement, simpleexp, term, factor in the Tiny example of README.md).

It would be nice to, instead of marking which rules don't generate nodes, to be able to mark which rules should generate nodes (perhaps with a node annotation or some other syntax?).

parser-gen is creating a bunch of global variables

Currently, requiring parser-gen is polluting the global scope with many global functions. These should all be made local and exported in the return statement if needed. The ones I managed to find were:

  • In equals.lua: equals
  • In errorgen.lua: getn
  • In parser-gen.lua: traverse, record, recorderror
  • In peg-parser.lua: concat, foldtable
  • In stack.lua: Stack

Skipping spaces after the matching of a recovery expressions

Hi, @vsbenas .

Currently, after a recovery expression matches parser-gen does not automatically consumes the spaces after it, as it does for regular patterns described in the grammar. This causes some unexpected errors. For example, in the following code:

`package.path = package.path .. ";../?.lua"
local pg = require "parser-gen"
local peg = require "peg-parser"
local errs = {
rcblk = { "missing end of block", "(!'}' .)* '}'" },
condw = {"missing condition in while", "'b'"},
body = {"missing body statement in while", "'d'"},
}
pg.setlabels(errs)

local grammar = pg.compile([[

prog <- blockstmt !.
blockstmt <- '{' stmt* '}'^rcblk
stmt <- whilestmt / blockstmt
whilestmt <- 'while' exp^condw stmt^body
exp <- [0-9]+
HELPER <- ';' / %nl / %s / !.
SYNC <- (!HELPER .)*
SKIP <- %s / %nl
]], _, false, false)
grammar:pcode()
local errors = 0
local function printerror(desc,line,col,sfail,trec)
errors = errors+1
print("Error #"..errors..": "..desc.." on line "..line.."(col "..col..")")
end

local function parse(input)
errors = 0
result, errors = pg.parse(input,grammar,printerror)
return result, errors
end

if arg[1] then
-- argument must be in quotes if it contains spaces
local input = io.open(arg[1]):read("*a")
res, errs = parse(input)
peg.print_t(res)
peg.print_r(errs)
end
local ret = {parse=parse}
return ret
`

When given following input:
`{
while 1 {
};

}`

I was expecting an error message related to label rcblk, but I got:
_Error #1: Syntax error on line 5(col 1)
nil
[1] => {
[msg] => 'Syntax error'
[line] => '5'
[col] => '1'
}
_

I fixed this issue by changing the initial rule to:
_prog <- blockstmt %s !. _

Then I got the expected error and a corresponding AST:
_Error #1: missing end of block on line 3(col 3)
rule='prog',
{
rule='blockstmt',
'{',
{
rule='stmt',
{
rule='whilestmt',
'while',
{
rule='exp',
'1',
},
{
rule='stmt',
{
rule='blockstmt',
'{',
'}',
},
},
},
},
},
[1] => {
[msg] => 'missing end of block'
[line] => '3'
[label] => 'rcblk'
[col] => '3'
}
_

I think a function such as pattspaces should be applied to
recovery expressions, in order to avoid the problem of handling
spaces after the matching of a recovery expression.

Tag v1.1 still on commit with <<< >>> merge artifacts

Hey, thanks for this module!

The commit that v1.1 is on (which is pointed to by the 1.1-0.rockspec) still contains the git merge artifacts that have now been removed.

Either the tag should be moved to exclude the artifacts or new tags and a new rockspec version.

I'm happy to do this if you don't have time

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.