Lua: register script name in global variable
The name of the Lua script which is executed is made available in the global Lua variable `PANDOC_SCRIPT_FILE`, both for Lua filters and custom writers. Closes: #4393
This commit is contained in:
parent
39dd7c794b
commit
b5bd8a9461
5 changed files with 21 additions and 4 deletions
|
@ -37,7 +37,7 @@ import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..),
|
|||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Definition (Pandoc)
|
||||
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
|
||||
import Text.Pandoc.Lua.Init (runPandocLua)
|
||||
import Text.Pandoc.Lua.Init (runPandocLua, registerScriptPath)
|
||||
import Text.Pandoc.Lua.Util (popValue)
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
import qualified Foreign.Lua as Lua
|
||||
|
@ -55,11 +55,12 @@ runLuaFilter' :: ReaderOptions -> FilePath -> String
|
|||
runLuaFilter' ropts filterPath format pd = do
|
||||
registerFormat
|
||||
registerReaderOptions
|
||||
registerScriptPath filterPath
|
||||
top <- Lua.gettop
|
||||
stat <- Lua.dofile filterPath
|
||||
if stat /= OK
|
||||
then do
|
||||
luaErrMsg <- peek (-1) <* Lua.pop 1
|
||||
luaErrMsg <- popValue
|
||||
Lua.throwLuaError luaErrMsg
|
||||
else do
|
||||
newtop <- Lua.gettop
|
||||
|
|
|
@ -31,6 +31,7 @@ module Text.Pandoc.Lua.Init
|
|||
, runPandocLua
|
||||
, initLuaState
|
||||
, luaPackageParams
|
||||
, registerScriptPath
|
||||
) where
|
||||
|
||||
import Control.Monad.Trans (MonadIO (..))
|
||||
|
@ -88,6 +89,11 @@ initLuaState luaPkgParams = do
|
|||
loadScriptFromDataDir (luaPkgDataDir luaPkgParams) "init.lua"
|
||||
putConstructorsInRegistry
|
||||
|
||||
registerScriptPath :: FilePath -> Lua ()
|
||||
registerScriptPath fp = do
|
||||
Lua.push fp
|
||||
Lua.setglobal "PANDOC_SCRIPT_FILE"
|
||||
|
||||
putConstructorsInRegistry :: Lua ()
|
||||
putConstructorsInRegistry = do
|
||||
Lua.getglobal "pandoc"
|
||||
|
@ -101,7 +107,7 @@ putConstructorsInRegistry = do
|
|||
Lua.pop 1
|
||||
where
|
||||
constrsToReg :: Data a => a -> Lua ()
|
||||
constrsToReg = mapM_ putInReg . map showConstr . dataTypeConstrs . dataTypeOf
|
||||
constrsToReg = mapM_ (putInReg . showConstr) . dataTypeConstrs . dataTypeOf
|
||||
|
||||
putInReg :: String -> Lua ()
|
||||
putInReg name = do
|
||||
|
|
|
@ -44,7 +44,7 @@ import Foreign.Lua.Api
|
|||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Error
|
||||
import Text.Pandoc.Lua.Init (runPandocLua)
|
||||
import Text.Pandoc.Lua.Init (runPandocLua, registerScriptPath)
|
||||
import Text.Pandoc.Lua.StackInstances ()
|
||||
import Text.Pandoc.Lua.Util (addValue, dostring')
|
||||
import Text.Pandoc.Options
|
||||
|
@ -106,6 +106,7 @@ writeCustom :: FilePath -> WriterOptions -> Pandoc -> PandocIO Text
|
|||
writeCustom luaFile opts doc@(Pandoc meta _) = do
|
||||
luaScript <- liftIO $ UTF8.readFile luaFile
|
||||
res <- runPandocLua $ do
|
||||
registerScriptPath luaFile
|
||||
stat <- dostring' luaScript
|
||||
-- check for error in lua script (later we'll change the return type
|
||||
-- to handle this more gracefully):
|
||||
|
|
|
@ -111,6 +111,12 @@ tests = map (localOption (QuickCheckTests 20))
|
|||
, plain (str "to_roman_numeral: OK")
|
||||
])
|
||||
|
||||
, testCase "Script filename is set" $
|
||||
assertFilterConversion "unexpected script name"
|
||||
"script-name.lua"
|
||||
(doc $ para "ignored")
|
||||
(doc $ para "lua/script-name.lua")
|
||||
|
||||
, testCase "Pandoc version is set" . runPandocLua' $ do
|
||||
Lua.getglobal' "table.concat"
|
||||
Lua.getglobal "PANDOC_VERSION"
|
||||
|
|
3
test/lua/script-name.lua
Normal file
3
test/lua/script-name.lua
Normal file
|
@ -0,0 +1,3 @@
|
|||
function Para (_)
|
||||
return pandoc.Para{pandoc.Str(PANDOC_SCRIPT_FILE)}
|
||||
end
|
Loading…
Add table
Reference in a new issue