Initial tests for writer

This commit is contained in:
Nikolay Yakimov 2015-03-03 14:37:02 +03:00
parent 65c80822e7
commit ae07d5ed49
9 changed files with 145 additions and 0 deletions

128
tests/Tests/Writers/Docx.hs Normal file
View file

@ -0,0 +1,128 @@
module Tests.Writers.Docx (tests) where
import Text.Pandoc.Options
import Text.Pandoc.Readers.Native
import Text.Pandoc.Definition
import Tests.Helpers
import Test.Framework
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Writers.Docx
type Options = (WriterOptions, ReaderOptions)
compareOutput :: Options
-> FilePath
-> IO (Pandoc, Pandoc)
compareOutput opts nativeFile = do
nf <- Prelude.readFile nativeFile
df <- writeDocx (fst opts) (readNative nf)
let (p, _) = readDocx (snd opts) df
return (p, readNative nf)
testCompareWithOptsIO :: Options -> String -> FilePath -> IO Test
testCompareWithOptsIO opts name nativeFile = do
(dp, np) <- compareOutput opts nativeFile
return $ test id name (dp, np)
testCompareWithOpts :: Options -> String -> FilePath -> Test
testCompareWithOpts opts name nativeFile =
buildTest $ testCompareWithOptsIO opts name nativeFile
testCompare :: String -> FilePath -> Test
testCompare = testCompareWithOpts def
tests :: [Test]
tests = [ testGroup "inlines"
[ testCompare
"font formatting"
"docx/inline_formatting_writer.native"
, testCompare
"font formatting with character styles"
"docx/char_styles.native"
, testCompare
"hyperlinks"
"docx/links_writer.native"
, testCompare
"inline image"
"docx/image_no_embed_writer.native"
, testCompare
"inline image in links"
"docx/inline_images_writer.native"
, testCompare
"handling unicode input"
"docx/unicode.native"
, testCompare
"literal tabs"
"docx/tabs.native"
, testCompare
"normalizing inlines"
"docx/normalize.native"
, testCompare
"normalizing inlines deep inside blocks"
"docx/deep_normalize.native"
, testCompare
"move trailing spaces outside of formatting"
"docx/trailing_spaces_in_formatting.native"
, testCompare
"inline code (with VerbatimChar style)"
"docx/inline_code.native"
, testCompare
"inline code in subscript and superscript"
"docx/verbatim_subsuper.native"
]
, testGroup "blocks"
[ testCompare
"headers"
"docx/headers.native"
, testCompare
"headers already having auto identifiers"
"docx/already_auto_ident.native"
, testCompare
"numbered headers automatically made into list"
"docx/numbered_header.native"
, testCompare
"i18n blocks (headers and blockquotes)"
"docx/i18n_blocks.native"
-- some level problems, look into that
-- , testCompare
-- "lists"
-- "docx/lists.native"
, testCompare
"definition lists"
"docx/definition_list.native"
, testCompare
"custom defined lists in styles"
"docx/german_styled_lists.native"
, testCompare
"footnotes and endnotes"
"docx/notes.native"
, testCompare
"blockquotes (parsing indent as blockquote)"
"docx/block_quotes_parse_indent.native"
, testCompare
"hanging indents"
"docx/hanging_indent.native"
-- tables headers do not survive round-trip, should look into that
-- , testCompare
-- "tables"
-- "docx/tables.native"
-- , testCompare
-- "tables with lists in cells"
-- "docx/table_with_list_cell.native"
, testCompare
"code block"
"docx/codeblock.native"
, testCompare
"dropcap paragraphs"
"docx/drop_cap.native"
]
, testGroup "metadata"
[ testCompareWithOpts (def,def{readerStandalone=True})
"metadata fields"
"docx/metadata.native"
, testCompareWithOpts (def,def{readerStandalone=True})
"stop recording metadata with normal text"
"docx/metadata_after_normal.native"
]
]

View file

@ -0,0 +1,2 @@
[Para [Str "An",Space,Str "image:"]
,Para [Image [] ("media/rId25.jpg","")]]

View file

@ -0,0 +1,5 @@
[Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."]
,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."]
,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Emph [Str "single",Space,Str "underlines",Space,Str "for",Space,Str "emphasis"],Str "."]
,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."]
,Para [Str "A",Space,Str "line",LineBreak,Str "break."]]

View file

@ -0,0 +1,2 @@
[Para [Str "This",Space,Str "picture",Space,Image [] ("media/rId26.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."]
,Para [Str "Here",Space,Str "is",Space,Link [Str "one",Space,Image [] ("media/rId27.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]]

View file

@ -0,0 +1,6 @@
[Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://johnmacfarlane.net/pandoc/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."]
,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]]

0
tests/media/rId25.jpg Normal file
View file

0
tests/media/rId26.jpg Normal file
View file

0
tests/media/rId27.jpg Normal file
View file

View file

@ -20,6 +20,7 @@ import qualified Tests.Writers.Native
import qualified Tests.Writers.Markdown import qualified Tests.Writers.Markdown
import qualified Tests.Writers.Plain import qualified Tests.Writers.Plain
import qualified Tests.Writers.AsciiDoc import qualified Tests.Writers.AsciiDoc
import qualified Tests.Writers.Docx
import qualified Tests.Shared import qualified Tests.Shared
import qualified Tests.Walk import qualified Tests.Walk
import Text.Pandoc.Shared (inDirectory) import Text.Pandoc.Shared (inDirectory)
@ -38,6 +39,7 @@ tests = [ testGroup "Old" Tests.Old.tests
, testGroup "Markdown" Tests.Writers.Markdown.tests , testGroup "Markdown" Tests.Writers.Markdown.tests
, testGroup "Plain" Tests.Writers.Plain.tests , testGroup "Plain" Tests.Writers.Plain.tests
, testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests , testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests
, testGroup "Docx" Tests.Writers.Docx.tests
] ]
, testGroup "Readers" , testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests [ testGroup "LaTeX" Tests.Readers.LaTeX.tests