2017-03-20 15:17:03 +01:00
|
|
|
|
--[[
|
|
|
|
|
pandoc.lua
|
|
|
|
|
|
2019-02-09 09:52:51 +01:00
|
|
|
|
Copyright © 2017–2019 Albert Krewinkel
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
|
|
|
|
Permission to use, copy, modify, and/or distribute this software for any purpose
|
|
|
|
|
with or without fee is hereby granted, provided that the above copyright notice
|
|
|
|
|
and this permission notice appear in all copies.
|
|
|
|
|
|
|
|
|
|
THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES WITH
|
|
|
|
|
REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
|
|
|
|
|
FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT,
|
|
|
|
|
INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS
|
|
|
|
|
OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER
|
|
|
|
|
TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF
|
|
|
|
|
THIS SOFTWARE.
|
|
|
|
|
]]
|
|
|
|
|
|
2017-04-13 19:10:51 +02:00
|
|
|
|
---
|
|
|
|
|
-- Lua functions for pandoc scripts.
|
|
|
|
|
--
|
|
|
|
|
-- @author Albert Krewinkel
|
2019-02-09 09:52:51 +01:00
|
|
|
|
-- @copyright © 2017–2019 Albert Krewinkel
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @license MIT
|
2018-01-13 23:05:42 +01:00
|
|
|
|
local M = {}
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
2019-02-09 09:52:51 +01:00
|
|
|
|
-- Re-export bundled modules
|
|
|
|
|
M.List = require 'pandoc.List'
|
|
|
|
|
M.mediabag = require 'pandoc.mediabag'
|
2019-05-04 07:06:30 +02:00
|
|
|
|
M.system = require 'pandoc.system'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.types = require 'pandoc.types'
|
2019-02-09 09:52:51 +01:00
|
|
|
|
M.utils = require 'pandoc.utils'
|
|
|
|
|
M.text = require 'text'
|
|
|
|
|
|
|
|
|
|
-- Local names for modules which this module depends on.
|
|
|
|
|
local List = M.List
|
|
|
|
|
local utils = M.utils
|
2017-11-29 01:20:01 +01:00
|
|
|
|
|
2019-02-07 09:50:06 +01:00
|
|
|
|
|
2018-01-08 23:26:38 +01:00
|
|
|
|
------------------------------------------------------------------------
|
|
|
|
|
-- Accessor objects
|
|
|
|
|
--
|
|
|
|
|
-- Create metatables which allow to access numerical indices via accessor
|
|
|
|
|
-- methods.
|
|
|
|
|
-- @section
|
|
|
|
|
-- @local
|
|
|
|
|
|
|
|
|
|
--- Create a new indexing function.
|
|
|
|
|
-- @param template function template
|
2018-01-09 07:29:56 +01:00
|
|
|
|
-- @param indices list of indices, starting with the most deeply nested
|
2018-01-08 23:26:38 +01:00
|
|
|
|
-- @return newly created function
|
|
|
|
|
-- @local
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
function make_indexing_function(template, ...)
|
|
|
|
|
local indices = {...}
|
2018-01-08 23:26:38 +01:00
|
|
|
|
local loadstring = loadstring or load
|
|
|
|
|
local bracketed = {}
|
2018-01-09 07:29:56 +01:00
|
|
|
|
for i = 1, #indices do
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
local idx = indices[#indices - i + 1]
|
|
|
|
|
bracketed[i] = type(idx) == 'number'
|
|
|
|
|
and string.format('[%d]', idx)
|
|
|
|
|
or string.format('.%s', idx)
|
2018-01-09 07:29:56 +01:00
|
|
|
|
end
|
2018-01-08 23:26:38 +01:00
|
|
|
|
local fnstr = string.format('return ' .. template, table.concat(bracketed))
|
|
|
|
|
return assert(loadstring(fnstr))()
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|
|
--- Create accessor functions using a function template.
|
|
|
|
|
-- @param fn_template function template in which '%s' is replacd with indices
|
|
|
|
|
-- @param accessors list of accessors
|
|
|
|
|
-- @return mapping from accessor names to accessor functions
|
|
|
|
|
-- @local
|
|
|
|
|
local function create_accessor_functions (fn_template, accessors)
|
|
|
|
|
local res = {}
|
|
|
|
|
function add_accessors(acc, ...)
|
2018-01-13 23:05:42 +01:00
|
|
|
|
if type(acc) == 'string' then
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
res[acc] = make_indexing_function(fn_template, ...)
|
2018-01-13 23:05:42 +01:00
|
|
|
|
elseif type(acc) == 'table' and #acc == 0 and next(acc) then
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
-- Named substructure: the given names are accessed via the substructure,
|
|
|
|
|
-- but the accessors are also added to the result table, enabling direct
|
|
|
|
|
-- access from the parent element. Mainly used for `attr`.
|
2018-01-13 23:05:42 +01:00
|
|
|
|
local name, substructure = next(acc)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
res[name] = make_indexing_function(fn_template, ...)
|
|
|
|
|
for _, subname in ipairs(substructure) do
|
|
|
|
|
res[subname] = make_indexing_function(fn_template, subname, ...)
|
|
|
|
|
end
|
2018-01-08 23:26:38 +01:00
|
|
|
|
else
|
|
|
|
|
for i = 1, #(acc or {}) do
|
2018-01-09 07:29:56 +01:00
|
|
|
|
add_accessors(acc[i], i, ...)
|
2018-01-08 23:26:38 +01:00
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
add_accessors(accessors)
|
|
|
|
|
return res
|
|
|
|
|
end
|
|
|
|
|
|
2018-10-20 15:06:16 +02:00
|
|
|
|
--- Get list of top-level fields from field descriptor table.
|
|
|
|
|
-- E.g.: `top_level_fields{'foo', {bar='baz'}, {'qux', 'quux'}}`
|
|
|
|
|
-- gives {'foo, 'bar', 'qux', 'quux'}
|
|
|
|
|
-- @local
|
|
|
|
|
local function top_level_fields (fields)
|
|
|
|
|
local result = List:new{}
|
|
|
|
|
for _, v in ipairs(fields) do
|
|
|
|
|
if type(v) == 'string' then
|
|
|
|
|
table.insert(result, v)
|
|
|
|
|
elseif type(v) == 'table' and #v == 0 and next(v) then
|
|
|
|
|
table.insert(result, (next(v)))
|
|
|
|
|
else
|
|
|
|
|
result:extend(top_level_fields(v))
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
return result
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|
|
--- Creates a function which behaves like next, but respects field names.
|
|
|
|
|
-- @local
|
|
|
|
|
local function make_next_function (fields)
|
|
|
|
|
local field_indices = {}
|
|
|
|
|
for i, f in ipairs(fields) do
|
|
|
|
|
field_indices[f] = i
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|
|
return function (t, field)
|
|
|
|
|
local raw_idx = field == nil and 0 or field_indices[field]
|
|
|
|
|
local next_field = fields[raw_idx + 1]
|
|
|
|
|
return next_field, t[next_field]
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
|
2018-01-08 23:26:38 +01:00
|
|
|
|
--- Create a new table which allows to access numerical indices via accessor
|
|
|
|
|
-- functions.
|
|
|
|
|
-- @local
|
|
|
|
|
local function create_accessor_behavior (tag, accessors)
|
|
|
|
|
local behavior = {tag = tag}
|
|
|
|
|
behavior.getters = create_accessor_functions(
|
|
|
|
|
'function (x) return x.c%s end',
|
|
|
|
|
accessors
|
|
|
|
|
)
|
|
|
|
|
behavior.setters = create_accessor_functions(
|
|
|
|
|
'function (x, v) x.c%s = v end',
|
|
|
|
|
accessors
|
|
|
|
|
)
|
2018-11-19 21:36:02 +01:00
|
|
|
|
behavior.__eq = utils.equals
|
2018-01-08 23:26:38 +01:00
|
|
|
|
behavior.__index = function(t, k)
|
|
|
|
|
if getmetatable(t).getters[k] then
|
|
|
|
|
return getmetatable(t).getters[k](t)
|
|
|
|
|
elseif k == "t" then
|
|
|
|
|
return getmetatable(t)["tag"]
|
|
|
|
|
else
|
|
|
|
|
return getmetatable(t)[k]
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
behavior.__newindex = function(t, k, v)
|
|
|
|
|
if getmetatable(t).setters[k] then
|
|
|
|
|
getmetatable(t).setters[k](t, v)
|
|
|
|
|
else
|
|
|
|
|
rawset(t, k, v)
|
|
|
|
|
end
|
|
|
|
|
end
|
2018-10-20 15:06:16 +02:00
|
|
|
|
behavior.__pairs = function (t)
|
|
|
|
|
if accessors == nil then
|
|
|
|
|
return next, t
|
|
|
|
|
end
|
|
|
|
|
local iterable_fields = type(accessors) == 'string'
|
|
|
|
|
and {accessors}
|
|
|
|
|
or top_level_fields(accessors)
|
|
|
|
|
return make_next_function(iterable_fields), t
|
|
|
|
|
end
|
2018-01-08 23:26:38 +01:00
|
|
|
|
return behavior
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|
|
|
2017-04-12 21:21:25 +02:00
|
|
|
|
------------------------------------------------------------------------
|
2018-01-06 23:25:08 +01:00
|
|
|
|
-- The base class for types
|
|
|
|
|
-- @type Type
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @local
|
2018-01-06 23:25:08 +01:00
|
|
|
|
local Type = {}
|
|
|
|
|
Type.name = 'Type'
|
|
|
|
|
Type.__index = Type
|
|
|
|
|
Type.behavior = {
|
|
|
|
|
__type = Type,
|
|
|
|
|
new = function (obj)
|
|
|
|
|
obj = obj or {}
|
|
|
|
|
setmetatable(obj, self)
|
|
|
|
|
return obj
|
|
|
|
|
end
|
|
|
|
|
}
|
|
|
|
|
Type.behavior.__index = Type.behavior
|
2017-04-12 21:21:25 +02:00
|
|
|
|
|
2018-01-06 23:25:08 +01:00
|
|
|
|
--- Set a new behavior for the type, inheriting that of the parent type if none
|
2018-06-09 00:15:36 +02:00
|
|
|
|
--- is specified explicitly
|
2018-01-06 23:25:08 +01:00
|
|
|
|
-- @param behavior the behavior object for this type.
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @local
|
2018-01-06 23:25:08 +01:00
|
|
|
|
function Type:set_behavior (behavior)
|
|
|
|
|
behavior = behavior or {}
|
|
|
|
|
behavior.__index = rawget(behavior, '__index') or behavior
|
|
|
|
|
behavior.__type = self
|
|
|
|
|
if not getmetatable(behavior) and getmetatable(self) then
|
|
|
|
|
setmetatable(behavior, getmetatable(self).behavior)
|
|
|
|
|
end
|
|
|
|
|
self.behavior = behavior
|
2017-03-20 15:17:03 +01:00
|
|
|
|
end
|
2017-04-12 21:21:25 +02:00
|
|
|
|
|
2018-01-06 23:25:08 +01:00
|
|
|
|
--- Create a new subtype, using the given table as base.
|
2018-01-07 22:41:59 +01:00
|
|
|
|
-- @param name name of the new type
|
|
|
|
|
-- @param[opt] behavior behavioral object for the new type.
|
|
|
|
|
-- @return a new type
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @local
|
2018-01-06 23:25:08 +01:00
|
|
|
|
function Type:make_subtype(name, behavior)
|
|
|
|
|
local newtype = setmetatable({}, self)
|
|
|
|
|
newtype.name = name
|
|
|
|
|
newtype.__index = newtype
|
|
|
|
|
newtype:set_behavior(behavior)
|
|
|
|
|
return newtype
|
2017-03-20 15:17:03 +01:00
|
|
|
|
end
|
|
|
|
|
|
2018-01-06 23:25:08 +01:00
|
|
|
|
|
|
|
|
|
------------------------------------------------------------------------
|
|
|
|
|
-- The base class for pandoc's AST elements.
|
|
|
|
|
-- @type AstElement
|
|
|
|
|
-- @local
|
|
|
|
|
local AstElement = Type:make_subtype 'AstElement'
|
2018-01-07 11:22:53 +01:00
|
|
|
|
AstElement.__call = function(t, ...)
|
2018-01-08 23:26:38 +01:00
|
|
|
|
local success, ret = pcall(t.new, t, ...)
|
2018-01-07 11:22:53 +01:00
|
|
|
|
if success then
|
|
|
|
|
return setmetatable(ret, t.behavior)
|
|
|
|
|
else
|
|
|
|
|
error(string.format('Constructor for %s failed: %s\n', t.name, ret))
|
|
|
|
|
end
|
|
|
|
|
end
|
2018-01-06 23:25:08 +01:00
|
|
|
|
|
2018-01-09 07:29:56 +01:00
|
|
|
|
--- Make a new subtype which constructs a new value when called.
|
|
|
|
|
-- @local
|
2018-01-08 23:26:38 +01:00
|
|
|
|
function AstElement:make_subtype(...)
|
|
|
|
|
local newtype = Type.make_subtype(self, ...)
|
|
|
|
|
newtype.__call = self.__call
|
|
|
|
|
return newtype
|
|
|
|
|
end
|
|
|
|
|
|
2017-04-12 21:21:25 +02:00
|
|
|
|
--- Create a new constructor
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @local
|
2017-04-12 21:21:25 +02:00
|
|
|
|
-- @param tag Tag used to identify the constructor
|
|
|
|
|
-- @param fn Function to be called when constructing a new element
|
2017-08-21 17:47:54 +02:00
|
|
|
|
-- @param accessors names to use as accessors for numerical fields
|
2017-04-12 21:21:25 +02:00
|
|
|
|
-- @return function that constructs a new element
|
2018-01-06 23:25:08 +01:00
|
|
|
|
function AstElement:create_constructor(tag, fn, accessors)
|
2018-01-08 23:26:38 +01:00
|
|
|
|
local constr = self:make_subtype(tag, create_accessor_behavior(tag, accessors))
|
2017-04-12 21:21:25 +02:00
|
|
|
|
function constr:new(...)
|
2018-01-06 23:25:08 +01:00
|
|
|
|
return setmetatable(fn(...), self.behavior)
|
2017-04-12 21:21:25 +02:00
|
|
|
|
end
|
2017-04-13 19:10:51 +02:00
|
|
|
|
self.constructor = self.constructor or {}
|
|
|
|
|
self.constructor[tag] = constr
|
2017-04-12 21:21:25 +02:00
|
|
|
|
return constr
|
|
|
|
|
end
|
|
|
|
|
|
2018-01-13 22:29:16 +01:00
|
|
|
|
--- Convert AstElement input into a list if necessary.
|
|
|
|
|
-- @local
|
|
|
|
|
local function ensureList (x)
|
|
|
|
|
if x.tag then
|
|
|
|
|
-- Lists are not tagged, but all elements are
|
|
|
|
|
return List:new{x}
|
|
|
|
|
else
|
|
|
|
|
return List:new(x)
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
|
2018-01-13 18:52:17 +01:00
|
|
|
|
--- Ensure a given object is an Inline element, or convert it into one.
|
2018-01-13 22:29:16 +01:00
|
|
|
|
-- @local
|
2018-01-13 18:52:17 +01:00
|
|
|
|
local function ensureInlineList (x)
|
2018-01-13 22:29:16 +01:00
|
|
|
|
if type(x) == 'string' then
|
2018-01-13 18:52:17 +01:00
|
|
|
|
return List:new{M.Str(x)}
|
|
|
|
|
else
|
2018-01-13 22:29:16 +01:00
|
|
|
|
return ensureList(x)
|
2018-01-13 18:52:17 +01:00
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
|
2019-01-13 16:51:15 +01:00
|
|
|
|
--- 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
|
|
|
|
|
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
--- 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)
|
|
|
|
|
end
|
|
|
|
|
-- print(arg, ...)
|
|
|
|
|
error('Could not convert to Attr')
|
|
|
|
|
end
|
|
|
|
|
|
2017-04-12 21:21:25 +02:00
|
|
|
|
------------------------------------------------------------------------
|
2017-04-13 19:10:51 +02:00
|
|
|
|
--- Pandoc Document
|
|
|
|
|
-- @section document
|
|
|
|
|
|
|
|
|
|
--- A complete pandoc document
|
2017-08-31 13:22:27 +02:00
|
|
|
|
-- @function Pandoc
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @tparam {Block,...} blocks document content
|
|
|
|
|
-- @tparam[opt] Meta meta document meta data
|
2018-01-07 11:22:53 +01:00
|
|
|
|
M.Pandoc = AstElement:make_subtype'Pandoc'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.Pandoc.behavior.clone = M.types.clone.Pandoc
|
2018-01-08 23:26:38 +01:00
|
|
|
|
function M.Pandoc:new (blocks, meta)
|
2017-03-20 15:17:03 +01:00
|
|
|
|
return {
|
2018-01-13 22:29:16 +01:00
|
|
|
|
blocks = ensureList(blocks),
|
2018-01-07 14:06:34 +01:00
|
|
|
|
meta = meta or {},
|
2017-03-20 15:17:03 +01:00
|
|
|
|
}
|
|
|
|
|
end
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-06-29 17:08:59 +02:00
|
|
|
|
-- DEPRECATED synonym:
|
|
|
|
|
M.Doc = M.Pandoc
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-12-01 17:58:12 +01:00
|
|
|
|
------------------------------------------------------------------------
|
|
|
|
|
-- Meta
|
|
|
|
|
-- @section Meta
|
|
|
|
|
|
|
|
|
|
--- Create a new Meta object. It sets the metatable of the given table to
|
|
|
|
|
--- `Meta`.
|
|
|
|
|
-- @function Meta
|
|
|
|
|
-- @tparam meta table table containing document meta information
|
2018-01-07 11:22:53 +01:00
|
|
|
|
M.Meta = AstElement:make_subtype'Meta'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.Meta.behavior.clone = M.types.clone.Meta
|
2018-01-08 23:26:38 +01:00
|
|
|
|
function M.Meta:new (meta) return meta end
|
2017-12-01 17:58:12 +01:00
|
|
|
|
|
|
|
|
|
|
2017-04-13 22:57:50 +02:00
|
|
|
|
------------------------------------------------------------------------
|
|
|
|
|
-- MetaValue
|
|
|
|
|
-- @section MetaValue
|
2018-01-07 11:22:53 +01:00
|
|
|
|
M.MetaValue = AstElement:make_subtype('MetaValue')
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.MetaValue.behavior.clone = M.types.clone.MetaValue
|
2018-01-07 11:22:53 +01:00
|
|
|
|
|
2017-04-13 22:57:50 +02:00
|
|
|
|
--- Meta blocks
|
|
|
|
|
-- @function MetaBlocks
|
|
|
|
|
-- @tparam {Block,...} blocks blocks
|
2018-01-09 07:29:56 +01:00
|
|
|
|
M.MetaBlocks = M.MetaValue:create_constructor(
|
|
|
|
|
'MetaBlocks',
|
2018-01-13 22:29:16 +01:00
|
|
|
|
function (content) return ensureList(content) end
|
2018-01-09 07:29:56 +01:00
|
|
|
|
)
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
2017-04-13 22:57:50 +02:00
|
|
|
|
--- Meta inlines
|
|
|
|
|
-- @function MetaInlines
|
|
|
|
|
-- @tparam {Inline,...} inlines inlines
|
2018-01-09 07:29:56 +01:00
|
|
|
|
M.MetaInlines = M.MetaValue:create_constructor(
|
|
|
|
|
'MetaInlines',
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function (content) return ensureInlineList(content) end
|
2018-01-09 07:29:56 +01:00
|
|
|
|
)
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
2017-04-13 22:57:50 +02:00
|
|
|
|
--- Meta list
|
|
|
|
|
-- @function MetaList
|
|
|
|
|
-- @tparam {MetaValue,...} meta_values list of meta values
|
2018-01-09 07:29:56 +01:00
|
|
|
|
M.MetaList = M.MetaValue:create_constructor(
|
|
|
|
|
'MetaList',
|
2018-10-15 21:00:50 +02:00
|
|
|
|
function (content)
|
|
|
|
|
if content.tag == 'MetaList' then
|
|
|
|
|
return content
|
|
|
|
|
end
|
|
|
|
|
return ensureList(content)
|
|
|
|
|
end
|
2018-01-09 07:29:56 +01:00
|
|
|
|
)
|
2018-10-15 21:08:39 +02:00
|
|
|
|
for k, v in pairs(List) do
|
|
|
|
|
M.MetaList.behavior[k] = v
|
|
|
|
|
end
|
2017-04-13 22:57:50 +02:00
|
|
|
|
|
2017-12-01 18:47:33 +01:00
|
|
|
|
--- Meta map
|
|
|
|
|
-- @function MetaMap
|
|
|
|
|
-- @tparam table key_value_map a string-indexed map of meta values
|
2017-12-19 09:12:16 +01:00
|
|
|
|
M.MetaMap = M.MetaValue:create_constructor(
|
|
|
|
|
"MetaMap",
|
|
|
|
|
function (mm) return mm end
|
|
|
|
|
)
|
2017-12-01 18:47:33 +01:00
|
|
|
|
|
2017-04-16 21:00:01 +02:00
|
|
|
|
--- Creates string to be used in meta data.
|
|
|
|
|
-- Does nothing, lua strings are meta strings.
|
|
|
|
|
-- @function MetaString
|
|
|
|
|
-- @tparam string str string value
|
|
|
|
|
function M.MetaString(str)
|
|
|
|
|
return str
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|
|
--- Creates boolean to be used in meta data.
|
|
|
|
|
-- Does nothing, lua booleans are meta booleans.
|
|
|
|
|
-- @function MetaBool
|
|
|
|
|
-- @tparam boolean bool boolean value
|
|
|
|
|
function M.MetaBool(bool)
|
|
|
|
|
return bool
|
|
|
|
|
end
|
|
|
|
|
|
2017-04-14 10:33:38 +02:00
|
|
|
|
------------------------------------------------------------------------
|
2017-04-15 00:12:51 +02:00
|
|
|
|
-- Blocks
|
2017-04-14 10:33:38 +02:00
|
|
|
|
-- @section Block
|
|
|
|
|
|
2017-04-15 00:12:51 +02:00
|
|
|
|
--- Block elements
|
2018-01-07 11:22:53 +01:00
|
|
|
|
M.Block = AstElement:make_subtype'Block'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.Block.behavior.clone = M.types.clone.Block
|
2017-04-12 21:21:25 +02:00
|
|
|
|
|
2017-04-14 10:33:38 +02:00
|
|
|
|
--- Creates a block quote element
|
|
|
|
|
-- @function BlockQuote
|
|
|
|
|
-- @tparam {Block,...} content block content
|
|
|
|
|
-- @treturn Block block quote element
|
|
|
|
|
M.BlockQuote = M.Block:create_constructor(
|
|
|
|
|
"BlockQuote",
|
2018-01-13 22:29:16 +01:00
|
|
|
|
function(content) return {c = ensureList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a bullet (i.e. unordered) list.
|
|
|
|
|
-- @function BulletList
|
|
|
|
|
-- @tparam {{Block,...},...} content list of items
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block bullet list element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.BulletList = M.Block:create_constructor(
|
|
|
|
|
"BulletList",
|
2019-01-13 16:51:15 +01:00
|
|
|
|
function(content) return {c = ensureList(content):map(ensureList)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a code block element
|
|
|
|
|
-- @function CodeBlock
|
2017-04-15 20:00:35 +02:00
|
|
|
|
-- @tparam string text code string
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr element attributes
|
2017-04-14 10:33:38 +02:00
|
|
|
|
-- @treturn Block code block element
|
|
|
|
|
M.CodeBlock = M.Block:create_constructor(
|
|
|
|
|
"CodeBlock",
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
function(text, attr) return {c = {ensureAttr(attr), text}} end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{attr = {"identifier", "classes", "attributes"}}, "text"}
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a definition list, containing terms and their explanation.
|
|
|
|
|
-- @function DefinitionList
|
2019-01-13 16:51:15 +01:00
|
|
|
|
-- @tparam {{{Inline,...},{{Block,...}}},...} content list of items
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block definition list element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.DefinitionList = M.Block:create_constructor(
|
|
|
|
|
"DefinitionList",
|
2019-01-13 16:51:15 +01:00
|
|
|
|
function(content)
|
|
|
|
|
return {c = ensureList(content):map(ensureDefinitionPairs)}
|
|
|
|
|
end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a div element
|
|
|
|
|
-- @function Div
|
|
|
|
|
-- @tparam {Block,...} content block content
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr element attributes
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block div element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.Div = M.Block:create_constructor(
|
|
|
|
|
"Div",
|
2017-05-18 00:04:48 +02:00
|
|
|
|
function(content, attr)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
return {c = {ensureAttr(attr), ensureList(content)}}
|
2017-05-18 00:04:48 +02:00
|
|
|
|
end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{attr = {"identifier", "classes", "attributes"}}, "content"}
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
2017-12-29 06:55:46 +01:00
|
|
|
|
--- Creates a header element.
|
2017-04-14 10:33:38 +02:00
|
|
|
|
-- @function Header
|
|
|
|
|
-- @tparam int level header level
|
|
|
|
|
-- @tparam {Inline,...} content inline content
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr element attributes
|
2017-04-14 10:33:38 +02:00
|
|
|
|
-- @treturn Block header element
|
|
|
|
|
M.Header = M.Block:create_constructor(
|
|
|
|
|
"Header",
|
2017-05-18 00:04:48 +02:00
|
|
|
|
function(level, content, attr)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
return {c = {level, ensureAttr(attr), ensureInlineList(content)}}
|
2017-04-15 20:00:35 +02:00
|
|
|
|
end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{"level", {attr = {"identifier", "classes", "attributes"}}, "content"}
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a horizontal rule.
|
|
|
|
|
-- @function HorizontalRule
|
|
|
|
|
-- @treturn Block horizontal rule
|
|
|
|
|
M.HorizontalRule = M.Block:create_constructor(
|
|
|
|
|
"HorizontalRule",
|
|
|
|
|
function() return {} end
|
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a line block element.
|
|
|
|
|
-- @function LineBlock
|
|
|
|
|
-- @tparam {{Inline,...},...} content inline content
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block line block element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.LineBlock = M.Block:create_constructor(
|
|
|
|
|
"LineBlock",
|
2019-01-13 16:51:15 +01:00
|
|
|
|
function(content) return {c = ensureList(content):map(ensureInlineList)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a null element.
|
|
|
|
|
-- @function Null
|
|
|
|
|
-- @treturn Block null element
|
|
|
|
|
M.Null = M.Block:create_constructor(
|
|
|
|
|
"Null",
|
|
|
|
|
function() return {} end
|
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates an ordered list.
|
|
|
|
|
-- @function OrderedList
|
|
|
|
|
-- @tparam {{Block,...},...} items list items
|
|
|
|
|
-- @param[opt] listAttributes list parameters
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block ordered list element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.OrderedList = M.Block:create_constructor(
|
|
|
|
|
"OrderedList",
|
|
|
|
|
function(items, listAttributes)
|
2018-10-11 22:28:24 +02:00
|
|
|
|
listAttributes = listAttributes or M.ListAttributes()
|
2019-01-13 16:51:15 +01:00
|
|
|
|
return {c = {listAttributes, ensureList(items):map(ensureList)}}
|
2017-04-15 20:00:35 +02:00
|
|
|
|
end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{listAttributes = {"start", "style", "delimiter"}}, "content"}
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a para element.
|
|
|
|
|
-- @function Para
|
|
|
|
|
-- @tparam {Inline,...} content inline content
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block paragraph element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.Para = M.Block:create_constructor(
|
|
|
|
|
"Para",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a plain element.
|
|
|
|
|
-- @function Plain
|
|
|
|
|
-- @tparam {Inline,...} content inline content
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block plain element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.Plain = M.Block:create_constructor(
|
|
|
|
|
"Plain",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a raw content block of the specified format.
|
|
|
|
|
-- @function RawBlock
|
|
|
|
|
-- @tparam string format format of content
|
2017-04-15 20:00:35 +02:00
|
|
|
|
-- @tparam string text string content
|
2017-12-29 06:55:46 +01:00
|
|
|
|
-- @treturn Block raw block element
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.RawBlock = M.Block:create_constructor(
|
|
|
|
|
"RawBlock",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(format, text) return {c = {format, text}} end,
|
|
|
|
|
{"format", "text"}
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
--- Creates a table element.
|
|
|
|
|
-- @function Table
|
2020-04-13 10:08:38 +02:00
|
|
|
|
-- @tparam Attr attr attributes
|
|
|
|
|
-- @tparam Caption caption table caption
|
|
|
|
|
-- @tparam {ColSpec,...} colspecs column alignments and widths
|
|
|
|
|
-- @tparam TableHead head table head
|
|
|
|
|
-- @tparam {TableBody,..} bodies table bodies
|
|
|
|
|
-- @treturn TableFoot foot table foot
|
2017-04-14 10:33:38 +02:00
|
|
|
|
M.Table = M.Block:create_constructor(
|
|
|
|
|
"Table",
|
2020-04-13 10:08:38 +02:00
|
|
|
|
function(attr, caption, colspecs, head, bodies, foot)
|
2017-11-29 01:20:01 +01:00
|
|
|
|
return {
|
|
|
|
|
c = {
|
2020-04-13 10:08:38 +02:00
|
|
|
|
attr,
|
|
|
|
|
caption,
|
|
|
|
|
List:new(colspecs),
|
|
|
|
|
head,
|
|
|
|
|
List:new(bodies),
|
|
|
|
|
foot
|
2017-11-29 01:20:01 +01:00
|
|
|
|
}
|
|
|
|
|
}
|
2017-06-27 17:11:42 +02:00
|
|
|
|
end,
|
2020-04-13 10:08:38 +02:00
|
|
|
|
{"attr", "caption", "colspecs", "head", "bodies", "foot"}
|
2017-04-14 10:33:38 +02:00
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
|
2017-04-12 21:21:25 +02:00
|
|
|
|
------------------------------------------------------------------------
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- Inline
|
|
|
|
|
-- @section Inline
|
2017-04-12 21:21:25 +02:00
|
|
|
|
|
2017-04-14 10:33:38 +02:00
|
|
|
|
--- Inline element class
|
2018-01-07 11:22:53 +01:00
|
|
|
|
M.Inline = AstElement:make_subtype'Inline'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.Inline.behavior.clone = M.types.clone.Inline
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
2017-04-13 19:10:51 +02:00
|
|
|
|
--- Creates a Cite inline element
|
|
|
|
|
-- @function Cite
|
|
|
|
|
-- @tparam {Inline,...} content List of inlines
|
|
|
|
|
-- @tparam {Citation,...} citations List of citations
|
|
|
|
|
-- @treturn Inline citations element
|
|
|
|
|
M.Cite = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Cite",
|
2017-11-29 01:20:01 +01:00
|
|
|
|
function(content, citations)
|
2018-01-13 22:29:16 +01:00
|
|
|
|
return {c = {ensureList(citations), ensureInlineList(content)}}
|
2017-11-29 01:20:01 +01:00
|
|
|
|
end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
{"citations", "content"}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Code inline element
|
|
|
|
|
-- @function Code
|
2018-10-06 21:44:20 +02:00
|
|
|
|
-- @tparam string text code string
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr additional attributes
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @treturn Inline code element
|
|
|
|
|
M.Code = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Code",
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
function(text, attr) return {c = {ensureAttr(attr), text}} end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{attr = {"identifier", "classes", "attributes"}}, "text"}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates an inline element representing emphasised text.
|
|
|
|
|
-- @function Emph
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline emphasis element
|
|
|
|
|
M.Emph = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Emph",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Image inline element
|
|
|
|
|
-- @function Image
|
|
|
|
|
-- @tparam {Inline,..} caption text used to describe the image
|
|
|
|
|
-- @tparam string src path to the image file
|
|
|
|
|
-- @tparam[opt] string title brief image description
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr additional attributes
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @treturn Inline image element
|
|
|
|
|
M.Image = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Image",
|
2017-05-18 00:04:48 +02:00
|
|
|
|
function(caption, src, title, attr)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
title = title or ""
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
return {c = {ensureAttr(attr), ensureInlineList(caption), {src, title}}}
|
2017-04-15 20:00:35 +02:00
|
|
|
|
end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{attr = {"identifier", "classes", "attributes"}}, "caption", {"src", "title"}}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-04-12 21:21:25 +02:00
|
|
|
|
--- Create a LineBreak inline element
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @function LineBreak
|
|
|
|
|
-- @treturn Inline linebreak element
|
|
|
|
|
M.LineBreak = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"LineBreak",
|
|
|
|
|
function() return {} end
|
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a link inline element, usually a hyperlink.
|
|
|
|
|
-- @function Link
|
|
|
|
|
-- @tparam {Inline,..} content text for this link
|
|
|
|
|
-- @tparam string target the link target
|
|
|
|
|
-- @tparam[opt] string title brief link description
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr additional attributes
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @treturn Inline image element
|
|
|
|
|
M.Link = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Link",
|
2017-05-18 00:04:48 +02:00
|
|
|
|
function(content, target, title, attr)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
title = title or ""
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
attr = ensureAttr(attr)
|
2018-01-13 18:52:17 +01:00
|
|
|
|
return {c = {attr, ensureInlineList(content), {target, title}}}
|
2017-04-15 20:00:35 +02:00
|
|
|
|
end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{attr = {"identifier", "classes", "attributes"}}, "content", {"target", "title"}}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-06-29 17:08:59 +02:00
|
|
|
|
--- Creates a Math element, either inline or displayed.
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @function Math
|
2017-04-15 00:10:33 +02:00
|
|
|
|
-- @tparam "InlineMath"|"DisplayMath" mathtype rendering specifier
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @tparam string text Math content
|
|
|
|
|
-- @treturn Inline Math element
|
|
|
|
|
M.Math = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Math",
|
2017-04-13 19:10:51 +02:00
|
|
|
|
function(mathtype, text)
|
|
|
|
|
return {c = {mathtype, text}}
|
2017-04-15 20:00:35 +02:00
|
|
|
|
end,
|
|
|
|
|
{"mathtype", "text"}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-06-29 17:08:59 +02:00
|
|
|
|
--- Creates a DisplayMath element (DEPRECATED).
|
2017-04-15 00:10:33 +02:00
|
|
|
|
-- @function DisplayMath
|
|
|
|
|
-- @tparam string text Math content
|
|
|
|
|
-- @treturn Inline Math element
|
|
|
|
|
M.DisplayMath = M.Inline:create_constructor(
|
|
|
|
|
"DisplayMath",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(text) return M.Math("DisplayMath", text) end,
|
|
|
|
|
{"mathtype", "text"}
|
2017-04-15 00:10:33 +02:00
|
|
|
|
)
|
2017-06-29 17:08:59 +02:00
|
|
|
|
--- Creates an InlineMath inline element (DEPRECATED).
|
2017-04-15 00:10:33 +02:00
|
|
|
|
-- @function InlineMath
|
|
|
|
|
-- @tparam string text Math content
|
|
|
|
|
-- @treturn Inline Math element
|
|
|
|
|
M.InlineMath = M.Inline:create_constructor(
|
|
|
|
|
"InlineMath",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(text) return M.Math("InlineMath", text) end,
|
|
|
|
|
{"mathtype", "text"}
|
2017-04-15 00:10:33 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Note inline element
|
|
|
|
|
-- @function Note
|
|
|
|
|
-- @tparam {Block,...} content footnote block content
|
|
|
|
|
M.Note = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Note",
|
2018-01-13 22:29:16 +01:00
|
|
|
|
function(content) return {c = ensureList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-06-29 17:08:59 +02:00
|
|
|
|
--- Creates a Quoted inline element given the quote type and quoted content.
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @function Quoted
|
2017-04-15 00:10:33 +02:00
|
|
|
|
-- @tparam "DoubleQuote"|"SingleQuote" quotetype type of quotes to be used
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline quoted element
|
|
|
|
|
M.Quoted = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Quoted",
|
2019-01-13 16:51:15 +01:00
|
|
|
|
function(quotetype, content)
|
|
|
|
|
return {c = {quotetype, ensureInlineList(content)}}
|
|
|
|
|
end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
{"quotetype", "content"}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-06-29 17:08:59 +02:00
|
|
|
|
--- Creates a single-quoted inline element (DEPRECATED).
|
2017-04-15 00:10:33 +02:00
|
|
|
|
-- @function SingleQuoted
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline quoted element
|
|
|
|
|
-- @see Quoted
|
|
|
|
|
M.SingleQuoted = M.Inline:create_constructor(
|
|
|
|
|
"SingleQuoted",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(content) return M.Quoted(M.SingleQuote, content) end,
|
|
|
|
|
{"quotetype", "content"}
|
2017-04-15 00:10:33 +02:00
|
|
|
|
)
|
2017-06-29 17:08:59 +02:00
|
|
|
|
--- Creates a single-quoted inline element (DEPRECATED).
|
2017-04-15 00:10:33 +02:00
|
|
|
|
-- @function DoubleQuoted
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline quoted element
|
|
|
|
|
-- @see Quoted
|
|
|
|
|
M.DoubleQuoted = M.Inline:create_constructor(
|
|
|
|
|
"DoubleQuoted",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(content) return M.Quoted("DoubleQuote", content) end,
|
|
|
|
|
{"quotetype", "content"}
|
2017-04-15 00:10:33 +02:00
|
|
|
|
)
|
|
|
|
|
|
2017-04-13 19:10:51 +02:00
|
|
|
|
--- Creates a RawInline inline element
|
|
|
|
|
-- @function RawInline
|
|
|
|
|
-- @tparam string format format of the contents
|
|
|
|
|
-- @tparam string text string content
|
|
|
|
|
-- @treturn Inline raw inline element
|
|
|
|
|
M.RawInline = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"RawInline",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(format, text) return {c = {format, text}} end,
|
|
|
|
|
{"format", "text"}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates text rendered in small caps
|
|
|
|
|
-- @function SmallCaps
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline smallcaps element
|
|
|
|
|
M.SmallCaps = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"SmallCaps",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a SoftBreak inline element.
|
|
|
|
|
-- @function SoftBreak
|
|
|
|
|
-- @treturn Inline softbreak element
|
|
|
|
|
M.SoftBreak = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"SoftBreak",
|
|
|
|
|
function() return {} end
|
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-04-12 21:21:25 +02:00
|
|
|
|
--- Create a Space inline element
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @function Space
|
|
|
|
|
-- @treturn Inline space element
|
|
|
|
|
M.Space = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Space",
|
|
|
|
|
function() return {} end
|
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Span inline element
|
|
|
|
|
-- @function Span
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
2017-05-18 00:04:48 +02:00
|
|
|
|
-- @tparam[opt] Attr attr additional attributes
|
2017-04-13 19:10:51 +02:00
|
|
|
|
-- @treturn Inline span element
|
|
|
|
|
M.Span = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Span",
|
2017-11-29 01:20:01 +01:00
|
|
|
|
function(content, attr)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
return {c = {ensureAttr(attr), ensureInlineList(content)}}
|
2017-11-29 01:20:01 +01:00
|
|
|
|
end,
|
2018-01-13 23:05:42 +01:00
|
|
|
|
{{attr = {"identifier", "classes", "attributes"}}, "content"}
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Str inline element
|
|
|
|
|
-- @function Str
|
|
|
|
|
-- @tparam string text content
|
|
|
|
|
-- @treturn Inline string element
|
|
|
|
|
M.Str = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Str",
|
2017-04-15 20:00:35 +02:00
|
|
|
|
function(text) return {c = text} end,
|
|
|
|
|
"text"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates text which is striked out.
|
|
|
|
|
-- @function Strikeout
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline strikeout element
|
|
|
|
|
M.Strikeout = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Strikeout",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Strong element, whose text is usually displayed in a bold font.
|
|
|
|
|
-- @function Strong
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline strong element
|
|
|
|
|
M.Strong = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Strong",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Subscript inline element
|
|
|
|
|
-- @function Subscript
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline subscript element
|
|
|
|
|
M.Subscript = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Subscript",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a Superscript inline element
|
|
|
|
|
-- @function Superscript
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
2020-04-28 16:53:06 +02:00
|
|
|
|
-- @treturn Inline superscript element
|
2017-04-13 19:10:51 +02:00
|
|
|
|
M.Superscript = M.Inline:create_constructor(
|
2017-04-12 21:21:25 +02:00
|
|
|
|
"Superscript",
|
2018-01-13 18:52:17 +01:00
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
2017-04-15 20:00:35 +02:00
|
|
|
|
"content"
|
2017-04-12 21:21:25 +02:00
|
|
|
|
)
|
|
|
|
|
|
2020-04-28 16:53:06 +02:00
|
|
|
|
--- Creates an Underline inline element
|
|
|
|
|
-- @function Underline
|
|
|
|
|
-- @tparam {Inline,..} content inline content
|
|
|
|
|
-- @treturn Inline underline element
|
|
|
|
|
M.Underline = M.Inline:create_constructor(
|
|
|
|
|
"Underline",
|
|
|
|
|
function(content) return {c = ensureInlineList(content)} end,
|
|
|
|
|
"content"
|
|
|
|
|
)
|
|
|
|
|
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
2017-04-13 19:10:51 +02:00
|
|
|
|
------------------------------------------------------------------------
|
2018-01-07 22:41:59 +01:00
|
|
|
|
-- Element components
|
|
|
|
|
-- @section components
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
2018-01-07 22:41:59 +01:00
|
|
|
|
--- 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
|
2017-11-29 01:20:01 +01:00
|
|
|
|
local function assoc_key_equals (x)
|
|
|
|
|
return function (y) return y[1] == x end
|
2017-11-20 18:37:40 +01:00
|
|
|
|
end
|
|
|
|
|
|
2018-01-07 22:41:59 +01:00
|
|
|
|
--- Lookup a value in an associative list
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- @function lookup
|
2018-01-07 22:41:59 +01:00
|
|
|
|
-- @local
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- @tparam {{key, value},...} alist associative list
|
|
|
|
|
-- @param key key for which the associated value is to be looked up
|
|
|
|
|
local function lookup(alist, key)
|
2017-11-29 01:20:01 +01:00
|
|
|
|
return (List.find_if(alist, assoc_key_equals(key)) or {})[2]
|
2017-11-20 18:37:40 +01:00
|
|
|
|
end
|
|
|
|
|
|
2018-01-07 22:41:59 +01:00
|
|
|
|
--- Return an iterator which returns key-value pairs of an associative list.
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- @function apairs
|
2018-01-07 22:41:59 +01:00
|
|
|
|
-- @local
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- @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
|
|
|
|
|
|
2018-01-07 22:41:59 +01:00
|
|
|
|
--- AttributeList, a metatable to allow table-like access to attribute lists
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- represented by associative lists.
|
2018-01-07 22:41:59 +01:00
|
|
|
|
-- @local
|
2017-11-20 18:37:40 +01:00
|
|
|
|
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)
|
2017-11-29 01:20:01 +01:00
|
|
|
|
local cur, idx = List.find_if(t, assoc_key_equals(k))
|
2019-06-11 19:39:42 +02:00
|
|
|
|
if v == nil and not cur then
|
|
|
|
|
-- deleted key does not exists in list
|
|
|
|
|
return
|
|
|
|
|
elseif v == nil then
|
2017-11-20 18:37:40 +01:00
|
|
|
|
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
|
|
|
|
|
}
|
|
|
|
|
|
2018-01-07 22:41:59 +01:00
|
|
|
|
--- Convert a table to an associative list. The order of key-value pairs in the
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- alist is undefined. The table should either contain no numeric keys or
|
|
|
|
|
-- already be an associative list.
|
2018-01-07 22:41:59 +01:00
|
|
|
|
-- @local
|
|
|
|
|
-- @tparam table tbl associative list or table without numeric keys.
|
2017-11-20 18:37:40 +01:00
|
|
|
|
-- @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
|
|
|
|
|
|
2017-04-30 11:50:09 +02:00
|
|
|
|
-- Attr
|
2018-01-07 22:41:59 +01:00
|
|
|
|
|
2017-04-15 00:12:51 +02:00
|
|
|
|
--- Create a new set of attributes (Attr).
|
2017-04-30 11:50:09 +02:00
|
|
|
|
-- @function Attr
|
|
|
|
|
-- @tparam[opt] string identifier element identifier
|
2017-04-15 00:12:51 +02:00
|
|
|
|
-- @tparam[opt] {string,...} classes element classes
|
2017-04-30 11:50:09 +02:00
|
|
|
|
-- @tparam[opt] table attributes table containing string keys and values
|
2017-04-15 00:12:51 +02:00
|
|
|
|
-- @return element attributes
|
2018-01-07 22:41:59 +01:00
|
|
|
|
M.Attr = AstElement:make_subtype'Attr'
|
2018-01-08 23:26:38 +01:00
|
|
|
|
function M.Attr:new (identifier, classes, attributes)
|
2017-04-30 11:50:09 +02:00
|
|
|
|
identifier = identifier or ''
|
2018-01-13 22:29:16 +01:00
|
|
|
|
classes = ensureList(classes or {})
|
2017-11-20 18:37:40 +01:00
|
|
|
|
attributes = setmetatable(to_alist(attributes or {}), AttributeList)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
return setmetatable({identifier, classes, attributes}, self.behavior)
|
2017-04-15 00:12:51 +02:00
|
|
|
|
end
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.Attr.behavior.clone = M.types.clone.Attr
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
M.Attr.behavior.tag = 'Attr'
|
2018-01-07 22:41:59 +01:00
|
|
|
|
M.Attr.behavior._field_names = {identifier = 1, classes = 2, attributes = 3}
|
2018-11-19 21:36:02 +01:00
|
|
|
|
M.Attr.behavior.__eq = utils.equals
|
2018-01-07 22:41:59 +01:00
|
|
|
|
M.Attr.behavior.__index = function(t, k)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
return (k == 't' and t.tag) or
|
|
|
|
|
rawget(t, getmetatable(t)._field_names[k]) or
|
2018-01-09 19:44:42 +01:00
|
|
|
|
getmetatable(t)[k]
|
2017-04-15 09:31:09 +02:00
|
|
|
|
end
|
2018-01-07 22:41:59 +01:00
|
|
|
|
M.Attr.behavior.__newindex = function(t, k, v)
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
if k == 'attributes' then
|
|
|
|
|
rawset(t, 3, setmetatable(to_alist(v or {}), AttributeList))
|
|
|
|
|
elseif getmetatable(t)._field_names[k] then
|
2018-01-09 19:44:42 +01:00
|
|
|
|
rawset(t, getmetatable(t)._field_names[k], v)
|
2017-04-15 09:31:09 +02:00
|
|
|
|
else
|
2017-04-30 11:50:09 +02:00
|
|
|
|
rawset(t, k, v)
|
2017-04-15 09:31:09 +02:00
|
|
|
|
end
|
|
|
|
|
end
|
2018-10-20 15:06:16 +02:00
|
|
|
|
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
|
2017-04-15 09:31:09 +02:00
|
|
|
|
|
Lua filters: allow passing of HTML-like tables instead of Attr (#5750)
Attr values can now be given as normal Lua tables; this can be used as a
convenient alternative to define Attr values, instead of constructing
values with `pandoc.Attr`. Identifiers are taken from the *id* field,
classes must be given as space separated words in the *class* field. All
remaining fields are included as misc attributes.
With this change, the following lines now create equal elements:
pandoc.Span('test', {id = 'test', class = 'a b', check = 1})
pandoc.Span('test', pandoc.Attr('test', {'a','b'}, {check = 1}))
This also works when using the *attr* setter:
local span = pandoc.Span 'text'
span.attr = {id = 'test', class = 'a b', check = 1}
Furthermore, the *attributes* field of AST elements can now be a plain
key-value table even when using the `attributes` accessor:
local span = pandoc.Span 'test'
span.attributes = {check = 1} -- works as expected now
Closes: #5744
2019-09-15 21:11:58 +02:00
|
|
|
|
-- 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)
|
|
|
|
|
if setters.attr then
|
|
|
|
|
local orig = setters.attr
|
|
|
|
|
setters.attr = function(k, v)
|
|
|
|
|
orig(k, ensureAttr(v))
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
end
|
|
|
|
|
for _, blk in pairs(M.Block.constructor) do
|
|
|
|
|
augment_attr_setter(blk.behavior.setters)
|
|
|
|
|
end
|
|
|
|
|
for _, inln in pairs(M.Inline.constructor) do
|
|
|
|
|
augment_attr_setter(inln.behavior.setters)
|
|
|
|
|
end
|
|
|
|
|
|
|
|
|
|
|
2018-01-05 08:15:43 +01:00
|
|
|
|
-- Citation
|
2018-01-07 11:22:53 +01:00
|
|
|
|
M.Citation = AstElement:make_subtype'Citation'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.Citation.behavior.clone = M.types.clone.Citation
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-04-15 00:12:51 +02:00
|
|
|
|
--- Creates a single citation.
|
|
|
|
|
-- @function Citation
|
|
|
|
|
-- @tparam string id citation identifier (like a bibtex key)
|
|
|
|
|
-- @tparam AuthorInText|SuppressAuthor|NormalCitation mode citation mode
|
|
|
|
|
-- @tparam[opt] {Inline,...} prefix citation prefix
|
|
|
|
|
-- @tparam[opt] {Inline,...} suffix citation suffix
|
|
|
|
|
-- @tparam[opt] int note_num note number
|
2017-08-21 17:47:54 +02:00
|
|
|
|
-- @tparam[opt] int hash hash number
|
2018-01-08 23:26:38 +01:00
|
|
|
|
function M.Citation:new (id, mode, prefix, suffix, note_num, hash)
|
2018-01-07 11:22:53 +01:00
|
|
|
|
return {
|
|
|
|
|
id = id,
|
|
|
|
|
mode = mode,
|
2018-01-13 22:29:16 +01:00
|
|
|
|
prefix = ensureList(prefix or {}),
|
|
|
|
|
suffix = ensureList(suffix or {}),
|
2018-01-07 11:22:53 +01:00
|
|
|
|
note_num = note_num or 0,
|
|
|
|
|
hash = hash or 0,
|
|
|
|
|
}
|
2017-04-15 00:12:51 +02:00
|
|
|
|
end
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
2018-10-11 22:28:24 +02:00
|
|
|
|
-- ListAttributes
|
|
|
|
|
M.ListAttributes = AstElement:make_subtype 'ListAttributes'
|
2019-06-12 18:58:38 +02:00
|
|
|
|
M.ListAttributes.behavior.clone = M.types.clone.ListAttributes
|
2018-10-11 22:28:24 +02:00
|
|
|
|
|
|
|
|
|
--- Creates a set of list attributes.
|
|
|
|
|
-- @function ListAttributes
|
|
|
|
|
-- @tparam[opt] integer start number of the first list item
|
|
|
|
|
-- @tparam[opt] string style style used for list numbering
|
|
|
|
|
-- @tparam[opt] DefaultDelim|Period|OneParen|TwoParens delimiter delimiter of list numbers
|
|
|
|
|
-- @treturn table list attributes table
|
|
|
|
|
function M.ListAttributes:new (start, style, delimiter)
|
|
|
|
|
start = start or 1
|
|
|
|
|
style = style or 'DefaultStyle'
|
|
|
|
|
delimiter = delimiter or 'DefaultDelim'
|
|
|
|
|
return {start, style, delimiter}
|
|
|
|
|
end
|
|
|
|
|
M.ListAttributes.behavior._field_names = {start = 1, style = 2, delimiter = 3}
|
2018-11-19 21:36:02 +01:00
|
|
|
|
M.ListAttributes.behavior.__eq = utils.equals
|
2018-10-11 22:28:24 +02:00
|
|
|
|
M.ListAttributes.behavior.__index = function (t, k)
|
|
|
|
|
return rawget(t, getmetatable(t)._field_names[k]) or
|
|
|
|
|
getmetatable(t)[k]
|
|
|
|
|
end
|
|
|
|
|
M.ListAttributes.behavior.__newindex = function (t, k, v)
|
|
|
|
|
if getmetatable(t)._field_names[k] then
|
|
|
|
|
rawset(t, getmetatable(t)._field_names[k], v)
|
|
|
|
|
else
|
|
|
|
|
rawset(t, k, v)
|
|
|
|
|
end
|
|
|
|
|
end
|
2018-10-20 15:06:16 +02:00
|
|
|
|
M.ListAttributes.behavior.__pairs = function(t)
|
|
|
|
|
local field_names = M.ListAttributes.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
|
2018-10-11 22:28:24 +02:00
|
|
|
|
|
2017-04-15 00:12:51 +02:00
|
|
|
|
|
|
|
|
|
------------------------------------------------------------------------
|
|
|
|
|
-- Constants
|
|
|
|
|
-- @section constants
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Author name is mentioned in the text.
|
|
|
|
|
-- @see Citation
|
|
|
|
|
-- @see Cite
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.AuthorInText = "AuthorInText"
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Author name is suppressed.
|
|
|
|
|
-- @see Citation
|
|
|
|
|
-- @see Cite
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.SuppressAuthor = "SuppressAuthor"
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
|
|
|
|
--- Default citation style is used.
|
|
|
|
|
-- @see Citation
|
|
|
|
|
-- @see Cite
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.NormalCitation = "NormalCitation"
|
2017-04-13 19:10:51 +02:00
|
|
|
|
|
2017-04-14 10:33:38 +02:00
|
|
|
|
--- Table cells aligned left.
|
|
|
|
|
-- @see Table
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.AlignLeft = "AlignLeft"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- Table cells right-aligned.
|
|
|
|
|
-- @see Table
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.AlignRight = "AlignRight"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- Table cell content is centered.
|
|
|
|
|
-- @see Table
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.AlignCenter = "AlignCenter"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- Table cells are alignment is unaltered.
|
|
|
|
|
-- @see Table
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.AlignDefault = "AlignDefault"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- Default list number delimiters are used.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.DefaultDelim = "DefaultDelim"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List numbers are delimited by a period.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.Period = "Period"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List numbers are delimited by a single parenthesis.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.OneParen = "OneParen"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List numbers are delimited by a double parentheses.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.TwoParens = "TwoParens"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List are numbered in the default style
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.DefaultStyle = "DefaultStyle"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List items are numbered as examples.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.Example = "Example"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List are numbered using decimal integers.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.Decimal = "Decimal"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List are numbered using lower-case roman numerals.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.LowerRoman = "LowerRoman"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List are numbered using upper-case roman numerals
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.UpperRoman = "UpperRoman"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List are numbered using lower-case alphabetic characters.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.LowerAlpha = "LowerAlpha"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
|
|
|
|
--- List are numbered using upper-case alphabetic characters.
|
|
|
|
|
-- @see OrderedList
|
2017-04-14 22:32:08 +02:00
|
|
|
|
M.UpperAlpha = "UpperAlpha"
|
2017-04-14 10:33:38 +02:00
|
|
|
|
|
2017-12-21 22:30:59 +01:00
|
|
|
|
------------------------------------------------------------------------
|
|
|
|
|
-- Functions which have moved to different modules
|
|
|
|
|
M.sha1 = utils.sha1
|
|
|
|
|
|
2017-03-20 15:17:03 +01:00
|
|
|
|
return M
|