Merge pull request #4001 from labdsf/fb2-tests

Add new style FB2 tests
This commit is contained in:
John MacFarlane 2017-11-01 00:37:29 -04:00 committed by GitHub
commit 1f393f1a8b
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
3 changed files with 37 additions and 0 deletions

View file

@ -596,6 +596,7 @@ test-suite test-pandoc
Tests.Writers.RST
Tests.Writers.TEI
Tests.Writers.Muse
Tests.Writers.FB2
ghc-options: -rtsopts -Wall -fno-warn-unused-do-bind -threaded
default-language: Haskell98

34
test/Tests/Writers/FB2.hs Normal file
View file

@ -0,0 +1,34 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.FB2 (tests) where
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
fb2 :: String -> String
fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++
"<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section>" ++ x ++ "</section></body></FictionBook>"
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeFB2 def) . toPandoc)
tests :: [TestTree]
tests = [ testGroup "block elements"
["para" =: para "Lorem ipsum cetera."
=?> fb2 "<p>Lorem ipsum cetera.</p>"
]
, testGroup "inlines"
[
"Emphasis" =: emph ("emphasized")
=?> fb2 "<emphasis>emphasized</emphasis>"
]
, "bullet list" =: bulletList [ plain $ text "first"
, plain $ text "second"
, plain $ text "third"
]
=?> fb2 "<p>\x2022 first</p><p>\x2022 second</p><p>\x2022 third</p>"
]

View file

@ -23,6 +23,7 @@ import qualified Tests.Writers.AsciiDoc
import qualified Tests.Writers.ConTeXt
import qualified Tests.Writers.Docbook
import qualified Tests.Writers.Docx
import qualified Tests.Writers.FB2
import qualified Tests.Writers.HTML
import qualified Tests.Writers.LaTeX
import qualified Tests.Writers.Markdown
@ -52,6 +53,7 @@ tests = testGroup "pandoc tests" [ Tests.Command.tests
, testGroup "RST" Tests.Writers.RST.tests
, testGroup "TEI" Tests.Writers.TEI.tests
, testGroup "Muse" Tests.Writers.Muse.tests
, testGroup "FB2" Tests.Writers.FB2.tests
]
, testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests