{-# LANGUAGE OverloadedStrings #-} module Tests.Writers.JATS (tests) where import Data.Text (Text) import Test.Tasty import Test.Tasty.HUnit (HasCallStack) import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder import qualified Data.Text as T jats :: (ToPandoc a) => a -> Text jats = purely (writeJATS def{ writerWrapText = WrapNone }) . toPandoc jatsArticleAuthoring :: (ToPandoc a) => a -> Text jatsArticleAuthoring = purely (writeJatsArticleAuthoring 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, HasCallStack) => String -> (a, Text) -> TestTree (=:) = test jats tests :: [TestTree] tests = [ testGroup "inline code" [ "basic" =: code "@&" =?> "

@&

" , "lang" =: codeWith ("", ["c"], []) "@&" =?> "

@&

" ] , testGroup "block code" [ "basic" =: codeBlock "@&" =?> "@&" , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "@&" ] , testGroup "images" [ "basic" =: image "/url" "title" mempty =?> "" ] , testGroup "inlines" [ "Emphasis" =: emph "emphasized" =?> "

emphasized

" , test jatsArticleAuthoring "footnote in articleauthoring tag set" ("test" <> note (para "footnote") =?> unlines [ "

test" , "

footnote

" , "

" ]) ] , testGroup "bullet list" [ "plain items" =: bulletList [ plain $ text "first" , plain $ text "second" , plain $ text "third" ] =?> "\n\ \ \n\ \

first

\n\ \
\n\ \ \n\ \

second

\n\ \
\n\ \ \n\ \

third

\n\ \
\n\ \
" , "item with implicit figure" =: bulletList [ simpleFigure (text "caption") "a.png" "" ] =?> T.unlines [ "" , " " , "

" , " " , "

caption

" , " " xlink:href=\"a.png\" xlink:title=\"\" />" , " " , "

" , "
" , "
" ] ] , testGroup "definition lists" [ "with internal link" =: definitionList [(link "#go" "" (str "testing"), [plain (text "hi there")])] =?> "\n\ \ \n\ \ testing\n\ \ \n\ \

hi there

\n\ \
\n\ \
\n\ \
" ] , testGroup "math" [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> "

\n\ \\n\ \σ|{x}

" ] , testGroup "headers" [ "unnumbered header" =: headerWith ("foo",["unnumbered"],[]) 1 (text "Header 1" <> note (plain $ text "note")) =?> "\n\ \ Header 1<xref ref-type=\"fn\" rid=\"fn1\">1</xref>\n\ \" , "unnumbered sub header" =: headerWith ("foo",["unnumbered"],[]) 1 (text "Header") <> headerWith ("foo",["unnumbered"],[]) 2 (text "Sub-Header") =?> "\n\ \ Header\n\ \ \n\ \ Sub-Header\n\ \ \n\ \" , "containing image" =: header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?> "\n\ \ <inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" />\n\ \" ] , testGroup "ids" [ "non-ASCII in header ID" =: headerWith ("smørbrød",[],[]) 1 (text "smørbrød") =?> T.unlines [ "" , " smørbrød" , "" ] , "disallowed symbol in header id" =: headerWith ("i/o",[],[]) 1 (text "I/O") =?> T.unlines [ "" , " I/O" , "" ] , "disallowed symbols in internal link target" =: link "#foo:bar" "" "baz" =?> "

baz

" , "code id starting with a number" =: codeWith ("7y",[],[]) "print 5" =?> "

print 5

" ] , testGroup "spans" [ "unwrapped if no attributes given" =: spanWith nullAttr "text in span" =?> "

text in span

" , "converted to named-content element if class given" =: spanWith ("a", ["genus-species"], [("alt", "aa")]) "C. elegans" =?> ("

" <> "C. elegans

") , "unwrapped if styled-content element would have no attributes" =: spanWith ("", [], [("hidden", "true")]) "text in span" =?> "

text in span

" , "use content-type attribute if present" =: spanWith ("", [], [("content-type", "species")]) "E. coli" =?> "

E. coli

" ] ]