diff options
-rw-r--r-- | tests/Tests/Helpers.hs | 11 | ||||
-rw-r--r-- | tests/Tests/Old.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/Docx.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Readers/Odt.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/AsciiDoc.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/ConTeXt.hs | 4 | ||||
-rw-r--r-- | tests/Tests/Writers/Docbook.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/HTML.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/LaTeX.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/Markdown.hs | 6 | ||||
-rw-r--r-- | tests/Tests/Writers/Native.hs | 4 | ||||
-rw-r--r-- | tests/Tests/Writers/Plain.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/RST.hs | 6 | ||||
-rw-r--r-- | tests/Tests/Writers/TEI.hs | 2 |
14 files changed, 28 insertions, 22 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs index 69f40fe48..28a11266b 100644 --- a/tests/Tests/Helpers.hs +++ b/tests/Tests/Helpers.hs @@ -3,6 +3,7 @@ module Tests.Helpers ( test , (=?>) + , purely , property , ToString(..) , ToPandoc(..) @@ -11,6 +12,7 @@ module Tests.Helpers ( test import Text.Pandoc.Definition import Text.Pandoc.Builder (Inlines, Blocks, doc, plain) +import Text.Pandoc.Class import Test.Framework import Test.Framework.Providers.HUnit import Test.Framework.Providers.QuickCheck2 @@ -49,6 +51,9 @@ vividize (Second s) = "+ " ++ s property :: QP.Testable a => TestName -> a -> Test property = testProperty +purely :: (b -> PandocPure a) -> b -> a +purely f = either (error . show) id . runPure . f + infix 5 =?> (=?>) :: a -> b -> (a,b) x =?> y = (x, y) @@ -57,17 +62,17 @@ class ToString a where toString :: a -> String instance ToString Pandoc where - toString d = writeNative def{ writerTemplate = s } $ toPandoc d + toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of (Pandoc (Meta m) _) | M.null m -> Nothing | otherwise -> Just "" -- need this to get meta output instance ToString Blocks where - toString = writeNative def . toPandoc + toString = purely (writeNative def) . toPandoc instance ToString Inlines where - toString = trimr . writeNative def . toPandoc + toString = trimr . purely (writeNative def) . toPandoc instance ToString String where toString = id diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index ef21990ba..bb0e2aac2 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -20,6 +20,7 @@ import qualified Data.ByteString.Lazy as B import Text.Pandoc.UTF8 (toStringLazy) import Text.Printf import Text.Pandoc.Error +import Tests.Helpers (purely) readFileUTF8 :: FilePath -> IO String readFileUTF8 f = B.readFile f >>= return . toStringLazy @@ -195,7 +196,7 @@ lhsReaderTest :: String -> Test lhsReaderTest format = testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm - where normalizer = writeNative def . normalize . handleError . readNative + where normalizer = purely $ writeNative def . normalize . handleError . readNative norm = if format == "markdown+lhs" then "lhs-test-markdown.native" else "lhs-test.native" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 0d31eb629..3e630dd49 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -26,7 +26,7 @@ noNorm :: Pandoc -> NoNormPandoc noNorm = NoNormPandoc instance ToString NoNormPandoc where - toString d = writeNative def{ writerTemplate = s } $ toPandoc d + toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index 56711c76b..dff62c54b 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -41,7 +41,7 @@ newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} deriving ( Show ) instance ToString NoNormPandoc where - toString d = writeNative def{ writerTemplate = s } $ toPandoc d + toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs index 8ab216753..7103b838b 100644 --- a/tests/Tests/Writers/AsciiDoc.hs +++ b/tests/Tests/Writers/AsciiDoc.hs @@ -7,7 +7,7 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() asciidoc :: (ToPandoc a) => a -> String -asciidoc = writeAsciiDoc def{ writerWrapText = WrapNone } . toPandoc +asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc tests :: [Test] tests = [ testGroup "emphasis" diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs index 629e58b8f..b3e12a571 100644 --- a/tests/Tests/Writers/ConTeXt.hs +++ b/tests/Tests/Writers/ConTeXt.hs @@ -8,10 +8,10 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() context :: (ToPandoc a) => a -> String -context = writeConTeXt def . toPandoc +context = purely (writeConTeXt def) . toPandoc context' :: (ToPandoc a) => a -> String -context' = writeConTeXt def{ writerWrapText = WrapNone } . toPandoc +context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs index a288242dc..adf6e9050 100644 --- a/tests/Tests/Writers/Docbook.hs +++ b/tests/Tests/Writers/Docbook.hs @@ -11,7 +11,7 @@ docbook :: (ToPandoc a) => a -> String docbook = docbookWithOpts def{ writerWrapText = WrapNone } docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String -docbookWithOpts opts = writeDocbook opts . toPandoc +docbookWithOpts opts = purely (writeDocbook opts) . toPandoc {- "my test" =: X =?> Y diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs index 5bea99f71..0ce9aecb3 100644 --- a/tests/Tests/Writers/HTML.hs +++ b/tests/Tests/Writers/HTML.hs @@ -8,7 +8,7 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() html :: (ToPandoc a) => a -> String -html = writeHtmlString def{ writerWrapText = WrapNone } . toPandoc +html = purely (writeHtmlString def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs index f140cc2dd..9eee1f58b 100644 --- a/tests/Tests/Writers/LaTeX.hs +++ b/tests/Tests/Writers/LaTeX.hs @@ -14,7 +14,7 @@ latexListing :: (ToPandoc a) => a -> String latexListing = latexWithOpts def{ writerListings = True } latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -latexWithOpts opts = writeLaTeX opts . toPandoc +latexWithOpts opts = purely (writeLaTeX opts) . toPandoc {- "my test" =: X =?> Y diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index aab916b38..aa8a732f1 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -9,10 +9,10 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() markdown :: (ToPandoc a) => a -> String -markdown = writeMarkdown def . toPandoc +markdown = purely (writeMarkdown def) . toPandoc markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -markdownWithOpts opts x = writeMarkdown opts $ toPandoc x +markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x {- "my test" =: X =?> Y @@ -179,7 +179,7 @@ shortcutLinkRefsTests = (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test - (=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc) + (=:) = test (purely (writeMarkdown def{writerReferenceLinks = True}) . toPandoc) in testGroup "Shortcut reference links" [ "Simple link (shortcutable)" =: (para (link "/url" "title" "foo")) diff --git a/tests/Tests/Writers/Native.hs b/tests/Tests/Writers/Native.hs index 7ec43b339..88bad7944 100644 --- a/tests/Tests/Writers/Native.hs +++ b/tests/Tests/Writers/Native.hs @@ -8,11 +8,11 @@ import Text.Pandoc.Arbitrary() p_write_rt :: Pandoc -> Bool p_write_rt d = - read (writeNative def{ writerTemplate = Just "" } d) == d + read (purely (writeNative def{ writerTemplate = Just "" }) d) == d p_write_blocks_rt :: [Block] -> Bool p_write_blocks_rt bs = length bs > 20 || - read (writeNative def (Pandoc nullMeta bs)) == + read (purely (writeNative def) (Pandoc nullMeta bs)) == bs tests :: [Test] diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs index 42f77e3ec..bead6857c 100644 --- a/tests/Tests/Writers/Plain.hs +++ b/tests/Tests/Writers/Plain.hs @@ -11,7 +11,7 @@ import Text.Pandoc.Arbitrary() infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test -(=:) = test (writePlain def . toPandoc) +(=:) = test (purely (writePlain def) . toPandoc) tests :: [Test] diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs index 77dafeb4c..68a890ca8 100644 --- a/tests/Tests/Writers/RST.hs +++ b/tests/Tests/Writers/RST.hs @@ -10,7 +10,7 @@ import Text.Pandoc.Arbitrary() infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test -(=:) = test (writeRST def{ writerHighlight = True } . toPandoc) +(=:) = test (purely (writeRST def{ writerHighlight = True }) . toPandoc) tests :: [Test] tests = [ testGroup "rubrics" @@ -47,7 +47,7 @@ tests = [ testGroup "rubrics" [ "foo" , "==="] -- note: heading normalization is only done in standalone mode - , test (writeRST def{ writerTemplate = Just "$body$\n" } . toPandoc) + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) "heading levels" $ header 1 (text "Header 1") <> header 3 (text "Header 2") <> @@ -77,7 +77,7 @@ tests = [ testGroup "rubrics" , "" , "Header 2" , "--------"] - , test (writeRST def{ writerTemplate = Just "$body$\n" } . toPandoc) + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) "minimal heading levels" $ header 2 (text "Header 1") <> header 3 (text "Header 2") <> diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs index 3eb8478b7..703f565bb 100644 --- a/tests/Tests/Writers/TEI.hs +++ b/tests/Tests/Writers/TEI.hs @@ -22,7 +22,7 @@ which is in turn shorthand for infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test -(=:) = test (writeTEI def . toPandoc) +(=:) = test (purely (writeTEI def) . toPandoc) tests :: [Test] tests = [ testGroup "block elements" |