module Tests.Writers.Muse (tests) where import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder muse :: (ToPandoc a) => a -> String muse = museWithOpts def{ writerWrapText = WrapNone } museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String museWithOpts opts = unpack . purely (writeMuse opts) . toPandoc infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> TestTree (=:) = test muse tests :: [TestTree] tests = [ testGroup "block elements" [ "plain" =: plain (text "Foo bar.") =?> "Foo bar." , testGroup "paragraphs" [ "single paragraph" =: para (text "Sample paragraph.") =?> "Sample paragraph." , "two paragraphs" =: para (text "First paragraph.") <> para (text "Second paragraph.") =?> unlines [ "First paragraph." , "" , "Second paragraph." ] ] , "line block" =: lineBlock [text "Foo", text "bar", text "baz"] =?> unlines [ "" , "Foo" , "bar" , "baz" , "" ] , "code block" =: codeBlock "int main(void) {\n\treturn 0;\n}" =?> unlines [ "" , "int main(void) {" , "\treturn 0;" , "}" , "" ] , "html raw block" =: rawBlock "html" "
" =?> unlines [ "" , "
" , "
" ] , "block quote" =: blockQuote (para (text "Foo")) =?> unlines [ "" , "Foo" , "" ] , testGroup "lists" [ testGroup "simple lists" [ "ordered list" =: orderedList [ plain $ text "first" , plain $ text "second" , plain $ text "third" ] =?> unlines [ " 1. first" , " 2. second" , " 3. third" ] , "ordered list with Roman numerals" =: orderedListWith (1, UpperRoman, DefaultDelim) [ plain $ text "first" , plain $ text "second" , plain $ text "third" ] =?> unlines [ " I. first" , " II. second" , " III. third" ] , "bullet list" =: bulletList [ plain $ text "first" , plain $ text "second" , plain $ text "third" ] =?> unlines [ " - first" , " - second" , " - third" ] , "definition list" =: definitionList [ (text "first definition", [plain $ text "first description"]) , (text "second definition", [plain $ text "second description"]) , (text "third definition", [plain $ text "third description"]) ] =?> unlines [ " first definition :: first description" , " second definition :: second description" , " third definition :: third description" ] ] -- Test that lists of the same type and style are separated with two blanklines , testGroup "sequential lists" [ "bullet lists" =: bulletList [ para $ text "First" , para $ text "Second" , para $ text "Third" ] <> bulletList [ para $ text "Fourth" , para $ text "Fifth" ] =?> unlines [ " - First" , " - Second" , " - Third" , "" , "" , " - Fourth" , " - Fifth" ] , "ordered lists of the same style" =: orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "First" , para $ text "Second" ] <> orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third" , para $ text "Fourth" ] =?> unlines [ " I. First" , " II. Second" , "" , "" , " I. Third" , " II. Fourth" ] , "ordered lists with equal styles" =: orderedList [ para $ text "First" , para $ text "Second" ] <> orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third" , para $ text "Fourth" ] =?> unlines [ " 1. First" , " 2. Second" , "" , "" , " 1. Third" , " 2. Fourth" ] , "bullet and ordered lists" =: bulletList [ para $ text "First" , para $ text "Second" ] <> orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third" , para $ text "Fourth" ] =?> unlines [ " - First" , " - Second" , "" , " I. Third" , " II. Fourth" ] , "different style ordered lists" =: orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "First" , para $ text "Second" ] <> orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third" , para $ text "Fourth" ] =?> unlines [ " I. First" , " II. Second" , "" , " 1. Third" , " 2. Fourth" ] ] , testGroup "nested lists" [ "nested ordered list" =: orderedList [ plain $ text "First outer" , plain (text "Second outer:") <> orderedList [ plain $ text "first" , plain $ text "second" ] , plain $ text "Third outer" ] =?> unlines [ " 1. First outer" , " 2. Second outer:" , " 1. first" , " 2. second" , " 3. Third outer" ] , "nested bullet lists" =: bulletList [ plain $ text "First outer" , plain (text "Second outer:") <> bulletList [ plain $ text "first" , plain $ text "second" ] , plain $ text "Third outer" ] =?> unlines [ " - First outer" , " - Second outer:" , " - first" , " - second" , " - Third outer" ] , "nested definition lists" =: definitionList [ (text "first definition", [plain $ text "first description"]) , (text "second definition", [ plain (text "second description") , definitionList [ ( text "first inner definition" , [plain $ text "first inner description"]) , ( text "second inner definition" , [plain $ text "second inner description"]) ] ] ) ] =?> unlines [ " first definition :: first description" , " second definition :: second description" , " first inner definition :: first inner description" , " second inner definition :: second inner description" ] ] -- Check that list is intended with one space even inside a quote , "List inside block quote" =: blockQuote (orderedList [ plain $ text "first" , plain $ text "second" , plain $ text "third" ]) =?> unlines [ "" , " 1. first" , " 2. second" , " 3. third" , "" ] ] , testGroup "headings" [ "normal heading" =: header 1 (text "foo") =?> "* foo" , "heading levels" =: header 1 (text "First level") <> header 3 (text "Third level") =?> unlines [ "* First level" , "" , "*** Third level" ] ] , "horizontal rule" =: horizontalRule =?> "----" , testGroup "tables" [ "table without header" =: let rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] ,[para $ text "Para 2.1", para $ text "Para 2.2"]] in simpleTable [] rows =?> unlines [ " Para 1.1 | Para 1.2" , " Para 2.1 | Para 2.2" ] , "table with header" =: let headers = [plain $ text "header 1", plain $ text "header 2"] rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] ,[para $ text "Para 2.1", para $ text "Para 2.2"]] in simpleTable headers rows =?> unlines [ " header 1 || header 2" , " Para 1.1 | Para 1.2" , " Para 2.1 | Para 2.2" ] , "table with header and caption" =: let caption = text "Table 1" headers = [plain $ text "header 1", plain $ text "header 2"] rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] ,[para $ text "Para 2.1", para $ text "Para 2.2"]] in table caption mempty headers rows =?> unlines [ " header 1 || header 2" , " Para 1.1 | Para 1.2" , " Para 2.1 | Para 2.2" , " |+ Table 1 +|" ] ] -- Div is trivial -- Null is trivial ] , testGroup "inline elements" [ testGroup "string" [ "string" =: str "foo" =?> "foo" , "escape footnote" =: str "[1]" =?> "[1]" , "escape verbatim close tag" =: str "foobar" =?> "foo</verbatim>bar" , "escape pipe to avoid accidental tables" =: str "foo | bar" =?> "foo | bar" , "escape definition list markers" =: str "::" =?> "::" -- We don't want colons to be escaped if they can't be confused -- with definition list item markers. , "do not escape colon" =: str ":" =?> ":" ] , testGroup "emphasis" [ "emph" =: emph (text "foo") =?> "foo" , "strong" =: strong (text "foo") =?> "foo" , "strikeout" =: strikeout (text "foo") =?> "foo" ] , "superscript" =: superscript (text "foo") =?> "foo" , "subscript" =: subscript (text "foo") =?> "foo" , "smallcaps" =: smallcaps (text "foo") =?> "foo" , "single quoted" =: singleQuoted (text "foo") =?> "'foo'" , "double quoted" =: doubleQuoted (text "foo") =?> "\"foo\"" -- Cite is trivial , testGroup "code" [ "simple" =: code "foo" =?> "foo" , "escape lightweight markup" =: code "foo = bar" =?> "foo = bar" , "escape tag" =: code "foo = bar baz" =?> "foo = bar baz" ] , testGroup "spaces" [ "space" =: text "a" <> space <> text "b" =?> "a b" , "soft break" =: text "a" <> softbreak <> text "b" =?> "a b" , test (museWithOpts def{ writerWrapText = WrapPreserve }) "preserve soft break" $ text "a" <> softbreak <> text "b" =?> "a\nb" , "line break" =: text "a" <> linebreak <> text "b" =?> "a
\nb" ] , testGroup "math" [ "inline math" =: math "2^3" =?> "23" , "display math" =: displayMath "2^3" =?> "23" ] , "raw inline" =: rawInline "html" "marked text" =?> "marked text" , testGroup "links" [ "link with description" =: link "https://example.com" "" (str "Link 1") =?> "[[https://example.com][Link 1]]" , "link without description" =: link "https://example.com" "" (str "https://example.com") =?> "[[https://example.com]]" -- Internal links in Muse include '#' , "link to anchor" =: link "#intro" "" (str "Introduction") =?> "[[#intro][Introduction]]" -- According to Emacs Muse manual, links to images should be prefixed with "URL:" , "link to image with description" =: link "1.png" "" (str "Link to image") =?> "[[URL:1.png][Link to image]]" , "link to image without description" =: link "1.png" "" (str "1.png") =?> "[[URL:1.png]]" ] , "image" =: image "image.png" "Image 1" (str "") =?> "[[image.png][Image 1]]" , "note" =: note (plain (text "Foo")) =?> unlines [ "[1]" , "" , "[1] Foo" ] , "span" =: spanWith ("",["foobar"],[]) (str "Some text") =?> "Some text" , testGroup "combined" [ "emph word before" =: para (text "foo" <> emph (text "bar")) =?> "foobar" , "emph word after" =: para (emph (text "foo") <> text "bar") =?> "foobar" , "emph quoted" =: para (doubleQuoted (emph (text "foo"))) =?> "\"foo\"" , "strong word before" =: para (text "foo" <> strong (text "bar")) =?> "foobar" , "strong word after" =: para (strong (text "foo") <> text "bar") =?> "foobar" , "strong quoted" =: para (singleQuoted (strong (text "foo"))) =?> "'foo'" ] ] ]