Lua: marshal ListAttributes values as userdata objects
This commit is contained in:
parent
a493c7029c
commit
f56d870631
8 changed files with 81 additions and 57 deletions
|
@ -349,48 +349,6 @@ function M.MetaBool(bool)
|
|||
end
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Element components
|
||||
-- @section components
|
||||
|
||||
-- ListAttributes
|
||||
M.ListAttributes = AstElement:make_subtype 'ListAttributes'
|
||||
M.ListAttributes.behavior.clone = M.types.clone.ListAttributes
|
||||
|
||||
--- Creates a set of list attributes.
|
||||
-- @function ListAttributes
|
||||
-- @tparam[opt] integer start number of the first list item
|
||||
-- @tparam[opt] string style style used for list numbering
|
||||
-- @tparam[opt] DefaultDelim|Period|OneParen|TwoParens delimiter delimiter of list numbers
|
||||
-- @treturn table list attributes table
|
||||
function M.ListAttributes:new (start, style, delimiter)
|
||||
start = start or 1
|
||||
style = style or 'DefaultStyle'
|
||||
delimiter = delimiter or 'DefaultDelim'
|
||||
return {start, style, delimiter}
|
||||
end
|
||||
M.ListAttributes.behavior._field_names = {start = 1, style = 2, delimiter = 3}
|
||||
M.ListAttributes.behavior.__eq = utils.equals
|
||||
M.ListAttributes.behavior.__index = function (t, k)
|
||||
return rawget(t, getmetatable(t)._field_names[k]) or
|
||||
getmetatable(t)[k]
|
||||
end
|
||||
M.ListAttributes.behavior.__newindex = function (t, k, v)
|
||||
if getmetatable(t)._field_names[k] then
|
||||
rawset(t, getmetatable(t)._field_names[k], v)
|
||||
else
|
||||
rawset(t, k, v)
|
||||
end
|
||||
end
|
||||
M.ListAttributes.behavior.__pairs = function(t)
|
||||
local field_names = M.ListAttributes.behavior._field_names
|
||||
local fields = {}
|
||||
for name, i in pairs(field_names) do
|
||||
fields[i] = name
|
||||
end
|
||||
return make_next_function(fields), t, nil
|
||||
end
|
||||
|
||||
--
|
||||
-- Legacy and compatibility types
|
||||
--
|
||||
|
||||
|
|
|
@ -781,6 +781,7 @@ library
|
|||
Text.Pandoc.Lua.Marshaling.CommonState,
|
||||
Text.Pandoc.Lua.Marshaling.Context,
|
||||
Text.Pandoc.Lua.Marshaling.List,
|
||||
Text.Pandoc.Lua.Marshaling.ListAttributes,
|
||||
Text.Pandoc.Lua.Marshaling.PandocError,
|
||||
Text.Pandoc.Lua.Marshaling.ReaderOptions,
|
||||
Text.Pandoc.Lua.Marshaling.SimpleTable,
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
72
src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs
Normal file
72
src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs
Normal file
|
@ -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."
|
|
@ -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,
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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 )
|
||||
|
|
Loading…
Add table
Reference in a new issue