Lua: set lpeg
, re
as globals; allow shared lib access via require
The `lpeg` and `re` modules are loaded into globals of the respective name, but they are not necessarily registered as loaded packages. This ensures that - the built-in library versions are preferred when setting the globals, - a shared library is used if pandoc has been compiled without `lpeg`, and - the `require` mechanism can be used to load the shared library if available, falling back to the internal version if possible and necessary.
This commit is contained in:
parent
3ac7deadce
commit
cd91f72843
3 changed files with 52 additions and 33 deletions
|
@ -253,17 +253,26 @@ variables.
|
|||
|
||||
`lpeg`
|
||||
: This variable holds the `lpeg` module, a package based on
|
||||
Parsing Expression Grammars (PEG). It provides excellent
|
||||
Parsing Expression Grammars (PEG). It provides excellent
|
||||
parsing utilities and is documented on the official [LPeg
|
||||
homepage]. Pandoc will try to load the module through the
|
||||
normal package mechanism, and fall back to a built-in version
|
||||
if necessary.
|
||||
homepage]. Pandoc uses a built-int version of the library,
|
||||
unless it has been configured by the package maintainer to
|
||||
rely on a system-wide installation.
|
||||
|
||||
Note that the result of `require 'lpeg'` is not necessarily
|
||||
equal to this value; the `require` mechanism prefers the
|
||||
system's lpeg library over the built-in version.
|
||||
|
||||
`re`
|
||||
: Contains the LPeg.re module, which is built on top of LPeg and
|
||||
offers an implementation of a [regex engine]. Pandoc will try
|
||||
to load the module through the normal package mechanism, and
|
||||
fall back to a built-in version if necessary.
|
||||
: Contains the LPeg.re module, which is built on top of LPeg
|
||||
and offers an implementation of a [regex engine]. Pandoc
|
||||
uses a built-in version of the library, unless it has been
|
||||
configured by the package maintainer to rely on a system-wide
|
||||
installation.
|
||||
|
||||
Note that the result of `require 're` is not necessarily
|
||||
equal to this value; the `require` mechanism prefers the
|
||||
system's lpeg library over the built-in version.
|
||||
|
||||
[LPeg homepage]: http://www.inf.puc-rio.br/~roberto/lpeg/
|
||||
[regex engine]: http://www.inf.puc-rio.br/~roberto/lpeg/re.html
|
||||
|
|
|
@ -47,7 +47,8 @@ initLuaState = do
|
|||
liftPandocLua Lua.openlibs
|
||||
installPandocPackageSearcher
|
||||
initPandocModule
|
||||
requireGlobalModules
|
||||
installLpegSearcher
|
||||
setGlobalModules
|
||||
loadInitScript "init.lua"
|
||||
where
|
||||
initPandocModule :: PandocLua ()
|
||||
|
@ -76,33 +77,32 @@ initLuaState = do
|
|||
PandocLuaError msg -> msg
|
||||
_ -> T.pack $ show err
|
||||
|
||||
requireGlobalModules :: PandocLua ()
|
||||
requireGlobalModules = liftPandocLua $
|
||||
setGlobalModules :: PandocLua ()
|
||||
setGlobalModules = liftPandocLua $
|
||||
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.pcall 1 1 Nothing >>= \case
|
||||
Lua.pushcfunction luaopen
|
||||
Lua.pcall 0 1 Nothing >>= \case
|
||||
OK -> pure () -- all good, loading succeeded
|
||||
_ -> do -- default mechanism failed, load included lib
|
||||
_ -> do -- built-in library failed, load system 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
|
||||
-- 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!
|
||||
|
||||
-- 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
|
||||
|
|
|
@ -17,7 +17,7 @@ module Tests.Lua ( runLuaTest, tests ) where
|
|||
import Control.Monad (when)
|
||||
import HsLua as Lua hiding (Operation (Div), error)
|
||||
import System.FilePath ((</>))
|
||||
import Test.Tasty (TestTree, localOption)
|
||||
import Test.Tasty (TestTree, testGroup, localOption)
|
||||
import Test.Tasty.HUnit ((@=?), Assertion, HasCallStack, assertEqual, testCase)
|
||||
import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty)
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -211,13 +211,23 @@ tests = map (localOption (QuickCheckTests 20))
|
|||
ty <- Lua.ltype Lua.top
|
||||
Lua.liftIO $ assertEqual "module should be a table" Lua.TypeTable ty
|
||||
|
||||
, testCase "module 'lpeg' is loaded into a global" . runLuaTest $ do
|
||||
s <- Lua.dostring "assert(type(lpeg)=='table');assert(lpeg==require'lpeg')"
|
||||
Lua.liftIO $ Lua.OK @=? s
|
||||
, testGroup "global modules"
|
||||
[ testCase "module 'lpeg' is loaded into a global" . runLuaTest $ do
|
||||
s <- Lua.dostring "assert(type(lpeg)=='table')"
|
||||
Lua.liftIO $ Lua.OK @=? s
|
||||
|
||||
, testCase "module 're' is available" . runLuaTest $ do
|
||||
s <- Lua.dostring "require 're'"
|
||||
Lua.liftIO $ Lua.OK @=? s
|
||||
, testCase "module 're' is loaded into a global" . runLuaTest $ do
|
||||
s <- Lua.dostring "assert(type(re)=='table')"
|
||||
Lua.liftIO $ Lua.OK @=? s
|
||||
|
||||
, testCase "module 'lpeg' is available via `require`" . runLuaTest $ do
|
||||
s <- Lua.dostring "require 'lpeg'"
|
||||
Lua.liftIO $ Lua.OK @=? s
|
||||
|
||||
, testCase "module 're' is available via `require`" . runLuaTest $ do
|
||||
s <- Lua.dostring "require 're'"
|
||||
Lua.liftIO $ Lua.OK @=? s
|
||||
]
|
||||
|
||||
, testCase "informative error messages" . runLuaTest $ do
|
||||
Lua.pushboolean True
|
||||
|
|
Loading…
Add table
Reference in a new issue