Lua: load re
module available into global of the same name
This commit is contained in:
parent
fe113dd5fa
commit
ebf7f782d3
2 changed files with 30 additions and 27 deletions
|
@ -245,15 +245,28 @@ variables.
|
|||
variable is of type [CommonState] and
|
||||
is read-only.
|
||||
|
||||
## Global modules
|
||||
`pandoc`
|
||||
: The *pandoc* module, described in the next section, is
|
||||
available through the global `pandoc`. The other modules
|
||||
described herein are loaded as subfields under their
|
||||
respective name.
|
||||
|
||||
There are two modules which are preloaded and accessible through
|
||||
global variables. The first is `pandoc`, which is described in the
|
||||
next section. The other is `lpeg`, a package based on Parsing
|
||||
Expression Grammars (PEG). See the official [LPeg homepage] for
|
||||
details.
|
||||
`lpeg`
|
||||
: This variable holds the `lpeg` module, a package based on
|
||||
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.
|
||||
|
||||
`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.
|
||||
|
||||
[LPeg homepage]: http://www.inf.puc-rio.br/~roberto/lpeg/
|
||||
[regex engine]: http://www.inf.puc-rio.br/~roberto/lpeg/re.html
|
||||
|
||||
# Pandoc Module
|
||||
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Lua
|
||||
|
@ -14,7 +13,7 @@ module Text.Pandoc.Lua.Init
|
|||
( runLua
|
||||
) where
|
||||
|
||||
import Control.Monad (when)
|
||||
import Control.Monad (forM_, when)
|
||||
import Control.Monad.Catch (throwM, try)
|
||||
import Control.Monad.Trans (MonadIO (..))
|
||||
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
|
||||
|
@ -46,8 +45,8 @@ initLuaState :: PandocLua ()
|
|||
initLuaState = do
|
||||
liftPandocLua Lua.openlibs
|
||||
installPandocPackageSearcher
|
||||
installLpegSearcher
|
||||
initPandocModule
|
||||
installLpegSearcher
|
||||
requireGlobalModules
|
||||
loadInitScript "init.lua"
|
||||
where
|
||||
|
@ -78,27 +77,18 @@ initLuaState = do
|
|||
_ -> 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
|
||||
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.
|
||||
Lua.getglobal "require"
|
||||
Lua.pushName "lpeg"
|
||||
Lua.pushName pkgname
|
||||
Lua.call 1 1 -- throws an exception if the module is not found
|
||||
|
||||
-- Module on top of stack. Register as global
|
||||
Lua.setglobal "lpeg"
|
||||
-- Module on top of stack. Register as global
|
||||
Lua.setglobal pkgname
|
||||
|
||||
installLpegSearcher :: PandocLua ()
|
||||
installLpegSearcher = liftPandocLua $ do
|
||||
|
|
Loading…
Add table
Reference in a new issue