aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/PandocLua.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-11-28 02:08:01 +0100
committerGitHub <noreply@github.com>2021-11-27 17:08:01 -0800
commit3692a1d1e83703fbf235214f2838cd92683c625c (patch)
tree2eb377285e1ca485c03ea60eef1d92ff58827666 /src/Text/Pandoc/Lua/PandocLua.hs
parent0d25232bbf2998cccf6ca4b1dc6e8d6f36eb9c60 (diff)
downloadpandoc-3692a1d1e83703fbf235214f2838cd92683c625c.tar.gz
Lua: use package pandoc-lua-marshal (#7719)
The marshaling functions for pandoc's AST are extracted into a separate package. The package comes with a number of changes: - Pandoc's List module was rewritten in C, thereby improving error messages. - Lists of `Block` and `Inline` elements are marshaled using the new list types `Blocks` and `Inlines`, respectively. These types currently behave identical to the generic List type, but give better error messages. This also opens up the possibility of adding element-specific methods to these lists in the future. - Elements of type `MetaValue` are no longer pushed as values which have `.t` and `.tag` properties. This was already true for `MetaString` and `MetaBool` values, which are still marshaled as Lua strings and booleans, respectively. Affected values: + `MetaBlocks` values are marshaled as a `Blocks` list; + `MetaInlines` values are marshaled as a `Inlines` list; + `MetaList` values are marshaled as a generic pandoc `List`s. + `MetaMap` values are marshaled as plain tables and no longer given any metatable. - The test suite for marshaled objects and their constructors has been extended and improved. - A bug in Citation objects, where setting a citation's suffix modified it's prefix, has been fixed.
Diffstat (limited to 'src/Text/Pandoc/Lua/PandocLua.hs')
-rw-r--r--src/Text/Pandoc/Lua/PandocLua.hs25
1 files changed, 3 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Lua/PandocLua.hs b/src/Text/Pandoc/Lua/PandocLua.hs
index 6c2ebc622..71fdf8d5c 100644
--- a/src/Text/Pandoc/Lua/PandocLua.hs
+++ b/src/Text/Pandoc/Lua/PandocLua.hs
@@ -22,20 +22,18 @@ module Text.Pandoc.Lua.PandocLua
( PandocLua (..)
, runPandocLua
, liftPandocLua
- , loadDefaultModule
) where
import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
import Control.Monad.Except (MonadError (catchError, throwError))
import Control.Monad.IO.Class (MonadIO)
import HsLua as Lua
-import Text.Pandoc.Class.PandocMonad (PandocMonad (..), readDefaultDataFile)
-import Text.Pandoc.Error (PandocError (PandocLuaError))
+import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
+import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
-import Text.Pandoc.Lua.Marshaling.CommonState (peekCommonState)
+import Text.Pandoc.Lua.Marshal.CommonState (peekCommonState)
import qualified Control.Monad.Catch as Catch
-import qualified Data.Text as T
import qualified Text.Pandoc.Class.IO as IO
-- | Type providing access to both, pandoc and Lua operations.
@@ -75,23 +73,6 @@ instance {-# OVERLAPPING #-} Exposable PandocError (PandocLua NumResults) where
instance Pushable a => Exposable PandocError (PandocLua a) where
partialApply _narg x = 1 <$ (unPandocLua x >>= Lua.push)
--- | Load a pure Lua module included with pandoc. Leaves the result on
--- the stack and returns @NumResults 1@.
---
--- The script is loaded from the default data directory. We do not load
--- from data directories supplied via command line, as this could cause
--- scripts to be executed even though they had not been passed explicitly.
-loadDefaultModule :: String -> PandocLua NumResults
-loadDefaultModule name = do
- script <- readDefaultDataFile (name <> ".lua")
- result <- liftPandocLua $ Lua.dostring script
- if result == Lua.OK
- then return (1 :: NumResults)
- else do
- msg <- liftPandocLua Lua.popValue
- let err = "Error while loading `" <> name <> "`.\n" <> msg
- throwError $ PandocLuaError (T.pack err)
-
-- | Global variables which should always be set.
defaultGlobals :: PandocMonad m => m [Global]
defaultGlobals = do