aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Global.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Global.hs')
-rw-r--r--src/Text/Pandoc/Lua/Global.hs52
1 files changed, 16 insertions, 36 deletions
diff --git a/src/Text/Pandoc/Lua/Global.hs b/src/Text/Pandoc/Lua/Global.hs
index 29b788f04..cf82890c6 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,19 @@ 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 HsLua.Module.Version (pushVersion)
import Paths_pandoc (version)
import Text.Pandoc.Class.CommonState (CommonState)
-import Text.Pandoc.Definition (Pandoc (Pandoc), pandocTypesVersion)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Util (addFunction)
+import Text.Pandoc.Definition (Pandoc, pandocTypesVersion)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.Marshal.CommonState (pushCommonState)
+import Text.Pandoc.Lua.Marshal.Pandoc (pushPandoc)
+import Text.Pandoc.Lua.Marshal.ReaderOptions (pushReaderOptionsReadonly)
+import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Options (ReaderOptions)
import qualified Data.Text as Text
-import qualified Foreign.Lua as Lua
-- | Permissible global Lua variables.
data Global =
@@ -40,50 +40,30 @@ 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
Lua.push format
Lua.setglobal "FORMAT"
PANDOC_API_VERSION -> do
- Lua.push pandocTypesVersion
+ pushVersion pandocTypesVersion
Lua.setglobal "PANDOC_API_VERSION"
PANDOC_DOCUMENT doc -> do
- Lua.push (LazyPandoc doc)
+ pushPandoc doc
Lua.setglobal "PANDOC_DOCUMENT"
PANDOC_READER_OPTIONS ropts -> do
- Lua.push ropts
+ pushReaderOptionsReadonly 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
+ pushVersion 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