diff options
Diffstat (limited to 'test')
-rw-r--r-- | test/Tests/Helpers.hs | 3 | ||||
-rw-r--r-- | test/Tests/Old.hs | 3 | ||||
-rw-r--r-- | test/Tests/Readers/Docx.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Man.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Muse.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Org/Block/Table.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Org/Directive.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Txt2Tags.hs | 2 | ||||
-rw-r--r-- | test/Tests/Shared.hs | 36 | ||||
-rw-r--r-- | test/Tests/Writers/OOXML.hs | 2 |
10 files changed, 27 insertions, 29 deletions
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 2ada79475..c9ee6d206 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -1,7 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE TypeSynonymInstances #-} {- | Module : Tests.Helpers Copyright : © 2006-2020 John MacFarlane @@ -104,7 +103,7 @@ findPandoc = do -- cabalv1 "test-pandoc" : "build" : ps -> joinPath (reverse ps) </> "build" </> "pandoc" - _ -> error $ "findPandoc: could not find pandoc executable" + _ -> error "findPandoc: could not find pandoc executable" let pandocPath = pandocDir </> "pandoc" #ifdef _WINDOWS <.> "exe" diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index ba6947eda..fc5721edb 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -14,7 +14,6 @@ module Tests.Old (tests) where import Prelude import Data.Algorithm.Diff -import Prelude hiding (readFile) import Data.List (intercalate) import Data.Maybe (catMaybes) import System.Exit @@ -291,7 +290,7 @@ fb2WriterTest pandocPath title opts inputfile normfile = where formatXML xml = splitTags $ zip xml (drop 1 xml) splitTags [] = [] - splitTags [end] = fst end : snd end : [] + splitTags [end] = [fst end, snd end] splitTags (('>','<'):rest) = ">\n" ++ splitTags rest splitTags ((c,_):rest) = c : splitTags rest ignoreBinary = unlines . filter (not . startsWith "<binary ") . lines diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index 456e0affe..80abc38f6 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -33,7 +33,7 @@ import Text.Pandoc.UTF8 as UTF8 -- tests. Since we do our own normalization, we want to make sure -- we're doing it right. -data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} +newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} deriving Show noNorm :: Pandoc -> NoNormPandoc diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs index 7280f15f2..f591aa00d 100644 --- a/test/Tests/Readers/Man.hs +++ b/test/Tests/Readers/Man.hs @@ -68,7 +68,7 @@ tests = [ testGroup "Escapes" [ "fonts" =: "aa\\fIbb\\fRcc" - =?>para (str "aa" <> (emph $ str "bb") <> str "cc") + =?>para (str "aa" <> emph (str "bb") <> str "cc") , "nested fonts" =: "\\f[BI]hi\\f[I] there\\f[R]" =?> para (emph (strong (text "hi") <> text " there")) diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 60a5e4b56..4ec1631e0 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -51,7 +51,7 @@ simpleTable' n capt headers rows (TableFoot nullAttr []) where toRow = Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] -- Tables don't round-trip yet -- diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs index d35d17979..ab404648e 100644 --- a/test/Tests/Readers/Org/Block/Table.hs +++ b/test/Tests/Readers/Org/Block/Table.hs @@ -35,7 +35,7 @@ simpleTable'' capt spec headers rows (TableFoot nullAttr []) where toRow = Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] tests :: [TestTree] tests = diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs index ba012a69f..727a29658 100644 --- a/test/Tests/Readers/Org/Directive.hs +++ b/test/Tests/Readers/Org/Directive.hs @@ -30,7 +30,7 @@ testWithFiles :: (ToString c) -> (T.Text, c) -- ^ (input, expected value) -> TestTree testWithFiles fileDefs = test (orgWithFiles fileDefs) - where + orgWithFiles :: [(FilePath, BS.ByteString)] -> T.Text -> Pandoc orgWithFiles fileDefs input = let readOrg' = readOrg def{ readerExtensions = getDefaultExtensions "org" } diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index 3989b2434..989b7f673 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -54,7 +54,7 @@ simpleTable'' spec headers rows (TableFoot nullAttr []) where toRow = Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] tests :: [TestTree] tests = diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs index 09391d9d0..a23edf452 100644 --- a/test/Tests/Shared.hs +++ b/test/Tests/Shared.hs @@ -35,24 +35,24 @@ tests = [ testGroup "compactifyDL" testCollapse :: [TestTree] testCollapse = map (testCase "collapse") - [ collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""]) - , collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"]) - , collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]]) - , collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"]) - , collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"]) - , collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"]) - , collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"]) - , collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""]) - , collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""]) - , collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."]) - , collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."]) - , collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."]) - , collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."]) - , collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"]) - , collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"]) - , collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"]) - , collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"]) - , collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"])] + [ collapseFilePath (joinPath [ ""]) @?= joinPath [ ""] + , collapseFilePath (joinPath [ ".","foo"]) @?= joinPath [ "foo"] + , collapseFilePath (joinPath [ ".",".","..","foo"]) @?= joinPath [ joinPath ["..", "foo"]] + , collapseFilePath (joinPath [ "..","foo"]) @?= joinPath [ "..","foo"] + , collapseFilePath (joinPath [ "","bar","..","baz"]) @?= joinPath [ "","baz"] + , collapseFilePath (joinPath [ "","..","baz"]) @?= joinPath [ "","..","baz"] + , collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= joinPath [ "baz"] + , collapseFilePath (joinPath [ ".",""]) @?= joinPath [ ""] + , collapseFilePath (joinPath [ ".",".",""]) @?= joinPath [ ""] + , collapseFilePath (joinPath [ "..",""]) @?= joinPath [ ".."] + , collapseFilePath (joinPath [ "..",".",""]) @?= joinPath [ ".."] + , collapseFilePath (joinPath [ ".","..",""]) @?= joinPath [ ".."] + , collapseFilePath (joinPath [ "..","..",""]) @?= joinPath [ "..",".."] + , collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= joinPath [ "parent","foo","bar"] + , collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= joinPath [ "parent","bar"] + , collapseFilePath (joinPath [ "parent","foo",".."]) @?= joinPath [ "parent"] + , collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= joinPath [ "","bar"] + , collapseFilePath (joinPath [ "",".","parent","foo"]) @?= joinPath [ "","parent","foo"]] testLegacyTable :: [TestTree] testLegacyTable = diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index f2762ddfe..628ea9409 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -48,7 +48,7 @@ displayDiff elemA elemB = showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB) goldenArchive :: FilePath -> IO Archive -goldenArchive fp = (toArchive . BL.fromStrict) <$> BS.readFile fp +goldenArchive fp = toArchive . BL.fromStrict <$> BS.readFile fp testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString) -> WriterOptions |