aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-10-26 14:40:11 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2021-10-26 14:40:11 +0200
commitf56d8706312df64d3956cea0c93768b51192958e (patch)
tree974b98342187a9b6db1fac01e9a085dab493e34c /src/Text/Pandoc/Lua/Marshaling
parenta493c7029cf2bc8490d96fff04b0a0c624987601 (diff)
downloadpandoc-f56d8706312df64d3956cea0c93768b51192958e.tar.gz
Lua: marshal ListAttributes values as userdata objects
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshaling')
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/AST.hs14
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs72
2 files changed, 74 insertions, 12 deletions
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."