From f56d8706312df64d3956cea0c93768b51192958e Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert@zeitkraut.de>
Date: Tue, 26 Oct 2021 14:40:11 +0200
Subject: Lua: marshal ListAttributes values as userdata objects

---
 src/Text/Pandoc/Lua/Init.hs                      |  1 -
 src/Text/Pandoc/Lua/Marshaling/AST.hs            | 14 +----
 src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs | 72 ++++++++++++++++++++++++
 src/Text/Pandoc/Lua/Module/Pandoc.hs             |  4 ++
 src/Text/Pandoc/Lua/Module/Types.hs              |  1 -
 src/Text/Pandoc/Lua/Module/Utils.hs              |  3 +-
 6 files changed, 80 insertions(+), 15 deletions(-)
 create mode 100644 src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs

(limited to 'src')

diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 60475e25c..87ae3a0d2 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -85,7 +85,6 @@ putConstructorsInRegistry :: PandocLua ()
 putConstructorsInRegistry = liftPandocLua $ do
   constrsToReg $ Pandoc.Meta mempty
   constrsToReg $ Pandoc.MetaList mempty
-  putInReg "ListAttributes"  -- used for ListAttributes type alias
   putInReg "List"  -- pandoc.List
   putInReg "SimpleTable"  -- helper for backward-compatible table handling
  where
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs
index 22c78bff9..d723fcb4c 100644
--- a/src/Text/Pandoc/Lua/Marshaling/AST.hs
+++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs
@@ -31,7 +31,6 @@ module Text.Pandoc.Lua.Marshaling.AST
   , peekInlineFuzzy
   , peekInlines
   , peekInlinesFuzzy
-  , peekListAttributes
   , peekMeta
   , peekMetaValue
   , peekPandoc
@@ -63,6 +62,8 @@ import Text.Pandoc.Error (PandocError (PandocLuaError))
 import Text.Pandoc.Lua.Util (pushViaConstr')
 import Text.Pandoc.Lua.Marshaling.Attr (peekAttr, pushAttr)
 import Text.Pandoc.Lua.Marshaling.List (pushPandocList)
+import Text.Pandoc.Lua.Marshaling.ListAttributes
+  (peekListAttributes, pushListAttributes)
 
 import qualified HsLua as Lua
 import qualified Text.Pandoc.Lua.Util as LuaUtil
@@ -794,17 +795,6 @@ peekBlocksFuzzy = choice
   , (<$!>) pure . peekBlockFuzzy
   ]
 
-pushListAttributes :: forall e. LuaError e => ListAttributes -> LuaE e ()
-pushListAttributes (start, style, delimiter) =
-    pushViaConstr' "ListAttributes"
-    [ push start, push style, push delimiter ]
-
-peekListAttributes :: LuaError e => Peeker e ListAttributes
-peekListAttributes = retrieving "ListAttributes" . peekTriple
-  peekIntegral
-  peekRead
-  peekRead
-
 -- * Orphan Instances
 
 instance Pushable Inline where
diff --git a/src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs b/src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs
new file mode 100644
index 000000000..5a6608644
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs
@@ -0,0 +1,72 @@
+{-# LANGUAGE OverloadedStrings    #-}
+{-# LANGUAGE TupleSections        #-}
+{- |
+Module      : Text.Pandoc.Lua.Marshaling.ListAttributes
+Copyright   : © 2021 Albert Krewinkel
+License     : GNU GPL, version 2 or above
+Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+
+Marshaling/unmarshaling functions and constructor for 'ListAttributes'
+values.
+-}
+module Text.Pandoc.Lua.Marshaling.ListAttributes
+  ( typeListAttributes
+  , peekListAttributes
+  , pushListAttributes
+  , mkListAttributes
+  ) where
+
+import Data.Maybe (fromMaybe)
+import HsLua
+import Text.Pandoc.Definition ( ListAttributes, ListNumberStyle (DefaultStyle)
+                              , ListNumberDelim (DefaultDelim))
+
+typeListAttributes :: LuaError e => DocumentedType e ListAttributes
+typeListAttributes = deftype "ListAttributes"
+  [ operation Eq $ lambda
+    ### liftPure2 (==)
+    <#> parameter peekListAttributes "a" "ListAttributes" ""
+    <#> parameter peekListAttributes "b" "ListAttributes" ""
+    =#> functionResult pushBool "boolean" "whether the two are equal"
+  ]
+  [ property "start" "number of the first list item"
+      (pushIntegral, \(start,_,_) -> start)
+      (peekIntegral, \(_,style,delim) -> (,style,delim))
+  , property "style" "style used for list numbering"
+      (pushString . show, \(_,classes,_) -> classes)
+      (peekRead, \(start,_,delim) -> (start,,delim))
+  , property "delimiter" "delimiter of list numbers"
+      (pushString . show, \(_,_,delim) -> delim)
+      (peekRead, \(start,style,_) -> (start,style,))
+  , method $ defun "clone"
+    ### return
+    <#> udparam typeListAttributes "a" ""
+    =#> functionResult (pushUD typeListAttributes) "ListAttributes"
+          "cloned ListAttributes value"
+  ]
+
+-- | Pushes a 'ListAttributes' value as userdata object.
+pushListAttributes :: LuaError e => Pusher e ListAttributes
+pushListAttributes = pushUD typeListAttributes
+
+-- | Retrieve a 'ListAttributes' triple, either from userdata or from a
+-- Lua tuple.
+peekListAttributes :: LuaError e => Peeker e ListAttributes
+peekListAttributes = retrieving "ListAttributes" . choice
+  [ peekUD typeListAttributes
+  , peekTriple peekIntegral peekRead peekRead
+  ]
+
+-- | Constructor for a new 'ListAttributes' value.
+mkListAttributes :: LuaError e => DocumentedFunction e
+mkListAttributes = defun "ListAttributes"
+  ### liftPure3 (\mstart mstyle mdelim ->
+                   ( fromMaybe 1 mstart
+                   , fromMaybe DefaultStyle mstyle
+                   , fromMaybe DefaultDelim mdelim
+                   ))
+  <#> optionalParameter peekIntegral "integer" "start" "number of first item"
+  <#> optionalParameter peekRead "string" "style" "list numbering style"
+  <#> optionalParameter peekRead "string" "delimiter" "list number delimiter"
+  =#> functionResult pushListAttributes "ListAttributes" "new ListAttributes"
+  #? "Creates a new ListAttributes object."
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index f08914eba..340c324ad 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -34,6 +34,8 @@ import Text.Pandoc.Lua.Marshaling ()
 import Text.Pandoc.Lua.Marshaling.AST
 import Text.Pandoc.Lua.Marshaling.Attr (mkAttr, mkAttributeList)
 import Text.Pandoc.Lua.Marshaling.List (List (..))
+import Text.Pandoc.Lua.Marshaling.ListAttributes ( mkListAttributes
+                                                 , peekListAttributes)
 import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua,
                                   loadDefaultModule)
 import Text.Pandoc.Options (ReaderOptions (readerExtensions))
@@ -301,6 +303,8 @@ otherConstructors =
     <#> optionalParameter peekIntegral "hash" "integer" "hash number"
     =#> functionResult pushCitation "Citation" "new citation object"
     #? "Creates a single citation."
+
+  , mkListAttributes
   ]
 
 walkElement :: (Walkable (SingletonsList Inline) a,
diff --git a/src/Text/Pandoc/Lua/Module/Types.hs b/src/Text/Pandoc/Lua/Module/Types.hs
index fb09235de..ff4a4e0d5 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 "Meta"      $ cloneWith peekMeta Lua.push
   addFunction "MetaValue" $ cloneWith peekMetaValue pushMetaValue
-  addFunction "ListAttributes" $ cloneWith peekListAttributes pushListAttributes
   return 1
 
 cloneWith :: Peeker PandocError a
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 7ce1cd18d..f83c34af7 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -29,7 +29,8 @@ import Text.Pandoc.Error (PandocError)
 import Text.Pandoc.Lua.Marshaling ()
 import Text.Pandoc.Lua.Marshaling.AST
   ( peekBlock, peekInline, peekPandoc, pushBlock, pushInline, pushPandoc
-  , peekAttr, peekListAttributes, peekMeta, peekMetaValue)
+  , peekAttr, peekMeta, peekMetaValue)
+import Text.Pandoc.Lua.Marshaling.ListAttributes (peekListAttributes)
 import Text.Pandoc.Lua.Marshaling.List (pushPandocList)
 import Text.Pandoc.Lua.Marshaling.SimpleTable
   ( SimpleTable (..), peekSimpleTable, pushSimpleTable )
-- 
cgit v1.2.3