aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Lua/Init.hs34
1 files changed, 20 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 23c51969c..bf87f0a41 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua
@@ -46,7 +47,6 @@ initLuaState = do
liftPandocLua Lua.openlibs
installPandocPackageSearcher
initPandocModule
- installLpegSearcher
requireGlobalModules
loadInitScript "init.lua"
where
@@ -78,25 +78,31 @@ initLuaState = do
requireGlobalModules :: PandocLua ()
requireGlobalModules = liftPandocLua $
- forM_ ["lpeg", "re"] $ \pkgname -> do
- -- Try loading via the normal package loading mechanism, which
- -- includes the custom LPeg searcher as a last resort. This
- -- means the system installation of the package, should it be
- -- available, is preferred.
+ forM_ [ ("lpeg", LPeg.luaopen_lpeg_ptr)
+ , ("re", LPeg.luaopen_re_ptr)
+ ] $
+ \(pkgname, luaopen) -> do
+ -- Try loading via the normal package loading mechanism, and
+ -- fall back to manual module loading if the normal mechanism
+ -- fails. This means the system installation of the package,
+ -- should it be available, is preferred.
Lua.getglobal "require"
Lua.pushName pkgname
- Lua.call 1 1 -- throws an exception if the module is not found
+ Lua.pcall 1 1 Nothing >>= \case
+ OK -> pure () -- all good, loading succeeded
+ _ -> do -- default mechanism failed, load included lib
+ Lua.pop 1 -- ignore error message
+ Lua.pushcfunction luaopen
+ Lua.call 0 1 -- Throws an exception if loading failed again!
+ -- Success. Add module to table @_LOADED@ in the registry
+ _ <- Lua.getfield Lua.registryindex Lua.loaded
+ Lua.pushvalue (Lua.nth 2) -- push module to top
+ Lua.setfield (Lua.nth 2) pkgname
+ Lua.pop 1 -- pop _LOADED
-- Module on top of stack. Register as global
Lua.setglobal pkgname
- installLpegSearcher :: PandocLua ()
- installLpegSearcher = liftPandocLua $ do
- Lua.getglobal' "package.searchers"
- 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