diff options
Diffstat (limited to 'test')
-rw-r--r-- | test/Tests/Helpers.hs | 7 | ||||
-rw-r--r-- | test/Tests/Readers/Docx.hs | 3 | ||||
-rw-r--r-- | test/Tests/Readers/LaTeX.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Odt.hs | 4 | ||||
-rw-r--r-- | test/Tests/Writers/AsciiDoc.hs | 3 | ||||
-rw-r--r-- | test/Tests/Writers/ConTeXt.hs | 5 | ||||
-rw-r--r-- | test/Tests/Writers/Docbook.hs | 3 | ||||
-rw-r--r-- | test/Tests/Writers/HTML.hs | 3 | ||||
-rw-r--r-- | test/Tests/Writers/LaTeX.hs | 5 | ||||
-rw-r--r-- | test/Tests/Writers/Markdown.hs | 5 | ||||
-rw-r--r-- | test/Tests/Writers/Muse.hs | 3 | ||||
-rw-r--r-- | test/Tests/Writers/Native.hs | 6 |
12 files changed, 30 insertions, 19 deletions
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 3a82867cb..2a6543ea0 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -106,17 +106,18 @@ class ToString a where toString :: a -> String instance ToString Pandoc where - toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d + toString d = unpack $ + 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 = purely (writeNative def) . toPandoc + toString = unpack . purely (writeNative def) . toPandoc instance ToString Inlines where - toString = trimr . purely (writeNative def) . toPandoc + toString = trimr . unpack . purely (writeNative def) . toPandoc instance ToString String where toString = id diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index e29f0acad..e55c3529b 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -3,6 +3,7 @@ module Tests.Readers.Docx (tests) where import Codec.Archive.Zip import qualified Data.ByteString.Lazy as B import qualified Data.ByteString as BS +import qualified Data.Text as T import qualified Data.Map as M import Test.Tasty import Test.Tasty.HUnit @@ -27,7 +28,7 @@ defopts :: ReaderOptions defopts = def{ readerExtensions = getDefaultExtensions "docx" } instance ToString NoNormPandoc where - toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d + toString d = T.unpack $ purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 390d80df9..afac9e8cb 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -6,7 +6,7 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -import Data.Text (Text, pack) +import Data.Text (Text) import qualified Data.Text as T latex :: Text -> Pandoc diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 61ccc8819..eed3a33b0 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -5,6 +5,7 @@ import qualified Data.ByteString.Lazy as B import qualified Data.ByteString as BS import qualified Text.Pandoc.UTF8 as UTF8 import qualified Data.Map as M +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -41,7 +42,8 @@ newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} deriving ( Show ) instance ToString NoNormPandoc where - toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d + toString d = unpack $ + purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs index 02ecb08f4..6b97c0761 100644 --- a/test/Tests/Writers/AsciiDoc.hs +++ b/test/Tests/Writers/AsciiDoc.hs @@ -1,5 +1,6 @@ module Tests.Writers.AsciiDoc (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -7,7 +8,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder asciidoc :: (ToPandoc a) => a -> String -asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc +asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc tests :: [TestTree] tests = [ testGroup "emphasis" diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index a5185e19f..783b601a9 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.ConTeXt (tests) where +import Data.Text (unpack) import Test.Tasty import Test.Tasty.QuickCheck import Tests.Helpers @@ -9,10 +10,10 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder context :: (ToPandoc a) => a -> String -context = purely (writeConTeXt def) . toPandoc +context = unpack . purely (writeConTeXt def) . toPandoc context' :: (ToPandoc a) => a -> String -context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc +context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs index d7da51aed..90ae073fa 100644 --- a/test/Tests/Writers/Docbook.hs +++ b/test/Tests/Writers/Docbook.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.Docbook (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -11,7 +12,7 @@ docbook :: (ToPandoc a) => a -> String docbook = docbookWithOpts def{ writerWrapText = WrapNone } docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String -docbookWithOpts opts = purely (writeDocbook4 opts) . toPandoc +docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 4246b033d..23ff718d3 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.HTML (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -8,7 +9,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder html :: (ToPandoc a) => a -> String -html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc +html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs index 5f8aea3e0..471d9d9e7 100644 --- a/test/Tests/Writers/LaTeX.hs +++ b/test/Tests/Writers/LaTeX.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.LaTeX (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -14,10 +15,10 @@ latexListing :: (ToPandoc a) => a -> String latexListing = latexWithOpts def{ writerListings = True } latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -latexWithOpts opts = purely (writeLaTeX opts) . toPandoc +latexWithOpts opts = unpack . purely (writeLaTeX opts) . toPandoc beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -beamerWithOpts opts = purely (writeBeamer opts) . toPandoc +beamerWithOpts opts = unpack . purely (writeBeamer opts) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs index 5b1e76a29..012e0888c 100644 --- a/test/Tests/Writers/Markdown.hs +++ b/test/Tests/Writers/Markdown.hs @@ -2,6 +2,7 @@ {-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Tests.Writers.Markdown (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -12,10 +13,10 @@ defopts :: WriterOptions defopts = def{ writerExtensions = pandocExtensions } markdown :: (ToPandoc a) => a -> String -markdown = purely (writeMarkdown defopts) . toPandoc +markdown = unpack . purely (writeMarkdown defopts) . toPandoc markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x +markdownWithOpts opts x = unpack . purely (writeMarkdown opts) $ toPandoc x {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 65bf3e99b..63fdd293c 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -1,5 +1,6 @@ module Tests.Writers.Muse (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -10,7 +11,7 @@ muse :: (ToPandoc a) => a -> String muse = museWithOpts def{ writerWrapText = WrapNone } museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -museWithOpts opts = purely (writeMuse opts) . toPandoc +museWithOpts opts = unpack . purely (writeMuse opts) . toPandoc infix 4 =: (=:) :: (ToString a, ToPandoc a) diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs index c92cb905c..c22185968 100644 --- a/test/Tests/Writers/Native.hs +++ b/test/Tests/Writers/Native.hs @@ -1,5 +1,6 @@ module Tests.Writers.Native (tests) where +import Data.Text (unpack) import Test.Tasty import Test.Tasty.QuickCheck import Tests.Helpers @@ -8,12 +9,11 @@ import Text.Pandoc.Arbitrary () p_write_rt :: Pandoc -> Bool p_write_rt d = - read (purely (writeNative def{ writerTemplate = Just "" }) d) == d + read (unpack $ purely (writeNative def{ writerTemplate = Just "" }) d) == d p_write_blocks_rt :: [Block] -> Bool p_write_blocks_rt bs = - read (purely (writeNative def) (Pandoc nullMeta bs)) == - bs + read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs tests :: [TestTree] tests = [ testProperty "p_write_rt" p_write_rt |