Lua: always load lpeg as global module
This commit is contained in:
parent
a1b6bf69f2
commit
d089d799e7
2 changed files with 27 additions and 5 deletions
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Lua
|
||||
|
@ -24,6 +25,7 @@ import Text.Pandoc.Error (PandocError (PandocLuaError))
|
|||
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
|
||||
|
||||
|
@ -45,6 +47,7 @@ initLuaState = do
|
|||
liftPandocLua Lua.openlibs
|
||||
installPandocPackageSearcher
|
||||
initPandocModule
|
||||
requireGlobalModules
|
||||
loadInitScript "init.lua"
|
||||
where
|
||||
initPandocModule :: PandocLua ()
|
||||
|
@ -53,8 +56,8 @@ initLuaState = do
|
|||
ModulePandoc.pushModule
|
||||
-- register as loaded module
|
||||
liftPandocLua $ do
|
||||
Lua.pushvalue Lua.top
|
||||
Lua.getfield Lua.registryindex Lua.loaded
|
||||
Lua.pushvalue (Lua.nth 2)
|
||||
Lua.setfield (Lua.nth 2) "pandoc"
|
||||
Lua.pop 1
|
||||
-- copy constructors into registry
|
||||
|
@ -73,6 +76,29 @@ initLuaState = do
|
|||
PandocLuaError msg -> msg
|
||||
_ -> T.pack $ show err
|
||||
|
||||
requireGlobalModules :: PandocLua ()
|
||||
requireGlobalModules = liftPandocLua $ do
|
||||
Lua.pushcfunction LPeg.luaopen_lpeg_ptr
|
||||
Lua.pcall 0 1 Nothing >>= \case
|
||||
Lua.OK -> do
|
||||
-- Success. Register as a loaded module.
|
||||
-- Get table "_LOADED" from registry, add entry.
|
||||
_ <- Lua.getfield Lua.registryindex Lua.loaded
|
||||
Lua.pushvalue (Lua.nth 2)
|
||||
Lua.setfield (Lua.nth 2) "lpeg"
|
||||
Lua.pop 1 -- pop _LOADED
|
||||
|
||||
_ -> do
|
||||
-- Maybe LPeg was not compiled into the program. Try loading via
|
||||
-- the normal package loading mechanism.
|
||||
pop 1 -- ignore error message
|
||||
Lua.getglobal "require"
|
||||
Lua.pushName "lpeg"
|
||||
Lua.call 1 1 -- throws an exception if the module is not found
|
||||
|
||||
-- Module on top of stack. Register as global
|
||||
Lua.setglobal "lpeg"
|
||||
|
||||
-- | 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
|
||||
|
|
|
@ -22,7 +22,6 @@ import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, loadDefaultModule)
|
|||
import qualified HsLua as Lua
|
||||
import qualified HsLua.Module.Path as Path
|
||||
import qualified HsLua.Module.Text as Text
|
||||
import qualified Lua.LPeg as LPeg
|
||||
import qualified Text.Pandoc.Lua.Module.Pandoc as Pandoc
|
||||
import qualified Text.Pandoc.Lua.Module.MediaBag as MediaBag
|
||||
import qualified Text.Pandoc.Lua.Module.System as System
|
||||
|
@ -36,9 +35,6 @@ installPandocPackageSearcher = liftPandocLua $ do
|
|||
shiftArray
|
||||
Lua.pushHaskellFunction $ Lua.toHaskellFunction pandocPackageSearcher
|
||||
Lua.rawseti (Lua.nth 2) 1
|
||||
-- add lpeg searcher as last searcher
|
||||
Lua.pushHaskellFunction $ Lua.state >>= Lua.liftIO . LPeg.lpeg_searcher
|
||||
Lua.rawseti (Lua.nth 2) 6
|
||||
Lua.pop 1 -- remove 'package.searchers' from stack
|
||||
where
|
||||
shiftArray = forM_ [4, 3, 2, 1] $ \i -> do
|
||||
|
|
Loading…
Reference in a new issue