From 230b133db53e8ef2677fe13304e1e03276ca6448 Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert@zeitkraut.de>
Date: Sun, 24 Oct 2021 22:49:34 +0200
Subject: [PATCH] Lua: marshal Citation values as userdata objects

---
 data/pandoc.lua                       | 23 --------------
 src/Text/Pandoc/Lua/Marshaling/AST.hs | 45 ++++++++++++++++++---------
 src/Text/Pandoc/Lua/Module/Pandoc.hs  | 23 ++++++++++++++
 src/Text/Pandoc/Lua/Module/Types.hs   |  1 -
 test/lua/module/pandoc.lua            |  2 ++
 5 files changed, 55 insertions(+), 39 deletions(-)

diff --git a/data/pandoc.lua b/data/pandoc.lua
index 8fbd2259b..47343b28c 100644
--- a/data/pandoc.lua
+++ b/data/pandoc.lua
@@ -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
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs
index 5791b39c1..e436ffffc 100644
--- a/src/Text/Pandoc/Lua/Marshaling/AST.hs
+++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs
@@ -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
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index eeadfa340..bc9ddc5e5 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -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,
diff --git a/src/Text/Pandoc/Lua/Module/Types.hs b/src/Text/Pandoc/Lua/Module/Types.hs
index 7307c6e88..4a7d14d2f 100644
--- a/src/Text/Pandoc/Lua/Module/Types.hs
+++ b/src/Text/Pandoc/Lua/Module/Types.hs
@@ -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
diff --git a/test/lua/module/pandoc.lua b/test/lua/module/pandoc.lua
index a1bcd53fe..ba6d2a1df 100644
--- a/test/lua/module/pandoc.lua
+++ b/test/lua/module/pandoc.lua
@@ -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),
   },