{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} module Text.MMarkSpec (spec) where import Data.Aeson import Data.Char import Data.List.NonEmpty (NonEmpty (..)) import Data.Monoid import Data.Text (Text) import Test.Hspec import Test.Hspec.Megaparsec import Text.MMark (MMarkErr (..)) import Text.MMark.Extension (Inline (..)) import Text.MMark.TestUtils import Text.Megaparsec (ErrorFancy (..)) import qualified Control.Foldl as L import qualified Data.List.NonEmpty as NE import qualified Data.Text as T import qualified Data.Text.IO as TIO import qualified Text.MMark as MMark import qualified Text.MMark.Extension as Ext -- NOTE This test suite is mostly based on (sometimes altered) examples from -- the Common Mark specification. We use the version 0.28 (2017-08-01), -- which can be found online here: -- -- spec :: Spec spec = parallel $ do describe "parse and render" $ do context "2.2 Tabs" $ do it "CM1" $ "\tfoo\tbaz\t\tbim" ==-> "
foo\tbaz\t\tbim\n
\n" it "CM2" $ " \tfoo\tbaz\t\tbim" ==-> "
foo\tbaz\t\tbim\n
\n" it "CM3" $ " a\ta\n ὐ\ta" ==-> "
a\ta\nὐ\ta\n
\n" it "CM4" $ " - foo\n\n\tbar" ==-> "\n" it "CM5" $ "- foo\n\n\t\tbar" ==-> "\n" it "CM6" $ ">\t\tfoo" ==-> "
\n
  foo\n
\n
\n" it "CM7" $ "-\t\tfoo" ==-> "\n" it "CM8" $ " foo\n\tbar" ==-> "
foo\nbar\n
\n" it "CM9" $ " - foo\n - bar\n\t - baz" ==-> "\n" it "CM10" $ "#\tFoo" ==-> "

Foo

\n" it "CM11" $ "*\t*\t*\t" ==-> "
\n" context "3.1 Precedence" $ it "CM12" $ let s = "- `one\n- two`" in s ~~-> [ err (posN 6 s) (ueib <> etok '`' <> ecsc) , err (posN 13 s) (ueib <> etok '`' <> ecsc) ] context "4.1 Thematic breaks" $ do it "CM13" $ "***\n---\n___" ==-> "
\n
\n
\n" it "CM14" $ "+++" ==-> "

+++

\n" it "CM15" $ "===" ==-> "

===

\n" it "CM16" $ let s = "--\n**\n__\n" in s ~-> errFancy (posN 3 s) (nonFlanking "**") it "CM17" $ " ***\n ***\n ***" ==-> "
\n
\n
\n" it "CM18" $ " ***" ==-> "
***\n
\n" it "CM19" $ let s = "Foo\n ***\n" in s ~-> errFancy (posN 8 s) (nonFlanking "***") it "CM20" $ "_____________________________________" ==-> "
\n" it "CM21" $ " - - -" ==-> "
\n" it "CM22" $ " ** * ** * ** * **" ==-> "
\n" it "CM23" $ "- - - -" ==-> "
\n" it "CM24" $ "- - - - " ==-> "
\n" it "CM25" $ let s = "_ _ _ _ a\n\na------\n\n---a---\n" in s ~-> errFancy posI (nonFlanking "_") it "CM26" $ " *-*" ==-> "

-

\n" it "CM27" $ "- foo\n***\n- bar" ==-> "\n
\n\n" it "CM28" $ "Foo\n***\nbar" ==-> "

Foo

\n
\n

bar

\n" it "CM29" $ "Foo\n---\nbar" ==-> "

Foo

\n
\n

bar

\n" it "CM30" $ "* Foo\n* * *\n* Bar" ==-> "\n" it "CM31" $ "- Foo\n- * * *" ==-> "\n" context "4.2 ATX headings" $ do it "CM32" $ "# foo\n## foo\n### foo\n#### foo\n##### foo\n###### foo" ==-> "

foo

\n

foo

\n

foo

\n

foo

\n
foo
\n
foo
\n" it "CM33" $ let s = "####### foo" in s ~-> err (posN 6 s) (utok '#' <> ews) it "CM34" $ let s = "#5 bolt\n\n#hashtag" in s ~~-> [ err (posN 1 s) (utok '5' <> etok '#' <> ews) , err (posN 10 s) (utok 'h' <> etok '#' <> ews) ] it "CM35" $ "\\## foo" ==-> "

## foo

\n" it "CM36" $ "# foo *bar* \\*baz\\*" ==-> "

foo bar *baz*

\n" it "CM37" $ "# foo " ==-> "

foo

\n" it "CM38" $ " ### foo\n ## foo\n # foo" ==-> "

foo

\n

foo

\n

foo

\n" it "CM39" $ " # foo" ==-> "
# foo\n
\n" it "CM40" $ "foo\n # bar" ==-> "

foo\n# bar

\n" it "CM41" $ "## foo ##\n ### bar ###" ==-> "

foo

\n

bar

\n" it "CM42" $ "# foo ##################################\n##### foo ##" ==-> "

foo

\n
foo
\n" it "CM43" $ "### foo ### " ==-> "

foo

\n" it "CM44" $ "### foo ### b" ==-> "

foo ### b

\n" it "CM45" $ "# foo#" ==-> "

foo#

\n" it "CM46" $ "### foo \\###\n## foo #\\##\n# foo \\#" ==-> "

foo ###

\n

foo ###

\n

foo #

\n" it "CM47" $ "****\n## foo\n****" ==-> "
\n

foo

\n
\n" it "CM48" $ "Foo bar\n# baz\nBar foo" ==-> "

Foo bar

\n

baz

\n

Bar foo

\n" it "CM49" $ let s = "## \n#\n### ###" in s ~~-> [ err (posN 3 s) (utok '\n' <> elabel "heading character" <> ews) , err (posN 5 s) (utok '\n' <> etok '#' <> ews) ] context "4.3 Setext headings" $ do -- NOTE we do not support them, the tests have been adjusted -- accordingly. it "CM50" $ "Foo *bar*\n=========\n\nFoo *bar*\n---------" ==-> "

Foo bar\n=========

\n

Foo bar

\n
\n" it "CM51" $ "Foo *bar\nbaz*\n====" ==-> "

Foo bar\nbaz\n====

\n" it "CM52" $ "Foo\n-------------------------\n\nFoo\n=" ==-> "

Foo

\n
\n

Foo\n=

\n" it "CM53" $ " Foo\n---\n\n Foo\n-----\n\n Foo\n ===" ==-> "

Foo

\n
\n

Foo

\n
\n

Foo\n===

\n" it "CM54" $ " Foo\n ---\n\n Foo\n---" ==-> "
Foo\n---\n\nFoo\n
\n
\n" it "CM55" $ "Foo\n ---- " ==-> "

Foo

\n
\n" it "CM56" $ "Foo\n ---" ==-> "

Foo\n---

\n" it "CM57" $ "Foo\n= =\n\nFoo\n--- -" ==-> "

Foo\n= =

\n

Foo

\n
\n" it "CM58" $ "Foo \n-----" ==-> "

Foo

\n
\n" it "CM59" $ "Foo\\\n----" ==-> "

Foo\\

\n
\n" it "CM60" $ let s = "`Foo\n----\n`\n\n\n" in s ~~-> [ err (posN 4 s) (ueib <> etok '`' <> ecsc) , err (posN 11 s) (ueib <> etok '`' <> ecsc) ] it "CM61" $ "> Foo\n---" ==-> "
\n

Foo

\n
\n
\n" it "CM62" $ "> foo\nbar\n===" ==-> "
\n

foo

\n
\n

bar\n===

\n" it "CM63" $ "- Foo\n---" ==-> "\n
\n" it "CM64" $ "Foo\nBar\n---" ==-> "

Foo\nBar

\n
\n" it "CM65" $ "---\nFoo\n---\nBar\n---\nBaz" ==-> "

Bar

\n
\n

Baz

\n" it "CM66" $ "\n====" ==-> "

====

\n" it "CM67" $ "---\n---" ==-> "" -- thinks that it's got a YAML block it "CM68" $ "- foo\n-----" ==-> "\n
\n" it "CM69" $ " foo\n---" ==-> "
foo\n
\n
\n" it "CM70" $ "> foo\n-----" ==-> "
\n

foo

\n
\n
\n" it "CM71" $ "\\> foo\n------" ==-> "

> foo

\n
\n" it "CM72" $ "Foo\n\nbar\n---\nbaz" ==-> "

Foo

\n

bar

\n
\n

baz

\n" it "CM73" $ "Foo\nbar\n\n---\n\nbaz" ==-> "

Foo\nbar

\n
\n

baz

\n" it "CM74" $ "Foo\nbar\n* * *\nbaz" ==-> "

Foo\nbar

\n
\n

baz

\n" it "CM75" $ "Foo\nbar\n\\---\nbaz" ==-> "

Foo\nbar\n---\nbaz

\n" context "4.4 Indented code blocks" $ do it "CM76" $ " a simple\n indented code block" ==-> "
a simple\n  indented code block\n
\n" it "CM77" $ " - foo\n\n bar" ==-> "\n" it "CM78" $ "1. foo\n\n - bar" ==-> "
    \n
  1. \n

    foo

    \n
      \n
    • \nbar\n
    • \n
    \n
  2. \n
\n" it "CM79" $ "
\n *hi*\n\n - one" ==-> "
<a/>\n*hi*\n\n- one\n
\n" it "CM80" $ " chunk1\n\n chunk2\n \n \n \n chunk3" ==-> "
chunk1\n\nchunk2\n\n\n\nchunk3\n
\n" it "CM81" $ " chunk1\n \n chunk2" ==-> "
chunk1\n  \n  chunk2\n
\n" it "CM82" $ "Foo\n bar\n" ==-> "

Foo\nbar

\n" it "CM83" $ " foo\nbar" ==-> "
foo\n
\n

bar

\n" it "CM84" $ "# Heading\n foo\nHeading\n------\n foo\n----\n" ==-> "

Heading

\n
foo\n
\n

Heading

\n
\n
foo\n
\n
\n" it "CM85" $ " foo\n bar" ==-> "
    foo\nbar\n
\n" it "CM86" $ "\n \n foo\n \n" ==-> "
foo\n
\n" it "CM87" $ " foo " ==-> "
foo  \n
\n" context "4.5 Fenced code blocks" $ do it "CM88" $ "```\n<\n >\n```" ==-> "
<\n >\n
\n" it "CM89" $ "~~~\n<\n >\n~~~" ==-> "
<\n >\n
\n" it "CM90" $ "``\nfoo\n``\n" ==-> "

foo

\n" it "CM91" $ "```\naaa\n~~~\n```" ==-> "
aaa\n~~~\n
\n" it "CM92" $ "~~~\naaa\n```\n~~~" ==-> "
aaa\n```\n
\n" it "CM93" $ "````\naaa\n```\n``````" ==-> "
aaa\n```\n
\n" it "CM94" $ "~~~~\naaa\n~~~\n~~~~" ==-> "
aaa\n~~~\n
\n" it "CM95" $ let s = "```" in s ~-> err (posN 3 s) (ueib <> etok '`' <> ecsc) it "CM96" $ let s = "`````\n\n```\naaa\n" in s ~-> err (posN 15 s) (ueof <> elabel "closing code fence" <> elabel "code block content") it "CM97" $ let s = "> ```\n> aaa\n\nbbb\n" in s ~-> err (posN 17 s) (ueof <> elabel "closing code fence" <> elabel "code block content") it "CM98" $ "```\n\n \n```" ==-> "
\n  \n
\n" it "CM99" $ "```\n```" ==-> "
\n" it "CM100" $ " ```\n aaa\naaa\n```" ==-> "
aaa\naaa\n
\n" it "CM101" $ " ```\naaa\n aaa\naaa\n ```" ==-> "
aaa\naaa\naaa\n
\n" it "CM102" $ " ```\n aaa\n aaa\n aaa\n ```" ==-> "
aaa\n aaa\naaa\n
\n" it "CM103" $ " ```\n aaa\n ```" ==-> "
```\naaa\n```\n
\n" it "CM104" $ "```\naaa\n ```" ==-> "
aaa\n
\n" it "CM105" $ " ```\naaa\n ```" ==-> "
aaa\n
\n" it "CM106" $ let s = "```\naaa\n ```\n" in s ~-> err (posN 16 s) (ueof <> elabel "closing code fence" <> elabel "code block content") it "CM107" $ "``` ```\naaa" ==-> "

\naaa

\n" it "CM108" $ let s = "~~~~~~\naaa\n~~~ ~~\n" in s ~-> err (posN 18 s) (ueof <> elabel "closing code fence" <> elabel "code block content") it "CM109" $ "foo\n```\nbar\n```\nbaz" ==-> "

foo

\n
bar\n
\n

baz

\n" it "CM110" $ "foo\n---\n~~~\nbar\n~~~\n# baz" ==-> "

foo

\n
\n
bar\n
\n

baz

\n" it "CM111" $ "```ruby\ndef foo(x)\n return 3\nend\n```" ==-> "
def foo(x)\n  return 3\nend\n
\n" it "CM112" $ "~~~~ ruby startline=3 $%@#$\ndef foo(x)\n return 3\nend\n~~~~~~~" ==-> "
def foo(x)\n  return 3\nend\n
\n" it "CM113" $ "````;\n````" ==-> "
\n" it "CM114" $ "``` aa ```\nfoo" ==-> "

aa\nfoo

\n" it "CM115" $ "```\n``` aaa\n```" ==-> "
``` aaa\n
\n" context "4.6 HTML blocks" $ -- NOTE We do not support HTML blocks, see the readme. return () context "4.7 Link reference definitions" $ do it "CM159" $ "[foo]: /url \"title\"\n\n[foo]" ==-> "

foo

\n" it "CM160" $ " [foo]: \n /url \n 'the title' \n\n[foo]" ==-> "

foo

\n" it "CM161" $ let s = "[Foo bar\\]]:my_(url) 'title (with parens)'\n\n[Foo bar\\]]" in s ~~-> [ err (posN 19 s) (utoks ") " <> etok '#' <> etok '/' <> etok '?' <> elabel "newline" <> elabel "the rest of path piece" <> ews ) , errFancy (posN 45 s) (couldNotMatchRef "Foo bar]" []) ] it "CM162" $ "[Foo bar]:\n\n'title'\n\n[Foo bar]" ==-> "

Foo bar

\n" it "CM163" $ "[foo]: /url '\ntitle\nline1\nline2\n'\n\n[foo]" ==-> "

foo

\n" it "CM164" $ "[foo]: /url 'title\n\nwith blank line'\n\n[foo]" ==-> "

foo

\n" it "CM165" $ "[foo]:\n/url\n\n[foo]" ==-> "

foo

\n" it "CM166" $ let s = "[foo]:\n\n[foo]" in s ~~-> [ err (posN 7 s) (utok '\n' <> etok '<' <> elabel "URI" <> ews) , errFancy (posN 9 s) (couldNotMatchRef "foo" []) ] it "CM167" $ let s = "[foo]: /url\\bar\\*baz \"foo\\\"bar\\baz\"\n\n[foo]\n" in s ~-> err (posN 11 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> elabel "the rest of path piece") it "CM168" $ "[foo]\n\n[foo]: url" ==-> "

foo

\n" it "CM169" $ let s = "[foo]\n\n[foo]: first\n[foo]: second\n" in s ~-> errFancy (posN 21 s) (duplicateRef "foo") it "CM170" $ "[FOO]: /url\n\n[Foo]" ==-> "

Foo

\n" it "CM171" $ "[ΑΓΩ]: /%CF%86%CE%BF%CF%85\n\n[αγω]" ==-> "

αγω

\n" it "CM172" $ "[foo]: /url" ==-> "" it "CM173" $ "[\nfoo\n]: /url\nbar" ==-> "

bar

\n" it "CM174" $ let s = "[foo]: /url \"title\" ok" in s ~-> err (posN 20 s) (utoks "ok" <> elabel "newline" <> ews) it "CM175" $ let s = "[foo]: /url\n\"title\" ok\n" in s ~-> err (posN 20 s) (utoks "ok" <> elabel "newline" <> ews) it "CM176" $ " [foo]: /url \"title\"" ==-> "
[foo]: /url "title"\n
\n" it "CM177" $ "```\n[foo]: /url\n```" ==-> "
[foo]: /url\n
\n" it "CM178" $ let s = "Foo\n[bar]: /baz\n\n[bar]\n" in s ~~-> [ errFancy (posN 5 s) (couldNotMatchRef "bar" []) , errFancy (posN 18 s) (couldNotMatchRef "bar" []) ] it "CM179" $ "# [Foo]\n[foo]: /url\n> bar" ==-> "

Foo

\n
\n

bar

\n
\n" it "CM180" $ "[foo]: /foo-url \"foo\"\n[bar]: /bar-url\n \"bar\"\n[baz]: /baz-url\n\n[foo],\n[bar],\n[baz]" ==-> "

foo,\nbar,\nbaz

\n" it "CM181" $ "[foo]\n\n> [foo]: /url" ==-> "

foo

\n
\n
\n" context "4.8 Paragraphs" $ do it "CM182" $ "aaa\n\nbbb" ==-> "

aaa

\n

bbb

\n" it "CM183" $ "aaa\nbbb\n\nccc\nddd" ==-> "

aaa\nbbb

\n

ccc\nddd

\n" it "CM184" $ "aaa\n\n\nbbb" ==-> "

aaa

\n

bbb

\n" it "CM185" $ " aaa\n bbb" ==-> "

aaa\nbbb

\n" it "CM186" $ "aaa\n bbb\n ccc" ==-> "

aaa\nbbb\nccc

\n" it "CM187" $ " aaa\nbbb" ==-> "

aaa\nbbb

\n" it "CM188" $ " aaa\nbbb" ==-> "
aaa\n
\n

bbb

\n" it "CM189" $ "aaa \nbbb " ==-> "

aaa\nbbb

\n" context "4.9 Blank lines" $ it "CM190" $ " \n\naaa\n \n\n# aaa\n\n " ==-> "

aaa

\n

aaa

\n" context "5.1 Block quotes" $ do it "CM191" $ "> # Foo\n bar\n baz" ==-> "
\n

Foo

\n

bar\nbaz

\n
\n" it "CM192" $ "># Foo\n bar\n baz" ==-> "
\n

Foo

\n

bar\nbaz

\n
\n" it "CM193" $ " > # Foo\n bar\n baz" ==-> "
\n

Foo

\n

bar\nbaz

\n
\n" it "CM194" $ " > # Foo\n > bar\n > baz" ==-> "
> # Foo\n> bar\n> baz\n
\n" it "CM195" $ "> # Foo\n> bar\nbaz" ==-> "
\n

Foo

\n
\n
\n

bar

\n
\n

baz

\n" it "CM196" $ "> bar\nbaz\n> foo" ==-> "
\n

bar

\n
\n

baz

\n
\n

foo

\n
\n" it "CM197" $ "> foo\n---" ==-> "
\n

foo

\n
\n
\n" it "CM198" $ "> - foo\n- bar" ==-> "
\n
    \n
  • \nfoo\n
  • \n
\n
\n\n" it "CM199" $ "> foo\n bar" ==-> "
\n
foo\n
\n

bar

\n
\n" it "CM200" $ "> ```\nfoo\n```" ==-> "
\n
foo\n
\n
\n" it "CM201" $ "> foo\n - bar" ==-> "
\n

foo

\n
    \n
  • \nbar\n
  • \n
\n
\n" it "CM202" $ ">" ==-> "
\n
\n" it "CM203" $ ">\n> \n> " ==-> "
\n
\n
\n
\n
\n
\n" it "CM204" $ ">\n foo\n " ==-> "
\n

foo

\n
\n" it "CM205" $ "> foo\n\n> bar" ==-> "
\n

foo

\n
\n
\n

bar

\n
\n" it "CM206" $ "> foo\n bar" ==-> "
\n

foo\nbar

\n
\n" it "CM207" $ "> foo\n\n bar" ==-> "
\n

foo

\n

bar

\n
\n" it "CM208" $ "foo\n> bar" ==-> "

foo

\n
\n

bar

\n
\n" it "CM209" $ "> aaa\n***\n> bbb" ==-> "
\n

aaa

\n
\n
\n
\n

bbb

\n
\n" it "CM210" $ "> bar\n baz" ==-> "
\n

bar\nbaz

\n
\n" it "CM211" $ "> bar\n\nbaz" ==-> "
\n

bar

\n
\n

baz

\n" it "CM212" $ "> bar\n\nbaz" ==-> "
\n

bar

\n
\n

baz

\n" it "CM213" $ "> > > foo\nbar" ==-> "
\n
\n
\n

foo

\n
\n
\n
\n

bar

\n" it "CM214" $ ">>> foo\n bar\n baz" ==-> "
\n
\n
\n

foo\nbar\nbaz

\n
\n
\n
\n" it "CM215" $ "> code\n\n> not code" ==-> "
\n
code\n
\n
\n
\n

not code

\n
\n" context "5.2 List items" $ do it "CM216" $ "A paragraph\nwith two lines.\n\n indented code\n\n> A block quote." ==-> "

A paragraph\nwith two lines.

\n
indented code\n
\n
\n

A block quote.

\n
\n" it "CM217" $ "1. A paragraph\n with two lines.\n\n indented code\n\n > A block quote." ==-> "
    \n
  1. \n

    A paragraph\nwith two lines.

    \n
    indented code\n
    \n
    \n

    A block quote.

    \n
    \n
  2. \n
\n" it "CM218" $ "- one\n\n two" ==-> "\n

two

\n" it "CM219" $ "- one\n\n two" ==-> "\n" it "CM220" $ " - one\n\n two" ==-> "\n
 two\n
\n" it "CM221" $ " - one\n\n two" ==-> "\n" it "CM222" $ " > > 1. one\n\n two" ==-> "
\n
\n
    \n
  1. \none\n
  2. \n
\n

two

\n
\n
\n" it "CM223" $ ">>- one\n\n two" ==-> "
\n
\n
    \n
  • \n

    one

    \n

    two

    \n
  • \n
\n
\n
\n" it "CM224" $ "-one\n\n2.two" ==-> "

-one

\n

2.two

\n" it "CM225" $ "- foo\n\n\n bar" ==-> "\n" it "CM226" $ "1. foo\n\n ```\n bar\n ```\n\n baz\n\n > bam" ==-> "
    \n
  1. \n

    foo

    \n
    bar\n
    \n

    baz

    \n
    \n

    bam

    \n
    \n
  2. \n
\n" it "CM227" $ "- Foo\n\n bar\n\n\n baz" ==-> "\n" it "CM228" $ "123456789. ok" ==-> "
    \n
  1. \nok\n
  2. \n
\n" it "CM229" $ let s = "1234567890. not ok\n" in s ~-> errFancy posI (indexTooBig 1234567890) it "CM230" $ "0. ok" ==-> "
    \n
  1. \nok\n
  2. \n
\n" it "CM231" $ "003. ok" ==-> "
    \n
  1. \nok\n
  2. \n
\n" it "CM232" $ "-1. not ok" ==-> "

-1. not ok

\n" it "CM233" $ "- foo\n\n bar" ==-> "\n" it "CM234" $ " 10. foo\n\n bar" ==-> "
    \n
  1. \n

    foo

    \n
    bar\n
    \n
  2. \n
\n" it "CM235" $ " indented code\n\nparagraph\n\n more code" ==-> "
indented code\n
\n

paragraph

\n
more code\n
\n" it "CM236" $ "1. indented code\n\n paragraph\n\n more code" ==-> "
    \n
  1. \n
    indented code\n
    \n

    paragraph

    \n
    more code\n
    \n
  2. \n
\n" it "CM237" $ "1. indented code\n\n paragraph\n\n more code" ==-> "
    \n
  1. \n
     indented code\n
    \n

    paragraph

    \n
    more code\n
    \n
  2. \n
\n" it "CM238" $ " foo\n\nbar" ==-> "

foo

\n

bar

\n" it "CM239" $ "- foo\n\n bar" ==-> "\n

bar

\n" it "CM240" $ "- foo\n\n bar" ==-> "\n" it "CM241" $ "-\n foo\n-\n ```\n bar\n ```\n-\n baz" ==-> "\n" it "CM242" $ "- \n foo" ==-> "\n" it "CM243a" $ "-\n\n foo" ==-> "\n

foo

\n" it "CM243b" $ "1.\n\n foo" ==-> "
    \n
  1. \n\n
  2. \n
\n

foo

\n" it "CM244" $ "- foo\n-\n- bar" ==-> "\n" it "CM245" $ "- foo\n- \n- bar" ==-> "\n" it "CM246" $ "1. foo\n2.\n3. bar" ==-> "
    \n
  1. \nfoo\n
  2. \n
  3. \n\n
  4. \n
  5. \nbar\n
  6. \n
\n" it "CM247" $ "*" ==-> "\n" it "CM248" $ "foo\n*\n\nfoo\n1." ==-> "

foo

\n\n

foo

\n
    \n
  1. \n\n
  2. \n
\n" it "CM249" $ " 1. A paragraph\n with two lines.\n\n indented code\n\n > A block quote." ==-> "
    \n
  1. \n

    A paragraph\nwith two lines.

    \n
    indented code\n
    \n
    \n

    A block quote.

    \n
    \n
  2. \n
\n" it "CM250" $ " 1. A paragraph\n with two lines.\n\n indented code\n\n > A block quote." ==-> "
    \n
  1. \n

    A paragraph\nwith two lines.

    \n
    indented code\n
    \n
    \n

    A block quote.

    \n
    \n
  2. \n
\n" it "CM251" $ " 1. A paragraph\n with two lines.\n\n indented code\n\n > A block quote." ==-> "
    \n
  1. \n

    A paragraph\nwith two lines.

    \n
    indented code\n
    \n
    \n

    A block quote.

    \n
    \n
  2. \n
\n" it "CM252" $ " 1. A paragraph\n with two lines.\n\n indented code\n\n > A block quote." ==-> "
1.  A paragraph\n    with two lines.\n\n        indented code\n\n    > A block quote.\n
\n" it "CM253" $ " 1. A paragraph\nwith two lines.\n\n indented code\n\n > A block quote." ==-> "
    \n
  1. \nA paragraph\n
  2. \n
\n

with two lines.

\n
      indented code\n\n  > A block quote.\n
\n" it "CM254" $ " 1. A paragraph\n with two lines." ==-> "
    \n
  1. \nA paragraph\n
  2. \n
\n
with two lines.\n
\n" it "CM255" $ "> 1. > Blockquote\ncontinued here." ==-> "
\n
    \n
  1. \n
    \n

    Blockquote

    \n
    \n
  2. \n
\n
\n

continued here.

\n" it "CM256" $ "> 1. > Blockquote\n continued here." ==-> "
\n
    \n
  1. \n
    \n

    Blockquote

    \n
    \n
  2. \n
\n

continued here.

\n
\n" it "CM257" $ "- foo\n - bar\n - baz\n - boo" ==-> "\n" it "CM258" $ "- foo\n - bar\n - baz\n - boo" ==-> "\n" it "CM259" $ "10) foo\n - bar" ==-> "
    \n
  1. \nfoo\n
      \n
    • \nbar\n
    • \n
    \n
  2. \n
\n" it "CM260" $ "10) foo\n - bar" ==-> "
    \n
  1. \nfoo\n
  2. \n
\n\n" it "CM261" $ "- - foo" ==-> "\n" it "CM262" $ "1. - 2. foo" ==-> "
    \n
  1. \n
      \n
    • \n
        \n
      1. \nfoo\n
      2. \n
      \n
    • \n
    \n
  2. \n
\n" it "CM263" $ "- # Foo\n- Bar\n ---\n baz" ==-> "\n" context "5.3 Lists" $ do it "CM264" $ "- foo\n- bar\n+ baz" ==-> "\n\n" it "CM265" $ "1. foo\n2. bar\n3) baz" ==-> "
    \n
  1. \nfoo\n
  2. \n
  3. \nbar\n
  4. \n
\n
    \n
  1. \nbaz\n
  2. \n
\n" it "CM266" $ "Foo\n- bar\n- baz" ==-> "

Foo

\n\n" it "CM267" $ "The number of windows in my house is\n14. The number of doors is 6." ==-> "

The number of windows in my house is

\n
    \n
  1. \nThe number of doors is 6.\n
  2. \n
\n" it "CM268" $ "The number of windows in my house is\n1. The number of doors is 6." ==-> "

The number of windows in my house is

\n
    \n
  1. \nThe number of doors is 6.\n
  2. \n
\n" it "CM269" $ "- foo\n\n- bar\n\n\n- baz" ==-> "\n" it "CM270" $ "- foo\n - bar\n - baz\n\n\n bim" ==-> "\n" it "CM271" $ "- foo\n- bar\n\n\n\n- baz\n- bim" ==-> "\n

<!-- -->

\n\n" it "CM272" $ "- foo\n\n notcode\n\n- foo\n\n\n\n code" ==-> "\n

<!-- -->

\n
code\n
\n" it "CM273" $ "- a\n - b\n - c\n - d\n - e\n - f\n - g\n - h\n- i" ==-> "\n" it "CM274" $ "1. a\n\n 2. b\n\n 3. c" ==-> "
    \n
  1. \n

    a

    \n
  2. \n
  3. \n

    b

    \n
  4. \n
  5. \n

    c

    \n
  6. \n
\n" it "CM275" $ "- a\n- b\n\n- c" ==-> "\n" it "CM276" $ "* a\n*\n\n* c" ==-> "\n" it "CM277" $ "- a\n- b\n\n c\n- d" ==-> "\n" it "CM278" $ "- a\n- b\n\n [ref]: /url\n- d" ==-> "\n" it "CM279" $ "- a\n- ```\n b\n\n\n ```\n- c" ==-> "\n" it "CM280" $ "- a\n - b\n\n c\n- d" ==-> "\n" it "CM281" $ "* a\n > b\n >\n* c" ==-> "\n" it "CM282" $ "- a\n > b\n ```\n c\n ```\n- d" ==-> "\n" it "CM283" $ "- a" ==-> "\n" it "CM284" $ "- a\n - b" ==-> "\n" it "CM285" $ "1. ```\n foo\n ```\n\n bar" ==-> "
    \n
  1. \n
    foo\n
    \n

    bar

    \n
  2. \n
\n" it "CM286" $ "* foo\n * bar\n\n baz" ==-> "\n" it "CM287" $ "- a\n - b\n - c\n\n- d\n - e\n - f" ==-> "\n" context "6 Inlines" $ it "CM288" $ let s = "`hi`lo`\n" in s ~-> err (posN 7 s) (ueib <> etok '`' <> ecsc) context "6.1 Blackslash escapes" $ do it "CM289" $ "\\!\\\"\\#\\$\\%\\&\\'\\(\\)\\*\\+\\,\\-\\.\\/\\:\\;\\<\\=\\>\\?\\@\\[\\\\\\]\\^\\_\\`\\{\\|\\}\\~\n" ==-> "

!"#$%&'()*+,-./:;<=>?@[\\]^_`{|}~

\n" it "CM290" $ "\\\t\\A\\a\\ \\3\\φ\\«" ==-> "

\\\t\\A\\a\\ \\3\\φ\\«

\n" it "CM291" $ "\\*not emphasized\\*\n\\
not a tag\n\\[not a link\\](/foo)\n\\`not code\\`\n1\\. not a list\n\\* not a list\n\\# not a heading\n\\[foo\\]: /url \"not a reference\"\n" ==-> "

*not emphasized*\n<br/> not a tag\n[not a link](/foo)\n`not code`\n1. not a list\n* not a list\n# not a heading\n[foo]: /url "not a reference"

\n" it "CM292" $ let s = "\\\\*emphasis*" in s ~-> errFancy (posN 2 s) (nonFlanking "*") it "CM293" $ "foo\\\nbar" ==-> "

foo
\nbar

\n" it "CM294" $ "`` \\[\\` ``" ==-> "

\\[\\`

\n" it "CM295" $ " \\[\\]" ==-> "
\\[\\]\n
\n" it "CM296" $ "~~~\n\\[\\]\n~~~" ==-> "
\\[\\]\n
\n" it "CM297" $ "" ==-> "

http://example.com/?find=*

\n" it "CM298" $ "" ==-> "

<a href="/bar/)">

\n" it "CM299" $ let s = "[foo](/bar\\* \"ti\\*tle\")" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) it "CM300" $ let s = "[foo]\n\n[foo]: /bar\\* \"ti\\*tle\"" in s ~~-> [ errFancy (posN 1 s) (couldNotMatchRef "foo" []) , err (posN 18 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) ] it "CM301" $ "``` foo\\+bar\nfoo\n```" ==-> "
foo\n
\n" context "6.2 Entity and numeric character references" $ do it "CM302" $ "  & © Æ Ď\n¾ ℋ ⅆ\n∲ ≧̸" ==-> "

  & © Æ Ď\n¾ ℋ ⅆ\n∲ ≧̸

\n" it "CM303a" $ "# Ӓ Ϡ" ==-> "

# Ӓ Ϡ

\n" it "CM303b" $ "�" ~-> errFancy posI (invalidNumChar 98765432) it "CM303c" $ "�" ~-> errFancy posI (invalidNumChar 0) it "CM304" $ "" ആ ಫ" ==-> "

" ആ ಫ

\n" it "CM305a" $ " " ==-> "

&nbsp

\n" it "CM305b" $ let s = "&x;" in s ~-> errFancy posI (unknownEntity "x") it "CM305c" $ let s = "&#;" in s ~-> err (posN 2 s) (utok ';' <> etok 'x' <> etok 'X' <> elabel "integer") it "CM305d" $ let s = "&#x;" in s ~-> err (posN 3 s) (utok ';' <> elabel "hexadecimal integer") it "CM305e" $ let s = "&ThisIsNotDefined;" in s ~-> errFancy posI (unknownEntity "ThisIsNotDefined") it "CM305f" $ "&hi?;" ==-> "

&hi?;

\n" it "CM306" $ "©" ==-> "

&copy

\n" it "CM307" $ let s = "&MadeUpEntity;" in s ~-> errFancy posI (unknownEntity "MadeUpEntity") it "CM308" $ "
" ==-> "

<a href="\246\246.html">

\n" it "CM309" $ "[foo](/föö \"föö\")" ==-> "

foo

\n" it "CM310" $ "[foo]\n\n[foo]: /föö \"föö\"" ==-> "

foo

\n" it "CM311" $ "``` föö\nfoo\n```" ==-> "
foo\n
\n" it "CM312" $ "`föö`" ==-> "

f&ouml;&ouml;

\n" it "CM313" $ " föfö" ==-> "
f&ouml;f&ouml;\n
\n" context "6.3 Code spans" $ do it "CM314" $ "`foo`" ==-> "

foo

\n" it "CM315" $ "`` foo ` bar ``" ==-> "

foo ` bar

\n" it "CM316" $ "` `` `" ==-> "

``

\n" it "CM317" $ "``\nfoo\n``" ==-> "

foo

\n" it "CM318" $ "`foo bar\n baz`" ==-> "

foo bar baz

\n" it "CM319" $ "`a  b`" ==-> "

a  b

\n" it "CM320" $ "`foo `` bar`" ==-> "

foo `` bar

\n" it "CM321" $ let s = "`foo\\`bar`\n" in s ~-> err (posN 10 s) (ueib <> etok '`' <> ecsc) it "CM322" $ let s = "*foo`*`\n" in s ~-> err (posN 7 s) (ueib <> etok '*' <> eic) it "CM323" $ let s = "[not a `link](/foo`)\n" in s ~-> err (posN 20 s) (ueib <> etok ']' <> eic) it "CM324" $ let s = "``\n" in s ~-> err (posN 14 s) (ueib <> etok '`' <> ecsc) it "CM325" $ "`" ==-> "

<a href="">

\n" it "CM326" $ let s = "``\n" in s ~-> err (posN 23 s) (ueib <> etok '`' <> ecsc) it "CM327" $ "`" ==-> "

<http://foo.bar.baz>

\n" it "CM328" $ let s = "```foo``\n" in s ~-> err (posN 8 s) (ueib <> etok '`' <> ecsc) it "CM329" $ let s = "`foo\n" in s ~-> err (posN 4 s) (ueib <> etok '`' <> ecsc) it "CM330" $ let s = "`foo``bar``\n" in s ~-> err (posN 11 s) (ueib <> etok '`' <> ecsc) context "6.4 Emphasis and strong emphasis" $ do it "CM331" $ "*foo bar*" ==-> "

foo bar

\n" it "CM332" $ let s = "a * foo bar*\n" in s ~-> errFancy (posN 2 s) (nonFlanking "*") it "CM333" $ let s = "a*\"foo\"*\n" in s ~-> errFancy (posN 1 s) (nonFlanking "*") it "CM334" $ let s = "* a *\n" in s ~-> errFancy posI (nonFlanking "*") it "CM335" $ let s = "foo*bar*\n" in s ~-> errFancy (posN 3 s) (nonFlanking "*") it "CM336" $ let s = "5*6*78\n" in s ~-> errFancy (posN 1 s) (nonFlanking "*") it "CM337" $ "_foo bar_" ==-> "

foo bar

\n" it "CM338" $ let s = "_ foo bar_\n" in s ~-> errFancy posI (nonFlanking "_") it "CM339" $ let s = "a_\"foo\"_\n" in s ~-> errFancy (posN 1 s) (nonFlanking "_") it "CM340" $ let s = "foo_bar_\n" in s ~-> errFancy (posN 3 s) (nonFlanking "_") it "CM341" $ let s = "5_6_78\n" in s ~-> errFancy (posN 1 s) (nonFlanking "_") it "CM342" $ let s = "пристаням_стремятся_\n" in s ~-> errFancy (posN 9 s) (nonFlanking "_") it "CM343" $ let s = "aa_\"bb\"_cc\n" in s ~-> errFancy (posN 2 s) (nonFlanking "_") it "CM344" $ let s = "foo-_(bar)_\n" in s ~-> errFancy (posN 4 s) (nonFlanking "_") it "CM345" $ let s = "_foo*\n" in s ~-> err (posN 4 s) (utok '*' <> etok '_' <> eic) it "CM346" $ let s = "*foo bar *\n" in s ~-> errFancy (posN 9 s) (nonFlanking "*") it "CM347" $ let s = "*foo bar\n*\n" in s ~-> err (posN 8 s) (ueib <> etok '*' <> eic) it "CM348" $ let s = "*(*foo)\n" in s ~-> err (posN 7 s) (ueib <> etok '*' <> eic) it "CM349" $ "*(*foo*)*" ==-> "

(foo)

\n" it "CM350" $ let s = "*foo*bar\n" in s ~-> errFancy (posN 4 s) (nonFlanking "*") it "CM351" $ let s = "_foo bar _\n" in s ~-> errFancy (posN 9 s) (nonFlanking "_") it "CM352" $ let s = "_(_foo)" in s ~-> err (posN 7 s) (ueib <> etok '_' <> eic) it "CM353" $ "_(_foo_)_" ==-> "

(foo)

\n" it "CM354" $ let s = "_foo_bar\n" in s ~-> errFancy (posN 4 s) (nonFlanking "_") it "CM355" $ let s = "_пристаням_стремятся\n" in s ~-> errFancy (posN 10 s) (nonFlanking "_") it "CM356" $ let s = "_foo_bar_baz_\n" in s ~-> errFancy (posN 4 s) (nonFlanking "_") it "CM357" $ "_(bar\\)_.\n" ==-> "

(bar).

\n" it "CM358" $ "**foo bar**\n" ==-> "

foo bar

\n" it "CM359" $ let s = "** foo bar**\n" in s ~-> errFancy posI (nonFlanking "**") it "CM360" $ let s = "a**\"foo\"**\n" in s ~-> errFancy (posN 1 s) (nonFlanking "**") it "CM361" $ let s = "foo**bar**\n" in s ~-> errFancy (posN 3 s) (nonFlanking "**") it "CM362" $ "__foo bar__" ==-> "

foo bar

\n" it "CM363" $ let s = "__ foo bar__\n" in s ~-> errFancy posI (nonFlanking "__") it "CM364" $ let s = "__\nfoo bar__\n" in s ~-> errFancy posI (nonFlanking "__") it "CM365" $ let s = "a__\"foo\"__\n" in s ~-> errFancy (posN 1 s) (nonFlanking "__") it "CM366" $ let s = "foo__bar__\n" in s ~-> errFancy (posN 3 s) (nonFlanking "__") it "CM367" $ let s = "5__6__78\n" in s ~-> errFancy (posN 1 s) (nonFlanking "__") it "CM368" $ let s = "пристаням__стремятся__\n" in s ~-> errFancy (posN 9 s) (nonFlanking "__") it "CM369" $ "__foo, __bar__, baz__" ==-> "

foo, bar, baz

\n" it "CM370" $ "foo-__\\(bar)__" ==-> "

foo-(bar)

\n" it "CM371" $ let s = "**foo bar **\n" in s ~-> errFancy (posN 10 s) (nonFlanking "**") it "CM372" $ let s = "**(**foo)\n" in s ~-> err (posN 9 s) (ueib <> etoks "**" <> eic) it "CM373" $ "*(**foo**)*" ==-> "

(foo)

\n" it "CM374" $ "**Gomphocarpus (*Gomphocarpus physocarpus*, syn.\n*Asclepias physocarpa*)**" ==-> "

Gomphocarpus (Gomphocarpus physocarpus, syn.\nAsclepias physocarpa)

\n" it "CM375" $ "**foo \"*bar*\" foo**" ==-> "

foo "bar" foo

\n" it "CM376" $ let s = "**foo**bar\n" in s ~-> errFancy (posN 5 s) (nonFlanking "**") it "CM377" $ let s = "__foo bar __\n" in s ~-> errFancy (posN 10 s) (nonFlanking "__") it "CM378" $ let s = "__(__foo)\n" in s ~-> err (posN 9 s) (ueib <> etoks "__" <> eic) it "CM379" $ "_(__foo__)_" ==-> "

(foo)

\n" it "CM380" $ let s = "__foo__bar\n" in s ~-> errFancy (posN 5 s) (nonFlanking "__") it "CM381" $ let s = "__пристаням__стремятся\n" in s ~-> errFancy (posN 11 s) (nonFlanking "__") it "CM382" $ "__foo\\_\\_bar\\_\\_baz__" ==-> "

foo__bar__baz

\n" it "CM383" $ "__(bar\\)__." ==-> "

(bar).

\n" it "CM384" $ "*foo [bar](/url)*" ==-> "

foo bar

\n" it "CM385" $ "*foo\nbar*" ==-> "

foo\nbar

\n" it "CM386" $ "_foo __bar__ baz_" ==-> "

foo bar baz

\n" it "CM387" $ "_foo _bar_ baz_" ==-> "

foo bar baz

\n" it "CM388" $ let s = "__foo_ bar_" in s ~-> err (posN 5 s) (utoks "_ " <> etoks "__" <> eic) it "CM389" $ "*foo *bar**" ==-> "

foo bar

\n" it "CM390" $ "*foo **bar** baz*" ==-> "

foo bar baz

\n" it "CM391" $ let s = "*foo**bar**baz*\n" in s ~-> errFancy (posN 5 s) (nonFlanking "*") it "CM392" $ "***foo** bar*\n" ==-> "

foo bar

\n" it "CM393" $ "*foo **bar***\n" ==-> "

foo bar

\n" it "CM394" $ let s = "*foo**bar***\n" in s ~-> errFancy (posN 5 s) (nonFlanking "*") it "CM395" $ "*foo **bar *baz* bim** bop*\n" ==-> "

foo bar baz bim bop

\n" it "CM396" $ "*foo [*bar*](/url)*\n" ==-> "

foo bar

\n" it "CM397" $ let s = "** is not an empty emphasis\n" in s ~-> errFancy posI (nonFlanking "**") it "CM398" $ let s = "**** is not an empty strong emphasis\n" in s ~-> errFancy posI (nonFlanking "****") it "CM399" $ "**foo [bar](/url)**" ==-> "

foo bar

\n" it "CM400" $ "**foo\nbar**" ==-> "

foo\nbar

\n" it "CM401" $ "__foo _bar_ baz__" ==-> "

foo bar baz

\n" it "CM402" $ "__foo __bar__ baz__" ==-> "

foo bar baz

\n" it "CM403" $ "____foo__ bar__" ==-> "

foo bar

\n" it "CM404" $ "**foo **bar****" ==-> "

foo bar

\n" it "CM405" $ "**foo *bar* baz**" ==-> "

foo bar baz

\n" it "CM406" $ let s = "**foo*bar*baz**\n" in s ~-> err (posN 5 s) (utoks "*b" <> etoks "**" <> eic) it "CM407" $ "***foo* bar**" ==-> "

foo bar

\n" it "CM408" $ "**foo *bar***" ==-> "

foo bar

\n" it "CM409" $ "**foo *bar **baz**\nbim* bop**" ==-> "

foo bar baz\nbim bop

\n" it "CM410" $ "**foo [*bar*](/url)**" ==-> "

foo bar

\n" it "CM411" $ let s = "__ is not an empty emphasis\n" in s ~-> errFancy posI (nonFlanking "__") it "CM412" $ let s = "____ is not an empty strong emphasis\n" in s ~-> errFancy posI (nonFlanking "____") it "CM413" $ let s = "foo ***\n" in s ~-> errFancy (posN 4 s) (nonFlanking "***") it "CM414" $ "foo *\\**" ==-> "

foo *

\n" it "CM415" $ "foo *\\_*\n" ==-> "

foo _

\n" it "CM416" $ let s = "foo *****\n" in s ~-> errFancy (posN 8 s) (nonFlanking "*") it "CM417" $ "foo **\\***" ==-> "

foo *

\n" it "CM418" $ "foo **\\_**\n" ==-> "

foo _

\n" it "CM419" $ let s = "**foo*\n" in s ~-> err (posN 5 s) (utok '*' <> etoks "**" <> eic) it "CM420" $ let s = "*foo**\n" in s ~-> errFancy (posN 5 s) (nonFlanking "*") it "CM421" $ let s = "***foo**\n" in s ~-> err (posN 8 s) (ueib <> etok '*' <> eic) it "CM422" $ let s = "****foo*\n" in s ~-> err (posN 7 s) (utok '*' <> etoks "**" <> eic) it "CM423" $ let s = "**foo***\n" in s ~-> errFancy (posN 7 s) (nonFlanking "*") it "CM424" $ let s = "*foo****\n" in s ~-> errFancy (posN 5 s) (nonFlanking "***") it "CM425" $ let s = "foo ___\n" in s ~-> errFancy (posN 4 s) (nonFlanking "___") it "CM426" $ "foo _\\__" ==-> "

foo _

\n" it "CM427" $ "foo _\\*_" ==-> "

foo *

\n" it "CM428" $ let s = "foo _____\n" in s ~-> errFancy (posN 8 s) (nonFlanking "_") it "CM429" $ "foo __\\___" ==-> "

foo _

\n" it "CM430" $ "foo __\\*__" ==-> "

foo *

\n" it "CM431" $ let s = "__foo_\n" in s ~-> err (posN 5 s) (utok '_' <> etoks "__" <> eic) it "CM432" $ let s = "_foo__\n" in s ~-> errFancy (posN 5 s) (nonFlanking "_") it "CM433" $ let s = "___foo__\n" in s ~-> err (posN 8 s) (ueib <> etok '_' <> eic) it "CM434" $ let s = "____foo_\n" in s ~-> err (posN 7 s) (utok '_' <> etoks "__" <> eic) it "CM435" $ let s = "__foo___\n" in s ~-> errFancy (posN 7 s) (nonFlanking "_") it "CM436" $ let s = "_foo____\n" in s ~-> errFancy (posN 5 s) (nonFlanking "___") it "CM437" $ "**foo**" ==-> "

foo

\n" it "CM438" $ "*_foo_*" ==-> "

foo

\n" it "CM439" $ "__foo__" ==-> "

foo

\n" it "CM440" $ "_*foo*_" ==-> "

foo

\n" it "CM441" $ "****foo****" ==-> "

foo

\n" it "CM442" $ "____foo____" ==-> "

foo

\n" it "CM443" $ "******foo******" ==-> "

foo

\n" it "CM444" $ "***foo***" ==-> "

foo

\n" it "CM445" $ "_____foo_____" ==-> "

foo

\n" it "CM446" $ let s = "*foo _bar* baz_\n" in s ~-> err (posN 9 s) (utok '*' <> etok '_' <> eic) it "CM447" $ let s = "*foo __bar *baz bim__ bam*\n" in s ~-> err (posN 19 s) (utok '_' <> etok '*' <> eic) it "CM448" $ let s = "**foo **bar baz**\n" in s ~-> err (posN 17 s) (ueib <> etoks "**" <> eic) it "CM449" $ let s = "*foo *bar baz*\n" in s ~-> err (posN 14 s) (ueib <> etok '*' <> eic) it "CM450" $ let s = "*[bar*](/url)\n" in s ~-> err (posN 5 s) (utok '*' <> etok ']' <> eic) it "CM451" $ let s = "_foo [bar_](/url)\n" in s ~-> err (posN 9 s) (utok '_' <> etok ']' <> eic) it "CM452" $ let s = "*\n" in s ~-> errFancy (posN 23 s) (nonFlanking "*") it "CM453" $ let s = "**" in s ~-> errFancy (posN 11 s) (nonFlanking "**") it "CM454" $ let s = "__\n" in s ~-> errFancy (posN 11 s) (nonFlanking "__") it "CM455" $ "*a `*`*" ==-> "

a *

\n" it "CM456" $ "_a `_`_" ==-> "

a _

\n" it "CM457" $ let s = "**a" in s ~-> err (posN 25 s) (ueib <> etoks "**" <> eic) it "CM458" $ let s = "__a" in s ~-> err (posN 26 s) (ueib <> etoks "__" <> eic) context "6.5 Links" $ do it "CM459" $ "[link](/uri \"title\")" ==-> "

link

\n" it "CM460" $ "[link](/uri)" ==-> "

link

\n" it "CM461" $ let s = "[link]()" in s ~-> err (posN 7 s) (utok ')' <> etok '<' <> elabel "URI" <> ews) it "CM462" $ "[link](<>)" ==-> "

link

\n" it "CM463" $ let s = "[link](/my uri)\n" in s ~-> err (posN 11 s) (utok 'u' <> etok '"' <> etok '\'' <> etok '(' <> etok ')' <> ews) it "CM464" $ let s = "[link]()\n" in s ~-> err (posN 11 s) (utok ' ' <> etok '#' <> etok '/' <> etok '>' <> etok '?' <> eppi) it "CM465" $ let s = "[link](foo\nbar)\n" in s ~-> err (posN 11 s) (utok 'b' <> etok '"' <> etok '\'' <> etok '(' <> etok ')' <> ews) it "CM466" $ let s = "[link]()\n" in s ~-> err (posN 11 s) (utok '\n' <> etok '#' <> etok '/' <> etok '>' <> etok '?' <> eppi) it "CM467" $ let s = "[link](\\(foo\\))" in s ~-> err (posN 7 s) (utok '\\' <> etoks "//" <> etok '#' <> etok '/' <> etok '<' <> etok '?' <> elabel "ASCII alpha character" <> euri <> elabel "path piece" <> ews) it "CM468" $ "[link](foo(and(bar)))\n" ==-> "

link))

\n" it "CM469" $ let s = "[link](foo\\(and\\(bar\\))" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) it "CM470" $ "[link]()" ==-> "

link

\n" it "CM471" $ let s = "[link](foo\\)\\:)" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) it "CM472" $ "[link](#fragment)\n\n[link](http://example.com#fragment)\n\n[link](http://example.com?foo=3#frag)\n" ==-> "

link

\n

link

\n

link

\n" it "CM473" $ let s = "[link](foo\\bar)" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) it "CM474" $ "[link](foo%20bä)" ==-> "

link

\n" it "CM475" $ let s = "[link](\"title\")" in s ~-> err (posN 7 s) (utok '"' <> etoks "//" <> etok '#' <> etok '/' <> etok '<' <> etok '?' <> elabel "ASCII alpha character" <> euri <> elabel "path piece" <> ews) it "CM476" $ "[link](/url \"title\")\n[link](/url 'title')\n[link](/url (title))" ==-> "

link\nlink\nlink

\n" it "CM477" $ "[link](/url \"title \\\""\")\n" ==-> "

link

\n" it "CM478" $ let s = "[link](/url \"title\")" in s ~-> err (posN 11 s) (utok ' ' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) it "CM479" $ let s = "[link](/url \"title \"and\" title\")\n" in s ~-> err (posN 20 s) (utok 'a' <> etok ')' <> ews) it "CM480" $ "[link](/url 'title \"and\" title')" ==-> "

link

\n" it "CM481" $ "[link]( /uri\n \"title\" )" ==-> "

link

\n" it "CM482" $ let s = "[link] (/uri)\n" in s ~-> errFancy (posN 1 s) (couldNotMatchRef "link" []) it "CM483" $ let s = "[link [foo [bar]]](/uri)\n" in s ~-> err (posN 6 s) (utok '[' <> etok ']' <> eic) it "CM484" $ let s = "[link] bar](/uri)\n" in s ~-> errFancy (posN 1 s) (couldNotMatchRef "link" []) it "CM485" $ let s = "[link [bar](/uri)\n" in s ~-> err (posN 6 s) (utok '[' <> etok ']' <> eic) it "CM486" $ "[link \\[bar](/uri)\n" ==-> "

link [bar

\n" it "CM487" $ "[link *foo **bar** `#`*](/uri)" ==-> "

link foo bar #

\n" it "CM488" $ "[![moon](moon.jpg)](/uri)" ==-> "

\"moon\"

\n" it "CM489" $ let s = "[foo [bar](/uri)](/uri)\n" in s ~-> err (posN 5 s) (utok '[' <> etok ']' <> eic) it "CM490" $ let s = "[foo *[bar [baz](/uri)](/uri)*](/uri)\n" in s ~-> err (posN 6 s) (utok '[' <> eic) it "CM491" $ let s = "![[[foo](uri1)](uri2)](uri3)" in s ~-> err (posN 3 s) (utok '[' <> eic) it "CM492" $ let s = "*[foo*](/uri)\n" in s ~-> err (posN 5 s) (utok '*' <> etok ']' <> eic) it "CM493" $ let s = "[foo *bar](baz*)\n" in s ~-> err (posN 9 s) (utok ']' <> etok '*' <> eic) it "CM494" $ let s = "*foo [bar* baz]\n" in s ~-> err (posN 9 s) (utok '*' <> etok ']' <> eic) it "CM495" $ "[foo " ==-> "

foo <bar attr="">

\n" it "CM496" $ let s = "[foo`](/uri)`\n" in s ~-> err (posN 13 s) (ueib <> etok ']' <> eic) it "CM497" $ "[foo" ==-> "

foo<http://example.com/?search=>

\n" it "CM498" $ "[foo][bar]\n\n[bar]: /url \"title\"" ==-> "

foo

\n" it "CM499" $ let s = "[link [foo [bar]]][ref]\n\n[ref]: /uri" in s ~-> err (posN 6 s) (utok '[' <> etok ']' <> eic) it "CM500" $ "[link \\[bar][ref]\n\n[ref]: /uri" ==-> "

link [bar

\n" it "CM501" $ "[link *foo **bar** `#`*][ref]\n\n[ref]: /uri" ==-> "

link foo bar #

\n" it "CM502" $ "[![moon](moon.jpg)][ref]\n\n[ref]: /uri" ==-> "

\"moon\"

\n" it "CM503" $ let s = "[foo [bar](/uri)][ref]\n\n[ref]: /uri" in s ~-> err (posN 5 s) (utok '[' <> etok ']' <> eic) it "CM504" $ let s = "[foo *bar [baz][ref]*][ref]\n\n[ref]: /uri" in s ~-> err (posN 10 s) (utok '[' <> etok '*' <> eic) it "CM505" $ let s = "*[foo*][ref]\n\n[ref]: /uri" in s ~-> err (posN 5 s) (utok '*' <> etok ']' <> eic) it "CM506" $ let s = "[foo *bar][ref]\n\n[ref]: /uri" in s ~-> err (posN 9 s) (utok ']' <> etok '*' <> eic) it "CM507" $ "[foo \n\n[ref]: /uri" ==-> "

foo <bar attr="">

\n" it "CM508" $ let s = "[foo`][ref]`\n\n[ref]: /uri" in s ~-> err (posN 12 s) (ueib <> etok ']' <> eic) it "CM509" $ "[foo\n\n[ref]: /uri" ==-> "

foo<http://example.com/?search=>

\n" it "CM510" $ "[foo][BaR]\n\n[bar]: /url \"title\"" ==-> "

foo

\n" it "CM511" $ "[Толпой][Толпой] is a Russian word.\n\n[ТОЛПОЙ]: /url" ==-> "

Толпой is a Russian word.

\n" it "CM512" $ "[Foo\n bar]: /url\n\n[Baz][Foo bar]" ==-> "

Baz

\n" it "CM513" $ let s = "[foo] [bar]\n\n[bar]: /url \"title\"" in s ~-> errFancy (posN 1 s) (couldNotMatchRef "foo" []) it "CM514" $ let s = "[foo]\n[bar]\n\n[bar]: /url \"title\"" in s ~-> errFancy (posN 1 s) (couldNotMatchRef "foo" []) it "CM515" $ let s = "[foo]: /url1\n\n[foo]: /url2\n\n[bar][foo]" in s ~-> errFancy (posN 15 s) (duplicateRef "foo") it "CM516" $ "[bar][foo\\!]\n\n[foo!]: /url" ==-> "

bar

\n" it "CM517" $ let s = "[foo][ref[]\n\n[ref[]: /uri" in s ~~-> [ err (posN 9 s) (utok '[' <> etok ']' <> elabel "the rest of reference label") , err (posN 17 s) (utok '[' <> etok ']' <> eic) ] it "CM518" $ let s = "[foo][ref[bar]]\n\n[ref[bar]]: /uri" in s ~~-> [ err (posN 9 s) (utok '[' <> etok ']' <> elabel "the rest of reference label") , err (posN 21 s) (utok '[' <> etok ']' <> eic) ] it "CM519" $ let s = "[[[foo]]]\n\n[[[foo]]]: /url" in s ~~-> [ err (posN 1 s) (utok '[' <> eic) , err (posN 12 s) (utok '[' <> eic) ] it "CM520" $ "[foo][ref\\[]\n\n[ref\\[]: /uri" ==-> "

foo

\n" it "CM521" $ "[bar\\\\]: /uri\n\n[bar\\\\]" ==-> "

bar\\

\n" it "CM522" $ let s = "[]\n\n[]: /uri" in s ~~-> [ err (posN 1 s) (utok ']' <> eic) , err (posN 5 s) (utok ']' <> eic) ] it "CM523" $ let s = "[\n ]\n\n[\n ]: /uri" in s ~~-> [ errFancy (posN 1 s) (couldNotMatchRef "" []) , errFancy (posN 7 s) (couldNotMatchRef "" []) ] it "CM524" $ "[foo][]\n\n[foo]: /url \"title\"" ==-> "

foo

\n" it "CM525" $ let s = "[*foo* bar][]\n\n[*foo* bar]: /url \"title\"" in s ~-> errFancy (posN 1 s) (couldNotMatchRef "foo bar" ["*foo* bar"]) it "CM526" $ "[Foo][]\n\n[foo]: /url \"title\"" ==-> "

Foo

\n" it "CM527" $ let s = "[foo] \n[]\n\n[foo]: /url \"title\"" in s ~-> err (posN 8 s) (utok ']' <> eic) it "CM528" $ "[foo]\n\n[foo]: /url \"title\"" ==-> "

foo

\n" it "CM529" $ let s = "[*foo* bar]\n\n[*foo* bar]: /url \"title\"" in s ~-> errFancy (posN 1 s) (couldNotMatchRef "foo bar" ["*foo* bar"]) it "CM530" $ let s = "[[*foo* bar]]\n\n[*foo* bar]: /url \"title\"" in s ~-> err (posN 1 s) (utok '[' <> eic) it "CM531" $ let s = "[[bar [foo]\n\n[foo]: /url" in s ~-> err (posN 1 s) (utok '[' <> eic) it "CM532" $ "[Foo]\n\n[foo]: /url \"title\"" ==-> "

Foo

\n" it "CM533" $ "[foo] bar\n\n[foo]: /url" ==-> "

foo bar

\n" it "CM534" $ let s = "\\[foo]\n\n[foo]: /url \"title\"" in s ~-> err (posN 5 s) (utok ']' <> eeib <> eic) it "CM535" $ let s = "[foo*]: /url\n\n*[foo*]" in s ~-> err (posN 19 s) (utok '*' <> etok ']' <> eic) it "CM536" $ "[foo][bar]\n\n[foo]: /url1\n[bar]: /url2" ==-> "

foo

\n" it "CM537" $ "[foo][]\n\n[foo]: /url1" ==-> "

foo

\n" it "CM538" $ let s = "[foo]()\n\n[foo]: /url1" in s ~-> err (posN 6 s) (utok ')' <> etok '<' <> elabel "URI" <> ews) it "CM539" $ let s = "[foo](not a link)\n\n[foo]: /url1" in s ~-> err (posN 10 s) (utok 'a' <> etok '"' <> etok '\'' <> etok '(' <> etok ')' <> ews) it "CM540" $ let s = "[foo][bar][baz]\n\n[baz]: /url" in s ~-> errFancy (posN 6 s) (couldNotMatchRef "bar" ["baz"]) it "CM541" $ "[foo][bar][baz]\n\n[baz]: /url1\n[bar]: /url2" ==-> "

foobaz

\n" it "CM542" $ let s = "[foo][bar][baz]\n\n[baz]: /url1\n[foo]: /url2" in s ~-> errFancy (posN 6 s) (couldNotMatchRef "bar" ["baz"]) context "6.6 Images" $ do it "CM543" $ "![foo](/url \"title\")" ==-> "

\"foo\"

\n" it "CM544" $ "![foo *bar*](train.jpg \"train & tracks\")" ==-> "

\"foo

\n" it "CM545" $ let s = "![foo ![bar](/url)](/url2)\n" in s ~-> err (posN 6 s) (utok '!' <> etok ']' <> eic) it "CM546" $ "![foo [bar](/url)](/url2)" ==-> "

\"foo

\n" it "CM547" $ let s = "![foo *bar*][]\n\n[foo *bar*]: train.jpg \"train & tracks\"\n" in s ~-> errFancy (posN 2 s) (couldNotMatchRef "foo bar" ["foo *bar*"]) it "CM548" $ "![foo *bar*][foobar]\n\n[FOOBAR]: train.jpg \"train & tracks\"" ==-> "

\"foo

\n" it "CM549" $ "![foo](train.jpg)" ==-> "

\"foo\"

\n" it "CM550" $ "My ![foo bar](/path/to/train.jpg \"title\" )" ==-> "

My \"foo

\n" it "CM551" $ "![foo]()" ==-> "

\"foo\"

\n" it "CM552" $ "![](/url)" ==-> "

\n" it "CM553" $ "![foo][bar]\n\n[bar]: /url" ==-> "

\"foo\"

\n" it "CM554" $ "![foo][bar]\n\n[BAR]: /url" ==-> "

\"foo\"

\n" it "CM555" $ "![foo][]\n\n[foo]: /url \"title\"" ==-> "

\"foo\"

\n" it "CM556" $ "![foo bar][]\n\n[foo bar]: /url \"title\"" ==-> "

\"foo

\n" it "CM557" $ "![Foo][]\n\n[foo]: /url \"title\"" ==-> "

\"Foo\"

\n" it "CM558" $ let s = "![foo] \n[]\n\n[foo]: /url \"title\"" in s ~-> err (posN 9 s) (utok ']' <> eic) it "CM559" $ "![foo]\n\n[foo]: /url \"title\"" ==-> "

\"foo\"

\n" it "CM560" $ "![*foo* bar]\n\n[foo bar]: /url \"title\"\n" ==-> "

\"foo

\n" it "CM561" $ let s = "![[foo]]\n\n[[foo]]: /url \"title\"" in s ~~-> [ errFancy (posN 3 s) (couldNotMatchRef "foo" []) , err (posN 11 s) (utok '[' <> eic) ] it "CM562" $ "![Foo]\n\n[foo]: /url \"title\"" ==-> "

\"Foo\"

\n" it "CM563" $ "!\\[foo\\]\n\n[foo]: /url \"title\"" ==-> "

![foo]

\n" it "CM564" $ "\\![foo]\n\n[foo]: /url \"title\"" ==-> "

!foo

\n" context "6.7 Autolinks" $ do it "CM565" $ "" ==-> "

http://foo.bar.baz/

\n" it "CM566" $ "" ==-> "

http://foo.bar.baz/test?q=hello&id=22&boolean

\n" it "CM567" $ "" ==-> "

irc://foo.bar:2233/baz

\n" it "CM568" $ "" ==-> "

FOO@BAR.BAZ

\n" it "CM569" $ "" ==-> "

a+b+c:d

\n" it "CM570" $ "" ==-> "

made-up-scheme://foo/,bar

\n" it "CM571" $ "" ==-> "

<http://../>

\n" it "CM572" $ "" ==-> "

localhost:5001/foo

\n" it "CM573" $ "\n" ==-> "

<http://foo.bar/baz bim>

\n" it "CM574" $ "" ==-> "

<http://example.com/[>

\n" it "CM575" $ "" ==-> "

foo@bar.example.com

\n" it "CM576" $ "" ==-> "

foo+special@Bar.baz-bar0.com

\n" it "CM577" $ "" ==-> "

<foo+@bar.example.com>

\n" it "CM578" $ "<>" ==-> "

<>

\n" it "CM579" $ "< http://foo.bar >" ==-> "

< http://foo.bar >

\n" it "CM580" $ "" ==-> "

m:abc

\n" it "CM581" $ "" ==-> "

foo.bar.baz

\n" it "CM582" $ "http://example.com" ==-> "

http://example.com

\n" it "CM583" $ "foo@bar.example.com" ==-> "

foo@bar.example.com

\n" context "6.8 Raw HTML" $ -- NOTE We do not support raw HTML, see the readme. return () context "6.9 Hard line breaks" $ do -- NOTE We currently do not support hard line breaks represented in -- markup as two spaces before newline. it "CM605" $ "foo \nbaz" ==-> "

foo\nbaz

\n" it "CM606" $ "foo\\\nbaz\n" ==-> "

foo
\nbaz

\n" it "CM607" $ "foo \nbaz" ==-> "

foo\nbaz

\n" it "CM608" $ "foo \n bar" ==-> "

foo\nbar

\n" it "CM609" $ "foo\\\n bar" ==-> "

foo
\nbar

\n" it "CM610" $ "*foo \nbar*" ==-> "

foo\nbar

\n" it "CM611" $ "*foo\\\nbar*" ==-> "

foo
\nbar

\n" it "CM612" $ "`code \nspan`" ==-> "

code span

\n" it "CM613" $ "`code\\\nspan`" ==-> "

code\\ span

\n" it "CM614" $ "" ==-> "

<a href="foo\nbar">

\n" it "CM615" $ "
" ==-> "

<a href="foo
\nbar">

\n" it "CM616" $ "foo\\" ==-> "

foo\\

\n" it "CM617" $ "foo " ==-> "

foo

\n" it "CM618" $ "### foo\\" ==-> "

foo\\

\n" it "CM619" $ "### foo " ==-> "

foo

\n" context "6.10 Soft line breaks" $ do it "CM620" $ "foo\nbaz" ==-> "

foo\nbaz

\n" it "CM621" $ "foo \n baz" ==-> "

foo\nbaz

\n" context "6.11 Textual content" $ do it "CM622" $ "hello $.;'there" ==-> "

hello $.;'there

\n" it "CM623" $ "Foo χρῆν" ==-> "

Foo χρῆν

\n" it "CM624" $ "Multiple spaces" ==-> "

Multiple spaces

\n" -- NOTE I don't test these so extensively because they share -- implementation with emphasis and strong emphasis which are thoroughly -- tested already. context "strikeout" $ do it "works in simplest form" $ "It's ~~bad~~ news." ==-> "

It's bad news.

\n" it "combines with emphasis" $ "**It's ~~bad~~** news." ==-> "

It's bad news.

\n" it "interacts with subscript reasonably (1)" $ "It's ~~~bad~~ news~." ==-> "

It's bad news.

\n" it "interacts with subscript reasonably (2)" $ "It's ~~~bad~ news~~." ==-> "

It's bad news.

\n" context "subscript" $ do it "works in simplest form" $ "It's ~bad~ news." ==-> "

It's bad news.

\n" it "combines with emphasis" $ "**It's ~bad~** news." ==-> "

It's bad news.

\n" context "superscript" $ do it "works in simplest form" $ "It's ^bad^ news." ==-> "

It's bad news.

\n" it "combines with emphasis" $ "**It's ^bad^** news." ==-> "

It's bad news.

\n" it "a composite, complex example" $ "***Something ~~~is not~~ going~ ^so well^** today*." ==-> "

Something is not going so well today.

\n" context "title parse errors" $ it "parse error is OK in reference definitions" $ let s = "[something]: something something" in s ~-> err (posN 23 s) (utoks "so" <> etok '\'' <> etok '\"' <> etok '(' <> elabel "white space" <> elabel "newline") context "tables" $ do it "recognizes single column tables" $ do let o = "\n\n\n\n\n\n\n
Foo
foo
\n" "|Foo\n---\nfoo" ==-> o "Foo|\n---\nfoo" ==-> o "| Foo |\n --- \n foo " ==-> o "| Foo |\n| --- |\n| foo |" ==-> o it "reports correct parse errors when parsing the header line" $ (let s = "Foo | Bar\na-- | ---" in s ~-> err (posN 10 s) (utok 'a' <> etok '-' <> etok ':' <> etok '|' <> elabel "white space")) >> (let s = "Foo | Bar\n-a- | ---" in s ~-> err (posN 11 s) (utok 'a' <> etok '-')) >> (let s = "Foo | Bar\n--a | ---" in s ~-> err (posN 12 s) (utok 'a' <> etok '-')) >> (let s = "Foo | Bar\n---a | ---" in s ~-> err (posN 13 s) (utok 'a' <> etok '-' <> etok ':' <> etok '|' <> elabel "white space")) it "falls back to paragraph when header line is weird enough" $ "Foo | Bar\nab- | ---" ==-> "

Foo | Bar\nab- | ---

\n" it "demands that number of columns in rows match number of columns in header" $ (let s = "Foo | Bar | Baz\n--- | --- | ---\nfoo | bar" in s ~-> err (posN 41 s) (ulabel "end of table block" <> etok '|' <> eic)) >> (let s = "Foo | Bar | Baz\n--- | --- | ---\nfoo | bar\n\nHere it goes." in s ~-> err (posN 41 s) (utok '\n' <> etok '|' <> eic)) it "recognizes escaped pipes" $ "Foo \\| | Bar\n--- | ---\nfoo | \\|" ==-> "\n\n\n\n\n\n\n
Foo |Bar
foo|
\n" it "escaped characters preserve backslashes for inline-level parser" $ "Foo | Bar\n--- | ---\n\\*foo\\* | bar" ==-> "\n\n\n\n\n\n\n
FooBar
*foo*bar
\n" it "escaped pipes do not fool position tracking" $ let s = "Foo | Bar\n--- | ---\n\\| *fo | bar" in s ~-> err (posN 26 s) (ueib <> etok '*' <> elabel "inline content") it "pipes in code spans in headers do not fool the parser" $ "`|Foo|` | `|Bar|`\n--- | ---\nfoo | bar" ==-> "\n\n\n\n\n\n\n
|Foo||Bar|
foobar
\n" it "pipes in code spans in cells do not fool the parser" $ "Foo | Bar\n--- | ---\n`|foo|` | `|bar|`" ==-> "\n\n\n\n\n\n\n
FooBar
|foo||bar|
\n" it "multi-line code spans are disallowed in table headers" $ "`Foo\nBar` | Bar\n--- | ---\nfoo | bar" ==-> "

Foo Bar | Bar\n--- | ---\nfoo | bar

\n" it "multi-line code spans are disallowed in table cells" $ let s = "Foo | Bar\n--- | ---\n`foo\nbar` | bar" in s ~~-> [ err (posN 24 s) (utok '\n' <> etok '`' <> ecsc) , err (posN 35 s) (ueib <> etok '`' <> ecsc) ] it "parses tables with just header row" $ "Foo | Bar\n--- | ---" ==-> "\n\n\n\n\n\n
FooBar
\n" it "recognizes end of table correctly" $ "Foo | Bar\n--- | ---\nfoo | bar\n\nHere goes a paragraph." ==-> "\n\n\n\n\n\n\n
FooBar
foobar
\n

Here goes a paragraph.

\n" it "is capable of reporting a parse error per cell" $ let s = "Foo | *Bar\n--- | ----\n_foo | bar_" in s ~~-> [ err (posN 10 s) (ueib <> etok '*' <> eic) , err (posN 26 s) (ueib <> etok '_' <> eic) , errFancy (posN 32 s) (nonFlanking "_") ] it "tables have higher precedence than unordered lists" $ do "+ foo | bar\n------|----\n" ==-> "\n\n\n\n\n\n
+ foobar
\n" "+ foo | bar\n -----|----\n" ==-> "\n\n\n\n\n\n
+ foobar
\n" it "tables have higher precedence than ordered lists" $ do "1. foo | bar\n-------|----\n" ==-> "\n\n\n\n\n\n
1. foobar
\n" "1. foo | bar\n ------|----\n" ==-> "\n\n\n\n\n\n
1. foobar
\n" it "if table is indented inside unordered list, it's put there" $ "+ foo | bar\n ----|----\n" ==-> "
    \n
  • \n\n\n\n\n\n\n
    foobar
    \n
  • \n
\n" it "if table is indented inside ordered list, it's put there" $ "1. foo | bar\n ----|----\n" ==-> "
    \n
  1. \n\n\n\n\n\n\n
    foobar
    \n
  2. \n
\n" it "renders a comprehensive table correctly" $ withFiles "data/table.md" "data/table.html" context "multiple parse errors" $ do it "they are reported in correct order" $ do let s = "Foo `\n\nBar `.\n" pe = ueib <> etok '`' <> ecsc s ~~-> [ err (posN 5 s) pe , err (posN 13 s) pe ] it "invalid headers are skipped properly" $ do let s = "#My header\n\nSomething goes __here __.\n" s ~~-> [ err (posN 1 s) (utok 'M' <> etok '#' <> ews) , err (posN 37 s) (ueib <> etoks "__" <> eic) ] describe "every block in a list gets its parse error propagated" $ do context "with unordered list" $ it "works" $ do let s = "- *foo\n\n *bar\n- *baz\n\n *quux\n" e = ueib <> etok '*' <> eic s ~~-> [ err (posN 6 s) e , err (posN 14 s) e , err (posN 21 s) e , err (posN 30 s) e ] context "with ordered list" $ it "works" $ do let s = "1. *foo\n\n *bar\n2. *baz\n\n *quux\n" e = ueib <> etok '*' <> eic s ~~-> [ err (posN 7 s) e , err (posN 16 s) e , err (posN 24 s) e , err (posN 34 s) e ] it "too big start index of ordered list does not prevent validation of inner inlines" $ do let s = "1234567890. *something\n1234567891. [\n" s ~~-> [ errFancy posI (indexTooBig 1234567890) , err (posN 22 s) (ueib <> etok '*' <> eic) , err (posN 36 s) (ueib <> eic) ] it "non-consecutive indices in ordered list do not prevent further validation" $ do let s = "1. *foo\n3. *bar\n4. *baz\n" e = ueib <> etok '*' <> eic s ~~-> [ err (posN 7 s) e , errFancy (posN 8 s) (indexNonCons 3 2) , err (posN 15 s) e , errFancy (posN 16 s) (indexNonCons 4 3) , err (posN 23 s) e ] context "given a complete, comprehensive document" $ it "outputs expected the HTML fragment" $ withFiles "data/comprehensive.md" "data/comprehensive.html" describe "parseErrorsPretty" $ it "renders parse errors correctly" $ do let s = "Foo\nBar\nBaz\n" e0 = err posI (utok 'F' <> etok 'Z') e1 = err (posN 4 s) (utok 'B' <> etok 'Z') e2 = err (posN 8 s) (utok 'B' <> etok 'Z') MMark.parseErrorsPretty s (e0:|[e1,e2]) `shouldBe` "1:1:\n |\n1 | Foo\n | ^\nunexpected 'F'\nexpecting 'Z'\n2:1:\n |\n2 | Bar\n | ^\nunexpected 'B'\nexpecting 'Z'\n3:1:\n |\n3 | Baz\n | ^\nunexpected 'B'\nexpecting 'Z'\n" describe "useExtension" $ it "applies given extension" $ do doc <- mkDoc "Here we go." toText (MMark.useExtension (append_ext "..") doc) `shouldBe` "

Here we go...

\n" describe "useExtensions" $ it "applies extensions in the right order" $ do doc <- mkDoc "Here we go." let exts = [ append_ext "3" , append_ext "2" , append_ext "1" ] toText (MMark.useExtensions exts doc) `shouldBe` "

Here we go.123

\n" describe "runScanner and scanner" $ it "extracts information from markdown document" $ do doc <- mkDoc "Here we go, pals." let n = MMark.runScanner doc (length_scan (const True)) n `shouldBe` 17 describe "combining of scanners" $ it "combines scanners" $ do doc <- mkDoc "Here we go, pals." let scan = (,,) <$> length_scan (const True) <*> length_scan isSpace <*> length_scan isPunctuation r = MMark.runScanner doc scan r `shouldBe` (17, 3, 2) describe "projectYaml" $ do context "when document does not contain a YAML section" $ it "returns Nothing" $ do doc <- mkDoc "Here we go." MMark.projectYaml doc `shouldBe` Nothing context "when document contains a YAML section" $ do context "when it is valid" $ do let r = object [ "x" .= Number 100 , "y" .= Number 200 ] it "returns the YAML section (1)" $ do doc <- mkDoc "---\nx: 100\ny: 200\n---\nHere we go." MMark.projectYaml doc `shouldBe` Just r it "returns the YAML section (2)" $ do doc <- mkDoc "---\nx: 100\ny: 200\n---\n\n" MMark.projectYaml doc `shouldBe` Just r context "when it is invalid" $ do let mappingErr = fancy . ErrorCustom . YamlParseError $ "mapping values are not allowed in this context" it "signal correct parse error" $ let s = "---\nx: 100\ny: x:\n---\nHere we go." in s ~-> errFancy (posN 15 s) mappingErr it "does not choke and can report more parse errors" $ let s = "---\nx: 100\ny: x:\n---\nHere we *go." in s ~~-> [ errFancy (posN 15 s) mappingErr , err (posN 33 s) (ueib <> etok '*' <> eic) ] ---------------------------------------------------------------------------- -- Testing extensions -- | Append given text to all 'Plain' blocks. append_ext :: Text -> MMark.Extension append_ext y = Ext.inlineTrans $ \case Plain x -> Plain (x <> y) other -> other ---------------------------------------------------------------------------- -- Testing scanners -- | Scan total number of characters satisfying a predicate in all 'Plain' -- inlines. length_scan :: (Char -> Bool) -> L.Fold (Ext.Block (NonEmpty Inline)) Int length_scan p = Ext.scanner 0 $ \n block -> getSum $ Sum n <> foldMap (foldMap f) block where f (Plain txt) = (Sum . T.length) (T.filter p txt) f _ = mempty ---------------------------------------------------------------------------- -- For testing with documents loaded externally -- | Load a complete markdown document from an external file and compare the -- final HTML rendering with contents of another file. withFiles :: FilePath -- ^ Markdown document -> FilePath -- ^ HTML document containing the correct result -> Expectation withFiles input output = do i <- TIO.readFile input o <- TIO.readFile output i ==-> o ---------------------------------------------------------------------------- -- Helpers -- | Unexpected end of inline block. ueib :: Ord t => ET t ueib = ulabel "end of inline block" -- | Expecting end of inline block. eeib :: Ord t => ET t eeib = elabel "end of inline block" -- | Expecting end of URI. euri :: Ord t => ET t euri = elabel "end of URI" -- | Expecting the rest of path piece. eppi :: Ord t => ET t eppi = elabel "the rest of path piece" -- | Expecting inline content. eic :: Ord t => ET t eic = elabel "inline content" -- | Expecting white space. ews :: Ord t => ET t ews = elabel "white space" -- | Expecting code span content. ecsc :: Ord t => ET t ecsc = elabel "code span content" -- | Error component complaining that the given 'Text' is not in left- or -- right- flanking position. nonFlanking :: Text -> EF MMarkErr nonFlanking = fancy . ErrorCustom . NonFlankingDelimiterRun . NE.fromList . T.unpack -- | Error component complaining that the given starting index of an ordered -- list is too big. indexTooBig :: Word -> EF MMarkErr indexTooBig = fancy . ErrorCustom . ListStartIndexTooBig -- | Error component complaining about non-consecutive indices in an ordered -- list. indexNonCons :: Word -> Word -> EF MMarkErr indexNonCons actual expected = fancy . ErrorCustom $ ListIndexOutOfOrder actual expected -- | Error component complaining about a missing link\/image reference. couldNotMatchRef :: Text -> [Text] -> EF MMarkErr couldNotMatchRef name names = fancy . ErrorCustom $ CouldNotFindReferenceDefinition name names -- | Error component complaining about a duplicate reference definition. duplicateRef :: Text -> EF MMarkErr duplicateRef = fancy . ErrorCustom . DuplicateReferenceDefinition -- | Error component complaining about an invalid numeric character. invalidNumChar :: Int -> EF MMarkErr invalidNumChar = fancy . ErrorCustom . InvalidNumericCharacter -- | Error component complaining about an unknown HTML5 entity name. unknownEntity :: Text -> EF MMarkErr unknownEntity = fancy . ErrorCustom . UnknownHtmlEntityName