aboutsummaryrefslogtreecommitdiff
path: root/data
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-10-20 21:40:07 +0200
committerJohn MacFarlane <jgm@berkeley.edu>2021-10-22 11:16:51 -0700
commit8523bb01b24424249aa409ea577388a1ea10d70a (patch)
treed172a9840cb9d3153e110f3068a197fef3da7423 /data
parente4287e6c950745ad78954b791bc87f322cd05530 (diff)
downloadpandoc-8523bb01b24424249aa409ea577388a1ea10d70a.tar.gz
Lua: marshal Attr values as userdata
- Adds a new `pandoc.AttributeList()` constructor, which creates the associative attribute list that is used as the third component of `Attr` values. Values of this type can often be passed to constructors instead of `Attr` values. - `AttributeList` values can no longer be indexed numerically.
Diffstat (limited to 'data')
-rw-r--r--data/pandoc.lua155
1 files changed, 3 insertions, 152 deletions
diff --git a/data/pandoc.lua b/data/pandoc.lua
index 173c8c179..059ff9a3a 100644
--- a/data/pandoc.lua
+++ b/data/pandoc.lua
@@ -281,33 +281,12 @@ local function ensureDefinitionPairs (pair)
return {inlines, blocks}
end
---- Split a string into it's words, using whitespace as separators.
-local function words (str)
- local ws = {}
- for w in str:gmatch("([^%s]+)") do ws[#ws + 1] = w end
- return ws
-end
-
--- Try hard to turn the arguments into an Attr object.
local function ensureAttr(attr)
- if type(attr) == 'table' then
- if #attr > 0 then return M.Attr(table.unpack(attr)) end
-
- -- assume HTML-like key-value pairs
- local ident = attr.id or ''
- local classes = words(attr.class or '')
- local attributes = attr
- attributes.id = nil
- attributes.class = nil
- return M.Attr(ident, classes, attributes)
- elseif attr == nil then
- return M.Attr()
- elseif type(attr) == 'string' then
- -- treat argument as ID
- return M.Attr(attr)
+ if type(attr) == 'userdata' then
+ return attr
end
- -- print(arg, ...)
- error('Could not convert to Attr')
+ return M.Attr(attr)
end
------------------------------------------------------------------------
@@ -831,134 +810,6 @@ M.Underline = M.Inline:create_constructor(
-- Element components
-- @section components
---- Check if the first element of a pair matches the given value.
--- @param x key value to be checked
--- @return function returning true iff first element of its argument matches x
--- @local
-local function assoc_key_equals (x)
- return function (y) return y[1] == x end
-end
-
---- Lookup a value in an associative list
--- @function lookup
--- @local
--- @tparam {{key, value},...} alist associative list
--- @param key key for which the associated value is to be looked up
-local function lookup(alist, key)
- return (List.find_if(alist, assoc_key_equals(key)) or {})[2]
-end
-
---- Return an iterator which returns key-value pairs of an associative list.
--- @function apairs
--- @local
--- @tparam {{key, value},...} alist associative list
-local apairs = function (alist)
- local i = 1
- local cur
- function nxt ()
- cur = rawget(alist, i)
- if cur then
- i = i + 1
- return cur[1], cur[2]
- end
- return nil
- end
- return nxt, nil, nil
-end
-
---- AttributeList, a metatable to allow table-like access to attribute lists
--- represented by associative lists.
--- @local
-local AttributeList = {
- __index = function (t, k)
- if type(k) == "number" then
- return rawget(t, k)
- else
- return lookup(t, k)
- end
- end,
-
- __newindex = function (t, k, v)
- local cur, idx = List.find_if(t, assoc_key_equals(k))
- if v == nil and not cur then
- -- deleted key does not exists in list
- return
- elseif v == nil then
- table.remove(t, idx)
- elseif cur then
- cur[2] = v
- elseif type(k) == "number" then
- rawset(t, k, v)
- else
- rawset(t, #t + 1, {k, v})
- end
- end,
-
- __pairs = apairs
-}
-
---- Convert a table to an associative list. The order of key-value pairs in the
--- alist is undefined. The table should either contain no numeric keys or
--- already be an associative list.
--- @local
--- @tparam table tbl associative list or table without numeric keys.
--- @treturn table associative list
-local to_alist = function (tbl)
- if #tbl ~= 0 or next(tbl) == nil then
- -- probably already an alist
- return tbl
- end
- local alist = {}
- local i = 1
- for k, v in pairs(tbl) do
- alist[i] = {k, v}
- i = i + 1
- end
- return alist
-end
-
--- Attr
-
---- Create a new set of attributes (Attr).
--- @function Attr
--- @tparam[opt] string identifier element identifier
--- @tparam[opt] {string,...} classes element classes
--- @tparam[opt] table attributes table containing string keys and values
--- @return element attributes
-M.Attr = AstElement:make_subtype'Attr'
-function M.Attr:new (identifier, classes, attributes)
- identifier = identifier or ''
- classes = ensureList(classes or {})
- attributes = setmetatable(to_alist(attributes or {}), AttributeList)
- return setmetatable({identifier, classes, attributes}, self.behavior)
-end
-M.Attr.behavior.clone = M.types.clone.Attr
-M.Attr.behavior.tag = 'Attr'
-M.Attr.behavior._field_names = {identifier = 1, classes = 2, attributes = 3}
-M.Attr.behavior.__eq = utils.equals
-M.Attr.behavior.__index = function(t, k)
- return (k == 't' and t.tag) or
- rawget(t, getmetatable(t)._field_names[k]) or
- getmetatable(t)[k]
-end
-M.Attr.behavior.__newindex = function(t, k, v)
- if k == 'attributes' then
- rawset(t, 3, setmetatable(to_alist(v or {}), AttributeList))
- elseif getmetatable(t)._field_names[k] then
- rawset(t, getmetatable(t)._field_names[k], v)
- else
- rawset(t, k, v)
- end
-end
-M.Attr.behavior.__pairs = function(t)
- local field_names = M.Attr.behavior._field_names
- local fields = {}
- for name, i in pairs(field_names) do
- fields[i] = name
- end
- return make_next_function(fields), t, nil
-end
-
-- Monkey-patch setters for `attr` fields to be more forgiving in the input that
-- results in a valid Attr value.
function augment_attr_setter (setters)