aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2023-03-20 14:55:12 +0100
committerAlbert Krewinkel <[email protected]>2023-03-20 16:06:19 +0100
commit0e4b397e7081eb20c55efc051c7caddaffd697f8 (patch)
treecca1460f28beb8924848496d2b54716deaf3c0d0 /pandoc-lua-engine
parent936f44d46013bb70e693a5f2947aae097cb48b5f (diff)
Lua: fix json.encode for nested AST elements.
Ensures that objects with nested AST elements can be encoded as JSON.
Diffstat (limited to 'pandoc-lua-engine')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs23
-rw-r--r--pandoc-lua-engine/test/lua/module/pandoc-json.lua6
2 files changed, 10 insertions, 19 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
index 586867672..35825a675 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
-{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
Module : Text.Pandoc.Lua.Module.JSON
@@ -107,24 +106,10 @@ decode = defun "decode"
-- | Encode a Lua object as JSON.
encode :: LuaError e => DocumentedFunction e
encode = defun "encode"
- ### (\idx -> do
- -- ensure that there are no other objects on the stack.
- settop (nthBottom 1)
- getmetafield idx "__tojson" >>= \case
- TypeNil -> do
- -- No metamethod, use default encoder.
- value <- forcePeek $ peekValue idx
- pushLazyByteString $ Aeson.encode value
- _ -> do
- -- Try to use the field value as function
- insert (nth 2)
- call 1 1
- ltype top >>= \case
- TypeString -> pure ()
- _ -> failLua
- "Call to __tojson metamethod did not yield a string")
- <#> parameter pure "any" "object" "object to convert"
- =#> functionResult pure "string" "JSON encoding of the given `object`"
+ ### liftPure Aeson.encode
+ <#> parameter peekValue "any" "object" "object to convert"
+ =#> functionResult pushLazyByteString "string"
+ "JSON encoding of the given `object`"
#? T.unlines
["Encodes a Lua object as JSON string."
, ""
diff --git a/pandoc-lua-engine/test/lua/module/pandoc-json.lua b/pandoc-lua-engine/test/lua/module/pandoc-json.lua
index c2d4f86d4..46400d572 100644
--- a/pandoc-lua-engine/test/lua/module/pandoc-json.lua
+++ b/pandoc-lua-engine/test/lua/module/pandoc-json.lua
@@ -64,6 +64,12 @@ return {
'string'
)
end),
+ test('Nested Inline', function ()
+ assert.are_equal(
+ json.encode({spc = pandoc.Space()}),
+ '{"spc":{"t":"Space"}}'
+ )
+ end)
},
group 'decode' {