aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-04 16:53:59 +0200
committerAlbert Krewinkel <[email protected]>2022-10-04 16:55:51 +0200
commit6ad05b74514f23a023718e199e7ef3c0509e99b2 (patch)
tree8cf33efd6335cf8d87883a6dd2a7320dbb320d91 /pandoc-lua-engine/src/Text
parent42566afa3f222d55ac2b59c66b775578522a610c (diff)
Lua: ensure that extensions marshaling is consistent.
Diffstat (limited to 'pandoc-lua-engine/src/Text')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Extensions.hs32
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs8
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs8
3 files changed, 38 insertions, 10 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Extensions.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Extensions.hs
new file mode 100644
index 000000000..99e5bc442
--- /dev/null
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Extensions.hs
@@ -0,0 +1,32 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshaling.Extensions
+ Copyright : © 2022 Albert Krewinkel
+ License : GPL-2.0-or-later
+ Maintainer : Albert Krewinkel <[email protected]>
+
+Marshaling functions and instance for 'Extensions'.
+-}
+module Text.Pandoc.Lua.Marshal.Extensions
+ ( peekExtensions
+ , pushExtensions
+ ) where
+
+import HsLua
+import Text.Pandoc.Extensions (Extensions)
+
+-- | Retrieves an 'Extensions' set from the Lua stack.
+peekExtensions :: LuaError e => Peeker e Extensions
+peekExtensions = peekViaJSON
+{-# INLINE peekExtensions #-}
+
+-- | Pushes a set of 'Extensions' to the top of the Lua stack.
+pushExtensions :: LuaError e => Pusher e Extensions
+pushExtensions = pushViaJSON
+{-# INLINE pushExtensions #-}
+
+instance Peekable Extensions where
+ safepeek = peekExtensions
+
+instance Pushable Extensions where
+ push = pushExtensions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
index bec7d81bf..0d23e0fb7 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
@@ -22,9 +22,7 @@ module Text.Pandoc.Lua.Marshal.ReaderOptions
import Data.Default (def)
import HsLua as Lua
-#if !MIN_VERSION_hslua(2,2,0)
-import HsLua.Aeson (peekViaJSON, pushViaJSON)
-#endif
+import Text.Pandoc.Lua.Marshal.Extensions (peekExtensions, pushExtensions)
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
import Text.Pandoc.Options (ReaderOptions (..))
@@ -91,8 +89,8 @@ readerOptionsMembers =
(pushText, readerDefaultImageExtension)
(peekText, \opts x -> opts{ readerDefaultImageExtension = x })
, property "extensions" ""
- (pushViaJSON, readerExtensions)
- (peekViaJSON, \opts x -> opts{ readerExtensions = x })
+ (pushExtensions, readerExtensions)
+ (peekExtensions, \opts x -> opts{ readerExtensions = x })
, property "indented_code_classes" ""
(pushPandocList pushText, readerIndentedCodeClasses)
(peekList peekText, \opts x -> opts{ readerIndentedCodeClasses = x })
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
index 86df682c5..bbd878907 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
@@ -21,9 +21,7 @@ module Text.Pandoc.Lua.Marshal.WriterOptions
import Control.Applicative (optional)
import Data.Default (def)
import HsLua as Lua
-#if !MIN_VERSION_hslua(2,2,0)
-import HsLua.Aeson (peekViaJSON, pushViaJSON)
-#endif
+import Text.Pandoc.Lua.Marshal.Extensions (peekExtensions, pushExtensions)
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
import Text.Pandoc.Lua.Marshal.Template (peekTemplate, pushTemplate)
import Text.Pandoc.Options (WriterOptions (..))
@@ -97,8 +95,8 @@ typeWriterOptions = deftype "WriterOptions"
, property "extensions"
"Markdown extensions that can be used"
- (pushViaJSON, writerExtensions)
- (peekViaJSON, \opts x -> opts{ writerExtensions = x })
+ (pushExtensions, writerExtensions)
+ (peekExtensions, \opts x -> opts{ writerExtensions = x })
, property "highlight_style"
"Style to use for highlighting (nil = no highlighting)"