Lua: drop useless filter function type parameter
The return-type parameter for lua filter functions is removed. It only complicated the code without introducing any additional type safety.
This commit is contained in:
parent
464db59394
commit
57a0759def
1 changed files with 20 additions and 28 deletions
|
@ -73,21 +73,18 @@ runAll [] = return
|
||||||
runAll (x:xs) = walkMWithLuaFilter x >=> runAll xs
|
runAll (x:xs) = walkMWithLuaFilter x >=> runAll xs
|
||||||
|
|
||||||
walkMWithLuaFilter :: LuaFilter -> Pandoc -> IO Pandoc
|
walkMWithLuaFilter :: LuaFilter -> Pandoc -> IO Pandoc
|
||||||
walkMWithLuaFilter (LuaFilter lua inlineFnMap blockFnMap docFnMap) =
|
walkMWithLuaFilter (LuaFilter lua fnMap) =
|
||||||
walkM (execInlineLuaFilter lua inlineFnMap) >=>
|
walkM (execInlineLuaFilter lua fnMap) >=>
|
||||||
walkM (execBlockLuaFilter lua blockFnMap) >=>
|
walkM (execBlockLuaFilter lua fnMap) >=>
|
||||||
walkM (execDocLuaFilter lua docFnMap)
|
walkM (execDocLuaFilter lua fnMap)
|
||||||
|
|
||||||
type InlineFunctionMap = Map String (LuaFilterFunction Inline)
|
type FunctionMap = Map String LuaFilterFunction
|
||||||
type BlockFunctionMap = Map String (LuaFilterFunction Block)
|
data LuaFilter = LuaFilter LuaState FunctionMap
|
||||||
type DocFunctionMap = Map String (LuaFilterFunction Pandoc)
|
|
||||||
data LuaFilter =
|
|
||||||
LuaFilter LuaState InlineFunctionMap BlockFunctionMap DocFunctionMap
|
|
||||||
|
|
||||||
newtype LuaFilterFunction a = LuaFilterFunction { functionIndex :: Int }
|
newtype LuaFilterFunction = LuaFilterFunction { functionIndex :: Int }
|
||||||
|
|
||||||
execDocLuaFilter :: LuaState
|
execDocLuaFilter :: LuaState
|
||||||
-> Map String (LuaFilterFunction Pandoc)
|
-> FunctionMap
|
||||||
-> Pandoc -> IO Pandoc
|
-> Pandoc -> IO Pandoc
|
||||||
execDocLuaFilter lua fnMap x = do
|
execDocLuaFilter lua fnMap x = do
|
||||||
let docFnName = "Doc"
|
let docFnName = "Doc"
|
||||||
|
@ -96,7 +93,7 @@ execDocLuaFilter lua fnMap x = do
|
||||||
Just fn -> runLuaFilterFunction lua fn x
|
Just fn -> runLuaFilterFunction lua fn x
|
||||||
|
|
||||||
execBlockLuaFilter :: LuaState
|
execBlockLuaFilter :: LuaState
|
||||||
-> Map String (LuaFilterFunction Block)
|
-> FunctionMap
|
||||||
-> Block -> IO Block
|
-> Block -> IO Block
|
||||||
execBlockLuaFilter lua fnMap x = do
|
execBlockLuaFilter lua fnMap x = do
|
||||||
let tryFilter :: String -> IO Block
|
let tryFilter :: String -> IO Block
|
||||||
|
@ -121,7 +118,7 @@ execBlockLuaFilter lua fnMap x = do
|
||||||
Table _ _ _ _ _ -> tryFilter "Table"
|
Table _ _ _ _ _ -> tryFilter "Table"
|
||||||
|
|
||||||
execInlineLuaFilter :: LuaState
|
execInlineLuaFilter :: LuaState
|
||||||
-> Map String (LuaFilterFunction Inline)
|
-> FunctionMap
|
||||||
-> Inline -> IO Inline
|
-> Inline -> IO Inline
|
||||||
execInlineLuaFilter lua fnMap x = do
|
execInlineLuaFilter lua fnMap x = do
|
||||||
let tryFilter :: String -> IO Inline
|
let tryFilter :: String -> IO Inline
|
||||||
|
@ -161,19 +158,14 @@ execInlineLuaFilter lua fnMap x = do
|
||||||
instance StackValue LuaFilter where
|
instance StackValue LuaFilter where
|
||||||
valuetype _ = Lua.TTABLE
|
valuetype _ = Lua.TTABLE
|
||||||
push = undefined
|
push = undefined
|
||||||
peek lua i = do
|
peek lua idx = fmap (LuaFilter lua) <$> Lua.peek lua idx
|
||||||
-- TODO: find a more efficient way of doing this in a typesafe manner.
|
|
||||||
inlineFnMap <- Lua.peek lua i
|
|
||||||
blockFnMap <- Lua.peek lua i
|
|
||||||
docFnMap <- Lua.peek lua i
|
|
||||||
return $ LuaFilter lua <$> inlineFnMap <*> blockFnMap <*> docFnMap
|
|
||||||
|
|
||||||
-- | Helper class for pushing a single value to the stack via a lua function.
|
-- | Helper class for pushing a single value to the stack via a lua function.
|
||||||
-- See @pushViaCall@.
|
-- See @pushViaCall@.
|
||||||
class PushViaFilterFunction a b where
|
class PushViaFilterFunction a where
|
||||||
pushViaFilterFunction' :: LuaState -> LuaFilterFunction a -> IO () -> Int -> b
|
pushViaFilterFunction' :: LuaState -> LuaFilterFunction -> IO () -> Int -> a
|
||||||
|
|
||||||
instance (StackValue a) => PushViaFilterFunction a (IO a) where
|
instance StackValue a => PushViaFilterFunction (IO a) where
|
||||||
pushViaFilterFunction' lua lf pushArgs num = do
|
pushViaFilterFunction' lua lf pushArgs num = do
|
||||||
pushFilterFunction lua lf
|
pushFilterFunction lua lf
|
||||||
pushArgs
|
pushArgs
|
||||||
|
@ -184,20 +176,20 @@ instance (StackValue a) => PushViaFilterFunction a (IO a) where
|
||||||
++ "value from lua stack."
|
++ "value from lua stack."
|
||||||
Just res -> res <$ Lua.pop lua 1
|
Just res -> res <$ Lua.pop lua 1
|
||||||
|
|
||||||
instance (PushViaFilterFunction a c, StackValue b) =>
|
instance (StackValue a, PushViaFilterFunction b) =>
|
||||||
PushViaFilterFunction a (b -> c) where
|
PushViaFilterFunction (a -> b) where
|
||||||
pushViaFilterFunction' lua lf pushArgs num x =
|
pushViaFilterFunction' lua lf pushArgs num x =
|
||||||
pushViaFilterFunction' lua lf (pushArgs *> push lua x) (num + 1)
|
pushViaFilterFunction' lua lf (pushArgs *> push lua x) (num + 1)
|
||||||
|
|
||||||
-- | Push an value to the stack via a lua filter function. The function is
|
-- | Push an value to the stack via a lua filter function. The function is
|
||||||
-- called with all arguments that are passed to this function and is expected to
|
-- called with all arguments that are passed to this function and is expected to
|
||||||
-- return a single value.
|
-- return a single value.
|
||||||
runLuaFilterFunction :: (StackValue a, PushViaFilterFunction a b)
|
runLuaFilterFunction :: PushViaFilterFunction a
|
||||||
=> LuaState -> LuaFilterFunction a -> b
|
=> LuaState -> LuaFilterFunction -> a
|
||||||
runLuaFilterFunction lua lf = pushViaFilterFunction' lua lf (return ()) 0
|
runLuaFilterFunction lua lf = pushViaFilterFunction' lua lf (return ()) 0
|
||||||
|
|
||||||
-- | Push the filter function to the top of the stack.
|
-- | Push the filter function to the top of the stack.
|
||||||
pushFilterFunction :: Lua.LuaState -> LuaFilterFunction a -> IO ()
|
pushFilterFunction :: Lua.LuaState -> LuaFilterFunction -> IO ()
|
||||||
pushFilterFunction lua lf = do
|
pushFilterFunction lua lf = do
|
||||||
-- 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.
|
||||||
push lua ("PANDOC_FILTER_FUNCTIONS"::String)
|
push lua ("PANDOC_FILTER_FUNCTIONS"::String)
|
||||||
|
@ -205,7 +197,7 @@ pushFilterFunction lua lf = do
|
||||||
Lua.rawgeti lua (-1) (functionIndex lf)
|
Lua.rawgeti lua (-1) (functionIndex lf)
|
||||||
Lua.remove lua (-2) -- remove registry table from stack
|
Lua.remove lua (-2) -- remove registry table from stack
|
||||||
|
|
||||||
instance StackValue (LuaFilterFunction a) where
|
instance StackValue LuaFilterFunction where
|
||||||
valuetype _ = Lua.TFUNCTION
|
valuetype _ = Lua.TFUNCTION
|
||||||
push lua v = pushFilterFunction lua v
|
push lua v = pushFilterFunction lua v
|
||||||
peek lua i = do
|
peek lua i = do
|
||||||
|
|
Loading…
Reference in a new issue