aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Init.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/Init.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/Init.hs')
-rw-r--r--src/Text/Pandoc/Lua/Init.hs37
1 files changed, 20 insertions, 17 deletions
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 94691666c..a9c3695a4 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -13,23 +14,23 @@ module Text.Pandoc.Lua.Init
) where
import Control.Monad (when)
-import Control.Monad.Catch (try)
+import Control.Monad.Catch (throwM, try)
import Control.Monad.Trans (MonadIO (..))
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
-import Foreign.Lua (Lua)
+import HsLua as Lua hiding (status, try)
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
-import Text.Pandoc.Class.PandocMonad (readDataFile, PandocMonad)
-import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Class.PandocMonad (PandocMonad, readDataFile)
+import Text.Pandoc.Error (PandocError (PandocLuaError))
import Text.Pandoc.Lua.Packages (installPandocPackageSearcher)
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua)
-import Text.Pandoc.Lua.Util (throwTopMessageAsError')
-import qualified Foreign.Lua as Lua
+import qualified Data.Text as T
import qualified Text.Pandoc.Definition as Pandoc
import qualified Text.Pandoc.Lua.Module.Pandoc as ModulePandoc
-- | Run the lua interpreter, using pandoc's default way of environment
-- initialization.
-runLua :: (PandocMonad m, MonadIO m) => Lua a -> m (Either PandocError a)
+runLua :: (PandocMonad m, MonadIO m)
+ => LuaE PandocError a -> m (Either PandocError a)
runLua luaOp = do
enc <- liftIO $ getForeignEncoding <* setForeignEncoding utf8
res <- runPandocLua . try $ do
@@ -52,9 +53,9 @@ initLuaState = do
ModulePandoc.pushModule
-- register as loaded module
liftPandocLua $ do
- Lua.pushvalue Lua.stackTop
- Lua.getfield Lua.registryindex Lua.loadedTableRegistryField
- Lua.setfield (Lua.nthFromTop 2) "pandoc"
+ Lua.pushvalue Lua.top
+ Lua.getfield Lua.registryindex Lua.loaded
+ Lua.setfield (Lua.nth 2) "pandoc"
Lua.pop 1
-- copy constructors into registry
putConstructorsInRegistry
@@ -65,10 +66,12 @@ initLuaState = do
loadInitScript scriptFile = do
script <- readDataFile scriptFile
status <- liftPandocLua $ Lua.dostring script
- when (status /= Lua.OK) . liftPandocLua $
- throwTopMessageAsError'
- (("Couldn't load '" ++ scriptFile ++ "'.\n") ++)
-
+ when (status /= Lua.OK) . liftPandocLua $ do
+ err <- popException
+ let prefix = "Couldn't load '" <> T.pack scriptFile <> "':\n"
+ throwM . PandocLuaError . (prefix <>) $ case err of
+ PandocLuaError msg -> msg
+ _ -> T.pack $ show err
-- | AST elements are marshaled via normal constructor functions in the
-- @pandoc@ module. However, accessing Lua globals from Haskell is
@@ -91,12 +94,12 @@ putConstructorsInRegistry = liftPandocLua $ do
putInReg "List" -- pandoc.List
putInReg "SimpleTable" -- helper for backward-compatible table handling
where
- constrsToReg :: Data a => a -> Lua ()
+ constrsToReg :: Data a => a -> LuaE PandocError ()
constrsToReg = mapM_ (putInReg . showConstr) . dataTypeConstrs . dataTypeOf
- putInReg :: String -> Lua ()
+ putInReg :: String -> LuaE PandocError ()
putInReg name = do
Lua.push ("pandoc." ++ name) -- name in registry
Lua.push name -- in pandoc module
- Lua.rawget (Lua.nthFromTop 3)
+ Lua.rawget (Lua.nth 3)
Lua.rawset Lua.registryindex