Lua: marshal Citation values as userdata objects

This commit is contained in:
Albert Krewinkel 2021-10-24 22:49:34 +02:00
parent 113a66bd08
commit 230b133db5
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
5 changed files with 55 additions and 39 deletions

View file

@ -557,29 +557,6 @@ for _, blk in pairs(M.Block.constructor) do
augment_attr_setter(blk.behavior.setters)
end
-- Citation
M.Citation = AstElement:make_subtype'Citation'
M.Citation.behavior.clone = M.types.clone.Citation
--- 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
-- @tparam[opt] int hash hash number
function M.Citation:new (id, mode, prefix, suffix, note_num, hash)
return {
id = id,
mode = mode,
prefix = ensureList(prefix or {}),
suffix = ensureList(suffix or {}),
note_num = note_num or 0,
hash = hash or 0,
}
end
-- ListAttributes
M.ListAttributes = AstElement:make_subtype 'ListAttributes'
M.ListAttributes.behavior.clone = M.types.clone.ListAttributes

View file

@ -37,6 +37,7 @@ module Text.Pandoc.Lua.Marshaling.AST
, pushAttr
, pushBlock
, pushCitation
, pushInline
, pushListAttributes
, pushMetaValue
@ -109,24 +110,35 @@ instance Pushable Inline where
instance Pushable Citation where
push = pushCitation
pushCitation :: LuaError e => Pusher e Citation
pushCitation (Citation cid prefix suffix mode noteNum hash) =
pushViaConstr' "Citation"
[ push cid, push mode, push prefix, push suffix, push noteNum, push hash
typeCitation :: LuaError e => DocumentedType e Citation
typeCitation = deftype "Citation" []
[ property "id" "citation ID / key"
(pushText, citationId)
(peekText, \citation cid -> citation{ citationId = cid })
, property "mode" "citation mode"
(pushString . show, citationMode)
(peekRead, \citation mode -> citation{ citationMode = mode })
, property "prefix" "citation prefix"
(pushInlines, citationPrefix)
(peekInlines, \citation prefix -> citation{ citationPrefix = prefix })
, property "suffix" "citation suffix"
(pushInlines, citationSuffix)
(peekInlines, \citation suffix -> citation{ citationPrefix = suffix })
, property "note_num" "note number"
(pushIntegral, citationNoteNum)
(peekIntegral, \citation noteNum -> citation{ citationNoteNum = noteNum })
, property "hash" "hash number"
(pushIntegral, citationHash)
(peekIntegral, \citation hash -> citation{ citationHash = hash })
, method $ defun "clone" ### return <#> udparam typeCitation "obj" ""
=#> functionResult pushCitation "Citation" "copy of obj"
]
peekCitation :: LuaError e => Peeker e Citation
peekCitation = fmap (retrieving "Citation")
. typeChecked "table" Lua.istable $ \idx -> do
idx' <- liftLua $ absindex idx
Citation
<$!> peekFieldRaw peekText "id" idx'
<*> peekFieldRaw (peekList peekInline) "prefix" idx'
<*> peekFieldRaw (peekList peekInline) "suffix" idx'
<*> peekFieldRaw peekRead "mode" idx'
<*> peekFieldRaw peekIntegral "note_num" idx'
<*> peekFieldRaw peekIntegral "hash" idx'
pushCitation :: LuaError e => Pusher e Citation
pushCitation = pushUD typeCitation
peekCitation :: LuaError e => Peeker e Citation
peekCitation = peekUD typeCitation
instance Pushable Alignment where
push = Lua.pushString . show
@ -289,6 +301,9 @@ peekBlocks = peekList peekBlock
peekInlines :: LuaError e => Peeker e [Inline]
peekInlines = peekList peekInline
pushInlines :: LuaError e => Pusher e [Inline]
pushInlines = pushPandocList pushInline
-- | Push Caption element
pushCaption :: LuaError e => Caption -> LuaE e ()
pushCaption (Caption shortCaption longCaption) = do

View file

@ -64,6 +64,7 @@ pushModule = do
pushName (functionName fn)
pushDocumentedFunction fn
rawset (nth 3)
forM_ otherConstructors addConstr
forM_ inlineConstructors addConstr
-- add constructors to Inlines.constructor
newtable -- constructor
@ -165,6 +166,28 @@ mkInlinesConstr name constr = defun name
<#> parameter peekFuzzyInlines "content" "Inlines" ""
=#> functionResult pushInline "Inline" "new object"
otherConstructors :: LuaError e => [DocumentedFunction e]
otherConstructors =
[ defun "Citation"
### (\cid mode mprefix msuffix mnote_num mhash ->
cid `seq` mode `seq` mprefix `seq` msuffix `seq`
mnote_num `seq` mhash `seq` return $! Citation
{ citationId = cid
, citationMode = mode
, citationPrefix = fromMaybe mempty mprefix
, citationSuffix = fromMaybe mempty msuffix
, citationNoteNum = fromMaybe 0 mnote_num
, citationHash = fromMaybe 0 mhash
})
<#> parameter peekText "string" "cid" "citation ID (e.g. bibtex key)"
<#> parameter peekRead "citation mode" "mode" "citation rendering mode"
<#> optionalParameter peekFuzzyInlines "prefix" "Inlines" ""
<#> optionalParameter peekFuzzyInlines "suffix" "Inlines" ""
<#> optionalParameter peekIntegral "note_num" "integer" "note number"
<#> optionalParameter peekIntegral "hash" "integer" "hash number"
=#> functionResult pushCitation "Citation" "new citation object"
#? "Creates a single citation."
]
walkElement :: (Walkable (SingletonsList Inline) a,
Walkable (SingletonsList Block) a,

View file

@ -37,7 +37,6 @@ pushCloneTable = do
Lua.newtable
addFunction "Attr" $ cloneWith peekAttr pushAttr
addFunction "Block" $ cloneWith peekBlock pushBlock
addFunction "Citation" $ cloneWith peekCitation Lua.push
addFunction "Inline" $ cloneWith peekInline pushInline
addFunction "Meta" $ cloneWith peekMeta Lua.push
addFunction "MetaValue" $ cloneWith peekMetaValue pushMetaValue

View file

@ -176,6 +176,8 @@ return {
local cloned = cite:clone()
cite.id = 'newton'
assert.are_same(cloned.id, 'leibniz')
assert.are_same(cite.id, 'newton')
assert.are_same(cite.mode, cloned.mode)
end),
},