aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Lua.hs24
-rw-r--r--src/Text/Pandoc/Lua/Filter.hs2
-rw-r--r--src/Text/Pandoc/Lua/Util.hs1
3 files changed, 8 insertions, 19 deletions
diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs
index ee259e3fd..d02963418 100644
--- a/src/Text/Pandoc/Lua.hs
+++ b/src/Text/Pandoc/Lua.hs
@@ -29,17 +29,16 @@ module Text.Pandoc.Lua
( LuaException (..)
, runLuaFilter
, runPandocLua
- , 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)
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,25 +62,16 @@ 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
-
--- | DEPRECATED: Push the pandoc module to the Lua Stack.
-pushPandocModule :: Maybe FilePath -> Lua Lua.NumResults
-pushPandocModule = pushModule
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs
index 687ab2be5..9e109bb52 100644
--- a/src/Text/Pandoc/Lua/Filter.hs
+++ b/src/Text/Pandoc/Lua/Filter.hs
@@ -164,5 +164,3 @@ singleElement x = do
Lua.throwLuaError $
"Error while trying to get a filter's return " ++
"value from lua stack.\n" ++ err
-
-
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index 1f7664fc0..2958bd734 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -37,6 +37,7 @@ module Text.Pandoc.Lua.Util
, setRawInt
, addRawInt
, raiseError
+ , popValue
, OrNil (..)
, PushViaCall
, pushViaCall