Text.Pandoc.Lua: respect metatable when getting filters
This change makes it possible to define a catch-all function using lua's metatable lookup functionality. function catch_all(el) … end return { setmetatable({}, {__index = function(_) return catch_all end}) } A further effect of this change is that the map with filter functions now only contains functions corresponding to AST element constructors.
This commit is contained in:
parent
915f201c78
commit
56fb854ad8
3 changed files with 102 additions and 52 deletions
|
@ -32,50 +32,50 @@ Pandoc lua utils.
|
||||||
-}
|
-}
|
||||||
module Text.Pandoc.Lua (LuaException (..), pushPandocModule, runLuaFilter) where
|
module Text.Pandoc.Lua (LuaException (..), pushPandocModule, runLuaFilter) where
|
||||||
|
|
||||||
import Control.Monad (unless, when, (>=>), mplus)
|
import Control.Monad (mplus, unless, when, (>=>))
|
||||||
import Control.Monad.Trans (MonadIO (..))
|
import Control.Monad.Trans (MonadIO (..))
|
||||||
import Data.Data (toConstr, showConstr, dataTypeOf, dataTypeConstrs, Data)
|
import Data.Data (DataType, Data, toConstr, showConstr, dataTypeOf,
|
||||||
|
dataTypeConstrs)
|
||||||
|
import Data.Foldable (foldrM)
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
import Data.Maybe (isJust)
|
import Data.Maybe (isJust)
|
||||||
import Foreign.Lua (Lua, FromLuaStack (peek), LuaException (..), StackIndex,
|
import Foreign.Lua (Lua, FromLuaStack (peek), LuaException (..), StackIndex,
|
||||||
Status(OK), ToLuaStack (push), call, isnil, dofile,
|
Status(OK), ToLuaStack (push))
|
||||||
getglobal', gettop, isfunction, newtable, openlibs, pcall,
|
|
||||||
peekEither, pop, pushvalue, rawgeti, rawseti, ref,
|
|
||||||
registryindex, runLua, setglobal, throwLuaError)
|
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Lua.PandocModule (pushPandocModule)
|
import Text.Pandoc.Lua.PandocModule (pushPandocModule)
|
||||||
import Text.Pandoc.Walk (Walkable (walkM))
|
import Text.Pandoc.Walk (Walkable (walkM))
|
||||||
|
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
|
import qualified Foreign.Lua as Lua
|
||||||
|
|
||||||
runLuaFilter :: (MonadIO m)
|
runLuaFilter :: (MonadIO m)
|
||||||
=> Maybe FilePath -> FilePath -> [String] -> Pandoc -> m Pandoc
|
=> Maybe FilePath -> FilePath -> [String] -> Pandoc -> m Pandoc
|
||||||
runLuaFilter datadir filterPath args pd = liftIO . runLua $ do
|
runLuaFilter datadir filterPath args pd = liftIO . Lua.runLua $ do
|
||||||
openlibs
|
Lua.openlibs
|
||||||
-- store module in global "pandoc"
|
-- store module in global "pandoc"
|
||||||
pushPandocModule datadir
|
pushPandocModule datadir
|
||||||
setglobal "pandoc"
|
Lua.setglobal "pandoc"
|
||||||
top <- gettop
|
top <- Lua.gettop
|
||||||
stat<- dofile filterPath
|
stat<- Lua.dofile filterPath
|
||||||
if stat /= OK
|
if stat /= OK
|
||||||
then do
|
then do
|
||||||
luaErrMsg <- peek (-1) <* pop 1
|
luaErrMsg <- peek (-1) <* Lua.pop 1
|
||||||
throwLuaError luaErrMsg
|
Lua.throwLuaError luaErrMsg
|
||||||
else do
|
else do
|
||||||
newtop <- gettop
|
newtop <- Lua.gettop
|
||||||
-- Use the implicitly defined global filter if nothing was returned
|
-- Use the implicitly defined global filter if nothing was returned
|
||||||
when (newtop - top < 1) $ pushGlobalFilter
|
when (newtop - top < 1) $ pushGlobalFilter
|
||||||
luaFilters <- peek (-1)
|
luaFilters <- peek (-1)
|
||||||
push args
|
push args
|
||||||
setglobal "PandocParameters"
|
Lua.setglobal "PandocParameters"
|
||||||
runAll luaFilters pd
|
runAll luaFilters pd
|
||||||
|
|
||||||
pushGlobalFilter :: Lua ()
|
pushGlobalFilter :: Lua ()
|
||||||
pushGlobalFilter = do
|
pushGlobalFilter = do
|
||||||
newtable
|
Lua.newtable
|
||||||
getglobal' "pandoc.global_filter"
|
Lua.getglobal' "pandoc.global_filter"
|
||||||
call 0 1
|
Lua.call 0 1
|
||||||
rawseti (-2) 1
|
Lua.rawseti (-2) 1
|
||||||
|
|
||||||
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
||||||
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
||||||
|
@ -85,29 +85,42 @@ walkMWithLuaFilter (LuaFilter fnMap) = walkLua
|
||||||
where
|
where
|
||||||
walkLua :: Pandoc -> Lua Pandoc
|
walkLua :: Pandoc -> Lua Pandoc
|
||||||
walkLua =
|
walkLua =
|
||||||
(if hasOneOf (constructorsFor (dataTypeOf (Str [])))
|
(if hasOneOf inlineFilterNames
|
||||||
then walkM (tryFilter fnMap :: Inline -> Lua Inline)
|
then walkM (tryFilter fnMap :: Inline -> Lua Inline)
|
||||||
else return)
|
else return)
|
||||||
>=>
|
>=>
|
||||||
(if hasOneOf (constructorsFor (dataTypeOf (Para [])))
|
(if hasOneOf blockFilterNames
|
||||||
then walkM (tryFilter fnMap :: Block -> Lua Block)
|
then walkM (tryFilter fnMap :: Block -> Lua Block)
|
||||||
else return)
|
else return)
|
||||||
>=>
|
>=>
|
||||||
(case Map.lookup "Meta" fnMap of
|
(case Map.lookup "Meta" fnMap of
|
||||||
Just fn -> walkM (\(Pandoc meta blocks) -> do
|
Just fn -> walkM (\(Pandoc meta blocks) -> do
|
||||||
meta' <- runFilterFunction fn meta
|
meta' <- runFilterFunction fn meta
|
||||||
return $ Pandoc meta' blocks)
|
return $ Pandoc meta' blocks)
|
||||||
Nothing -> return)
|
Nothing -> return)
|
||||||
>=>
|
>=>
|
||||||
(case Map.lookup "Pandoc" fnMap `mplus` Map.lookup "Doc" fnMap of
|
(case foldl mplus Nothing (map (`Map.lookup` fnMap) pandocFilterNames) of
|
||||||
Just fn -> runFilterFunction fn :: Pandoc -> Lua Pandoc
|
Just fn -> runFilterFunction fn :: Pandoc -> Lua Pandoc
|
||||||
Nothing -> return)
|
Nothing -> return)
|
||||||
hasOneOf = any (\k -> isJust (Map.lookup k fnMap))
|
hasOneOf = any (\k -> isJust (Map.lookup k fnMap))
|
||||||
constructorsFor x = map show (dataTypeConstrs x)
|
|
||||||
|
constructorsFor :: DataType -> [String]
|
||||||
|
constructorsFor x = map show (dataTypeConstrs x)
|
||||||
|
|
||||||
|
inlineFilterNames :: [String]
|
||||||
|
inlineFilterNames = constructorsFor (dataTypeOf (Str []))
|
||||||
|
|
||||||
|
blockFilterNames :: [String]
|
||||||
|
blockFilterNames = constructorsFor (dataTypeOf (Para []))
|
||||||
|
|
||||||
|
metaFilterName :: String
|
||||||
|
metaFilterName = "Meta"
|
||||||
|
|
||||||
|
pandocFilterNames :: [String]
|
||||||
|
pandocFilterNames = ["Pandoc", "Doc"]
|
||||||
|
|
||||||
type FunctionMap = Map String LuaFilterFunction
|
type FunctionMap = Map String LuaFilterFunction
|
||||||
data LuaFilter = LuaFilter FunctionMap
|
newtype LuaFilter = LuaFilter FunctionMap
|
||||||
|
|
||||||
newtype LuaFilterFunction = LuaFilterFunction { functionIndex :: Int }
|
newtype LuaFilterFunction = LuaFilterFunction { functionIndex :: Int }
|
||||||
|
|
||||||
-- | Try running a filter for the given element
|
-- | Try running a filter for the given element
|
||||||
|
@ -119,7 +132,18 @@ tryFilter fnMap x =
|
||||||
Just fn -> runFilterFunction fn x
|
Just fn -> runFilterFunction fn x
|
||||||
|
|
||||||
instance FromLuaStack LuaFilter where
|
instance FromLuaStack LuaFilter where
|
||||||
peek idx = LuaFilter <$> peek idx
|
peek idx =
|
||||||
|
let constrs = metaFilterName : pandocFilterNames
|
||||||
|
++ blockFilterNames
|
||||||
|
++ inlineFilterNames
|
||||||
|
fn c acc = do
|
||||||
|
Lua.getfield idx c
|
||||||
|
filterFn <- Lua.tryLua (peek (-1))
|
||||||
|
Lua.pop 1
|
||||||
|
return $ case filterFn of
|
||||||
|
Left _ -> acc
|
||||||
|
Right f -> (c, f) : acc
|
||||||
|
in LuaFilter . Map.fromList <$> foldrM fn [] constrs
|
||||||
|
|
||||||
-- | Push a value to the stack via a lua filter function. The filter function is
|
-- | Push a value to the stack via a lua filter function. The filter function is
|
||||||
-- called with given element as argument and is expected to return an element.
|
-- called with given element as argument and is expected to return an element.
|
||||||
|
@ -130,36 +154,36 @@ runFilterFunction :: (FromLuaStack a, ToLuaStack a)
|
||||||
runFilterFunction lf x = do
|
runFilterFunction lf x = do
|
||||||
pushFilterFunction lf
|
pushFilterFunction lf
|
||||||
push x
|
push x
|
||||||
z <- pcall 1 1 Nothing
|
z <- Lua.pcall 1 1 Nothing
|
||||||
if z /= OK
|
if z /= OK
|
||||||
then do
|
then do
|
||||||
msg <- peek (-1)
|
msg <- peek (-1)
|
||||||
let prefix = "Error while running filter function: "
|
let prefix = "Error while running filter function: "
|
||||||
throwLuaError $ prefix ++ msg
|
Lua.throwLuaError $ prefix ++ msg
|
||||||
else do
|
else do
|
||||||
noExplicitFilter <- isnil (-1)
|
noExplicitFilter <- Lua.isnil (-1)
|
||||||
if noExplicitFilter
|
if noExplicitFilter
|
||||||
then pop 1 *> return x
|
then Lua.pop 1 *> return x
|
||||||
else do
|
else do
|
||||||
mbres <- peekEither (-1)
|
mbres <- Lua.peekEither (-1)
|
||||||
case mbres of
|
case mbres of
|
||||||
Left err -> throwLuaError
|
Left err -> Lua.throwLuaError
|
||||||
("Error while trying to get a filter's return "
|
("Error while trying to get a filter's return "
|
||||||
++ "value from lua stack.\n" ++ err)
|
++ "value from lua stack.\n" ++ err)
|
||||||
Right res -> res <$ pop 1
|
Right res -> res <$ Lua.pop 1
|
||||||
|
|
||||||
-- | Push the filter function to the top of the stack.
|
-- | Push the filter function to the top of the stack.
|
||||||
pushFilterFunction :: LuaFilterFunction -> Lua ()
|
pushFilterFunction :: LuaFilterFunction -> Lua ()
|
||||||
pushFilterFunction lf =
|
pushFilterFunction lf =
|
||||||
-- The function is stored in a lua registry table, retrieve it from there.
|
-- The function is stored in a lua registry table, retrieve it from there.
|
||||||
rawgeti registryindex (functionIndex lf)
|
Lua.rawgeti Lua.registryindex (functionIndex lf)
|
||||||
|
|
||||||
registerFilterFunction :: StackIndex -> Lua LuaFilterFunction
|
registerFilterFunction :: StackIndex -> Lua LuaFilterFunction
|
||||||
registerFilterFunction idx = do
|
registerFilterFunction idx = do
|
||||||
isFn <- isfunction idx
|
isFn <- Lua.isfunction idx
|
||||||
unless isFn . throwLuaError $ "Not a function at index " ++ show idx
|
unless isFn . Lua.throwLuaError $ "Not a function at index " ++ show idx
|
||||||
pushvalue idx
|
Lua.pushvalue idx
|
||||||
refIdx <- ref registryindex
|
refIdx <- Lua.ref Lua.registryindex
|
||||||
return $ LuaFilterFunction refIdx
|
return $ LuaFilterFunction refIdx
|
||||||
|
|
||||||
instance ToLuaStack LuaFilterFunction where
|
instance ToLuaStack LuaFilterFunction where
|
||||||
|
|
|
@ -64,6 +64,12 @@ tests = map (localOption (QuickCheckTests 20))
|
||||||
"single-to-double-quoted.lua"
|
"single-to-double-quoted.lua"
|
||||||
(doc . para . singleQuoted $ str "simple")
|
(doc . para . singleQuoted $ str "simple")
|
||||||
(doc . para . doubleQuoted $ str "simple")
|
(doc . para . doubleQuoted $ str "simple")
|
||||||
|
|
||||||
|
, testCase "Count inlines via metatable catch-all" $
|
||||||
|
assertFilterConversion "filtering with metatable catch-all failed"
|
||||||
|
"metatable-catch-all.lua"
|
||||||
|
(doc . para $ "four words, three spaces")
|
||||||
|
(doc . para $ str "7")
|
||||||
]
|
]
|
||||||
|
|
||||||
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
|
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
|
||||||
|
|
20
test/lua/metatable-catch-all.lua
Normal file
20
test/lua/metatable-catch-all.lua
Normal file
|
@ -0,0 +1,20 @@
|
||||||
|
local num_inlines = 0
|
||||||
|
|
||||||
|
function catch_all(el)
|
||||||
|
if el.tag and pandoc.Inline.constructor[el.tag] then
|
||||||
|
num_inlines = num_inlines + 1
|
||||||
|
end
|
||||||
|
end
|
||||||
|
|
||||||
|
function Pandoc(blocks, meta)
|
||||||
|
return pandoc.Pandoc {
|
||||||
|
pandoc.Para{pandoc.Str(num_inlines)}
|
||||||
|
}
|
||||||
|
end
|
||||||
|
|
||||||
|
return {
|
||||||
|
setmetatable(
|
||||||
|
{Pandoc = Pandoc},
|
||||||
|
{__index = function(_) return catch_all end}
|
||||||
|
)
|
||||||
|
}
|
Loading…
Reference in a new issue