diff options
| author | John MacFarlane <[email protected]> | 2021-03-11 15:49:27 -0800 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2021-03-13 15:05:37 -0800 |
| commit | 8be95ad8e5150d5cab66c4abdf59baaf4670c6c8 (patch) | |
| tree | 9655036efbaabda6a2a7802dc971c7fba5a987ca /test/Tests/Readers | |
| parent | 35b66a76718205c303f416bf0afc01c098e8a171 (diff) | |
Use custom Prelude based on relude.relude
The Prelude now longer exports partial functions, so
a large number of uses of these functions in the
code base have been rewritten.
A .ghci file has been added; this is necessary for
ghci to work properly with the custom Prelude.
Currently there are lots of compiler warnings.
We should either fix these or go to using a custom
Prelude that changes less than relude.
Diffstat (limited to 'test/Tests/Readers')
| -rw-r--r-- | test/Tests/Readers/Creole.hs | 2 | ||||
| -rw-r--r-- | test/Tests/Readers/Docx.hs | 14 | ||||
| -rw-r--r-- | test/Tests/Readers/DokuWiki.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Readers/FB2.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Readers/HTML.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Readers/Jira.hs | 2 | ||||
| -rw-r--r-- | test/Tests/Readers/LaTeX.hs | 16 | ||||
| -rw-r--r-- | test/Tests/Readers/Man.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Readers/Markdown.hs | 11 | ||||
| -rw-r--r-- | test/Tests/Readers/Muse.hs | 25 | ||||
| -rw-r--r-- | test/Tests/Readers/Odt.hs | 10 | ||||
| -rw-r--r-- | test/Tests/Readers/Org/Directive.hs | 4 | ||||
| -rw-r--r-- | test/Tests/Readers/Org/Inline/Citation.hs | 14 | ||||
| -rw-r--r-- | test/Tests/Readers/Org/Meta.hs | 18 | ||||
| -rw-r--r-- | test/Tests/Readers/Org/Shared.hs | 2 | ||||
| -rw-r--r-- | test/Tests/Readers/RST.hs | 2 | ||||
| -rw-r--r-- | test/Tests/Readers/Txt2Tags.hs | 2 |
17 files changed, 70 insertions, 68 deletions
diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs index 3320b78e8..582df693b 100644 --- a/test/Tests/Readers/Creole.hs +++ b/test/Tests/Readers/Creole.hs @@ -25,7 +25,7 @@ creole :: Text -> Pandoc creole = purely $ readCreole def{ readerStandalone = True } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test creole diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index 263e04173..59bac0213 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -40,8 +40,8 @@ noNorm = NoNormPandoc defopts :: ReaderOptions defopts = def{ readerExtensions = getDefaultExtensions "docx" } -instance ToString NoNormPandoc where - toString d = T.unpack $ purely (writeNative def{ writerTemplate = s }) $ toPandoc d +instance ToText NoNormPandoc where + toText d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing @@ -73,14 +73,14 @@ testCompareWithOpts opts name docxFile nativeFile = testCompare :: String -> FilePath -> FilePath -> TestTree testCompare = testCompareWithOpts defopts -testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO TestTree +testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [Text] -> IO TestTree testForWarningsWithOptsIO opts name docxFile expected = do df <- B.readFile docxFile logs <- runIOorExplode $ setVerbosity ERROR >> readDocx opts df >> P.getLog let warns = [m | DocxParserWarning m <- logs] - return $ test id name (T.unlines warns, unlines expected) + return $ test id name (T.unlines warns, T.unlines expected) -testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> TestTree +testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [Text] -> TestTree testForWarningsWithOpts opts name docxFile expected = unsafePerformIO $ testForWarningsWithOptsIO opts name docxFile expected @@ -96,10 +96,10 @@ compareMediaPathIO mediaPath mediaBag docxPath = do docxMedia <- getMedia docxPath mediaPath let mbBS = case lookupMedia mediaPath mediaBag of Just (_, bs) -> bs - Nothing -> error ("couldn't find " ++ + Nothing -> error $ T.pack ("couldn't find " ++ mediaPath ++ " in media bag") - docxBS = fromMaybe (error ("couldn't find " ++ + docxBS = fromMaybe (error $ T.pack ("couldn't find " ++ mediaPath ++ " in media bag")) docxMedia return $ mbBS == docxBS diff --git a/test/Tests/Readers/DokuWiki.hs b/test/Tests/Readers/DokuWiki.hs index 84ba86d46..fa344b910 100644 --- a/test/Tests/Readers/DokuWiki.hs +++ b/test/Tests/Readers/DokuWiki.hs @@ -19,13 +19,13 @@ import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B dokuwiki :: Text -> Pandoc dokuwiki = purely $ readDokuWiki def{ readerStandalone = True } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test dokuwiki diff --git a/test/Tests/Readers/FB2.hs b/test/Tests/Readers/FB2.hs index 42054a235..ac7db9be1 100644 --- a/test/Tests/Readers/FB2.hs +++ b/test/Tests/Readers/FB2.hs @@ -16,7 +16,7 @@ import Tests.Helpers import Test.Tasty.Golden (goldenVsString) import qualified Data.ByteString as BS import Text.Pandoc -import Text.Pandoc.UTF8 (toText, fromStringLazy) +import Text.Pandoc.UTF8 as UTF8 import Data.Text (Text, unpack) import System.FilePath (replaceExtension) @@ -25,7 +25,7 @@ fb2ToNative = purely (writeNative def{ writerTemplate = Just mempty }) . purely fb2Test :: TestName -> FilePath -> TestTree fb2Test name path = goldenVsString name native - (fromStringLazy . filter (/='\r') . unpack . fb2ToNative . toText + (UTF8.fromStringLazy . filter (/='\r') . unpack . fb2ToNative . UTF8.toText <$> BS.readFile path) where native = replaceExtension path ".native" diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs index f23af2cb1..6a8a10cef 100644 --- a/test/Tests/Readers/HTML.hs +++ b/test/Tests/Readers/HTML.hs @@ -21,7 +21,7 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Shared (isHeaderBlock) import Text.Pandoc.Arbitrary () -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B import Text.Pandoc.Walk (walk) html :: Text -> Pandoc @@ -47,7 +47,7 @@ removeRawInlines x = x roundTrip :: Blocks -> Bool roundTrip b = d'' == d''' where d = walk removeRawInlines $ - walk makeRoundTrip $ Pandoc nullMeta $ toList b + walk makeRoundTrip $ Pandoc nullMeta $ B.toList b d' = rewrite d d'' = rewrite d' d''' = rewrite d'' diff --git a/test/Tests/Readers/Jira.hs b/test/Tests/Readers/Jira.hs index cb7dde4ea..2881a83e5 100644 --- a/test/Tests/Readers/Jira.hs +++ b/test/Tests/Readers/Jira.hs @@ -25,7 +25,7 @@ jira :: Text -> Pandoc jira = purely $ readJira def infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test jira diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 4bda15140..a631e55af 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -18,14 +18,14 @@ import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B latex :: Text -> Pandoc latex = purely $ readLaTeX def{ readerExtensions = getDefaultExtensions "latex" } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test latex @@ -338,10 +338,10 @@ natbibCitations = testGroup "natbib" =?> para (cite [baseCitation] (rt "\\citet{item1}")) , "suffix" =: "\\citet[p.~30]{item1}" =?> para - (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\citet[p.~30]{item1}")) + (cite [baseCitation{ citationSuffix = B.toList $ text "p.\160\&30" }] (rt "\\citet[p.~30]{item1}")) , "suffix long" =: "\\citet[p.~30, with suffix]{item1}" =?> para (cite [baseCitation{ citationSuffix = - toList $ text "p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}")) + B.toList $ text "p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}")) , "multiple" =: "\\citeauthor{item1} \\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}" =?> para (cite [baseCitation{ citationMode = AuthorInText } ,baseCitation{ citationMode = SuppressAuthor @@ -365,7 +365,7 @@ natbibCitations = testGroup "natbib" , citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\citep[pp.~33, 35--37, and nowhere else]{item1}")) , "suffix only" =: "\\citep[and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = toList $ text "and nowhere else" }] (rt "\\citep[and nowhere else]{item1}")) + , citationSuffix = B.toList $ text "and nowhere else" }] (rt "\\citep[and nowhere else]{item1}")) , "no author" =: "\\citeyearpar{item1}, and now Doe with a locator \\citeyearpar[p.~44]{item2}" =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\citeyearpar{item1}") <> text ", and now Doe with a locator " <> @@ -385,10 +385,10 @@ biblatexCitations = testGroup "biblatex" =?> para (cite [baseCitation] (rt "\\textcite{item1}")) , "suffix" =: "\\textcite[p.~30]{item1}" =?> para - (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\textcite[p.~30]{item1}")) + (cite [baseCitation{ citationSuffix = B.toList $ text "p.\160\&30" }] (rt "\\textcite[p.~30]{item1}")) , "suffix long" =: "\\textcite[p.~30, with suffix]{item1}" =?> para (cite [baseCitation{ citationSuffix = - toList $ text "p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}")) + B.toList $ text "p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}")) , "multiple" =: "\\textcites{item1}[p.~30]{item2}[see also][]{item3}" =?> para (cite [baseCitation{ citationMode = AuthorInText } ,baseCitation{ citationMode = NormalCitation @@ -412,7 +412,7 @@ biblatexCitations = testGroup "biblatex" , citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\autocite[pp.~33, 35--37, and nowhere else]{item1}")) , "suffix only" =: "\\autocite[and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = toList $ text "and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}")) + , citationSuffix = B.toList $ text "and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}")) , "no author" =: "\\autocite*{item1}, and now Doe with a locator \\autocite*[p.~44]{item2}" =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\autocite*{item1}") <> text ", and now Doe with a locator " <> diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs index d36151d58..ff1f14a29 100644 --- a/test/Tests/Readers/Man.hs +++ b/test/Tests/Readers/Man.hs @@ -18,14 +18,14 @@ import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B import Text.Pandoc.Readers.Man man :: Text -> Pandoc man = purely $ readMan def infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test man diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index 0930deae6..8e6700639 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -19,6 +19,7 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +import qualified Relude.Unsafe as Unsafe markdown :: Text -> Pandoc markdown = purely $ readMarkdown def { readerExtensions = @@ -37,7 +38,7 @@ markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test markdown @@ -205,15 +206,15 @@ tests = [ testGroup "inline code" ] <> [ "lists with newlines and indent in backticks" =: T.intercalate ("\n" <> T.replicate 4 " ") (zipWith (\i (_, lt, _) -> lt <> i) lis lsts) - =?> let (_, _, f) = head lsts - in f [plain $ code $ T.intercalate (T.replicate 5 " ") $ head lis' : zipWith (\i (_, lt, _) -> lt <> i) (tail lis') (tail lsts)] + =?> let (_, _, f) = Unsafe.head lsts + in f [plain $ code $ T.intercalate (T.replicate 5 " ") $ Unsafe.head lis' : zipWith (\i (_, lt, _) -> lt <> i) (Unsafe.tail lis') (Unsafe.tail lsts)] | lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists] ] <> [ "lists with blank lines and indent in backticks" =: T.intercalate ("\n\n" <> T.replicate 4 " ") (zipWith (\i (_, lt, _) -> lt <> i) lis lsts) <> "\n" - =?> let (_, _, f) = head lsts - in f . pure $ (para . text $ head lis) <> bldLsts para (tail lsts) (tail lis) + =?> let (_, _, f) = Unsafe.head lsts + in f . pure $ (para . text $ Unsafe.head lis) <> bldLsts para (Unsafe.tail lsts) (Unsafe.tail lis) | lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists] ] , testGroup "emph and strong" diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 68bdc87b4..6304a0dd8 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -22,7 +22,7 @@ import Test.Tasty.Options (IsOption(defaultValue)) import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B import Text.Pandoc.Writers.Shared (toLegacyTable) import Text.Pandoc.Walk @@ -33,7 +33,7 @@ emacsMuse :: Text -> Pandoc emacsMuse = purely $ readMuse def { readerExtensions = emptyExtensions } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test amuse @@ -59,7 +59,8 @@ makeRoundTrip t@(Table tattr blkCapt specs thead tbody tfoot) = then t else Para [Str "table was here"] where (_, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot - numcols = maximum (length aligns : length widths : map length (headers:rows)) + numcols = maximum1 + (length aligns :| length widths : map length (headers:rows)) isLineBreak LineBreak = Any True isLineBreak _ = Any False hasLineBreak = getAny . query isLineBreak @@ -107,7 +108,7 @@ makeRoundTrip x = x -- Currently we remove tables and compare first rewrite to the second. roundTrip :: Blocks -> Bool roundTrip b = d' == d'' - where d = walk makeRoundTrip $ Pandoc nullMeta $ toList b + where d = walk makeRoundTrip $ Pandoc nullMeta $ B.toList b d' = rewrite d d'' = rewrite d' rewrite = amuse . T.pack . (++ "\n") . T.unpack . @@ -801,7 +802,7 @@ tests = , testGroup "Directives" [ "Title" =: "#title Document title" =?> - let titleInline = toList "Document title" + let titleInline = B.toList "Document title" meta = setMeta "title" (MetaInlines titleInline) nullMeta in Pandoc meta mempty -- Emacs Muse documentation says that "You can use any combination @@ -809,25 +810,25 @@ tests = -- but also allows '-', which is not documented, but used for disable-tables. , test emacsMuse "Disable tables" ("#disable-tables t" =?> - Pandoc (setMeta "disable-tables" (MetaInlines $ toList "t") nullMeta) mempty) + Pandoc (setMeta "disable-tables" (MetaInlines $ B.toList "t") nullMeta) mempty) , "Multiple directives" =: T.unlines [ "#title Document title" , "#subtitle Document subtitle" ] =?> - Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $ - setMeta "subtitle" (MetaInlines $ toList "Document subtitle") nullMeta) mempty + Pandoc (setMeta "title" (MetaInlines $ B.toList "Document title") $ + setMeta "subtitle" (MetaInlines $ B.toList "Document subtitle") nullMeta) mempty , "Multiline directive" =: T.unlines [ "#title Document title" , "#notes First line" , "and second line" , "#author Name" ] =?> - Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $ - setMeta "notes" (MetaInlines $ toList "First line\nand second line") $ - setMeta "author" (MetaInlines $ toList "Name") nullMeta) mempty + Pandoc (setMeta "title" (MetaInlines $ B.toList "Document title") $ + setMeta "notes" (MetaInlines $ B.toList "First line\nand second line") $ + setMeta "author" (MetaInlines $ B.toList "Name") nullMeta) mempty , "Amusewiki's #cover is translated to pandoc's #cover-image" =: "#cover cover.png" =?> - let titleInline = toList "cover.png" + let titleInline = B.toList "cover.png" meta = setMeta "cover-image" (MetaInlines titleInline) nullMeta in Pandoc meta mempty ] diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 9b5ec6b9e..f1155d23e 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -17,7 +17,7 @@ import Control.Monad (liftM) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import qualified Data.Map as M -import Data.Text (unpack) +import qualified Data.Text as T import System.IO.Unsafe (unsafePerformIO) import Test.Tasty import Tests.Helpers @@ -54,9 +54,8 @@ testsComparingToNative = map nameToTest namesOfTestsComparingToNative newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} deriving ( Show ) -instance ToString NoNormPandoc where - toString d = unpack $ - purely (writeNative def{ writerTemplate = s }) $ toPandoc d +instance ToText NoNormPandoc where + toText d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing @@ -66,7 +65,8 @@ instance ToPandoc NoNormPandoc where toPandoc = unNoNorm getNoNormVia :: (a -> Pandoc) -> String -> Either PandocError a -> NoNormPandoc -getNoNormVia _ readerName (Left _) = error (readerName ++ " reader failed") +getNoNormVia _ readerName (Left _) = + error $ T.pack (readerName ++ " reader failed") getNoNormVia f _ (Right a) = NoNormPandoc (f a) type TestCreator = ReaderOptions diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs index 85d1bc088..c2409ce80 100644 --- a/test/Tests/Readers/Org/Directive.hs +++ b/test/Tests/Readers/Org/Directive.hs @@ -15,14 +15,14 @@ module Tests.Readers.Org.Directive (tests) where import Data.Time (UTCTime (UTCTime), secondsToDiffTime) import Data.Time.Calendar (Day (ModifiedJulianDay)) import Test.Tasty (TestTree, testGroup) -import Tests.Helpers ((=?>), ToString, purely, test) +import Tests.Helpers ((=?>), ToString, ToText, purely, test) import Tests.Readers.Org.Shared ((=:), tagSpan) import Text.Pandoc import Text.Pandoc.Builder import qualified Data.ByteString as BS import qualified Data.Text as T -testWithFiles :: (ToString c) +testWithFiles :: (ToText c) => [(FilePath, BS.ByteString)] -> String -- ^ name of test case -> (T.Text, c) -- ^ (input, expected value) diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs index a11804983..fa1560772 100644 --- a/test/Tests/Readers/Org/Inline/Citation.hs +++ b/test/Tests/Readers/Org/Inline/Citation.hs @@ -15,7 +15,7 @@ module Tests.Readers.Org.Inline.Citation (tests) where import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:)) -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B tests :: [TestTree] tests = @@ -160,8 +160,8 @@ tests = "[[citep:Dominik201408][See page 20::, for example]]" =?> let citation = Citation { citationId = "Dominik201408" - , citationPrefix = toList "See page 20" - , citationSuffix = toList ", for example" + , citationPrefix = B.toList "See page 20" + , citationSuffix = B.toList ", for example" , citationMode = NormalCitation , citationNoteNum = 0 , citationHash = 0 @@ -198,17 +198,17 @@ tests = , "Berkeley-style parenthetical citation list" =: "[(cite): see; @Dominik201408;also @Pandoc; and others]" =?> let pandocCite' = pandocCite { - citationPrefix = toList "also" - , citationSuffix = toList "and others" + citationPrefix = B.toList "also" + , citationSuffix = B.toList "and others" } dominikCite' = dominikCite { - citationPrefix = toList "see" + citationPrefix = B.toList "see" } in (para $ cite [dominikCite', pandocCite'] "") , "Berkeley-style plain citation list" =: "[cite: See; @Dominik201408; and @Pandoc; and others]" =?> - let pandocCite' = pandocInText { citationPrefix = toList "and" } + let pandocCite' = pandocInText { citationPrefix = B.toList "and" } in (para $ "See " <> cite [dominikInText] "" <> "," <> space diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs index 6363d84b0..f38ee7194 100644 --- a/test/Tests/Readers/Org/Meta.hs +++ b/test/Tests/Readers/Org/Meta.hs @@ -16,7 +16,7 @@ import Test.Tasty (TestTree, testGroup) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:), spcSep) import Text.Pandoc -import Text.Pandoc.Builder +import Text.Pandoc.Builder as B import qualified Data.Text as T tests :: [TestTree] @@ -43,14 +43,14 @@ tests = , testGroup "Export settings" [ "Title" =: "#+title: Hello, World" =?> - let titleInline = toList $ "Hello," <> space <> "World" + let titleInline = B.toList $ "Hello," <> space <> "World" meta = setMeta "title" (MetaInlines titleInline) nullMeta in Pandoc meta mempty , testGroup "Author" [ "sets 'author' field" =: "#+author: John /Emacs-Fanboy/ Doe" =?> - let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ] + let author = B.toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ] meta = setMeta "author" (MetaInlines author) nullMeta in Pandoc meta mempty @@ -58,8 +58,8 @@ tests = T.unlines [ "#+author: James Dewey Watson," , "#+author: Francis Harry Compton Crick" ] =?> - let watson = toList "James Dewey Watson," - crick = toList "Francis Harry Compton Crick" + let watson = B.toList "James Dewey Watson," + crick = B.toList "Francis Harry Compton Crick" meta = setMeta "author" (MetaInlines (watson ++ SoftBreak : crick)) nullMeta @@ -68,7 +68,7 @@ tests = , "Date" =: "#+date: Feb. *28*, 2014" =?> - let date = toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ] + let date = B.toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ] meta = setMeta "date" (MetaInlines date) nullMeta in Pandoc meta mempty @@ -102,7 +102,7 @@ tests = T.unlines [ "#+keywords: pandoc, testing," , "#+keywords: Org" ] =?> - let keywords = toList $ "pandoc, testing," <> softbreak <> "Org" + let keywords = B.toList $ "pandoc, testing," <> softbreak <> "Org" meta = setMeta "keywords" (MetaInlines keywords) nullMeta in Pandoc meta mempty @@ -128,7 +128,7 @@ tests = [ "LATEX_HEADER" =: "#+latex_header: \\usepackage{tikz}" =?> let latexInlines = rawInline "latex" "\\usepackage{tikz}" - inclList = MetaList [MetaInlines (toList latexInlines)] + inclList = MetaList [MetaInlines (B.toList latexInlines)] meta = setMeta "header-includes" inclList nullMeta in Pandoc meta mempty @@ -162,7 +162,7 @@ tests = [ "HTML_HEAD values are added to header-includes" =: "#+html_head: <meta/>" =?> let html = rawInline "html" "<meta/>" - inclList = MetaList [MetaInlines (toList html)] + inclList = MetaList [MetaInlines (B.toList html)] meta = setMeta "header-includes" inclList nullMeta in Pandoc meta mempty diff --git a/test/Tests/Readers/Org/Shared.hs b/test/Tests/Readers/Org/Shared.hs index c584eff19..a1baaf75e 100644 --- a/test/Tests/Readers/Org/Shared.hs +++ b/test/Tests/Readers/Org/Shared.hs @@ -29,7 +29,7 @@ org :: Text -> Pandoc org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test org diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs index a12b59fc2..95e64c489 100644 --- a/test/Tests/Readers/RST.hs +++ b/test/Tests/Readers/RST.hs @@ -25,7 +25,7 @@ rst :: Text -> Pandoc rst = purely $ readRST def{ readerStandalone = True } infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test rst diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index 013f29d68..eb96b20ee 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -30,7 +30,7 @@ t2t = purely $ \s -> do readTxt2Tags def s infix 4 =: -(=:) :: ToString c +(=:) :: ToText c => String -> (Text, c) -> TestTree (=:) = test t2t |
