Text.Pandoc.Lua: support Inline and Block catch-alls

Try function `Inline`/`Block` if no other filter function of the
respective type matches an element.

Closes: #3859
This commit is contained in:
Albert Krewinkel 2017-08-22 23:12:39 +02:00
parent 56fb854ad8
commit 41baaff327
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
4 changed files with 27 additions and 7 deletions

View file

@ -808,7 +808,8 @@ function M.global_filter()
function is_filter_function(k)
return M.Inline.constructor[k] or
M.Block.constructor[k] or
k == "Meta" or k == "Doc" or k == "Pandoc"
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

View file

@ -35,7 +35,7 @@ module Text.Pandoc.Lua (LuaException (..), pushPandocModule, runLuaFilter) where
import Control.Monad (mplus, unless, when, (>=>))
import Control.Monad.Trans (MonadIO (..))
import Data.Data (DataType, Data, toConstr, showConstr, dataTypeOf,
dataTypeConstrs)
dataTypeConstrs, dataTypeName)
import Data.Foldable (foldrM)
import Data.Map (Map)
import Data.Maybe (isJust)
@ -108,10 +108,10 @@ constructorsFor :: DataType -> [String]
constructorsFor x = map show (dataTypeConstrs x)
inlineFilterNames :: [String]
inlineFilterNames = constructorsFor (dataTypeOf (Str []))
inlineFilterNames = "Inline" : constructorsFor (dataTypeOf (Str []))
blockFilterNames :: [String]
blockFilterNames = constructorsFor (dataTypeOf (Para []))
blockFilterNames = "Block" : constructorsFor (dataTypeOf (Para []))
metaFilterName :: String
metaFilterName = "Meta"
@ -126,10 +126,12 @@ newtype LuaFilterFunction = LuaFilterFunction { functionIndex :: Int }
-- | Try running a filter for the given element
tryFilter :: (Data a, FromLuaStack a, ToLuaStack a) => FunctionMap -> a -> Lua a
tryFilter fnMap x =
let filterFnName = showConstr (toConstr x) in
case Map.lookup filterFnName fnMap of
Nothing -> return x
let filterFnName = showConstr (toConstr x)
catchAllName = dataTypeName (dataTypeOf x)
in
case Map.lookup filterFnName fnMap `mplus` Map.lookup catchAllName fnMap of
Just fn -> runFilterFunction fn x
Nothing -> return x
instance FromLuaStack LuaFilter where
peek idx =

View file

@ -70,6 +70,12 @@ tests = map (localOption (QuickCheckTests 20))
"metatable-catch-all.lua"
(doc . para $ "four words, three spaces")
(doc . para $ str "7")
, testCase "Count blocks via Block-specific catch-all" $
assertFilterConversion "filtering with Block catch-all failed"
"block-count.lua"
(doc $ para "one" <> para "two")
(doc $ para "2")
]
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion

11
test/lua/block-count.lua Normal file
View file

@ -0,0 +1,11 @@
local num_blocks = 0
function Block(el)
num_blocks = num_blocks + 1
end
function Pandoc(blocks, meta)
return pandoc.Pandoc {
pandoc.Para{pandoc.Str(num_blocks)}
}
end