Fuller sample custom reader.
This commit is contained in:
parent
4a3b3b1ac6
commit
822f894984
1 changed files with 63 additions and 20 deletions
|
@ -1,42 +1,85 @@
|
||||||
-- A sample custom reader for a very simple markup language.
|
-- A sample custom reader for a very simple markup language.
|
||||||
-- This parses a document into paragraphs separated by blank lines.
|
-- This parses a document into paragraphs separated by blank lines.
|
||||||
-- This is _{italic} and this is *{boldface}
|
-- This is /italic/ and this is *boldface* and this is `code`
|
||||||
-- This is an escaped special character: \_, \*, \{, \}
|
-- and `code``with backtick` (doubled `` = ` inside backticks).
|
||||||
|
-- This is an escaped special character: \_, \*, \\
|
||||||
-- == text makes a level-2 heading
|
-- == text makes a level-2 heading
|
||||||
-- That's it!
|
-- That's it!
|
||||||
|
|
||||||
-- For better performance we put these functions in local variables:
|
-- For better performance we put these functions in local variables:
|
||||||
local P, S, R, Cf, Cc, Ct, V, Cs, Cg, Cb, B =
|
local P, S, R, Cf, Cc, Ct, V, Cs, Cg, Cb, B, C, Cmt =
|
||||||
lpeg.P, lpeg.S, lpeg.R, lpeg.Cf, lpeg.Cc, lpeg.Ct, lpeg.V,
|
lpeg.P, lpeg.S, lpeg.R, lpeg.Cf, lpeg.Cc, lpeg.Ct, lpeg.V,
|
||||||
lpeg.Cs, lpeg.Cg, lpeg.Cb, lpeg.B
|
lpeg.Cs, lpeg.Cg, lpeg.Cb, lpeg.B, lpeg.C, lpeg.Cmt
|
||||||
|
|
||||||
|
--- if item is a table, concatenate it to acc;
|
||||||
|
-- otherwise insert it at the end.
|
||||||
|
local function add_item(acc, item)
|
||||||
|
if acc == nil then
|
||||||
|
acc = {}
|
||||||
|
end
|
||||||
|
if type(item) == "table" then
|
||||||
|
for i = 1,#item do
|
||||||
|
add_item(acc, item[i])
|
||||||
|
end
|
||||||
|
else
|
||||||
|
acc[#acc + 1] = item
|
||||||
|
end
|
||||||
|
return acc
|
||||||
|
end
|
||||||
|
|
||||||
|
local function Many1(parser)
|
||||||
|
return Cf(Cc(nil) * parser^1 , add_item)
|
||||||
|
end
|
||||||
|
|
||||||
|
local function Many(parser)
|
||||||
|
return (Many1(parser) + Cc{})
|
||||||
|
end
|
||||||
|
|
||||||
local whitespacechar = S(" \t\r\n")
|
local whitespacechar = S(" \t\r\n")
|
||||||
local specialchar = S("_*{}\\")
|
local specialchar = S("/*\\`")
|
||||||
local escapedchar = P"\\" * specialchar
|
local wordchar = (1 - (whitespacechar + specialchar))
|
||||||
/ function (x) return string.sub(x,2) end
|
|
||||||
local wordchar = (P(1) - (whitespacechar + specialchar)) + escapedchar
|
|
||||||
local spacechar = S(" \t")
|
local spacechar = S(" \t")
|
||||||
local newline = P"\r"^-1 * P"\n"
|
local newline = P"\r"^-1 * P"\n"
|
||||||
local blanklines = newline * spacechar^0 * newline^1
|
local blanklines = newline * (spacechar^0 * newline)^1
|
||||||
local endline = newline - blanklines
|
local endline = newline - blanklines
|
||||||
|
|
||||||
|
local function BetweenDelims(c, parser, constructor)
|
||||||
|
local starter = P(c) * #(- whitespacechar)
|
||||||
|
local ender = B(1 - whitespacechar) * P(c)
|
||||||
|
return starter * Many(parser - ender) * C(ender^-1) /
|
||||||
|
function(contents, ender)
|
||||||
|
if ender == "" then -- fallback
|
||||||
|
return { pandoc.Str(c) , contents }
|
||||||
|
else
|
||||||
|
return constructor(contents)
|
||||||
|
end
|
||||||
|
end
|
||||||
|
end
|
||||||
|
|
||||||
|
|
||||||
-- Grammar
|
-- Grammar
|
||||||
G = P{ "Pandoc",
|
G = P{ "Pandoc",
|
||||||
Pandoc = blanklines^-1 * Ct(V"Block"^0) / pandoc.Pandoc;
|
Pandoc = Many(V"Block") / pandoc.Pandoc;
|
||||||
Block = V"Header" + V"Para";
|
Block = blanklines^0 * (V"Header" + V"Para") ;
|
||||||
Para = Ct(V"Inline"^1) * blanklines^-1 / pandoc.Para;
|
Para = Many1(V"Inline") * blanklines^-1 / pandoc.Para;
|
||||||
Header = Ct(Cg(P("=")^1 / function(x) return #x end, "length")
|
Header = (P("=")^1 / string.len)
|
||||||
* spacechar^1
|
* spacechar^1
|
||||||
* Cg(Ct(V"Inline"^0), "contents")
|
* Many(V"Inline" - (spacechar^0 * P("=")^0 * blanklines))
|
||||||
* blanklines^-1) /
|
* spacechar^0
|
||||||
function(res) return pandoc.Header(res.length, res.contents) end;
|
* P("=")^0
|
||||||
Inline = V"Emph" + V"Str" + V"Space" + V"SoftBreak" + V"Special" ;
|
* blanklines^-1 /
|
||||||
|
function(lev, contents) return pandoc.Header(lev, contents) end;
|
||||||
|
Inline = V"Emph" + V"Strong" + V"Str" + V"Space" + V"SoftBreak" +
|
||||||
|
V"Code" + V"Escaped" + V"Special";
|
||||||
Str = wordchar^1 / pandoc.Str;
|
Str = wordchar^1 / pandoc.Str;
|
||||||
|
Escaped = "\\" * C(specialchar) / function(s) return pandoc.Str(s) end;
|
||||||
Space = spacechar^1 / pandoc.Space;
|
Space = spacechar^1 / pandoc.Space;
|
||||||
SoftBreak = endline / pandoc.SoftBreak;
|
SoftBreak = endline / pandoc.SoftBreak;
|
||||||
Emph = Ct(P"_{" * Cg(Ct((V"Inline" - P"}")^1), "contents") * P"}") /
|
Emph = BetweenDelims("/", V"Inline", pandoc.Emph);
|
||||||
function(res) return pandoc.Emph(res.contents) end;
|
Strong = BetweenDelims("*", V"Inline", pandoc.Strong);
|
||||||
Special = specialchar / pandoc.Str;
|
Code = P"`" * Ct(( (P"``" / "`") + (C(1) - S"`"))^1) * P"`"
|
||||||
|
/ table.concat / pandoc.Code;
|
||||||
|
Special = S"`\\" / pandoc.Str;
|
||||||
}
|
}
|
||||||
|
|
||||||
function Reader(input)
|
function Reader(input)
|
||||||
|
|
Loading…
Reference in a new issue