Merge pull request #3952 from tarleb/lua-pipe-wrapper

Lua pipe wrapper
This commit is contained in:
John MacFarlane 2017-10-03 15:36:23 -04:00 committed by GitHub
commit 582169cdca
2 changed files with 34 additions and 15 deletions

View file

@ -782,7 +782,7 @@ M.UpperAlpha = "UpperAlpha"
-- assert(block.content[1].t == "Emph")
function M.read(markup, format)
format = format or "markdown"
local pd = pandoc.__read(format, markup)
local pd = pandoc._read(format, markup)
if type(pd) == "string" then
error(pd)
else
@ -790,6 +790,29 @@ function M.read(markup, format)
end
end
--- Runs command with arguments, passing it some input, and returns the output.
-- @treturn string Output of command.
-- @usage
-- local ec, output = pandoc.pipe("sed", {"-e","s/a/b/"}, "abc")
function M.pipe (command, args, input)
local ec, output = pandoc._pipe(command, args, input)
if ec ~= 0 then
err = setmetatable(
{ command = command, error_code = ec, output = output},
{ __tostring = function(e)
return "Error running " .. e.command
.. " (error code " .. e.error_code .. "): "
.. e.output
end
}
)
-- TODO: drop the wrapping call to `tostring` as soon as hslua supports
-- non-string error objects.
error(tostring(err))
end
return output
end
--- Use functions defined in the global namespace to create a pandoc filter.
-- All globally defined functions which have names of pandoc elements are
-- collected into a new table.

View file

@ -41,6 +41,7 @@ import Data.IORef
import Data.Maybe (fromMaybe)
import Data.Text (pack)
import Foreign.Lua (Lua, FromLuaStack, ToLuaStack, NumResults, liftIO)
import Foreign.Lua.FunctionCalling (ToHaskellFunction)
import Text.Pandoc.Class (readDataFile, runIO,
runIOorExplode, setUserDataDir, CommonState(..),
putCommonState, fetchItem, setMediaBag)
@ -62,15 +63,9 @@ pushPandocModule datadir = do
script <- liftIO (pandocModuleScript datadir)
status <- Lua.loadstring script
unless (status /= Lua.OK) $ Lua.call 0 1
Lua.push "__read"
Lua.pushHaskellFunction readDoc
Lua.rawset (-3)
Lua.push "sha1"
Lua.pushHaskellFunction sha1HashFn
Lua.rawset (-3)
Lua.push "pipe"
Lua.pushHaskellFunction pipeFn
Lua.rawset (-3)
addFunction "_pipe" pipeFn
addFunction "_read" readDoc
addFunction "sha1" sha1HashFn
-- | Get the string representation of the pandoc module
pandocModuleScript :: Maybe FilePath -> IO String
@ -102,11 +97,12 @@ pushMediaBagModule commonState mediaBagRef = do
addFunction "list" (mediaDirectoryFn mediaBagRef)
addFunction "fetch" (fetch commonState mediaBagRef)
return ()
where
addFunction name fn = do
Lua.push name
Lua.pushHaskellFunction fn
Lua.rawset (-3)
addFunction :: ToHaskellFunction a => String -> a -> Lua ()
addFunction name fn = do
Lua.push name
Lua.pushHaskellFunction fn
Lua.rawset (-3)
sha1HashFn :: BL.ByteString
-> Lua NumResults