diff options
author | Albert Krewinkel <albert@zeitkraut.de> | 2021-10-20 21:40:07 +0200 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2021-10-22 11:16:51 -0700 |
commit | 9e74826ba9ce4139bfdd3f057a79efa8b644e85a (patch) | |
tree | 954692554bfc024b6927de385923ab5c69a4b5df /test | |
parent | e10f495a0163738a09c3fd18fce11788832c82b7 (diff) | |
download | pandoc-9e74826ba9ce4139bfdd3f057a79efa8b644e85a.tar.gz |
Switch to hslua-2.0
The new HsLua version takes a somewhat different approach to marshalling
and unmarshalling, relying less on typeclasses and more on specialized
types. This allows for better performance and improved error messages.
Furthermore, new abstractions allow to document the code and exposed
functions.
Diffstat (limited to 'test')
-rw-r--r-- | test/Tests/Lua.hs | 63 | ||||
-rw-r--r-- | test/lua/module/pandoc-types.lua | 25 |
2 files changed, 37 insertions, 51 deletions
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs index 31c011900..e19f6f9e8 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 @@ -14,9 +15,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.HUnit (Assertion, HasCallStack, assertEqual, testCase) import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty) import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith, @@ -25,8 +27,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), Meta, pandocTypesVersion) import Text.Pandoc.Error (PandocError (PandocLuaError)) import Text.Pandoc.Filter (Filter (LuaFilter), applyFilters) import Text.Pandoc.Lua (runLua) @@ -34,23 +36,22 @@ 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)) + ioProperty . roundtripEqual @Inline , testProperty "block elements can be round-tripped through the lua stack" $ - \x -> ioProperty (roundtripEqual (x::Block)) + ioProperty . roundtripEqual @Block , testProperty "meta blocks can be round-tripped through the lua stack" $ - \x -> ioProperty (roundtripEqual (x::Meta)) + ioProperty . roundtripEqual @Meta , testProperty "documents can be round-tripped through the lua stack" $ - \x -> ioProperty (roundtripEqual (x::Pandoc)) + ioProperty . roundtripEqual @Pandoc , testCase "macro expansion via filter" $ assertFilterConversion "a '{{helloworld}}' string is expanded" @@ -163,12 +164,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 +178,47 @@ 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 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 , 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 = "table expected, got boolean\n" + <> "\twhile retrieving Pandoc value" 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,19 +231,20 @@ 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 :: forall a. (Eq a, Lua.Pushable a, Lua.Peekable a) + => a -> IO Bool roundtripEqual x = (x ==) <$> roundtripped where - roundtripped :: Lua.Peekable a => IO a + roundtripped :: 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) + Lua.peek Lua.top -runLuaTest :: Lua.Lua a -> IO a +runLuaTest :: HasCallStack => Lua.LuaE PandocError a -> IO a runLuaTest op = runIOorExplode $ do setUserDataDir (Just "../data") res <- runLua op diff --git a/test/lua/module/pandoc-types.lua b/test/lua/module/pandoc-types.lua index d4e063a5c..d9c9f82ac 100644 --- a/test/lua/module/pandoc-types.lua +++ b/test/lua/module/pandoc-types.lua @@ -55,31 +55,6 @@ return { end), }, - group 'list-like behavior' { - test('can access version component numbers', function () - local version = Version '2.7.3' - assert.is_nil(version[0]) - assert.are_equal(version[1], 2) - assert.are_equal(version[2], 7) - assert.are_equal(version[3], 3) - end), - test('can be iterated over', function () - local version_list = {2, 7, 3} - local final_index = 0 - for i, v in pairs(Version(version_list)) do - assert.are_equal(v, version_list[i]) - final_index = i - end - assert.are_equal(final_index, 3) - end), - test('length is the number of components', function () - assert.are_equal(#(Version '0'), 1) - assert.are_equal(#(Version '1.6'), 2) - assert.are_equal(#(Version '8.7.5'), 3) - assert.are_equal(#(Version '2.9.1.5'), 4) - end) - }, - group 'conversion to string' { test('converting from and to string is a noop', function () local version_string = '1.19.4' |