Lua: fix global module loading (#7701)
This commit is contained in:
parent
2b23861948
commit
c1a82896c6
1 changed files with 27 additions and 7 deletions
|
@ -14,10 +14,11 @@ module Text.Pandoc.Lua.Init
|
|||
( runLua
|
||||
) where
|
||||
|
||||
import Control.Monad (forM_, when)
|
||||
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)
|
||||
import Text.Pandoc.Class.PandocMonad (PandocMonad, readDataFile)
|
||||
|
@ -78,23 +79,42 @@ initLuaState = do
|
|||
_ -> T.pack $ show err
|
||||
|
||||
setGlobalModules :: PandocLua ()
|
||||
setGlobalModules = liftPandocLua $
|
||||
forM_ [ ("lpeg", LPeg.luaopen_lpeg_ptr)
|
||||
, ("re", LPeg.luaopen_re_ptr)
|
||||
] $
|
||||
setGlobalModules = liftPandocLua $ do
|
||||
let globalModules =
|
||||
[ ("lpeg", LPeg.luaopen_lpeg_ptr) -- must be loaded first
|
||||
, ("re", LPeg.luaopen_re_ptr) -- re depends on lpeg
|
||||
]
|
||||
loadedBuiltInModules <- fmap catMaybes . forM globalModules $
|
||||
\(pkgname, luaopen) -> do
|
||||
Lua.pushcfunction luaopen
|
||||
Lua.pcall 0 1 Nothing >>= \case
|
||||
OK -> pure () -- all good, loading succeeded
|
||||
usedBuiltIn <- Lua.pcall 0 1 Nothing >>= \case
|
||||
OK -> do -- all good, loading succeeded
|
||||
-- register as loaded module so later modules can rely on this
|
||||
Lua.getfield Lua.registryindex Lua.loaded
|
||||
Lua.pushvalue (Lua.nth 2)
|
||||
Lua.setfield (Lua.nth 2) pkgname
|
||||
Lua.pop 1 -- pop _LOADED
|
||||
return True
|
||||
_ -> do -- built-in library failed, load system lib
|
||||
Lua.pop 1 -- ignore error message
|
||||
-- Try loading via the normal package loading mechanism.
|
||||
Lua.getglobal "require"
|
||||
Lua.pushName pkgname
|
||||
Lua.call 1 1 -- Throws an exception if loading failed again!
|
||||
return False
|
||||
|
||||
-- Module on top of stack. Register as global
|
||||
Lua.setglobal pkgname
|
||||
return $ if usedBuiltIn then Just pkgname else Nothing
|
||||
|
||||
-- Remove module entry from _LOADED table in registry if we used a
|
||||
-- built-in library. This ensures that later calls to @require@ will
|
||||
-- prefer the shared library, if any.
|
||||
forM_ loadedBuiltInModules $ \pkgname -> do
|
||||
Lua.getfield Lua.registryindex Lua.loaded
|
||||
Lua.pushnil
|
||||
Lua.setfield (Lua.nth 2) pkgname
|
||||
Lua.pop 1 -- registry
|
||||
|
||||
installLpegSearcher :: PandocLua ()
|
||||
installLpegSearcher = liftPandocLua $ do
|
||||
|
|
Loading…
Add table
Reference in a new issue