aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
authorHamish Mackenzie <Hamish.K.Mackenzie@googlemail.com>2017-12-13 12:06:22 +1300
committerHamish Mackenzie <Hamish.K.Mackenzie@googlemail.com>2017-12-13 12:06:22 +1300
commitec1693505c65ef5dfca1df09d415f852a2787c15 (patch)
tree7c81603936b65d7ab69a27ca5cdf1d2bec6df147 /test
parent7d23031b904d9371de8ce9ffe943e426bd5056c8 (diff)
downloadpandoc-ec1693505c65ef5dfca1df09d415f852a2787c15.tar.gz
fig, table-wrap & caption Divs for JATS writer
Support writing <fig> and <table-wrap> elements with <title> and <caption> inside them by using Divs with class set to on of fig, table-wrap or cation. The title is included as a Heading so the constraint on where Heading can occur is also relaxed. Also leaves out empty alt attributes on links.
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Writers/JATS.hs119
-rw-r--r--test/test-pandoc.hs2
2 files changed, 121 insertions, 0 deletions
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
new file mode 100644
index 000000000..cd4609849
--- /dev/null
+++ b/test/Tests/Writers/JATS.hs
@@ -0,0 +1,119 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.JATS (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+jats :: (ToPandoc a) => a -> String
+jats = unpack . purely (writeJATS def{ writerWrapText = WrapNone }) . toPandoc
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test jats "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test jats "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test jats
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<p>\n <monospace>@&amp;</monospace>\n</p>"
+ ]
+ , testGroup "images"
+ [ "basic" =:
+ image "/url" "title" mempty
+ =?> "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
+ ]
+ , testGroup "inlines"
+ [ "Emphasis" =: emph ("emphasized")
+ =?> "<p>\n <italic>emphasized</italic>\n</p>"
+ ]
+ , "bullet list" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ first\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ second\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ third\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \</list>"
+ , testGroup "definition lists"
+ [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
+ [plain (text "hi there")])] =?>
+ "<def-list>\n\
+ \ <def-item>\n\
+ \ <term>\n\
+ \ <xref alt=\"testing\" rid=\"go\">testing</xref>\n\
+ \ </term>\n\
+ \ <def>\n\
+ \ <p>\n\
+ \ hi there\n\
+ \ </p>\n\
+ \ </def>\n\
+ \ </def-item>\n\
+ \</def-list>"
+ ]
+ , testGroup "math"
+ [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \ <mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula>\n\
+ \</p>"
+ ]
+ , testGroup "headers"
+ [ "unnumbered header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header 1" <> note (plain $ text "note")) =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header 1<fn>\n\
+ \ <p>\n\
+ \ note\n\
+ \ </p>\n\
+ \ </fn></title>\n\
+ \</sec>"
+ , "unnumbered sub header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header")
+ <> headerWith ("foo",["unnumbered"],[]) 2
+ (text "Sub-Header") =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header</title>\n\
+ \ <sec id=\"foo\">\n\
+ \ <title>Sub-Header</title>\n\
+ \ </sec>\n\
+ \</sec>"
+ , "containing image" =:
+ header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
+ "<sec>\n\
+ \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
+ \</sec>"
+ ]
+ ]
+
+
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index e1ce1bc70..123434411 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -25,6 +25,7 @@ import qualified Tests.Writers.Docbook
import qualified Tests.Writers.Docx
import qualified Tests.Writers.FB2
import qualified Tests.Writers.HTML
+import qualified Tests.Writers.JATS
import qualified Tests.Writers.LaTeX
import qualified Tests.Writers.Markdown
import qualified Tests.Writers.Muse
@@ -44,6 +45,7 @@ tests = testGroup "pandoc tests" [ Tests.Command.tests
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests
, testGroup "LaTeX" Tests.Writers.LaTeX.tests
, testGroup "HTML" Tests.Writers.HTML.tests
+ , testGroup "JATS" Tests.Writers.JATS.tests
, testGroup "Docbook" Tests.Writers.Docbook.tests
, testGroup "Markdown" Tests.Writers.Markdown.tests
, testGroup "Org" Tests.Writers.Org.tests