data/pandoc.lua: drop function pandoc.global_filter

The function `global_filter` was used internally to get the implicitly
defined global filter. It was of little value to end-users, but caused
unnecessary code duplication in pandoc. The function has hence been
dropped. Internally, the global filter is now received by interpreting
the global table as lua filter.

This is a Lua API change.
This commit is contained in:
Albert Krewinkel 2017-12-29 09:40:22 +01:00
parent 820ee07f72
commit 9be2c7624c
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
5 changed files with 9 additions and 68 deletions

View file

@ -23,7 +23,7 @@ THIS SOFTWARE.
-- @copyright © 2017 Albert Krewinkel
-- @license MIT
local M = {
_VERSION = "0.3.0"
_VERSION = "0.4.0"
}
local List = require 'pandoc.List'
@ -868,41 +868,6 @@ M.LowerAlpha = "LowerAlpha"
-- @see OrderedList
M.UpperAlpha = "UpperAlpha"
------------------------------------------------------------------------
-- Helper Functions
-- @section helpers
--- 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.
-- @return A list of filter functions
-- @usage
-- -- within a file defining a pandoc filter:
-- text = require 'text'
-- function Str(elem)
-- return pandoc.Str(text.upper(elem.text))
-- end
--
-- return {pandoc.global_filter()}
-- -- the above is equivalent to
-- -- return {{Str = Str}}
function M.global_filter()
local res = {}
function is_filter_function(k)
return M.Inline.constructor[k] or
M.Block.constructor[k] or
k == "Meta" or k == "Doc" or k == "Pandoc" or
k == "Block" or k == "Inline"
end
for k, v in pairs(_G) do
if is_filter_function(k) then
res[k] = v
end
end
return res
end
------------------------------------------------------------------------
-- Functions which have moved to different modules
local utils = require 'pandoc.utils'

View file

@ -1325,25 +1325,6 @@ Lua functions for pandoc scripts.
## Helper Functions
[`global_filter ()`]{#global_filter}
: Use functions defined in the global namespace to create a
pandoc filter.
Returns: A list of filter functions
Usage:
-- within a file defining a pandoc filter:
text = require 'text'
function Str(elem)
return pandoc.Str(text.upper(elem.text))
end
return {pandoc.global_filter()}
-- the above is equivalent to
-- return {{Str = Str}}
[`pipe (command, args, input)`]{#pipe}
: Runs command with arguments, passing it some input, and

View file

@ -32,7 +32,7 @@ module Text.Pandoc.Lua
, pushPandocModule
) where
import Control.Monad (when, (>=>))
import Control.Monad ((>=>))
import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..),
Status (OK), ToLuaStack (push))
import Text.Pandoc.Class (PandocIO)
@ -40,6 +40,7 @@ import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
import Text.Pandoc.Lua.Init (runPandocLua)
import Text.Pandoc.Lua.Module.Pandoc (pushModule) -- TODO: remove
import Text.Pandoc.Lua.Util (popValue)
import qualified Foreign.Lua as Lua
-- | Run the Lua filter in @filterPath@ for a transformation to target
@ -63,22 +64,17 @@ runLuaFilter' filterPath format pd = do
Lua.throwLuaError luaErrMsg
else do
newtop <- Lua.gettop
-- Use the implicitly defined global filter if nothing was returned
when (newtop - top < 1) pushGlobalFilter
luaFilters <- peek (-1)
-- Use the returned filters, or the implicitly defined global filter if
-- nothing was returned.
luaFilters <- if (newtop - top >= 1)
then peek (-1)
else Lua.getglobal "_G" *> fmap (:[]) popValue
runAll luaFilters pd
where
registerFormat = do
push format
Lua.setglobal "FORMAT"
pushGlobalFilter :: Lua ()
pushGlobalFilter = do
Lua.newtable
Lua.getglobal' "pandoc.global_filter"
Lua.call 0 1
Lua.rawseti (-2) 1
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
runAll = foldr ((>=>) . walkMWithLuaFilter) return

View file

@ -164,5 +164,3 @@ singleElement x = do
Lua.throwLuaError $
"Error while trying to get a filter's return " ++
"value from lua stack.\n" ++ err

View file

@ -37,6 +37,7 @@ module Text.Pandoc.Lua.Util
, setRawInt
, addRawInt
, raiseError
, popValue
, OrNil (..)
, PushViaCall
, pushViaCall