From 6208d4e7fcf1792203b3069d0002ad5cb1ec05dd Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Mon, 20 May 2019 18:52:28 +0200 Subject: Improve output of Lua tests (#5499) This makes use of tasty-lua, a package to write tests in Lua and integrate the results into Tasty output. Test output becomes more informative: individual tests and test groups become visible in test output. Failures are reported with helpful error messages. --- test/Tests/Lua.hs | 36 +++------- test/Tests/Lua/Module.hs | 27 ++++++++ test/lua/module/pandoc.lua | 58 ++++++++++++++++ test/lua/module/pandoc.utils.lua | 96 +++++++++++++++++++++++++++ test/lua/test-pandoc-utils.lua | 138 --------------------------------------- test/test-pandoc.hs | 6 +- 6 files changed, 196 insertions(+), 165 deletions(-) create mode 100644 test/Tests/Lua/Module.hs create mode 100644 test/lua/module/pandoc.lua create mode 100644 test/lua/module/pandoc.utils.lua delete mode 100644 test/lua/test-pandoc-utils.lua (limited to 'test') diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs index 4040c38ac..c585182e4 100644 --- a/test/Tests/Lua.hs +++ b/test/Tests/Lua.hs @@ -11,7 +11,7 @@ Unit and integration tests for pandoc's Lua subsystem. -} -module Tests.Lua ( tests ) where +module Tests.Lua ( runLuaTest, tests ) where import Prelude import Control.Monad (when) @@ -128,29 +128,13 @@ tests = map (localOption (QuickCheckTests 20)) (doc $ divWith ("", [], kv_before) (para "nil")) (doc $ divWith ("", [], kv_after) (para "nil")) - , testCase "Test module pandoc.utils" $ - assertFilterConversion "pandoc.utils doesn't work as expected." - "test-pandoc-utils.lua" - (doc $ para "doesn't matter") - (doc $ mconcat [ plain (str "blocks_to_inlines: OK") - , plain (str "hierarchicalize: OK") - , plain (str "normalize_date: OK") - , plain (str "pipe: OK") - , plain (str "failing pipe: OK") - , plain (str "read: OK") - , plain (str "failing read: OK") - , plain (str "sha1: OK") - , plain (str "stringify: OK") - , plain (str "to_roman_numeral: OK") - ]) - , testCase "Script filename is set" $ assertFilterConversion "unexpected script name" "script-name.lua" (doc $ para "ignored") (doc $ para (str $ "lua" "script-name.lua")) - , testCase "Pandoc version is set" . runLua' $ do + , testCase "Pandoc version is set" . runLuaTest $ do Lua.getglobal' "table.concat" Lua.getglobal "PANDOC_VERSION" Lua.push ("." :: String) -- separator @@ -158,13 +142,13 @@ tests = map (localOption (QuickCheckTests 20)) Lua.liftIO . assertEqual "pandoc version is wrong" pandocVersion =<< Lua.peek Lua.stackTop - , testCase "Pandoc types version is set" . runLua' $ do + , testCase "Pandoc types version is set" . runLuaTest $ do let versionNums = versionBranch pandocTypesVersion Lua.getglobal "PANDOC_API_VERSION" Lua.liftIO . assertEqual "pandoc-types version is wrong" versionNums =<< Lua.peek Lua.stackTop - , testCase "Allow singleton inline in constructors" . runLua' $ do + , testCase "Allow singleton inline in constructors" . runLuaTest $ do Lua.liftIO . assertEqual "Not the exptected Emph" (Emph [Str "test"]) =<< Lua.callFunc "pandoc.Emph" (Str "test") Lua.liftIO . assertEqual "Unexpected element" (Para [Str "test"]) @@ -178,19 +162,19 @@ tests = map (localOption (QuickCheckTests 20)) Lua.peek Lua.stackTop ) - , testCase "Elements with Attr have `attr` accessor" . runLua' $ do + , testCase "Elements with Attr have `attr` accessor" . runLuaTest $ do Lua.push (Div ("hi", ["moin"], []) [Para [Str "ignored"]]) Lua.getfield Lua.stackTop "attr" Lua.liftIO . assertEqual "no accessor" (("hi", ["moin"], []) :: Attr) =<< Lua.peek Lua.stackTop - , testCase "module `pandoc.system` is present" . runLua' $ do + , testCase "module `pandoc.system` is present" . runLuaTest $ do Lua.getglobal' "pandoc.system" ty <- Lua.ltype Lua.stackTop Lua.liftIO $ assertEqual "module should be a table" Lua.TypeTable ty - , testCase "informative error messages" . runLua' $ do + , testCase "informative error messages" . runLuaTest $ do Lua.pushboolean True err <- Lua.peekEither Lua.stackTop case (err :: Either String Pandoc) of @@ -212,7 +196,7 @@ roundtripEqual :: (Eq a, Lua.Peekable a, Lua.Pushable a) => a -> IO Bool roundtripEqual x = (x ==) <$> roundtripped where roundtripped :: (Lua.Peekable a, Lua.Pushable a) => IO a - roundtripped = runLua' $ do + roundtripped = runLuaTest $ do oldSize <- Lua.gettop Lua.push x size <- Lua.gettop @@ -223,8 +207,8 @@ roundtripEqual x = (x ==) <$> roundtripped Left e -> error (show e) Right y -> return y -runLua' :: Lua.Lua a -> IO a -runLua' op = runIOorExplode $ do +runLuaTest :: Lua.Lua a -> IO a +runLuaTest op = runIOorExplode $ do setUserDataDir (Just "../data") res <- runLua op case res of diff --git a/test/Tests/Lua/Module.hs b/test/Tests/Lua/Module.hs new file mode 100644 index 000000000..82c9330e5 --- /dev/null +++ b/test/Tests/Lua/Module.hs @@ -0,0 +1,27 @@ +{- | +Module : Tests.Lua.Module +Copyright : © 2019 Albert Krewinkel +License : GNU GPL, version 2 or above + +Maintainer : Albert Krewinkel +Stability : alpha +Portability : portable + +Lua module tests +-} +module Tests.Lua.Module (tests) where + +import System.FilePath (()) +import Test.Tasty (TestName, TestTree) +import Test.Tasty.Lua (testLuaFile) + +import Tests.Lua (runLuaTest) + +tests :: [TestTree] +tests = + [ testPandocLua "pandoc" ("lua" "module" "pandoc.lua") + , testPandocLua "pandoc.util" ("lua" "module" "pandoc.utils.lua") + ] + +testPandocLua :: TestName -> FilePath -> TestTree +testPandocLua = testLuaFile runLuaTest diff --git a/test/lua/module/pandoc.lua b/test/lua/module/pandoc.lua new file mode 100644 index 000000000..b9509cdb6 --- /dev/null +++ b/test/lua/module/pandoc.lua @@ -0,0 +1,58 @@ +local tasty = require 'tasty' + +local test = tasty.test_case +local group = tasty.test_group +local assert = tasty.assert + +function os_is_windows () + return package.config:sub(1,1) == '\\' +end + +return { + group 'pipe' { + test('external string processing', function () + if os_is_windows() then + local pipe_result = pandoc.pipe('find', {'hi'}, 'hi') + assert.are_equal('hi', pipe_result:match '%a+') + else + local pipe_result = pandoc.pipe('tr', {'a', 'b'}, 'abc') + assert.are_equal('bbc', pipe_result:match '%a+') + end + end), + test('failing pipe', function () + if os_is_windows() then + local success, err = pcall(pandoc.pipe, 'find', {'/a'}, 'hi') + assert.is_falsy(success) + assert.are_equal('find', err.command) + assert.is_truthy(err.error_code ~= 0) + else + local success, err = pcall(pandoc.pipe, 'false', {}, 'abc') + assert.is_falsy(success) + assert.are_equal('false', err.command) + assert.are_equal(1, err.error_code) + assert.are_equal('', err.output) + end + end) + }, + + group 'read' { + test('Markdown', function () + local valid_markdown = '*Hello*, World!\n' + local expected = pandoc.Pandoc({ + pandoc.Para { + pandoc.Emph { pandoc.Str 'Hello' }, + pandoc.Str ',', + pandoc.Space(), + pandoc.Str 'World!' + } + }) + assert.are_same(expected, pandoc.read(valid_markdown)) + end), + test('failing read', function () + assert.error_matches( + function () pandoc.read('foo', 'nosuchreader') end, + 'Unknown reader: nosuchreader' + ) + end) + }, +} diff --git a/test/lua/module/pandoc.utils.lua b/test/lua/module/pandoc.utils.lua new file mode 100644 index 000000000..dc37ec354 --- /dev/null +++ b/test/lua/module/pandoc.utils.lua @@ -0,0 +1,96 @@ +local tasty = require 'tasty' +local utils = require 'pandoc.utils' + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + group 'blocks_to_inlines' { + test('default separator', function () + local blocks = { + pandoc.Para { pandoc.Str 'Paragraph1' }, + pandoc.Para { pandoc.Emph { pandoc.Str 'Paragraph2' } } + } + local expected = { + pandoc.Str 'Paragraph1', + pandoc.Space(), pandoc.Str '¶', pandoc.Space(), + pandoc.Emph { pandoc.Str 'Paragraph2' } + } + assert.are_same( + expected, + utils.blocks_to_inlines(blocks) + ) + end), + test('custom separator', function () + local blocks = { + pandoc.Para{ pandoc.Str 'Paragraph1' }, + pandoc.Para{ pandoc.Emph 'Paragraph2' } + } + local expected = { + pandoc.Str 'Paragraph1', + pandoc.LineBreak(), + pandoc.Emph { pandoc.Str 'Paragraph2' } + } + assert.are_same( + expected, + utils.blocks_to_inlines(blocks, { pandoc.LineBreak() }) + ) + end) + }, + + group 'hierarchicalize' { + test('sanity check', function () + local blks = { + pandoc.Header(1, {pandoc.Str 'First'}), + pandoc.Header(2, {pandoc.Str 'Second'}), + pandoc.Header(2, {pandoc.Str 'Third'}), + } + local hblks = utils.hierarchicalize(blks) + -- cannot create Elements directly; performing only an approximate + -- sanity checking instead of a full equality comparison. + assert.are_equal('Sec', hblks[1].t) + assert.are_equal('Sec', hblks[1].contents[1].t) + assert.are_equal(1, hblks[1].contents[2].numbering[1]) + assert.are_equal(2, hblks[1].contents[2].numbering[2]) + end) + }, + + group 'normalize_date' { + test('09 Nov 1989', function () + assert.are_equal('1989-11-09', utils.normalize_date '09 Nov 1989') + end), + test('12/31/2017', function () + assert.are_equal('2017-12-31', utils.normalize_date '12/31/2017') + end), + }, + + group 'sha1' { + test('hashing', function () + local ref_hash = '0a0a9f2a6772942557ab5355d76af442f8f65e01' + assert.are_equal(ref_hash, utils.sha1 'Hello, World!') + end) + }, + + group 'stringify' { + test('inlines', function () + local inline = pandoc.Emph{ + pandoc.Str 'Cogito', + pandoc.Space(), + pandoc.Str 'ergo', + pandoc.Space(), + pandoc.Str 'sum.', + } + assert.are_equal('Cogito ergo sum.', utils.stringify(inline)) + end) + }, + + group 'to_roman_numeral' { + test('convertes number', function () + assert.are_equal('MDCCCLXXXVIII', utils.to_roman_numeral(1888)) + end), + test('fails on non-convertible argument', function () + assert.is_falsy(pcall(utils.to_roman_numeral, 'not a number')) + end) + }, +} diff --git a/test/lua/test-pandoc-utils.lua b/test/lua/test-pandoc-utils.lua deleted file mode 100644 index 4421603ec..000000000 --- a/test/lua/test-pandoc-utils.lua +++ /dev/null @@ -1,138 +0,0 @@ -utils = require 'pandoc.utils' - --- Squash blocks to inlines ------------------------------------------------------------------------- -function test_blocks_to_inlines () - local blocks = { - pandoc.Para{ pandoc.Str 'Paragraph1' }, - pandoc.Para{ pandoc.Emph 'Paragraph2' } - } - local inlines = utils.blocks_to_inlines(blocks, {pandoc.LineBreak()}) - return #inlines == 3 - and inlines[1].text == "Paragraph1" - and inlines[2].t == 'LineBreak' - and inlines[3].content[1].text == "Paragraph2" -end - --- hierarchicalize ------------------------------------------------------------------------- -function test_hierarchicalize () - local blks = { - pandoc.Header(1, {pandoc.Str 'First'}), - pandoc.Header(2, {pandoc.Str 'Second'}), - pandoc.Header(2, {pandoc.Str 'Third'}), - } - local hblks = utils.hierarchicalize(blks) - return hblks[1].t == "Sec" - and hblks[1].contents[1].t == "Sec" - and hblks[1].contents[2].numbering[1] == 1 - and hblks[1].contents[2].numbering[2] == 2 -end - --- SHA1 ------------------------------------------------------------------------- -function test_sha1 () - local ref_hash = '0a0a9f2a6772942557ab5355d76af442f8f65e01' - local hash = utils.sha1 'Hello, World!' - return hash == ref_hash -end - --- Pipe ------------------------------------------------------------------------- -function file_exists (filename) - local fh = io.open(filename, 'r') - return fh ~= nil and (fh:close() or true) -end - -function warn (...) io.stderr:write(...) end - -function os_is_windows () - return package.config:sub(1,1) == '\\' -end - -function test_pipe () - if os_is_windows() then - local pipe_result = pandoc.pipe('find', {'hi'}, 'hi') - return pipe_result:match("%a+") == 'hi' - else - local pipe_result = pandoc.pipe('tr', {'a', 'b'}, 'abc') - return pipe_result:match("%a+") == 'bbc' - end -end - -function test_failing_pipe () - if os_is_windows() then - local res, err = pcall(pandoc.pipe, 'find', {'/a'}, 'hi') - return not res and - err.command == 'find' and - err.error_code ~= 0 - else - local res, err = pcall(pandoc.pipe, 'false', {}, 'abc') - return not res and - err.command == 'false' and - err.error_code == 1 and - err.output == '' - end -end - --- Read ------------------------------------------------------------------------- -function test_read () - local valid_markdown = '*Hello*, World!\n' - local res = pandoc.read(valid_markdown).blocks[1].content - return res[1].t == 'Emph' and res[3].t == 'Space' and res[4].t == 'Str' -end - -function test_failing_read () - local res, err = pcall(pandoc.read, 'foo', 'nosuchreader') - return not res and err:match 'Unknown reader: nosuchreader' -end - --- Stringify ------------------------------------------------------------------------- -function test_stringify () - local inline = pandoc.Emph{ - pandoc.Str 'Cogito', - pandoc.Space(), - pandoc.Str 'ergo', - pandoc.Space(), - pandoc.Str 'sum.', - } - return utils.stringify(inline) == 'Cogito ergo sum.' -end - --- to_roman_numeral ------------------------------------------------------------------------- -function test_to_roman_numeral () - return utils.to_roman_numeral(1888) == 'MDCCCLXXXVIII' - -- calling with a string fails - and not pcall(utils.to_roman_numeral, 'not a number') -end - --- normalize_date ------------------------------------------------------------------------- -function test_normalize_date () - return utils.normalize_date("12/31/2017") == '2017-12-31' - and utils.normalize_date("pandoc") == nil -end - --- Return result ------------------------------------------------------------------------- -function run(fn) - return fn() and "OK" or "FAIL" -end - -function Para (el) - return { - pandoc.Plain{pandoc.Str("blocks_to_inlines: " .. run(test_blocks_to_inlines))}, - pandoc.Plain{pandoc.Str("hierarchicalize: " .. run(test_hierarchicalize))}, - pandoc.Plain{pandoc.Str("normalize_date: " .. run(test_normalize_date))}, - pandoc.Plain{pandoc.Str("pipe: " .. run(test_pipe))}, - pandoc.Plain{pandoc.Str("failing pipe: " .. run(test_failing_pipe))}, - pandoc.Plain{pandoc.Str("read: " .. run(test_read))}, - pandoc.Plain{pandoc.Str("failing read: " .. run(test_failing_read))}, - pandoc.Plain{pandoc.Str("sha1: " .. run(test_sha1))}, - pandoc.Plain{pandoc.Str("stringify: " .. run(test_stringify))}, - pandoc.Plain{pandoc.Str("to_roman_numeral: " .. run(test_to_roman_numeral))}, - } -end diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 64f381021..775f998ca 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -8,6 +8,7 @@ import GHC.IO.Encoding import Test.Tasty import qualified Tests.Command import qualified Tests.Lua +import qualified Tests.Lua.Module import qualified Tests.Old import qualified Tests.Readers.Creole import qualified Tests.Readers.Docx @@ -84,7 +85,10 @@ tests pandocPath = testGroup "pandoc tests" , testGroup "FB2" Tests.Readers.FB2.tests , testGroup "DokuWiki" Tests.Readers.DokuWiki.tests ] - , testGroup "Lua filters" Tests.Lua.tests + , testGroup "Lua" + [ testGroup "Lua filters" Tests.Lua.tests + , testGroup "Lua modules" Tests.Lua.Module.tests + ] ] main :: IO () -- cgit v1.2.3