aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Global.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-10-20 21:40:07 +0200
committerJohn MacFarlane <jgm@berkeley.edu>2021-10-22 11:16:51 -0700
commit9e74826ba9ce4139bfdd3f057a79efa8b644e85a (patch)
tree954692554bfc024b6927de385923ab5c69a4b5df /src/Text/Pandoc/Lua/Global.hs
parente10f495a0163738a09c3fd18fce11788832c82b7 (diff)
downloadpandoc-9e74826ba9ce4139bfdd3f057a79efa8b644e85a.tar.gz
Switch to hslua-2.0
The new HsLua version takes a somewhat different approach to marshalling and unmarshalling, relying less on typeclasses and more on specialized types. This allows for better performance and improved error messages. Furthermore, new abstractions allow to document the code and exposed functions.
Diffstat (limited to 'src/Text/Pandoc/Lua/Global.hs')
-rw-r--r--src/Text/Pandoc/Lua/Global.hs45
1 files changed, 15 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Lua/Global.hs b/src/Text/Pandoc/Lua/Global.hs
index 29b788f04..df300a8c6 100644
--- a/src/Text/Pandoc/Lua/Global.hs
+++ b/src/Text/Pandoc/Lua/Global.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -14,19 +14,17 @@ module Text.Pandoc.Lua.Global
, setGlobals
) where
-import Data.Data (Data)
-import Foreign.Lua (Lua, Peekable, Pushable)
-import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
- , metatableName)
+import HsLua as Lua
import Paths_pandoc (version)
import Text.Pandoc.Class.CommonState (CommonState)
import Text.Pandoc.Definition (Pandoc (Pandoc), pandocTypesVersion)
+import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Util (addFunction)
+import Text.Pandoc.Lua.Marshaling.CommonState (pushCommonState)
+import Text.Pandoc.Lua.Marshaling.ReaderOptions (pushReaderOptions)
import Text.Pandoc.Options (ReaderOptions)
import qualified Data.Text as Text
-import qualified Foreign.Lua as Lua
-- | Permissible global Lua variables.
data Global =
@@ -40,10 +38,10 @@ data Global =
-- Cannot derive instance of Data because of CommonState
-- | Set all given globals.
-setGlobals :: [Global] -> Lua ()
+setGlobals :: [Global] -> LuaE PandocError ()
setGlobals = mapM_ setGlobal
-setGlobal :: Global -> Lua ()
+setGlobal :: Global -> LuaE PandocError ()
setGlobal global = case global of
-- This could be simplified if Global was an instance of Data.
FORMAT format -> do
@@ -53,37 +51,24 @@ setGlobal global = case global of
Lua.push pandocTypesVersion
Lua.setglobal "PANDOC_API_VERSION"
PANDOC_DOCUMENT doc -> do
- Lua.push (LazyPandoc doc)
+ pushUD typePandocLazy doc
Lua.setglobal "PANDOC_DOCUMENT"
PANDOC_READER_OPTIONS ropts -> do
- Lua.push ropts
+ pushReaderOptions ropts
Lua.setglobal "PANDOC_READER_OPTIONS"
PANDOC_SCRIPT_FILE filePath -> do
Lua.push filePath
Lua.setglobal "PANDOC_SCRIPT_FILE"
PANDOC_STATE commonState -> do
- Lua.push commonState
+ pushCommonState commonState
Lua.setglobal "PANDOC_STATE"
PANDOC_VERSION -> do
Lua.push version
Lua.setglobal "PANDOC_VERSION"
-- | Readonly and lazy pandoc objects.
-newtype LazyPandoc = LazyPandoc Pandoc
- deriving (Data)
-
-instance Pushable LazyPandoc where
- push lazyDoc = pushAnyWithMetatable pushPandocMetatable lazyDoc
- where
- pushPandocMetatable = ensureUserdataMetatable (metatableName lazyDoc) $
- addFunction "__index" indexLazyPandoc
-
-instance Peekable LazyPandoc where
- peek = Lua.peekAny
-
-indexLazyPandoc :: LazyPandoc -> String -> Lua Lua.NumResults
-indexLazyPandoc (LazyPandoc (Pandoc meta blks)) field = 1 <$
- case field of
- "blocks" -> Lua.push blks
- "meta" -> Lua.push meta
- _ -> Lua.pushnil
+typePandocLazy :: LuaError e => DocumentedType e Pandoc
+typePandocLazy = deftype "Pandoc (lazy)" []
+ [ readonly "meta" "document metadata" (push, \(Pandoc meta _) -> meta)
+ , readonly "blocks" "content blocks" (push, \(Pandoc _ blocks) -> blocks)
+ ]