{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.Muse (tests) where
import Prelude
import Data.List (intersperse)
import Data.Text (Text)
import qualified Data.Text as T
import Test.Tasty
import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
import Text.Pandoc.Shared (underlineSpan)
import Text.Pandoc.Walk (walk)
amuse :: Text -> Pandoc
amuse = purely $ readMuse def { readerExtensions = extensionsFromList [Ext_amuse]}
emacsMuse :: Text -> Pandoc
emacsMuse = purely $ readMuse def { readerExtensions = emptyExtensions }
infix 4 =:
(=:) :: ToString c
=> String -> (Text, c) -> TestTree
(=:) = test amuse
spcSep :: [Inlines] -> Inlines
spcSep = mconcat . intersperse space
-- Tables don't round-trip yet
--
makeRoundTrip :: Block -> Block
makeRoundTrip Table{} = Para [Str "table was here"]
makeRoundTrip (OrderedList (start, LowerAlpha, _) items) = OrderedList (start, Decimal, Period) items
makeRoundTrip (OrderedList (start, UpperAlpha, _) items) = OrderedList (start, Decimal, Period) items
makeRoundTrip x = x
-- Demand that any AST produced by Muse reader and written by Muse writer can be read back exactly the same way.
-- Currently we remove tables and compare first rewrite to the second.
roundTrip :: Block -> Bool
roundTrip b = d' == d''
where d = walk makeRoundTrip $ Pandoc nullMeta [b]
d' = rewrite d
d'' = rewrite d'
rewrite = amuse . T.pack . (++ "\n") . T.unpack .
purely (writeMuse def { writerExtensions = extensionsFromList [Ext_amuse]
, writerWrapText = WrapPreserve
})
tests :: [TestTree]
tests =
[ testGroup "Inlines"
[ "Plain String" =:
"Hello, World" =?>
para "Hello, World"
, "Muse is not XML" =: "<" =?> para "<"
, "Emphasis" =:
"*Foo bar*" =?>
para (emph . spcSep $ ["Foo", "bar"])
, "Comma after closing *" =:
"Foo *bar*, baz" =?>
para ("Foo " <> emph "bar" <> ", baz")
, "Letter after closing *" =:
"Foo *bar*x baz" =?>
para "Foo *bar*x baz"
, "Letter before opening *" =:
"Foo x*bar* baz" =?>
para "Foo x*bar* baz"
, "Emphasis tag" =:
"Foo bar" =?>
para (emph . spcSep $ ["Foo", "bar"])
, "Strong" =:
"**Cider**" =?>
para (strong "Cider")
, "Strong tag" =: "Strong" =?> para (strong "Strong")
, "Strong Emphasis" =:
"***strength***" =?>
para (strong . emph $ "strength")
, test emacsMuse "Underline"
("_Underline_" =?> para (underlineSpan "Underline"))
, "Superscript tag" =: "Superscript" =?> para (superscript "Superscript")
, "Subscript tag" =: "Subscript" =?> para (subscript "Subscript")
, "Strikeout tag" =: " foo Strikeout" =?> para (strikeout "Strikeout")
, "Opening inline tags" =: "foo bar baz" =?> para "foo bar baz"
, "Closing inline tags" =: "foo bar baz" =?> para "foo bar baz"
, "Tag soup" =: "foo bar baz" =?> para "foo bar baz"
-- Both inline tags must be within the same paragraph
, "No multiparagraph inline tags" =:
T.unlines [ "First line"
, "Second line"
, ""
, "Fourth line"
] =?>
para "First line\nSecond line" <>
para "Fourth line"
, "Linebreak" =: "Line
break" =?> para ("Line" <> linebreak <> "break")
, "Trailing whitespace inside paragraph" =:
T.unlines [ "First line " -- trailing whitespace here
, "second line"
]
=?> para "First line\nsecond line"
, "Non-breaking space" =: "Foo~~bar" =?> para "Foo\160bar"
, "Single ~" =: "Foo~bar" =?> para "Foo~bar"
, testGroup "Code markup"
[ "Code" =: "=foo(bar)=" =?> para (code "foo(bar)")
, "Not code" =: "a=b= =c=d" =?> para (text "a=b= =c=d")
-- Emacs Muse 3.20 parses this as code, we follow Amusewiki
, "Not code if closing = is detached" =: "=this is not a code =" =?> para "=this is not a code ="
, "Not code if opening = is detached" =: "= this is not a code=" =?> para "= this is not a code="
, "Code if followed by comma" =:
"Foo =bar=, baz" =?>
para (text "Foo " <> code "bar" <> text ", baz")
, "One character code" =: "=c=" =?> para (code "c")
, "Three = characters is not a code" =: "===" =?> para "==="
, "Multiline code markup" =:
"foo =bar\nbaz= end of code" =?>
para (text "foo " <> code "bar\nbaz" <> text " end of code")
{- Emacs Muse 3.20 has a bug: it publishes
- bar
-
- baz
foofoo(bar)
" =?> para (code "foo(bar)")
, "Math tag" =: "" =?> para (math "\\sum_{i=0}^n i^2")
, "Verbatim tag" =: "*
" =?> para (code ""
, " Not a nested quote"
, "
"
] =?>
blockQuote (para "Not a nested quote")
, "Multiline quote" =:
T.unlines [ " This is a quotation"
, " with a continuation"
] =?>
blockQuote (para "This is a quotation\nwith a continuation")
, testGroup "Div"
[ "Div without id" =:
T.unlines [ "
" , "" ] =?> blockQuote mempty , "Quote tag" =: T.unlines [ "
" , "Hello, world" , "" ] =?> blockQuote (para $ text "Hello, world") , "Nested quote tag" =: T.unlines [ "
" , "foo" , "" ] =?> blockQuote (para "foo" <> blockQuote (para "bar") <> para "baz") , "Indented quote inside list" =: T.unlines [ " -" , "bar" , "" , "baz" , "
" , " foo" , "" ] =?> bulletList [ blockQuote (para "foo") ] , "Verse tag" =: T.unlines [ "
" , "* Hi" , "" ] =?> blockQuote (para "* Hi") , "Headers consume anchors" =: T.unlines [ "; A comment to make sure anchor is not parsed as a directive" , "#bar" , "** Foo" ] =?> headerWith ("bar",[],[]) 2 "Foo" , "Headers don't consume anchors separated with a blankline" =: T.unlines [ "; A comment to make sure anchor is not parsed as a directive" , "#bar" , "" , "** Foo" ] =?> para (spanWith ("bar", [], []) mempty) <> header 2 "Foo" , "Headers terminate paragraph" =: T.unlines [ "foo" , "* bar" ] =?> para "foo" <> header 1 "bar" , "Headers terminate lists" =: T.unlines [ " - foo" , "* bar" ] =?> bulletList [ para "foo" ] <> header 1 "bar" , test emacsMuse "Paragraphs terminate Emacs Muse headers" (T.unlines [ "* Foo" , "bar" ] =?> header 1 "Foo" <> para "bar") , "Paragraphs don't terminate Text::Amuse headers" =: T.unlines [ "* Foo" , "bar" ] =?> header 1 "Foo\nbar" ] , testGroup "Directives" [ "Title" =: "#title Document title" =?> let titleInline = toList "Document title" meta = setMeta "title" (MetaInlines titleInline) nullMeta in Pandoc meta mempty -- Emacs Muse documentation says that "You can use any combination -- of uppercase and lowercase letters for directives", -- but also allows '-', which is not documented, but used for disable-tables. , test emacsMuse "Disable tables" ("#disable-tables t" =?> Pandoc (setMeta "disable-tables" (MetaInlines $ toList "t") nullMeta) mempty) , "Multiple directives" =: T.unlines [ "#title Document title" , "#subtitle Document subtitle" ] =?> Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $ setMeta "subtitle" (MetaInlines $ toList "Document subtitle") nullMeta) mempty , "Multiline directive" =: T.unlines [ "#title Document title" , "#notes First line" , "and second line" , "#author Name" ] =?> Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $ setMeta "notes" (MetaInlines $ toList "First line\nand second line") $ setMeta "author" (MetaInlines $ toList "Name") nullMeta) mempty ] , testGroup "Anchors" [ "Anchor" =: T.unlines [ "; A comment to make sure anchor is not parsed as a directive" , "#anchor Target" ] =?> para (spanWith ("anchor", [], []) mempty <> "Target") , "Anchor cannot start with a number" =: T.unlines [ "; A comment to make sure anchor is not parsed as a directive" , "#0notanchor Target" ] =?> para "#0notanchor Target" , "Not anchor if starts with a space" =: " #notanchor Target" =?> para "#notanchor Target" , "Anchor inside a paragraph" =: T.unlines [ "Paragraph starts here" , "#anchor and ends here." ] =?> para ("Paragraph starts here\n" <> spanWith ("anchor", [], []) mempty <> "and ends here.") , "Anchor with \"-\"" =: T.unlines [ "; A comment to make sure anchor is not parsed as a directive" , "#anchor-id Target" ] =?> para (spanWith ("anchor-id", [], []) mempty <> "Target") ] , testGroup "Footnotes" [ "Simple footnote" =: T.unlines [ "Here is a footnote[1]." , "" , "[1] Footnote contents" ] =?> para (text "Here is a footnote" <> note (para "Footnote contents") <> str ".") , "Recursive footnote" =: T.unlines [ "Start recursion here[1]" , "" , "[1] Recursion continues here[1]" ] =?> para (text "Start recursion here" <> note (para "Recursion continues here[1]")) , "Nested footnotes" =: T.unlines [ "Footnote: [1]" , "" , "[1] Nested: [2]" , "" , "[2] No recursion: [1]" ] =?> para (text "Footnote: " <> note (para (text "Nested: " <> note (para $ text "No recursion: [1]")))) , "No zero footnotes" =: T.unlines [ "Here is a footnote[0]." , "" , "[0] Footnote contents" ] =?> para "Here is a footnote[0]." <> para "[0] Footnote contents" , "Footnotes can't start with zero" =: T.unlines [ "Here is a footnote[01]." , "" , "[01] Footnote contents" ] =?> para "Here is a footnote[01]." <> para "[01] Footnote contents" , testGroup "Multiparagraph footnotes" [ "Amusewiki multiparagraph footnotes" =: T.unlines [ "Multiparagraph[1] footnotes[2]" , "" , "[1] First footnote paragraph" , "" , " Second footnote paragraph" , "with continuation" , "" , "Not a note" , "[2] Second footnote" ] =?> para (text "Multiparagraph" <> note (para "First footnote paragraph" <> para "Second footnote paragraph\nwith continuation") <> text " footnotes" <> note (para "Second footnote")) <> para (text "Not a note") -- Verse requires precise indentation, so it is good to test indentation requirements , "Note continuation with verse" =: T.unlines [ "Foo[1]" , "" , "[1] Bar" , "" , " > Baz" ] =?> para ("Foo" <> note (para "Bar" <> lineBlock ["Baz"])) , test emacsMuse "Emacs multiparagraph footnotes" (T.unlines [ "First footnote reference[1] and second footnote reference[2]." , "" , "[1] First footnote paragraph" , "" , "Second footnote" , "paragraph" , "" , "[2] Third footnote paragraph" , "" , "Fourth footnote paragraph" ] =?> para (text "First footnote reference" <> note (para "First footnote paragraph" <> para "Second footnote\nparagraph") <> text " and second footnote reference" <> note (para "Third footnote paragraph" <> para "Fourth footnote paragraph") <> text ".")) ] ] ] , testGroup "Tables" [ "Two cell table" =: "One | Two" =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [] [[plain "One", plain "Two"]] , "Table with multiple words" =: "One two | three four" =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [] [[plain "One two", plain "three four"]] , "Not a table" =: "One| Two" =?> para (text "One| Two") , "Not a table again" =: "One |Two" =?> para (text "One |Two") , "Two line table" =: T.unlines [ "One | Two" , "Three | Four" ] =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [] [[plain "One", plain "Two"], [plain "Three", plain "Four"]] , "Table with one header" =: T.unlines [ "First || Second" , "Third | Fourth" ] =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [plain "First", plain "Second"] [[plain "Third", plain "Fourth"]] , "Table with two headers" =: T.unlines [ "First || header" , "Second || header" , "Foo | bar" ] =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [plain "First", plain "header"] [[plain "Second", plain "header"], [plain "Foo", plain "bar"]] , "Header and footer reordering" =: T.unlines [ "Foo ||| bar" , "Baz || foo" , "Bar | baz" ] =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [plain "Baz", plain "foo"] [[plain "Bar", plain "baz"], [plain "Foo", plain "bar"]] , "Table with caption" =: T.unlines [ "Foo || bar || baz" , "First | row | here" , "Second | row | there" , "|+ Table caption +|" ] =?> table (text "Table caption") (replicate 3 (AlignDefault, 0.0)) [plain "Foo", plain "bar", plain "baz"] [[plain "First", plain "row", plain "here"], [plain "Second", plain "row", plain "there"]] , "Caption without table" =: "|+ Foo bar baz +|" =?> table (text "Foo bar baz") [] [] [] , "Table indented with space" =: T.unlines [ " Foo | bar" , " Baz | foo" , " Bar | baz" ] =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [] [[plain "Foo", plain "bar"], [plain "Baz", plain "foo"], [plain "Bar", plain "baz"]] , "Empty cells" =: T.unlines [ " | Foo" , " |" , " bar |" , " || baz" ] =?> table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] [plain "", plain "baz"] [[plain "", plain "Foo"], [plain "", plain ""], [plain "bar", plain ""]] ] , testGroup "Lists" [ "Bullet list" =: T.unlines [ " - Item1" , "" , " - Item2" ] =?> bulletList [ para "Item1" , para "Item2" ] , "Ordered list" =: T.unlines [ " 1. Item1" , "" , " 2. Item2" ] =?> orderedListWith (1, Decimal, Period) [ para "Item1" , para "Item2" ] , "Ordered list with implicit numbers" =: T.unlines [ " 1. Item1" , "" , " 1. Item2" , "" , " 1. Item3" ] =?> orderedListWith (1, Decimal, Period) [ para "Item1" , para "Item2" , para "Item3" ] , "Ordered list with roman numerals" =: T.unlines [ " i. First" , " ii. Second" , " iii. Third" , " iv. Fourth" ] =?> orderedListWith (1, LowerRoman, Period) [ para "First" , para "Second" , para "Third" , para "Fourth" ] , "Bullet list with empty items" =: T.unlines [ " -" , "" , " - Item2" ] =?> bulletList [ mempty , para "Item2" ] , "Ordered list with empty items" =: T.unlines [ " 1." , "" , " 2." , "" , " 3. Item3" ] =?> orderedListWith (1, Decimal, Period) [ mempty , mempty , para "Item3" ] , "Bullet list with last item empty" =: T.unlines [ " -" , "" , "foo" ] =?> bulletList [ mempty ] <> para "foo" , testGroup "Nested lists" [ "Nested bullet list" =: T.unlines [ " - Item1" , " - Item2" , " - Item3" , " - Item4" , " - Item5" , " - Item6" ] =?> bulletList [ para "Item1" <> bulletList [ para "Item2" <> bulletList [ para "Item3" ] , para "Item4" <> bulletList [ para "Item5" ] ] , para "Item6" ] , "Nested ordered list" =: T.unlines [ " 1. Item1" , " 1. Item2" , " 1. Item3" , " 2. Item4" , " 1. Item5" , " 2. Item6" ] =?> orderedListWith (1, Decimal, Period) [ para "Item1" <> orderedListWith (1, Decimal, Period) [ para "Item2" <> orderedListWith (1, Decimal, Period) [ para "Item3" ] , para "Item4" <> orderedListWith (1, Decimal, Period) [ para "Item5" ] ] , para "Item6" ] , "Mixed nested list" =: T.unlines [ " - Item1" , " - Item2" , " - Item3" , " - Item4" , " 1. Nested" , " 2. Ordered" , " 3. List" ] =?> bulletList [ mconcat [ para "Item1" , bulletList [ para "Item2" , para "Item3" ] ] , mconcat [ para "Item4" , orderedListWith (1, Decimal, Period) [ para "Nested" , para "Ordered" , para "List" ] ] ] , "Text::Amuse includes only one space in list marker" =: T.unlines [ " - First item" , " - Nested item" ] =?> bulletList [ para "First item" <> bulletList [ para "Nested item"]] ] , "List continuation" =: T.unlines [ " - a" , "" , " b" , "" , " c" ] =?> bulletList [ mconcat [ para "a" , para "b" , para "c" ] ] , "List continuation afeter nested list" =: T.unlines [ " - - foo" , "" , " bar" ] =?> bulletList [ bulletList [ para "foo" ] <> para "bar" ] -- Emacs Muse allows to separate lists with two or more blank lines. -- Text::Amuse (Amusewiki engine) always creates a single list as of version 0.82. -- pandoc follows Emacs Muse behavior , testGroup "Blank lines" [ "Blank lines between list items are not required" =: T.unlines [ " - Foo" , " - Bar" ] =?> bulletList [ para "Foo" , para "Bar" ] , "One blank line between list items is allowed" =: T.unlines [ " - Foo" , "" , " - Bar" ] =?> bulletList [ para "Foo" , para "Bar" ] , "Two blank lines separate lists" =: T.unlines [ " - Foo" , "" , "" , " - Bar" ] =?> bulletList [ para "Foo" ] <> bulletList [ para "Bar" ] , "No blank line after multiline first item" =: T.unlines [ " - Foo" , " bar" , " - Baz" ] =?> bulletList [ para "Foo\nbar" , para "Baz" ] , "One blank line after multiline first item" =: T.unlines [ " - Foo" , " bar" , "" , " - Baz" ] =?> bulletList [ para "Foo\nbar" , para "Baz" ] , "Two blank lines after multiline first item" =: T.unlines [ " - Foo" , " bar" , "" , "" , " - Baz" ] =?> bulletList [ para "Foo\nbar" ] <> bulletList [ para "Baz" ] , "No blank line after list continuation" =: T.unlines [ " - Foo" , "" , " bar" , " - Baz" ] =?> bulletList [ para "Foo" <> para "bar" , para "Baz" ] , "One blank line after list continuation" =: T.unlines [ " - Foo" , "" , " bar" , "" , " - Baz" ] =?> bulletList [ para "Foo" <> para "bar" , para "Baz" ] , "Two blank lines after list continuation" =: T.unlines [ " - Foo" , "" , " bar" , "" , "" , " - Baz" ] =?> bulletList [ para "Foo" <> para "bar" ] <> bulletList [ para "Baz" ] , "No blank line after blockquote" =: T.unlines [ " -
" , " foo" , "" , " - bar" ] =?> bulletList [ blockQuote $ para "foo", para "bar" ] , "One blank line after blockquote" =: T.unlines [ " -
" , " foo" , "" , "" , " - bar" ] =?> bulletList [ blockQuote $ para "foo", para "bar" ] , "Two blank lines after blockquote" =: T.unlines [ " -
" , " foo" , "" , "" , "" , " - bar" ] =?> bulletList [ blockQuote $ para "foo" ] <> bulletList [ para "bar" ] , "No blank line after verse" =: T.unlines [ " - > foo" , " - bar" ] =?> bulletList [ lineBlock [ "foo" ], para "bar" ] , "One blank line after verse" =: T.unlines [ " - > foo" , "" , " - bar" ] =?> bulletList [ lineBlock [ "foo" ], para "bar" ] , "Two blank lines after verse" =: T.unlines [ " - > foo" , "" , "" , " - bar" ] =?> bulletList [ lineBlock [ "foo" ] ] <> bulletList [ para "bar" ] ] -- Test that definition list requires a leading space. -- Emacs Muse does not require a space, we follow Amusewiki here. , "Not a definition list" =: T.unlines [ "First :: second" , "Foo :: bar" ] =?> para "First :: second\nFoo :: bar" , test emacsMuse "Emacs Muse definition list" (T.unlines [ "First :: second" , "Foo :: bar" ] =?> definitionList [ ("First", [ para "second" ]) , ("Foo", [ para "bar" ]) ]) , "Definition list" =: T.unlines [ " First :: second" , " Foo :: bar" ] =?> definitionList [ ("First", [ para "second" ]) , ("Foo", [ para "bar" ]) ] , "Definition list term cannot include newline" =: T.unlines [ " Foo" -- "Foo" is not a part of the definition list term , " Bar :: baz" ] =?> para "Foo" <> definitionList [ ("Bar", [ para "baz" ]) ] , "One-line definition list" =: " foo :: bar" =?> definitionList [ ("foo", [ para "bar" ]) ] , "Definition list term may include single colon" =: " foo:bar :: baz" =?> definitionList [ ("foo:bar", [ para "baz" ]) ] , "Definition list term with emphasis" =: " *Foo* :: bar\n" =?> definitionList [ (emph "Foo", [ para "bar" ]) ] , "Definition list term with :: inside code" =: " foo
::
:: bar ::
baz\n" =?>
definitionList [ ("foo " <> code " :: ", [ para $ "bar " <> code " :: " <> " baz" ]) ]
, "Multi-line definition lists" =:
T.unlines
[ " First term :: Definition of first term"
, "and its continuation."
, " Second term :: Definition of second term."
] =?>
definitionList [ ("First term", [ para "Definition of first term\nand its continuation." ])
, ("Second term", [ para "Definition of second term." ])
]
, "Definition list with verse" =:
T.unlines
[ " First term :: Definition of first term"
, " > First verse"
, " > Second line of first verse"
, ""
, " > Second verse"
, " > Second line of second verse"
] =?>
definitionList [ ("First term", [ para "Definition of first term" <>
lineBlock [ text "First verse"
, text "Second line of first verse"
] <>
lineBlock [ text "Second verse"
, text "Second line of second verse"
]
])
]
, test emacsMuse "Multi-line definition lists from Emacs Muse manual"
(T.unlines
[ "Term1 ::"
, " This is a first definition"
, " And it has two lines;"
, "no, make that three."
, ""
, "Term2 :: This is a second definition"
] =?>
definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."])
, ("Term2", [ para "This is a second definition"])
])
-- Text::Amuse requires indentation with one space
, "Multi-line definition lists from Emacs Muse manual with initial space" =:
(T.unlines
[ " Term1 ::"
, " This is a first definition"
, " And it has two lines;"
, "no, make that three."
, ""
, " Term2 :: This is a second definition"
] =?>
definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."])
, ("Term2", [ para "This is a second definition"])
])
, "One-line nested definition list" =:
" Foo :: bar :: baz" =?>
definitionList [ ("Foo", [ definitionList [ ("bar", [ para "baz" ])]])]
, "Nested definition list" =:
T.unlines
[ " First :: Second :: Third"
, " Fourth :: Fifth :: Sixth"
, " Seventh :: Eighth"
] =?>
definitionList [ ("First", [ definitionList [ ("Second", [ para "Third" ]),
("Fourth", [ definitionList [ ("Fifth", [ para "Sixth"] ) ] ] ) ] ] )
, ("Seventh", [ para "Eighth" ])
]
, testGroup "Definition lists with multiple descriptions"
[ "Correctly indented second description" =:
T.unlines
[ " First term :: first description"
, " :: second description"
] =?>
definitionList [ ("First term", [ para "first description"
, para "second description"
])
]
, "Incorrectly indented second description" =:
T.unlines
[ " First term :: first description"
, " :: second description"
] =?>
definitionList [ ("First term", [ para "first description" ])
, ("", [ para "second description" ])
]
]
, "Two blank lines separate definition lists" =:
T.unlines
[ " First :: list"
, ""
, ""
, " Second :: list"
] =?>
definitionList [ ("First", [ para "list" ]) ] <>
definitionList [ ("Second", [ para "list" ]) ]
-- Headers in first column of list continuation are not allowed
, "No headers in list continuation" =:
T.unlines
[ " - Foo"
, ""
, " * Bar"
] =?>
bulletList [ mconcat [ para "Foo"
, para "* Bar"
]
]
, "Bullet list inside a tag" =:
T.unlines
[ "" , " - First" , "" , " - Second" , "" , " - Third" , "" ] =?> blockQuote (bulletList [ para "First" , para "Second" , para "Third" ]) , "Ordered list inside a tag" =: T.unlines [ "
" , " 1. First" , "" , " 2. Second" , "" , " 3. Third" , "" ] =?> blockQuote (orderedListWith (1, Decimal, Period) [ para "First" , para "Second" , para "Third" ]) -- Regression test for a bug caught by round-trip test , "Do not consume whitespace while looking for end tag" =: T.unlines [ "
" , " -, "" ] =?> blockQuote (bulletList [ blockQuote $ para "foo" ] <> para "bar") , "Unclosed quote tag" =: T.unlines [ "" , " foo" , "" , " bar" -- Do not consume whitespace while looking for arbitrarily indented
" , "" , "" ] =?> para "" , "
" <> lineBlock [ "" ] , "Unclosed quote tag inside list" =: T.unlines [ " -
" , "" , " " ] =?> bulletList [ para "" , "
" <> lineBlock [ "" ] ] -- Allowing indented closing tags is dangerous, -- as they may terminate lists , "No indented closing tags" =: T.unlines [ "
" , "" , " - Foo" , "" , "" , "" , " bar" , "" , "
" <> bulletList [ para "Foo" <> para "" <> para "bar" <> lineBlock [ "" ] ] ] ]