{-# LANGUAGE OverloadedStrings #-} module Tests.Writers.JATS (tests) where import Data.Text (Text) import Test.Tasty 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) => String -> (a, Text) -> TestTree (=:) = test jats tests :: [TestTree] tests = [ testGroup "inline code" [ "basic" =: code "@&" =?> "
@&
@&
"
]
, testGroup "images"
[ "basic" =:
image "/url" "title" mempty
=?> "test footnote
first
\n\ \second
\n\ \third
\n\ \hi there
\n\ \text in span
" , "converted to named-content element if class given" =: spanWith ("a", ["genus-species"], [("alt", "aa")]) "C. elegans" =?> ("text in span
" , "use content-type attribute if present" =: spanWith ("", [], [("content-type", "species")]) "E. coli" =?> "