aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Init.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Init.hs')
-rw-r--r--src/Text/Pandoc/Lua/Init.hs50
1 files changed, 20 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 2f113bff2..835da1fc9 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -17,7 +17,6 @@ module Text.Pandoc.Lua.Init
import Control.Monad (forM, forM_, when)
import Control.Monad.Catch (throwM, try)
import Control.Monad.Trans (MonadIO (..))
-import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
import Data.Maybe (catMaybes)
import HsLua as Lua hiding (status, try)
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
@@ -27,7 +26,6 @@ import Text.Pandoc.Lua.Packages (installPandocPackageSearcher)
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua)
import qualified Data.Text as T
import qualified Lua.LPeg as LPeg
-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
@@ -42,6 +40,19 @@ runLua luaOp = do
liftIO $ setForeignEncoding enc
return res
+-- | Modules that are loaded at startup and assigned to fields in the
+-- pandoc module.
+loadedModules :: [(Name, Name)]
+loadedModules =
+ [ ("pandoc.List", "List")
+ , ("pandoc.mediabag", "mediabag")
+ , ("pandoc.path", "path")
+ , ("pandoc.system", "system")
+ , ("pandoc.types", "types")
+ , ("pandoc.utils", "utils")
+ , ("text", "text")
+ ]
+
-- | Initialize the lua state with all required values
initLuaState :: PandocLua ()
initLuaState = do
@@ -61,9 +72,13 @@ initLuaState = do
Lua.getfield Lua.registryindex Lua.loaded
Lua.pushvalue (Lua.nth 2)
Lua.setfield (Lua.nth 2) "pandoc"
- Lua.pop 1
- -- copy constructors into registry
- putConstructorsInRegistry
+ Lua.pop 1 -- remove LOADED table
+ -- load modules and add them to the `pandoc` module table.
+ liftPandocLua $ forM_ loadedModules $ \(pkgname, fieldname) -> do
+ Lua.getglobal "require"
+ Lua.pushName pkgname
+ Lua.call 1 1
+ Lua.setfield (nth 2) fieldname
-- assign module to global variable
liftPandocLua $ Lua.setglobal "pandoc"
@@ -122,28 +137,3 @@ initLuaState = do
Lua.pushHaskellFunction $ Lua.state >>= liftIO . LPeg.lpeg_searcher
Lua.rawseti (Lua.nth 2) . (+1) . fromIntegral =<< Lua.rawlen (Lua.nth 2)
Lua.pop 1 -- remove 'package.searchers' from stack
-
--- | AST elements are marshaled via normal constructor functions in the
--- @pandoc@ module. However, accessing Lua globals from Haskell is
--- expensive (due to error handling). Accessing the Lua registry is much
--- cheaper, which is why the constructor functions are copied into the
--- Lua registry and called from there.
---
--- This function expects the @pandoc@ module to be at the top of the
--- stack.
-putConstructorsInRegistry :: PandocLua ()
-putConstructorsInRegistry = liftPandocLua $ do
- constrsToReg $ Pandoc.Meta mempty
- constrsToReg $ Pandoc.MetaList mempty
- putInReg "List" -- pandoc.List
- putInReg "SimpleTable" -- helper for backward-compatible table handling
- where
- constrsToReg :: Data a => a -> LuaE PandocError ()
- constrsToReg = mapM_ (putInReg . showConstr) . dataTypeConstrs . dataTypeOf
-
- putInReg :: String -> LuaE PandocError ()
- putInReg name = do
- Lua.push ("pandoc." ++ name) -- name in registry
- Lua.push name -- in pandoc module
- Lua.rawget (Lua.nth 3)
- Lua.rawset Lua.registryindex