{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.JATS (tests) where import Prelude 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 "@&" =?> "

@&

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

@&

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

emphasized

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

first

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

second

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

third

\n\ \
\n\ \
" , 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<fn>\n\ \ <p>note</p>\n\ \ </fn>\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\ \" ] ]