aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Lua.hs
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Lua.hs')
-rw-r--r--test/Tests/Lua.hs15
1 files changed, 8 insertions, 7 deletions
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 0943b17aa..14800f7bb 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Tests.Lua
Copyright : © 2017-2020 Albert Krewinkel
@@ -28,11 +29,13 @@ import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith,
import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
import Text.Pandoc.Definition (Block (BlockQuote, Div, Para), Inline (Emph, Str),
Attr, Meta, Pandoc, pandocTypesVersion)
+import Text.Pandoc.Error (PandocError (PandocLuaError))
import Text.Pandoc.Filter (Filter (LuaFilter), applyFilters)
import Text.Pandoc.Lua (runLua)
import Text.Pandoc.Options (def)
import Text.Pandoc.Shared (pandocVersion)
+import qualified Control.Monad.Catch as Catch
import qualified Foreign.Lua as Lua
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
@@ -197,12 +200,13 @@ tests = map (localOption (QuickCheckTests 20))
, testCase "informative error messages" . runLuaTest $ do
Lua.pushboolean True
- err <- Lua.peekEither Lua.stackTop
- case (err :: Either String Pandoc) of
- Left msg -> do
+ eitherPandoc <- Catch.try (Lua.peek Lua.stackTop :: Lua.Lua Pandoc)
+ case eitherPandoc of
+ Left (PandocLuaError msg) -> do
let expectedMsg = "Could not get Pandoc value: "
<> "table expected, got boolean"
Lua.liftIO $ assertEqual "unexpected error message" expectedMsg msg
+ Left e -> error ("Expected a Lua error, but got " <> show e)
Right _ -> error "Getting a Pandoc element from a bool should fail."
]
@@ -223,10 +227,7 @@ roundtripEqual x = (x ==) <$> roundtripped
size <- Lua.gettop
when (size - oldSize /= 1) $
error ("not exactly one additional element on the stack: " ++ show size)
- res <- Lua.peekEither (-1)
- case res of
- Left e -> error (show e)
- Right y -> return y
+ Lua.peek (-1)
runLuaTest :: Lua.Lua a -> IO a
runLuaTest op = runIOorExplode $ do