Tests: improve location reporting of failing tests
This commit is contained in:
parent
3d7eb129bd
commit
d6916e2a40
23 changed files with 53 additions and 31 deletions
|
@ -16,6 +16,7 @@ module Tests.Readers.Creole (tests) where
|
|||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -25,7 +26,7 @@ creole :: Text -> Pandoc
|
|||
creole = purely $ readCreole def{ readerStandalone = True }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test creole
|
||||
|
||||
|
|
|
@ -17,6 +17,7 @@ module Tests.Readers.DokuWiki (tests) where
|
|||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -26,7 +27,7 @@ dokuwiki :: Text -> Pandoc
|
|||
dokuwiki = purely $ readDokuWiki def{ readerStandalone = True }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test dokuwiki
|
||||
|
||||
|
@ -305,13 +306,13 @@ tests = [ testGroup "inlines"
|
|||
T.unlines [ "^ 0 ^ 1 ^ 2 ^ 3 ^"
|
||||
, "| a | b | c |d |"
|
||||
] =?>
|
||||
table emptyCaption
|
||||
(map (, ColWidthDefault) [AlignLeft, AlignCenter, AlignRight, AlignDefault])
|
||||
(TableHead nullAttr
|
||||
table emptyCaption
|
||||
(map (, ColWidthDefault) [AlignLeft, AlignCenter, AlignRight, AlignDefault])
|
||||
(TableHead nullAttr
|
||||
[Row nullAttr . map (simpleCell . plain) $ ["0", "1", "2", "3"]])
|
||||
[TableBody nullAttr 0 []
|
||||
[Row nullAttr . map (simpleCell . plain) $ ["a", "b", "c", "d"]]]
|
||||
(TableFoot nullAttr [])
|
||||
(TableFoot nullAttr [])
|
||||
, "Table with colspan" =:
|
||||
T.unlines [ "^ 0,0 ^ 0,1 ^ 0,2 ^"
|
||||
, "| 1,0 | 1,1 ||"
|
||||
|
|
|
@ -16,6 +16,7 @@ module Tests.Readers.Jira (tests) where
|
|||
import Prelude hiding (unlines)
|
||||
import Data.Text (Text, unlines)
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers (ToString, purely, test, (=?>))
|
||||
import Text.Pandoc (def)
|
||||
import Text.Pandoc.Readers.Jira (readJira)
|
||||
|
@ -25,7 +26,7 @@ jira :: Text -> Pandoc
|
|||
jira = purely $ readJira def
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test jira
|
||||
|
||||
|
|
|
@ -15,6 +15,7 @@ module Tests.Readers.LaTeX (tests) where
|
|||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -25,7 +26,7 @@ latex = purely $ readLaTeX def{
|
|||
readerExtensions = getDefaultExtensions "latex" }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test latex
|
||||
|
||||
|
@ -166,7 +167,7 @@ tests = [ testGroup "basic"
|
|||
, simpleCell (plain "Two")
|
||||
]
|
||||
, Row nullAttr [ simpleCell (plain "Three") ]
|
||||
, Row nullAttr [ simpleCell (plain "Four")
|
||||
, Row nullAttr [ simpleCell (plain "Four")
|
||||
, simpleCell (plain "Five")
|
||||
, simpleCell (plain "Six")
|
||||
, simpleCell (plain "Seven")
|
||||
|
@ -174,8 +175,8 @@ tests = [ testGroup "basic"
|
|||
]
|
||||
, "Table with multicolumn header" =:
|
||||
T.unlines [ "\\begin{tabular}{ |l|l| }"
|
||||
, "\\hline\\multicolumn{2}{|c|}{Header}\\\\"
|
||||
, "\\hline key & val\\\\"
|
||||
, "\\hline\\multicolumn{2}{|c|}{Header}\\\\"
|
||||
, "\\hline key & val\\\\"
|
||||
, "\\hline\\end{tabular}"
|
||||
] =?>
|
||||
table emptyCaption
|
||||
|
|
|
@ -15,6 +15,7 @@ module Tests.Readers.Man (tests) where
|
|||
|
||||
import Data.Text (Text)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -25,7 +26,7 @@ man :: Text -> Pandoc
|
|||
man = purely $ readMan def
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test man
|
||||
|
||||
|
|
|
@ -15,6 +15,7 @@ module Tests.Readers.Markdown (tests) where
|
|||
import Data.Text (Text, unpack)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -40,7 +41,7 @@ markdownMMD :: Text -> Pandoc
|
|||
markdownMMD = purely $ readMarkdown def {
|
||||
readerExtensions = multimarkdownExtensions }
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test markdown
|
||||
|
||||
|
|
|
@ -17,6 +17,7 @@ import Data.Monoid (Any (..))
|
|||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Test.Tasty.QuickCheck
|
||||
import Test.Tasty.Options (IsOption(defaultValue))
|
||||
import Tests.Helpers
|
||||
|
@ -33,7 +34,7 @@ emacsMuse :: Text -> Pandoc
|
|||
emacsMuse = purely $ readMuse def { readerExtensions = emptyExtensions }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test amuse
|
||||
|
||||
|
|
|
@ -21,6 +21,7 @@ import Data.List (intersperse)
|
|||
import Data.Text (Text)
|
||||
import Tests.Helpers (ToString, purely, test)
|
||||
import Test.Tasty (TestTree)
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Text.Pandoc (Pandoc, ReaderOptions (readerExtensions),
|
||||
def, getDefaultExtensions, readOrg)
|
||||
import Text.Pandoc.Builder (Inlines, smallcaps, space, spanWith, str)
|
||||
|
@ -29,7 +30,7 @@ org :: Text -> Pandoc
|
|||
org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test org
|
||||
|
||||
|
|
|
@ -16,6 +16,7 @@ module Tests.Readers.RST (tests) where
|
|||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -25,7 +26,7 @@ rst :: Text -> Pandoc
|
|||
rst = purely $ readRST def{ readerStandalone = True }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test rst
|
||||
|
||||
|
|
|
@ -17,6 +17,7 @@ import Data.List (intersperse)
|
|||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -30,7 +31,7 @@ t2t = purely $ \s -> do
|
|||
readTxt2Tags def s
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
(=:) :: (ToString c, HasCallStack)
|
||||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test t2t
|
||||
|
||||
|
|
|
@ -3,6 +3,7 @@ module Tests.Writers.ConTeXt (tests) where
|
|||
|
||||
import Data.Text (unpack, pack)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Test.Tasty.QuickCheck
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
|
@ -34,7 +35,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test context
|
||||
|
||||
|
|
|
@ -2,6 +2,7 @@
|
|||
module Tests.Writers.FB2 (tests) where
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -12,7 +13,7 @@ fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++
|
|||
"<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section>" ++ x ++ "</section></body></FictionBook>"
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writeFB2 def) . toPandoc)
|
||||
|
||||
|
|
|
@ -4,6 +4,7 @@ module Tests.Writers.HTML (tests) where
|
|||
import Data.Text (unpack)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -33,7 +34,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test html
|
||||
|
||||
|
|
|
@ -3,6 +3,7 @@ module Tests.Writers.JATS (tests) where
|
|||
|
||||
import Data.Text (Text)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -31,7 +32,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, Text) -> TestTree
|
||||
(=:) = test jats
|
||||
|
||||
|
|
|
@ -3,6 +3,7 @@ module Tests.Writers.LaTeX (tests) where
|
|||
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -33,7 +34,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test latex
|
||||
|
||||
|
|
|
@ -4,6 +4,7 @@ module Tests.Writers.Markdown (tests) where
|
|||
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -33,7 +34,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test markdown
|
||||
|
||||
|
@ -182,7 +183,7 @@ noteTests = testGroup "note and reference location"
|
|||
shortcutLinkRefsTests :: TestTree
|
||||
shortcutLinkRefsTests =
|
||||
let infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc)
|
||||
|
|
|
@ -2,6 +2,7 @@
|
|||
module Tests.Writers.Markua (tests) where
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -20,7 +21,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writeMarkua def) . toPandoc)
|
||||
|
||||
|
|
|
@ -2,12 +2,13 @@
|
|||
module Tests.Writers.Ms (tests) where
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Builder
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writeMs def . toPandoc))
|
||||
|
||||
|
|
|
@ -4,6 +4,7 @@ module Tests.Writers.Muse (tests) where
|
|||
import Prelude hiding (unlines)
|
||||
import Data.Text (Text, unlines)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -21,7 +22,7 @@ museWithOpts :: (ToPandoc a) => WriterOptions -> a -> Text
|
|||
museWithOpts opts = purely (writeMuse opts) . toPandoc
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, Text) -> TestTree
|
||||
(=:) = test muse
|
||||
|
||||
|
|
|
@ -3,13 +3,14 @@ module Tests.Writers.Org (tests) where
|
|||
|
||||
import Data.Text as T
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, Text) -> TestTree
|
||||
(=:) = test org
|
||||
|
||||
|
|
|
@ -2,6 +2,7 @@
|
|||
module Tests.Writers.Plain (tests) where
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -9,7 +10,7 @@ import Text.Pandoc.Builder
|
|||
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writePlain def{ writerExtensions =
|
||||
enableExtension Ext_gutenberg plainExtensions }) .
|
||||
|
|
|
@ -12,7 +12,7 @@ import Text.Pandoc.Writers.RST
|
|||
import qualified Data.Text as T
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writeRST def . toPandoc))
|
||||
|
||||
|
|
|
@ -2,6 +2,7 @@
|
|||
module Tests.Writers.TEI (tests) where
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (HasCallStack)
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
|
@ -20,7 +21,7 @@ which is in turn shorthand for
|
|||
-}
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: (ToString a, ToPandoc a)
|
||||
(=:) :: (ToString a, ToPandoc a, HasCallStack)
|
||||
=> String -> (a, String) -> TestTree
|
||||
(=:) = test (purely (writeTEI def) . toPandoc)
|
||||
|
||||
|
|
Loading…
Add table
Reference in a new issue