{-# LANGUAGE OverloadedStrings #-} {- | Module : Tests.Readers.JATS Copyright : © 2017 Hamish Mackenzie License : GNU GPL, version 2 or above Maintainer : Hamish Mackenzie Stability : alpha Portability : portable Tests for the JATS reader. -} module Tests.Readers.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 :: Text -> Pandoc jats = purely $ readJATS def tests :: [TestTree] tests = [ testGroup "inline code" [ test jats "basic" $ "

\n @&\n

" =?> para (code "@&") ] , testGroup "block code" [ test jats "basic" $ "@&" =?> codeBlock "@&" , test jats "lang" $ "@&" =?> codeBlockWith ("", ["c"], []) "@&" ] , testGroup "images" [ test jats "basic" $ "" =?> para (image "/url" "title" mempty) , test jats "alt-text" $ "\n\ \ Alternative text of the graphic\n\ \ \n\ \ This is the title of the caption\n\ \

Google doodle from 14 March 2003

\n\ \
" =?> Para [ Image ( "graphic001" , [ "This" , "is" , "the" , "role" , "of" , "the" , "graphic" ] , [] ) [ Str "Alternative" , Space , Str "text" , Space , Str "of" , Space , Str "the" , Space , Str "graphic" ] ( "https://lh3.googleusercontent.com/dB7iirJ3ncQaVMBGE2YX-WCeoAVIChb6NAzoFcKCFChMsrixJvD7ZRbvcaC-ceXEzXYaoH4K5vaoRDsUyBHFkpIDPnsn3bnzovbvi0a2Gg=s660" , "This is the title of the graphic" ) ] ] , test jats "bullet list" $ "\n\ \ \n\ \

\n\ \ first\n\ \

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

\n\ \ second\n\ \

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

\n\ \ third\n\ \

\n\ \
\n\ \
" =?> bulletList [ para $ text "first" , para $ text "second" , para $ text "third" ] , testGroup "definition lists" [ test jats "with internal link" $ "\n\ \ \n\ \ \n\ \ testing\n\ \ \n\ \ \n\ \

\n\ \ hi there\n\ \

\n\ \
\n\ \
\n\ \
" =?> definitionList [(link "#go" "" (str "testing"), [para (text "hi there")])] ] , testGroup "math" [ test jats "escape |" $ "

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

" =?> para (math "\\sigma|_{\\{x\\}}") , test jats "tex-math only" $ "

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

" =?> para (math "\\sigma|_{\\{x\\}}") , test jats "math ml only" $ "

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

" =?> para (math "\\sigma|_{\\{ x\\}}") ] , testGroup "headers" -- TODO fix footnotes in headers -- [ test jats "unnumbered header" $ -- "\n\ -- \ Header 1<fn>\n\ -- \ <p>\n\ -- \ note\n\ -- \ </p>\n\ -- \ </fn>\n\ -- \" -- =?> header 1 -- (text "Header 1" <> note (plain $ text "note")) [ test jats "unnumbered sub header" $ "\n\ \ Header\n\ \ \n\ \ Sub-Header\n\ \ \n\ \" =?> headerWith ("foo", [], []) 1 (text "Header") <> headerWith ("foo2", [], []) 2 (text "Sub-Header") , test jats "containing image" $ "\n\ \ <inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" />\n\ \" =?> header 1 (image "imgs/foo.jpg" "" mempty) ] , testGroup "metadata" [ test jats "abstract" $ T.unlines [ "" , "" , "" , "

Paragraph 1

" , "

Paragraph 2

" , "
" , "
" , "
" ] =?> let abstract = para "Paragraph 1" <> para "Paragraph 2" in setMeta "abstract" abstract $ doc mempty ] ]