pandoc/tests/Tests/Readers/Odt.hs
hubertp-lshift 015dead0bb [odt] Infer table's caption from the paragraph (#3224)
ODT's reader always put empty captions for the parsed
tables. This commit
1) checks paragraphs that follow the table definition
2) treats specially a paragraph with a style named 'Table'
3) does some postprocessing of the paragraphs that combines
 tables followed immediately by captions

The ODT writer used 'TableCaption' style name for the caption
paragraph. This commit follows the open office approach which
allows for appending captions to table but uses a built-in style
named 'Table' instead of 'TableCaption'. Any users of odt format
(both writer and reader) are therefore required to change the
style's name to 'Table', if necessary.
2016-11-26 21:45:56 +01:00

164 lines
6.2 KiB
Haskell

module Tests.Readers.Odt (tests) where
import Control.Monad ( liftM )
import Text.Pandoc.Options
import Text.Pandoc.Readers.Native
import Text.Pandoc.Readers.Markdown
import Text.Pandoc.Definition
import Tests.Helpers
import Test.Framework
import qualified Data.ByteString.Lazy as B
import Text.Pandoc.Readers.Odt
import Text.Pandoc.Writers.Native (writeNative)
import qualified Data.Map as M
import Text.Pandoc.Error
tests :: [Test]
tests = testsComparingToMarkdown ++ testsComparingToNative
testsComparingToMarkdown :: [Test]
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"
testsComparingToNative :: [Test]
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
toString d = writeNative def{ writerStandalone = s } $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> False
| otherwise -> True
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
nativeFile <- Prelude.readFile nativePath
odtFile <- B.readFile odtPath
let native = getNoNormVia id "native" $ readNative nativeFile
let odt = getNoNormVia fst "odt" $ readOdt opts odtFile
return (odt,native)
compareOdtToMarkdown :: TestCreator
compareOdtToMarkdown opts odtPath markdownPath = do
markdownFile <- Prelude.readFile markdownPath
odtFile <- B.readFile odtPath
let markdown = getNoNormVia id "markdown" $ readMarkdown opts markdownFile
let odt = getNoNormVia fst "odt" $ readOdt opts odtFile
return (odt,markdown)
createTest :: TestCreator
-> TestName
-> FilePath -> FilePath
-> Test
createTest creator name path1 path2 =
buildTest $ liftM (test id name) (creator def path1 path2)
{-
--
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
testMediaBagIO :: String -> FilePath -> IO Test
testMediaBagIO name odtFile = do
outcome <- compareMediaBagIO odtFile
return $ testCase name (assertBool
("Media didn't match media bag in file " ++ odtFile)
outcome)
testMediaBag :: String -> FilePath -> Test
testMediaBag name odtFile = buildTest $ testMediaBagIO name odtFile
-}
--
namesOfTestsComparingToMarkdown :: [ String ]
namesOfTestsComparingToMarkdown = [ "bold"
-- , "citation"
, "endnote"
, "externalLink"
, "footnote"
, "headers"
-- , "horizontalRule"
, "italic"
-- , "listBlocks"
, "paragraph"
, "strikeout"
-- , "trackedChanges"
, "underlined"
]
namesOfTestsComparingToNative :: [ String ]
namesOfTestsComparingToNative = [ "blockquote"
, "image"
, "imageIndex"
, "imageWithCaption"
, "inlinedCode"
, "orderedListMixed"
, "orderedListRoman"
, "orderedListSimple"
, "referenceToChapter"
, "referenceToListItem"
, "referenceToText"
, "simpleTable"
, "simpleTableWithCaption"
-- , "table"
, "unicode"
, "unorderedList"
]