aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-01-03 21:23:15 +0100
committerJohn MacFarlane <[email protected]>2022-01-04 11:55:59 -0800
commit974a9d353a91c4a23a92d82d0d5a92b55018e086 (patch)
treef38352867c2c6ec611e8d7814e3a4e6d21ef288a /src
parent6a5ac90bf18f46beb6df4921f428dfb48ccb1fa8 (diff)
Lua: marshal templates as opaque userdata values
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Template.hs31
-rw-r--r--src/Text/Pandoc/Lua/Marshal/WriterOptions.hs27
2 files changed, 37 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Lua/Marshal/Template.hs b/src/Text/Pandoc/Lua/Marshal/Template.hs
new file mode 100644
index 000000000..56878b109
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/Template.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+Module : Text.Pandoc.Lua.Marshal.Template
+Copyright : © 2021-2022 Albert Krewinkel
+License : GNU GPL, version 2 or above
+Maintainer : Albert Krewinkel <[email protected]>
+
+Marshal 'Template' 'Text'.
+-}
+module Text.Pandoc.Lua.Marshal.Template
+ ( pushTemplate
+ , peekTemplate
+ , typeTemplate
+ ) where
+
+import Data.Text (Text)
+import HsLua as Lua
+import Text.DocTemplates (Template)
+
+-- | Pushes a 'Template' as a an opaque userdata value.
+pushTemplate :: LuaError e => Pusher e (Template Text)
+pushTemplate = pushUD typeTemplate
+
+-- | Retrieves a 'Template' 'Text' value from the stack.
+peekTemplate :: LuaError e => Peeker e (Template Text)
+peekTemplate = peekUD typeTemplate
+
+-- | Template object type.
+typeTemplate :: LuaError e => DocumentedType e (Template Text)
+typeTemplate = deftype "pandoc Template" [] []
diff --git a/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs b/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
index b5b1f715e..a04e0bd94 100644
--- a/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
+++ b/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
@@ -18,13 +18,12 @@ module Text.Pandoc.Lua.Marshal.WriterOptions
) where
import Control.Applicative (optional)
-import Data.Aeson as Aeson
import Data.Default (def)
import HsLua as Lua
-import HsLua.Aeson (peekValue, pushValue)
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+import Text.Pandoc.Lua.Marshal.Template (peekTemplate, pushTemplate)
+import Text.Pandoc.Lua.Util (peekViaJSON, pushViaJSON)
import Text.Pandoc.Options (WriterOptions (..))
-import Text.Pandoc.UTF8 (fromString)
--
-- Writer Options
@@ -188,9 +187,10 @@ typeWriterOptions = deftype "WriterOptions"
(pushBool, writerTableOfContents)
(peekBool, \opts x -> opts{ writerTableOfContents = x })
- -- , property "template" "Template to use"
- -- (maybe pushnil pushViaJSON, writerTemplate)
- -- (optional . peekViaJSON, \opts x -> opts{ writerTemplate = x })
+ , property "template"
+ "Template to use"
+ (maybe pushnil pushTemplate, writerTemplate)
+ (optional . peekTemplate, \opts x -> opts{ writerTemplate = x })
-- :: Maybe (Template Text)
, property "toc_depth"
@@ -239,18 +239,3 @@ peekWriterOptionsTable idx = retrieving "WriterOptions (table)" $ do
instance Pushable WriterOptions where
push = pushWriterOptions
-
--- These will become part of hslua-aeson in future versions.
-
--- | Retrieves a value from the Lua stack via JSON.
-peekViaJSON :: (Aeson.FromJSON a, LuaError e) => Peeker e a
-peekViaJSON idx = do
- value <- peekValue idx
- case fromJSON value of
- Aeson.Success x -> pure x
- Aeson.Error msg -> failPeek $ "failed to decode: " <>
- fromString msg
-
--- | Pushes a value to the Lua stack as a JSON-like value.
-pushViaJSON :: (Aeson.ToJSON a, LuaError e) => Pusher e a
-pushViaJSON = pushValue . toJSON