data/pandoc.lua: auto-fix nested constructor arguments

Incorrect types to pandoc element constructors are automatically
converted to the correct types when possible. This was already done for
most constructors, but conversions are now also done for nested
types (like lists of lists).
This commit is contained in:
Albert Krewinkel 2019-01-13 16:51:15 +01:00
parent 9ac5b9d710
commit 42a7b80c04
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
3 changed files with 43 additions and 10 deletions

View file

@ -254,6 +254,14 @@ local function ensureInlineList (x)
end
end
--- Ensure that the given object is a definition pair, convert if necessary.
-- @local
local function ensureDefinitionPairs (pair)
local inlines = ensureInlineList(pair[1] or {})
local blocks = ensureList(pair[2] or {}):map(ensureList)
return {inlines, blocks}
end
------------------------------------------------------------------------
--- Pandoc Document
-- @section document
@ -369,7 +377,7 @@ M.BlockQuote = M.Block:create_constructor(
-- @treturn Block bullet list element
M.BulletList = M.Block:create_constructor(
"BulletList",
function(content) return {c = ensureList(content)} end,
function(content) return {c = ensureList(content):map(ensureList)} end,
"content"
)
@ -386,11 +394,13 @@ M.CodeBlock = M.Block:create_constructor(
--- Creates a definition list, containing terms and their explanation.
-- @function DefinitionList
-- @tparam {{{Inline,...},{Block,...}},...} content list of items
-- @tparam {{{Inline,...},{{Block,...}}},...} content list of items
-- @treturn Block definition list element
M.DefinitionList = M.Block:create_constructor(
"DefinitionList",
function(content) return {c = ensureList(content)} end,
function(content)
return {c = ensureList(content):map(ensureDefinitionPairs)}
end,
"content"
)
@ -435,7 +445,7 @@ M.HorizontalRule = M.Block:create_constructor(
-- @treturn Block line block element
M.LineBlock = M.Block:create_constructor(
"LineBlock",
function(content) return {c = ensureList(content)} end,
function(content) return {c = ensureList(content):map(ensureInlineList)} end,
"content"
)
@ -456,7 +466,7 @@ M.OrderedList = M.Block:create_constructor(
"OrderedList",
function(items, listAttributes)
listAttributes = listAttributes or M.ListAttributes()
return {c = {listAttributes, ensureList(items)}}
return {c = {listAttributes, ensureList(items):map(ensureList)}}
end,
{{listAttributes = {"start", "style", "delimiter"}}, "content"}
)
@ -647,7 +657,9 @@ M.Note = M.Inline:create_constructor(
-- @treturn Inline quoted element
M.Quoted = M.Inline:create_constructor(
"Quoted",
function(quotetype, content) return {c = {quotetype, ensureInlineList(content)}} end,
function(quotetype, content)
return {c = {quotetype, ensureInlineList(content)}}
end,
{"quotetype", "content"}
)
--- Creates a single-quoted inline element (DEPRECATED).

View file

@ -10,10 +10,10 @@ import Test.Tasty (TestTree, localOption)
import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty)
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
header, linebreak, para, plain, rawBlock,
singleQuoted, space, str, strong,
math, displayMath)
import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith,
doc, doubleQuoted, emph, header, lineBlock,
linebreak, math, orderedList, para, plain, rawBlock,
singleQuoted, space, str, strong)
import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
import Text.Pandoc.Definition (Block (BlockQuote, Div, Para), Inline (Emph, Str),
Attr, Meta, Pandoc, pandocTypesVersion)
@ -92,6 +92,17 @@ tests = map (localOption (QuickCheckTests 20))
(doc $ para "one" <> para "two")
(doc $ para "2")
, testCase "Smart constructors" $
assertFilterConversion "smart constructors returned a wrong result"
"smart-constructors.lua"
(doc $ para "")
(doc $ mconcat
[ bulletList [para "Hello", para "World"]
, definitionList [("foo", [para "placeholder"])]
, lineBlock ["Moin", "Welt"]
, orderedList [plain "one", plain "two"]
])
, testCase "Convert header upper case" $
assertFilterConversion "converting header to upper case failed"
"uppercase-header.lua"

View file

@ -0,0 +1,10 @@
-- Test that constructors are "smart" in that they autoconvert
-- types where sensible.
function Para (_)
return {
pandoc.BulletList{pandoc.Para "Hello", pandoc.Para "World"},
pandoc.DefinitionList{{"foo", pandoc.Para "placeholder"}},
pandoc.LineBlock{"Moin", "Welt"},
pandoc.OrderedList{pandoc.Plain{pandoc.Str "one"}, pandoc.Plain "two"}
}
end