aboutsummaryrefslogtreecommitdiff
path: root/data
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-11-06 16:37:57 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-11-06 16:38:12 -0700
commit822f8949841f851a56bbd964433aa60205609d20 (patch)
treef9bb82d9dd9473292eaf0a06e32aaa50952ecb5f /data
parent4a3b3b1ac6b8dc0770fd1bbebb297c160d6ee57b (diff)
downloadpandoc-822f8949841f851a56bbd964433aa60205609d20.tar.gz
Fuller sample custom reader.
Diffstat (limited to 'data')
-rw-r--r--data/reader.lua83
1 files changed, 63 insertions, 20 deletions
diff --git a/data/reader.lua b/data/reader.lua
index 4aca4edd3..5cc2dfc0c 100644
--- a/data/reader.lua
+++ b/data/reader.lua
@@ -1,42 +1,85 @@
-- A sample custom reader for a very simple markup language.
-- This parses a document into paragraphs separated by blank lines.
--- This is _{italic} and this is *{boldface}
--- This is an escaped special character: \_, \*, \{, \}
+-- This is /italic/ and this is *boldface* and this is `code`
+-- and `code``with backtick` (doubled `` = ` inside backticks).
+-- This is an escaped special character: \_, \*, \\
-- == text makes a level-2 heading
-- That's it!
-- 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.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 specialchar = S("_*{}\\")
-local escapedchar = P"\\" * specialchar
- / function (x) return string.sub(x,2) end
-local wordchar = (P(1) - (whitespacechar + specialchar)) + escapedchar
+local specialchar = S("/*\\`")
+local wordchar = (1 - (whitespacechar + specialchar))
local spacechar = S(" \t")
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 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
G = P{ "Pandoc",
- Pandoc = blanklines^-1 * Ct(V"Block"^0) / pandoc.Pandoc;
- Block = V"Header" + V"Para";
- Para = Ct(V"Inline"^1) * blanklines^-1 / pandoc.Para;
- Header = Ct(Cg(P("=")^1 / function(x) return #x end, "length")
+ Pandoc = Many(V"Block") / pandoc.Pandoc;
+ Block = blanklines^0 * (V"Header" + V"Para") ;
+ Para = Many1(V"Inline") * blanklines^-1 / pandoc.Para;
+ Header = (P("=")^1 / string.len)
* spacechar^1
- * Cg(Ct(V"Inline"^0), "contents")
- * blanklines^-1) /
- function(res) return pandoc.Header(res.length, res.contents) end;
- Inline = V"Emph" + V"Str" + V"Space" + V"SoftBreak" + V"Special" ;
+ * Many(V"Inline" - (spacechar^0 * P("=")^0 * blanklines))
+ * spacechar^0
+ * P("=")^0
+ * 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;
+ Escaped = "\\" * C(specialchar) / function(s) return pandoc.Str(s) end;
Space = spacechar^1 / pandoc.Space;
SoftBreak = endline / pandoc.SoftBreak;
- Emph = Ct(P"_{" * Cg(Ct((V"Inline" - P"}")^1), "contents") * P"}") /
- function(res) return pandoc.Emph(res.contents) end;
- Special = specialchar / pandoc.Str;
+ Emph = BetweenDelims("/", V"Inline", pandoc.Emph);
+ Strong = BetweenDelims("*", V"Inline", pandoc.Strong);
+ Code = P"`" * Ct(( (P"``" / "`") + (C(1) - S"`"))^1) * P"`"
+ / table.concat / pandoc.Code;
+ Special = S"`\\" / pandoc.Str;
}
function Reader(input)