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:
parent
56fb854ad8
commit
41baaff327
4 changed files with 27 additions and 7 deletions
|
@ -808,7 +808,8 @@ function M.global_filter()
|
||||||
function is_filter_function(k)
|
function is_filter_function(k)
|
||||||
return M.Inline.constructor[k] or
|
return M.Inline.constructor[k] or
|
||||||
M.Block.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
|
end
|
||||||
for k, v in pairs(_G) do
|
for k, v in pairs(_G) do
|
||||||
if is_filter_function(k) then
|
if is_filter_function(k) then
|
||||||
|
|
|
@ -35,7 +35,7 @@ module Text.Pandoc.Lua (LuaException (..), pushPandocModule, runLuaFilter) where
|
||||||
import Control.Monad (mplus, unless, when, (>=>))
|
import Control.Monad (mplus, unless, when, (>=>))
|
||||||
import Control.Monad.Trans (MonadIO (..))
|
import Control.Monad.Trans (MonadIO (..))
|
||||||
import Data.Data (DataType, Data, toConstr, showConstr, dataTypeOf,
|
import Data.Data (DataType, Data, toConstr, showConstr, dataTypeOf,
|
||||||
dataTypeConstrs)
|
dataTypeConstrs, dataTypeName)
|
||||||
import Data.Foldable (foldrM)
|
import Data.Foldable (foldrM)
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust)
|
||||||
|
@ -108,10 +108,10 @@ constructorsFor :: DataType -> [String]
|
||||||
constructorsFor x = map show (dataTypeConstrs x)
|
constructorsFor x = map show (dataTypeConstrs x)
|
||||||
|
|
||||||
inlineFilterNames :: [String]
|
inlineFilterNames :: [String]
|
||||||
inlineFilterNames = constructorsFor (dataTypeOf (Str []))
|
inlineFilterNames = "Inline" : constructorsFor (dataTypeOf (Str []))
|
||||||
|
|
||||||
blockFilterNames :: [String]
|
blockFilterNames :: [String]
|
||||||
blockFilterNames = constructorsFor (dataTypeOf (Para []))
|
blockFilterNames = "Block" : constructorsFor (dataTypeOf (Para []))
|
||||||
|
|
||||||
metaFilterName :: String
|
metaFilterName :: String
|
||||||
metaFilterName = "Meta"
|
metaFilterName = "Meta"
|
||||||
|
@ -126,10 +126,12 @@ newtype LuaFilterFunction = LuaFilterFunction { functionIndex :: Int }
|
||||||
-- | Try running a filter for the given element
|
-- | Try running a filter for the given element
|
||||||
tryFilter :: (Data a, FromLuaStack a, ToLuaStack a) => FunctionMap -> a -> Lua a
|
tryFilter :: (Data a, FromLuaStack a, ToLuaStack a) => FunctionMap -> a -> Lua a
|
||||||
tryFilter fnMap x =
|
tryFilter fnMap x =
|
||||||
let filterFnName = showConstr (toConstr x) in
|
let filterFnName = showConstr (toConstr x)
|
||||||
case Map.lookup filterFnName fnMap of
|
catchAllName = dataTypeName (dataTypeOf x)
|
||||||
Nothing -> return x
|
in
|
||||||
|
case Map.lookup filterFnName fnMap `mplus` Map.lookup catchAllName fnMap of
|
||||||
Just fn -> runFilterFunction fn x
|
Just fn -> runFilterFunction fn x
|
||||||
|
Nothing -> return x
|
||||||
|
|
||||||
instance FromLuaStack LuaFilter where
|
instance FromLuaStack LuaFilter where
|
||||||
peek idx =
|
peek idx =
|
||||||
|
|
|
@ -70,6 +70,12 @@ tests = map (localOption (QuickCheckTests 20))
|
||||||
"metatable-catch-all.lua"
|
"metatable-catch-all.lua"
|
||||||
(doc . para $ "four words, three spaces")
|
(doc . para $ "four words, three spaces")
|
||||||
(doc . para $ str "7")
|
(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
|
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
|
||||||
|
|
11
test/lua/block-count.lua
Normal file
11
test/lua/block-count.lua
Normal 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
|
Loading…
Reference in a new issue