diff options
Diffstat (limited to 'src/Text/Pandoc/Lua.hs')
-rw-r--r-- | src/Text/Pandoc/Lua.hs | 26 |
1 files changed, 12 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs index cd7117074..e160f7123 100644 --- a/src/Text/Pandoc/Lua.hs +++ b/src/Text/Pandoc/Lua.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE NoImplicitPrelude #-} {- Copyright © 2017–2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -16,6 +15,7 @@ You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} +{-# LANGUAGE NoImplicitPrelude #-} {- | Module : Text.Pandoc.Lua Copyright : Copyright © 2017–2018 Albert Krewinkel @@ -34,14 +34,14 @@ module Text.Pandoc.Lua import Prelude import Control.Monad ((>=>)) -import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..), - Status (OK), ToLuaStack (push)) +import Foreign.Lua (Lua) import Text.Pandoc.Class (PandocIO) import Text.Pandoc.Definition (Pandoc) import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter) -import Text.Pandoc.Lua.Init (runPandocLua, registerScriptPath) -import Text.Pandoc.Lua.Util (popValue) +import Text.Pandoc.Lua.Init (LuaException (..), runPandocLua, registerScriptPath) +import Text.Pandoc.Lua.Util (dofileWithTraceback) import Text.Pandoc.Options (ReaderOptions) + import qualified Foreign.Lua as Lua -- | Run the Lua filter in @filterPath@ for a transformation to target @@ -59,26 +59,24 @@ runLuaFilter' ropts filterPath format pd = do registerReaderOptions registerScriptPath filterPath top <- Lua.gettop - stat <- Lua.dofile filterPath - if stat /= OK - then do - luaErrMsg <- popValue - Lua.throwLuaError luaErrMsg + stat <- dofileWithTraceback filterPath + if stat /= Lua.OK + then Lua.throwTopMessage else do newtop <- Lua.gettop -- 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 + then Lua.peek Lua.stackTop + else Lua.pushglobaltable *> fmap (:[]) Lua.popValue runAll luaFilters pd where registerFormat = do - push format + Lua.push format Lua.setglobal "FORMAT" registerReaderOptions = do - push ropts + Lua.push ropts Lua.setglobal "PANDOC_READER_OPTIONS" runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc |