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.hs101
1 files changed, 52 insertions, 49 deletions
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 31c011900..00193614d 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -1,5 +1,6 @@
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
{- |
Module : Tests.Lua
Copyright : © 2017-2021 Albert Krewinkel
@@ -13,11 +14,10 @@ Unit and integration tests for pandoc's Lua subsystem.
-}
module Tests.Lua ( runLuaTest, tests ) where
-import Control.Monad (when)
+import HsLua as Lua hiding (Operation (Div), error)
import System.FilePath ((</>))
-import Test.Tasty (TestTree, localOption)
-import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
-import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty)
+import Test.Tasty (TestTree, testGroup)
+import Test.Tasty.HUnit ((@=?), Assertion, HasCallStack, assertEqual, testCase)
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith,
doc, doubleQuoted, emph, header, lineBlock,
@@ -25,8 +25,8 @@ import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith,
singleQuoted, space, str, strong,
HasMeta (setMeta))
import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
-import Text.Pandoc.Definition (Block (BlockQuote, Div, Para), Inline (Emph, Str),
- Attr, Meta, Pandoc, pandocTypesVersion)
+import Text.Pandoc.Definition (Attr, Block (BlockQuote, Div, Para), Pandoc,
+ Inline (Emph, Str), pandocTypesVersion)
import Text.Pandoc.Error (PandocError (PandocLuaError))
import Text.Pandoc.Filter (Filter (LuaFilter), applyFilters)
import Text.Pandoc.Lua (runLua)
@@ -34,25 +34,12 @@ 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
tests :: [TestTree]
-tests = map (localOption (QuickCheckTests 20))
- [ testProperty "inline elements can be round-tripped through the lua stack" $
- \x -> ioProperty (roundtripEqual (x::Inline))
-
- , testProperty "block elements can be round-tripped through the lua stack" $
- \x -> ioProperty (roundtripEqual (x::Block))
-
- , testProperty "meta blocks can be round-tripped through the lua stack" $
- \x -> ioProperty (roundtripEqual (x::Meta))
-
- , testProperty "documents can be round-tripped through the lua stack" $
- \x -> ioProperty (roundtripEqual (x::Pandoc))
-
- , testCase "macro expansion via filter" $
+tests =
+ [ testCase "macro expansion via filter" $
assertFilterConversion "a '{{helloworld}}' string is expanded"
"strmacro.lua"
(doc . para $ str "{{helloworld}}")
@@ -163,12 +150,12 @@ tests = map (localOption (QuickCheckTests 20))
Lua.getglobal "PANDOC_VERSION"
Lua.liftIO .
assertEqual "pandoc version is wrong" (TE.encodeUtf8 pandocVersion)
- =<< Lua.tostring' Lua.stackTop
+ =<< Lua.tostring' Lua.top
, testCase "Pandoc types version is set" . runLuaTest $ do
Lua.getglobal "PANDOC_API_VERSION"
Lua.liftIO . assertEqual "pandoc-types version is wrong" pandocTypesVersion
- =<< Lua.peek Lua.stackTop
+ =<< Lua.peek Lua.top
, testCase "require file" $
assertFilterConversion "requiring file failed"
@@ -177,38 +164,67 @@ tests = map (localOption (QuickCheckTests 20))
(doc $ para (str . T.pack $ "lua" </> "require-file.lua"))
, testCase "Allow singleton inline in constructors" . runLuaTest $ do
- Lua.liftIO . assertEqual "Not the expected Emph" (Emph [Str "test"])
- =<< Lua.callFunc "pandoc.Emph" (Str "test")
- Lua.liftIO . assertEqual "Unexpected element" (Para [Str "test"])
- =<< Lua.callFunc "pandoc.Para" ("test" :: String)
+ Lua.liftIO . assertEqual "Not the expected Emph"
+ (Emph [Str "test"]) =<< do
+ Lua.OK <- Lua.dostring "return pandoc.Emph"
+ Lua.push @Inline (Str "test")
+ Lua.call 1 1
+ Lua.peek @Inline top
+ Lua.liftIO . assertEqual "Unexpected element"
+ (Para [Str "test"]) =<< do
+ Lua.getglobal' "pandoc.Para"
+ Lua.pushString "test"
+ Lua.call 1 1
+ Lua.peek @Block top
Lua.liftIO . assertEqual "Unexptected element"
(BlockQuote [Para [Str "foo"]]) =<< (
do
Lua.getglobal' "pandoc.BlockQuote"
Lua.push (Para [Str "foo"])
_ <- Lua.call 1 1
- Lua.peek Lua.stackTop
+ Lua.peek @Block Lua.top
)
, testCase "Elements with Attr have `attr` accessor" . runLuaTest $ do
Lua.push (Div ("hi", ["moin"], [])
[Para [Str "ignored"]])
- Lua.getfield Lua.stackTop "attr"
+ Lua.getfield Lua.top "attr"
Lua.liftIO . assertEqual "no accessor" (("hi", ["moin"], []) :: Attr)
- =<< Lua.peek Lua.stackTop
+ =<< Lua.peek @Attr Lua.top
, testCase "module `pandoc.system` is present" . runLuaTest $ do
Lua.getglobal' "pandoc.system"
- ty <- Lua.ltype Lua.stackTop
+ ty <- Lua.ltype Lua.top
Lua.liftIO $ assertEqual "module should be a table" Lua.TypeTable ty
+ , testGroup "global modules"
+ [ testCase "module 'lpeg' is loaded into a global" . runLuaTest $ do
+ s <- Lua.dostring "assert(type(lpeg)=='table')"
+ Lua.liftIO $ Lua.OK @=? s
+
+ , testCase "module 're' is loaded into a global" . runLuaTest $ do
+ s <- Lua.dostring "assert(type(re)=='table')"
+ Lua.liftIO $ Lua.OK @=? s
+
+ , testCase "module 'lpeg' is available via `require`" . runLuaTest $ do
+ s <- Lua.dostring
+ "package.path = ''; package.cpath = ''; require 'lpeg'"
+ Lua.liftIO $ Lua.OK @=? s
+
+ , testCase "module 're' is available via `require`" . runLuaTest $ do
+ s <- Lua.dostring
+ "package.path = ''; package.cpath = ''; require 're'"
+ Lua.liftIO $ Lua.OK @=? s
+ ]
+
, testCase "informative error messages" . runLuaTest $ do
Lua.pushboolean True
- eitherPandoc <- Catch.try (Lua.peek Lua.stackTop :: Lua.Lua Pandoc)
+ -- Lua.newtable
+ eitherPandoc <- Catch.try (peek @Pandoc Lua.top)
case eitherPandoc of
Left (PandocLuaError msg) -> do
- let expectedMsg = "Could not get Pandoc value: "
- <> "table expected, got boolean"
+ let expectedMsg = "Pandoc expected, got boolean\n"
+ <> "\twhile retrieving Pandoc"
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."
@@ -221,21 +237,8 @@ assertFilterConversion msg filterPath docIn expectedDoc = do
applyFilters def [LuaFilter ("lua" </> filterPath)] ["HTML"] docIn
assertEqual msg expectedDoc actualDoc
-roundtripEqual :: (Eq a, Lua.Peekable a, Lua.Pushable a) => a -> IO Bool
-roundtripEqual x = (x ==) <$> roundtripped
- where
- roundtripped :: Lua.Peekable a => IO a
- roundtripped = runLuaTest $ do
- oldSize <- Lua.gettop
- Lua.push x
- size <- Lua.gettop
- when (size - oldSize /= 1) $
- error ("not exactly one additional element on the stack: " ++ show size)
- Lua.peek (-1)
-
-runLuaTest :: Lua.Lua a -> IO a
+runLuaTest :: HasCallStack => Lua.LuaE PandocError a -> IO a
runLuaTest op = runIOorExplode $ do
- setUserDataDir (Just "../data")
res <- runLua op
case res of
Left e -> error (show e)