Lua filter: use Attributes constructor for Attrs

Element attributes are pushed to the stack via the `Attributes`
function. `Attributes` creates an Attr like triple, but the triple also
allows table-like access to key-value pairs.
This commit is contained in:
Albert Krewinkel 2017-04-15 09:31:09 +02:00
parent ac275528c2
commit 3d6edbd9e3
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
2 changed files with 76 additions and 30 deletions

View file

@ -550,16 +550,6 @@ M.Superscript = M.Inline:create_constructor(
-- Attributes -- Attributes
M.Attributes = {} M.Attributes = {}
setmetatable(M.Attributes, M.Attributes)
M.Attributes.__index = function(t, k)
if k == "id" then
return t[1]
elseif k == "class" then
return table.concat(t[2], ' ')
else
return t.kv[k]
end
end
--- Create a new set of attributes (Attr). --- Create a new set of attributes (Attr).
-- @function Attributes -- @function Attributes
-- @tparam table key_values table containing string keys and values -- @tparam table key_values table containing string keys and values
@ -567,17 +557,61 @@ end
-- @tparam[opt] {string,...} classes element classes -- @tparam[opt] {string,...} classes element classes
-- @return element attributes -- @return element attributes
M.Attributes.__call = function(t, key_values, id, classes) M.Attributes.__call = function(t, key_values, id, classes)
local kv = {}
for i = 1, #key_values do
kv[key_values[i][1]] = key_values[i][2]
end
id = id or '' id = id or ''
classes = classes or {} classes = classes or {}
local attr = {id, classes, key_values, kv = kv} local attr = {id, classes, key_values}
setmetatable(attr, t) setmetatable(attr, t)
return attr return attr
end end
M.Attributes.empty = M.Attributes('', {}, {}) M.Attributes.__index = function(t, k)
if rawget(t, k) then
return rawget(t, k)
elseif k == "id" then
if rawget(t, 1) == '' then
return nil
else
return rawget(t, 1)
end
elseif k == "class" then
if #(rawget(t, 2)) == 0 then
return nil
else
return table.concat(t[2], ' ')
end
else
for _, p in ipairs(t[3]) do
if k == p[1] then
return p[2]
end
end
return nil
end
end
M.Attributes.__newindex = function(t, k, v)
if rawget(t, k) then
rawset(t, k, v)
elseif k == "id" then
rawset(t, 1, v)
elseif k == "class" then
if type(v) == "string" then
rawset(t, 2, {v})
else
rawset(t, 2, v)
end
else
for _, p in ipairs(rawget(t, 3)) do
if k == p[1] then
p[2] = v
return
end
end
kv = rawget(t, 3)
kv[#kv + 1] = {k, v}
rawset(t, 3, kv)
end
end
setmetatable(M.Attributes, M.Attributes)
--- Creates a single citation. --- Creates a single citation.
-- @function Citation -- @function Citation

View file

@ -170,10 +170,10 @@ pushBlock :: LuaState -> Block -> IO ()
pushBlock lua = \case pushBlock lua = \case
BlockQuote blcks -> pushViaConstructor lua "BlockQuote" blcks BlockQuote blcks -> pushViaConstructor lua "BlockQuote" blcks
BulletList items -> pushViaConstructor lua "BulletList" items BulletList items -> pushViaConstructor lua "BulletList" items
CodeBlock attr code -> pushViaConstructor lua "CodeBlock" code attr CodeBlock attr code -> pushViaConstructor lua "CodeBlock" code (LuaAttr attr)
DefinitionList items -> pushViaConstructor lua "DefinitionList" items DefinitionList items -> pushViaConstructor lua "DefinitionList" items
Div attr blcks -> pushViaConstructor lua "Div" blcks attr Div attr blcks -> pushViaConstructor lua "Div" blcks (LuaAttr attr)
Header lvl attr inlns -> pushViaConstructor lua "Header" lvl attr inlns Header lvl attr inlns -> pushViaConstructor lua "Header" lvl (LuaAttr attr) inlns
HorizontalRule -> pushViaConstructor lua "HorizontalRule" HorizontalRule -> pushViaConstructor lua "HorizontalRule"
LineBlock blcks -> pushViaConstructor lua "LineBlock" blcks LineBlock blcks -> pushViaConstructor lua "LineBlock" blcks
OrderedList lstAttr list -> pushViaConstructor lua "OrderedList" list lstAttr OrderedList lstAttr list -> pushViaConstructor lua "OrderedList" list lstAttr
@ -193,10 +193,10 @@ peekBlock lua idx = do
Just t -> case t of Just t -> case t of
"BlockQuote" -> fmap BlockQuote <$> elementContent "BlockQuote" -> fmap BlockQuote <$> elementContent
"BulletList" -> fmap BulletList <$> elementContent "BulletList" -> fmap BulletList <$> elementContent
"CodeBlock" -> fmap (uncurry CodeBlock) <$> elementContent "CodeBlock" -> fmap (withAttr CodeBlock) <$> elementContent
"DefinitionList" -> fmap DefinitionList <$> elementContent "DefinitionList" -> fmap DefinitionList <$> elementContent
"Div" -> fmap (uncurry Div) <$> elementContent "Div" -> fmap (withAttr Div) <$> elementContent
"Header" -> fmap (\(lvl, attr, lst) -> Header lvl attr lst) "Header" -> fmap (\(lvl, LuaAttr attr, lst) -> Header lvl attr lst)
<$> elementContent <$> elementContent
"HorizontalRule" -> return (Just HorizontalRule) "HorizontalRule" -> return (Just HorizontalRule)
"LineBlock" -> fmap LineBlock <$> elementContent "LineBlock" -> fmap LineBlock <$> elementContent
@ -218,11 +218,11 @@ peekBlock lua idx = do
pushInline :: LuaState -> Inline -> IO () pushInline :: LuaState -> Inline -> IO ()
pushInline lua = \case pushInline lua = \case
Cite citations lst -> pushViaConstructor lua "Cite" lst citations Cite citations lst -> pushViaConstructor lua "Cite" lst citations
Code attr lst -> pushViaConstructor lua "Code" lst attr Code attr lst -> pushViaConstructor lua "Code" lst (LuaAttr attr)
Emph inlns -> pushViaConstructor lua "Emph" inlns Emph inlns -> pushViaConstructor lua "Emph" inlns
Image attr alt (src,tit) -> pushViaConstructor lua "Image" alt src tit attr Image attr alt (src,tit) -> pushViaConstructor lua "Image" alt src tit (LuaAttr attr)
LineBreak -> pushViaConstructor lua "LineBreak" LineBreak -> pushViaConstructor lua "LineBreak"
Link attr lst (src,tit) -> pushViaConstructor lua "Link" lst src tit attr Link attr lst (src,tit) -> pushViaConstructor lua "Link" lst src tit (LuaAttr attr)
Note blcks -> pushViaConstructor lua "Note" blcks Note blcks -> pushViaConstructor lua "Note" blcks
Math mty str -> pushViaConstructor lua "Math" mty str Math mty str -> pushViaConstructor lua "Math" mty str
Quoted qt inlns -> pushViaConstructor lua "Quoted" qt inlns Quoted qt inlns -> pushViaConstructor lua "Quoted" qt inlns
@ -230,7 +230,7 @@ pushInline lua = \case
SmallCaps inlns -> pushViaConstructor lua "SmallCaps" inlns SmallCaps inlns -> pushViaConstructor lua "SmallCaps" inlns
SoftBreak -> pushViaConstructor lua "SoftBreak" SoftBreak -> pushViaConstructor lua "SoftBreak"
Space -> pushViaConstructor lua "Space" Space -> pushViaConstructor lua "Space"
Span attr inlns -> pushViaConstructor lua "Span" inlns attr Span attr inlns -> pushViaConstructor lua "Span" inlns (LuaAttr attr)
Str str -> pushViaConstructor lua "Str" str Str str -> pushViaConstructor lua "Str" str
Strikeout inlns -> pushViaConstructor lua "Strikeout" inlns Strikeout inlns -> pushViaConstructor lua "Strikeout" inlns
Strong inlns -> pushViaConstructor lua "Strong" inlns Strong inlns -> pushViaConstructor lua "Strong" inlns
@ -245,11 +245,11 @@ peekInline lua idx = do
Nothing -> return Nothing Nothing -> return Nothing
Just t -> case t of Just t -> case t of
"Cite" -> fmap (uncurry Cite) <$> elementContent "Cite" -> fmap (uncurry Cite) <$> elementContent
"Code" -> fmap (uncurry Code) <$> elementContent "Code" -> fmap (withAttr Code) <$> elementContent
"Emph" -> fmap Emph <$> elementContent "Emph" -> fmap Emph <$> elementContent
"Image" -> fmap (\(attr, lst, tgt) -> Image attr lst tgt) "Image" -> fmap (\(LuaAttr attr, lst, tgt) -> Image attr lst tgt)
<$> elementContent <$> elementContent
"Link" -> fmap (\(attr, lst, tgt) -> Link attr lst tgt) "Link" -> fmap (\(LuaAttr attr, lst, tgt) -> Link attr lst tgt)
<$> elementContent <$> elementContent
"LineBreak" -> return (Just LineBreak) "LineBreak" -> return (Just LineBreak)
"Note" -> fmap Note <$> elementContent "Note" -> fmap Note <$> elementContent
@ -259,7 +259,7 @@ peekInline lua idx = do
"SmallCaps" -> fmap SmallCaps <$> elementContent "SmallCaps" -> fmap SmallCaps <$> elementContent
"SoftBreak" -> return (Just SoftBreak) "SoftBreak" -> return (Just SoftBreak)
"Space" -> return (Just Space) "Space" -> return (Just Space)
"Span" -> fmap (uncurry Span) <$> elementContent "Span" -> fmap (withAttr Span) <$> elementContent
"Str" -> fmap Str <$> elementContent "Str" -> fmap Str <$> elementContent
"Strikeout" -> fmap Strikeout <$> elementContent "Strikeout" -> fmap Strikeout <$> elementContent
"Strong" -> fmap Strong <$> elementContent "Strong" -> fmap Strong <$> elementContent
@ -270,3 +270,15 @@ peekInline lua idx = do
-- Get the contents of an AST element. -- Get the contents of an AST element.
elementContent :: StackValue a => IO (Maybe a) elementContent :: StackValue a => IO (Maybe a)
elementContent = getTable lua idx "c" elementContent = getTable lua idx "c"
withAttr :: (Attr -> a -> b) -> (LuaAttr, a) -> b
withAttr f (attributes, x) = f (fromLuaAttr attributes) x
-- | Wrapper for Attr
newtype LuaAttr = LuaAttr { fromLuaAttr :: Attr }
instance StackValue LuaAttr where
push lua (LuaAttr (id', classes, kv)) =
pushViaConstructor lua "Attributes" kv id' classes
peek lua idx = fmap LuaAttr <$> peek lua idx
valuetype _ = TTABLE