Switch to new pandoc-types and use Text instead of String [API change].
PR #5884.
+ Use pandoc-types 1.20 and texmath 0.12.
+ Text is now used instead of String, with a few exceptions.
+ In the MediaBag module, some of the types using Strings
were switched to use FilePath instead (not Text).
+ In the Parsing module, new parsers `manyChar`, `many1Char`,
`manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`,
`mantyUntilChar` have been added: these are like their
unsuffixed counterparts but pack some or all of their output.
+ `glob` in Text.Pandoc.Class still takes String since it seems
to be intended as an interface to Glob, which uses strings.
It seems to be used only once in the package, in the EPUB writer,
so that is not hard to change.
2019-11-04 22:12:37 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-02-04 22:52:31 +01:00
|
|
|
{- |
|
|
|
|
Module : Tests.Readers.Odt
|
2022-01-01 20:02:31 +01:00
|
|
|
Copyright : © 2015-2022 John MacFarlane
|
2019-02-04 22:52:31 +01:00
|
|
|
2015 Martin Linnemann
|
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Tests for the ODT reader.
|
|
|
|
-}
|
2015-07-23 09:06:14 +02:00
|
|
|
module Tests.Readers.Odt (tests) where
|
|
|
|
|
2017-03-04 13:03:41 +01:00
|
|
|
import Control.Monad (liftM)
|
2017-06-10 18:26:44 +02:00
|
|
|
import qualified Data.ByteString as BS
|
2017-10-28 05:28:29 +02:00
|
|
|
import qualified Data.ByteString.Lazy as B
|
2015-07-23 09:06:14 +02:00
|
|
|
import qualified Data.Map as M
|
2017-06-10 23:39:49 +02:00
|
|
|
import Data.Text (unpack)
|
2017-10-28 05:28:29 +02:00
|
|
|
import System.IO.Unsafe (unsafePerformIO)
|
2017-03-14 17:05:36 +01:00
|
|
|
import Test.Tasty
|
2017-03-04 13:03:41 +01:00
|
|
|
import Tests.Helpers
|
|
|
|
import Text.Pandoc
|
2017-10-28 05:28:29 +02:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
2017-01-15 20:42:00 +01:00
|
|
|
|
|
|
|
defopts :: ReaderOptions
|
|
|
|
defopts = def{ readerExtensions = getDefaultExtensions "odt" }
|
2015-07-23 09:06:14 +02:00
|
|
|
|
2017-03-14 17:05:36 +01:00
|
|
|
tests :: [TestTree]
|
2015-07-23 09:06:14 +02:00
|
|
|
tests = testsComparingToMarkdown ++ testsComparingToNative
|
|
|
|
|
2017-03-14 17:05:36 +01:00
|
|
|
testsComparingToMarkdown :: [TestTree]
|
2015-07-23 09:06:14 +02:00
|
|
|
testsComparingToMarkdown = map nameToTest namesOfTestsComparingToMarkdown
|
|
|
|
where nameToTest name = createTest
|
|
|
|
compareOdtToMarkdown
|
|
|
|
name
|
|
|
|
(toOdtPath name)
|
|
|
|
(toMarkdownPath name)
|
|
|
|
toOdtPath name = "odt/odt/" ++ name ++ ".odt"
|
|
|
|
toMarkdownPath name = "odt/markdown/" ++ name ++ ".md"
|
|
|
|
|
2017-03-14 17:05:36 +01:00
|
|
|
testsComparingToNative :: [TestTree]
|
2015-07-23 09:06:14 +02:00
|
|
|
testsComparingToNative = map nameToTest namesOfTestsComparingToNative
|
|
|
|
where nameToTest name = createTest
|
|
|
|
compareOdtToNative
|
|
|
|
name
|
|
|
|
(toOdtPath name)
|
|
|
|
(toNativePath name)
|
|
|
|
toOdtPath name = "odt/odt/" ++ name ++ ".odt"
|
|
|
|
toNativePath name = "odt/native/" ++ name ++ ".native"
|
|
|
|
|
|
|
|
|
|
|
|
newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
|
|
|
|
deriving ( Show )
|
|
|
|
|
|
|
|
instance ToString NoNormPandoc where
|
2017-06-10 23:39:49 +02:00
|
|
|
toString d = unpack $
|
|
|
|
purely (writeNative def{ writerTemplate = s }) $ toPandoc d
|
2015-07-23 09:06:14 +02:00
|
|
|
where s = case d of
|
|
|
|
NoNormPandoc (Pandoc (Meta m) _)
|
2016-11-30 15:34:58 +01:00
|
|
|
| M.null m -> Nothing
|
2019-07-26 21:00:44 +02:00
|
|
|
| otherwise -> Just mempty -- need this for Meta output
|
2015-07-23 09:06:14 +02:00
|
|
|
|
|
|
|
instance ToPandoc NoNormPandoc where
|
|
|
|
toPandoc = unNoNorm
|
|
|
|
|
|
|
|
getNoNormVia :: (a -> Pandoc) -> String -> Either PandocError a -> NoNormPandoc
|
|
|
|
getNoNormVia _ readerName (Left _) = error (readerName ++ " reader failed")
|
|
|
|
getNoNormVia f _ (Right a) = NoNormPandoc (f a)
|
|
|
|
|
|
|
|
type TestCreator = ReaderOptions
|
|
|
|
-> FilePath -> FilePath
|
|
|
|
-> IO (NoNormPandoc, NoNormPandoc)
|
|
|
|
|
|
|
|
compareOdtToNative :: TestCreator
|
|
|
|
compareOdtToNative opts odtPath nativePath = do
|
2017-06-10 18:26:44 +02:00
|
|
|
nativeFile <- UTF8.toText <$> BS.readFile nativePath
|
2015-07-23 09:06:14 +02:00
|
|
|
odtFile <- B.readFile odtPath
|
2016-12-10 16:52:35 +01:00
|
|
|
native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile)
|
2016-12-01 18:47:05 +01:00
|
|
|
odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
|
2015-07-23 09:06:14 +02:00
|
|
|
return (odt,native)
|
|
|
|
|
|
|
|
compareOdtToMarkdown :: TestCreator
|
|
|
|
compareOdtToMarkdown opts odtPath markdownPath = do
|
2017-06-10 18:26:44 +02:00
|
|
|
markdownFile <- UTF8.toText <$> BS.readFile markdownPath
|
2015-07-23 09:06:14 +02:00
|
|
|
odtFile <- B.readFile odtPath
|
2017-01-15 20:42:00 +01:00
|
|
|
markdown <- getNoNormVia id "markdown" <$>
|
|
|
|
runIO (readMarkdown def{ readerExtensions = pandocExtensions }
|
|
|
|
markdownFile)
|
2016-12-01 18:47:05 +01:00
|
|
|
odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
|
2015-07-23 09:06:14 +02:00
|
|
|
return (odt,markdown)
|
|
|
|
|
|
|
|
|
|
|
|
createTest :: TestCreator
|
|
|
|
-> TestName
|
|
|
|
-> FilePath -> FilePath
|
2017-03-14 17:05:36 +01:00
|
|
|
-> TestTree
|
2015-07-23 09:06:14 +02:00
|
|
|
createTest creator name path1 path2 =
|
2017-03-14 17:05:36 +01:00
|
|
|
unsafePerformIO $ liftM (test id name) (creator defopts path1 path2)
|
2015-07-23 09:06:14 +02:00
|
|
|
|
|
|
|
{-
|
|
|
|
--
|
|
|
|
|
|
|
|
getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
|
|
|
|
getMedia archivePath mediaPath = do
|
|
|
|
zf <- B.readFile archivePath >>= return . toArchive
|
|
|
|
return $ findEntryByPath ("Pictures/" ++ mediaPath) zf >>= (Just . fromEntry)
|
|
|
|
|
|
|
|
compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool
|
|
|
|
compareMediaPathIO mediaPath mediaBag odtPath = do
|
|
|
|
odtMedia <- getMedia odtPath mediaPath
|
|
|
|
let mbBS = case lookupMedia mediaPath mediaBag of
|
|
|
|
Just (_, bs) -> bs
|
|
|
|
Nothing -> error ("couldn't find " ++
|
|
|
|
mediaPath ++
|
|
|
|
" in media bag")
|
|
|
|
odtBS = case odtMedia of
|
|
|
|
Just bs -> bs
|
|
|
|
Nothing -> error ("couldn't find " ++
|
|
|
|
mediaPath ++
|
|
|
|
" in media bag")
|
|
|
|
return $ mbBS == odtBS
|
|
|
|
|
|
|
|
compareMediaBagIO :: FilePath -> IO Bool
|
|
|
|
compareMediaBagIO odtFile = do
|
|
|
|
df <- B.readFile odtFile
|
|
|
|
let (_, mb) = readOdt def df
|
|
|
|
bools <- mapM
|
|
|
|
(\(fp, _, _) -> compareMediaPathIO fp mb odtFile)
|
|
|
|
(mediaDirectory mb)
|
|
|
|
return $ and bools
|
|
|
|
|
2017-03-14 17:05:36 +01:00
|
|
|
testMediaBagIO :: String -> FilePath -> IO TestTree
|
2015-07-23 09:06:14 +02:00
|
|
|
testMediaBagIO name odtFile = do
|
|
|
|
outcome <- compareMediaBagIO odtFile
|
|
|
|
return $ testCase name (assertBool
|
|
|
|
("Media didn't match media bag in file " ++ odtFile)
|
|
|
|
outcome)
|
|
|
|
|
2017-03-14 17:05:36 +01:00
|
|
|
testMediaBag :: String -> FilePath -> TestTree
|
2015-07-23 09:06:14 +02:00
|
|
|
testMediaBag name odtFile = buildTest $ testMediaBagIO name odtFile
|
|
|
|
-}
|
|
|
|
--
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
namesOfTestsComparingToMarkdown :: [ String ]
|
|
|
|
namesOfTestsComparingToMarkdown = [ "bold"
|
|
|
|
-- , "citation"
|
|
|
|
, "endnote"
|
|
|
|
, "externalLink"
|
|
|
|
, "footnote"
|
2019-06-20 21:08:09 +02:00
|
|
|
, "formula"
|
2015-07-23 09:06:14 +02:00
|
|
|
, "headers"
|
|
|
|
-- , "horizontalRule"
|
|
|
|
, "italic"
|
|
|
|
-- , "listBlocks"
|
|
|
|
, "paragraph"
|
|
|
|
, "strikeout"
|
|
|
|
-- , "trackedChanges"
|
|
|
|
, "underlined"
|
|
|
|
]
|
|
|
|
|
|
|
|
namesOfTestsComparingToNative :: [ String ]
|
|
|
|
namesOfTestsComparingToNative = [ "blockquote"
|
2016-10-17 16:35:13 +02:00
|
|
|
, "image"
|
|
|
|
, "imageIndex"
|
|
|
|
, "imageWithCaption"
|
2016-10-26 15:53:33 +02:00
|
|
|
, "inlinedCode"
|
2015-07-23 09:06:14 +02:00
|
|
|
, "orderedListMixed"
|
|
|
|
, "orderedListRoman"
|
|
|
|
, "orderedListSimple"
|
2022-01-02 11:28:38 +01:00
|
|
|
, "orderedListHeader"
|
2015-07-23 09:06:14 +02:00
|
|
|
, "referenceToChapter"
|
|
|
|
, "referenceToListItem"
|
|
|
|
, "referenceToText"
|
|
|
|
, "simpleTable"
|
2016-11-26 21:45:56 +01:00
|
|
|
, "simpleTableWithCaption"
|
2021-04-01 01:44:34 +02:00
|
|
|
, "tab"
|
2015-07-23 09:06:14 +02:00
|
|
|
-- , "table"
|
2016-12-13 17:20:10 +01:00
|
|
|
, "textMixedStyles"
|
2016-12-13 14:20:21 +01:00
|
|
|
, "tableWithContents"
|
2015-07-23 09:06:14 +02:00
|
|
|
, "unicode"
|
|
|
|
, "unorderedList"
|
2022-01-02 11:28:38 +01:00
|
|
|
, "unorderedListHeader"
|
2016-10-17 16:35:13 +02:00
|
|
|
]
|