{-# 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 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" xit "CM4" $ -- FIXME pending lists " - foo\n\n\tbar" ==-> "\n" xit "CM5" $ -- FIXME pending lists "- foo\n\n\t\tbar" ==-> "\n" xit "CM6" $ -- FIXME pending blockquotes ">\t\tfoo" ==-> "
\n
  foo\n
\n
\n" xit "CM7" $ -- FIXME pending lists "-\t\tfoo" ==-> "\n" it "CM8" $ " foo\n\tbar" ==-> "
foo\nbar\n
\n" xit "CM9" $ -- FIXME pending lists " - foo\n - bar\n\t - baz" ==-> "\n" it "CM10" $ "#\tFoo" ==-> "

Foo

\n" it "CM11" $ "*\t*\t*\t" ==-> "
\n" context "3.1 Precedence" $ xit "CM12" $ -- FIXME pending lists "- `one\n- two`" ==-> "\n" 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 4 s) (nonFlanking "*") it "CM17" $ " ***\n ***\n ***" ==-> "
\n
\n
\n" it "CM18" $ " ***" ==-> "
***\n
\n" it "CM19" $ let s = "Foo\n ***\n" in s ~-> errFancy (posN 10 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" xit "CM27" $ -- FIXME pending lists "- foo\n***\n- bar" ==-> "\n
\n\n" it "CM28" $ let s = "Foo\n***\nbar" in s ~-> errFancy (posN 6 s) (nonFlanking "*") xit "CM29" $ -- FIXME pending setext headings "Foo\n---\nbar" ==-> "

Foo

\n

bar

\n" xit "CM30" $ -- FIXME pending lists "* Foo\n* * *\n* Bar" ==-> "\n
\n\n" xit "CM31" $ -- FIXME pending lists "- 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 '#' <> elabel "white space") it "CM34" $ let s = "#5 bolt\n\n#hashtag" in s ~~-> [ err (posN 1 s) (utok '5' <> etok '#' <> elabel "white space") , err (posN 10 s) (utok 'h' <> etok '#' <> elabel "white space") ] 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\nBar foo

\n" it "CM49" $ let s = "## \n#\n### ###" in s ~~-> [ err (posN 3 s) (utok '\n' <> elabel "heading character" <> elabel "white space") , err (posN 5 s) (utok '\n' <> etok '#' <> elabel "white space") ] context "4.4 Indented code blocks" $ do it "CM76" $ " a simple\n indented code block" ==-> "
a simple\n  indented code block\n
\n" xit "CM77" $ -- FIXME pending lists " - foo\n\n bar" ==-> "\n" xit "CM78" $ -- FIXME pending lists "1. foo\n\n - bar" ==-> "
    \n
  1. \n

    foo

    \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" xit "CM84" $ -- FIXME pending setext headings "# Heading\n foo\nHeading\n------\n foo\n----\n" ==-> "

Heading

\n
foo\n
\n

Heading

\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" $ "```\naaa\n~~~\n```" ==-> "
aaa\n~~~\n
\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" $ let s = "```" in s ~-> err (posN 3 s) (ueof <> etok '`' <> elabel "info string" <> elabel "newline") it "CM95" $ let s = "`````\n\n```\naaa\n" in s ~-> err (posN 15 s) (ueof <> elabel "closing code fence" <> elabel "code block content") xit "CM96" $ -- FIXME pending blockquotes "> ```\n> aaa\n\nbbb" ==-> "
\n
aaa\n
\n
\n

bbb

\n" it "CM97" $ "```\n\n \n```" ==-> "
\n  \n
\n" it "CM98" $ "```\n```" ==-> "
\n" it "CM99" $ " ```\n aaa\naaa\n```" ==-> "
aaa\naaa\n
\n" it "CM100" $ " ```\naaa\n aaa\naaa\n ```" ==-> "
aaa\naaa\naaa\n
\n" it "CM101" $ " ```\n aaa\n aaa\n aaa\n ```" ==-> "
aaa\n aaa\naaa\n
\n" it "CM102" $ " ```\n aaa\n ```" ==-> "
```\naaa\n```\n
\n" it "CM103" $ "```\naaa\n ```" ==-> "
aaa\n
\n" it "CM104" $ " ```\naaa\n ```" ==-> "
aaa\n
\n" it "CM105" $ let s = "```\naaa\n ```\n" in s ~-> err (posN 16 s) (ueof <> elabel "closing code fence" <> elabel "code block content") it "CM106" $ "``` ```\naaa" ==-> "

\naaa

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

foo\nbar\nbaz

\n" xit "CM109" $ -- FIXME pending setext headings "foo\n---\n~~~\nbar\n~~~\n# baz" ==-> "

foo

\n
bar\n
\n

baz

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

aa\nfoo

\n" it "CM114" $ "```\n``` aaa\n```" ==-> "
``` aaa\n
\n" context "4.8 Paragraphs" $ do it "CM180" $ "aaa\n\nbbb" ==-> "

aaa

\n

bbb

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

aaa\nbbb

\n

ccc\nddd

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

aaa

\n

bbb

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

aaa\nbbb

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

aaa\nbbb\nccc

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

aaa\nbbb

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

bbb

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

aaa\nbbb

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

aaa

\n

aaa

\n" context "6 Inlines" $ it "CM286" $ let s = "`hi`lo`\n" in s ~-> err (posN 7 s) (ueib <> etok '`' <> elabel "code span content") context "6.1 Blackslash escapes" $ do it "CM287" $ "\\!\\\"\\#\\$\\%\\&\\'\\(\\)\\*\\+\\,\\-\\.\\/\\:\\;\\<\\=\\>\\?\\@\\[\\\\\\]\\^\\_\\`\\{\\|\\}\\~\n" ==-> "

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

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

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

\n" it "CM289" $ "\\*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 "CM290" $ let s = "\\\\*emphasis*" in s ~-> err (posN 2 s) (utok '*' <> eeib <> eric) xit "CM291" $ "foo\\\nbar" ==-> "

foo
\nbar

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

\\[\\`

\n" it "CM293" $ " \\[\\]" ==-> "
\\[\\]\n
\n" it "CM294" $ "~~~\n\\[\\]\n~~~" ==-> "
\\[\\]\n
\n" it "CM295" $ "" ==-> "

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

\n" xit "CM296" $ -- FIXME pending HTML inlines "" ==-> "

<a href="/bar/)">

\n" it "CM297" $ let s = "[foo](/bar\\* \"ti\\*tle\")" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) xit "CM298" $ -- FIXME pending reference links "[foo]\n\n[foo]: /bar\\* \"ti\\*tle\"" ==-> "

foo

\n" it "CM299" $ "``` foo\\+bar\nfoo\n```" ==-> "
foo\n
\n" context "6.2 Entity and numeric character references" $ xit "CM300" $ -- FIXME pending entity references "  & © Æ Ď\n¾ ℋ ⅆ\n∲ ≧̸" ==-> "

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

\n" context "6.3 Code spans" $ do it "CM312" $ "`foo`" ==-> "

foo

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

foo ` bar

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

``

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

foo

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

foo bar baz

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

a  b

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

foo `` bar

\n" it "CM319" $ let s = "`foo\\`bar`\n" in s ~-> err (posN 10 s) (ueib <> etok '`' <> elabel "code span content") it "CM320" $ let s = "*foo`*`\n" in s ~-> err (posN 7 s) (ueib <> etok '*' <> eic) it "CM321" $ let s = "[not a `link](/foo`)\n" in s ~-> err (posN 20 s) (ueib <> etok ']' <> eic <> eric) it "CM322" $ let s = "``\n" in s ~-> err (posN 14 s) (ueib <> etok '`' <> elabel "code span content") xit "CM323" $ -- FIXME pending HTML inlines "`" ==-> "

`

\n" it "CM324" $ let s = "``\n" in s ~-> err (posN 23 s) (ueib <> etok '`' <> elabel "code span content") it "CM325" $ "`" ==-> "

<http://foo.bar.baz>

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

foo bar

\n" it "CM330" $ let s = "a * foo bar*\n" in s ~-> err (posN 2 s) (utok '*' <> eeib <> eric) it "CM331" $ let s = "a*\"foo\"*\n" in s ~-> err (posN 1 s) (utok '*' <> eeib <> eric) it "CM332" $ let s = "* a *\n" in s ~-> errFancy posI (nonFlanking "*") it "CM333" $ let s = "foo*bar*\n" in s ~-> err (posN 3 s) (utok '*' <> eeib <> eric) it "CM334" $ let s = "5*6*78\n" in s ~-> err (posN 1 s) (utok '*' <> eeib <> eric) it "CM335" $ "_foo bar_" ==-> "

foo bar

\n" it "CM336" $ let s = "_ foo bar_\n" in s ~-> errFancy posI (nonFlanking "_") it "CM337" $ let s = "a_\"foo\"_\n" in s ~-> err (posN 1 s) (utok '_' <> eeib <> eric) it "CM338" $ let s = "foo_bar_\n" in s ~-> err (posN 3 s) (utok '_' <> eeib <> eric) it "CM339" $ let s = "5_6_78\n" in s ~-> err (posN 1 s) (utok '_' <> eeib <> eric) it "CM340" $ let s = "пристаням_стремятся_\n" in s ~-> err (posN 9 s) (utok '_' <> eeib <> eric) it "CM341" $ let s = "aa_\"bb\"_cc\n" in s ~-> err (posN 2 s) (utok '_' <> eeib <> eric) it "CM342" $ let s = "foo-_(bar)_\n" in s ~-> err (posN 4 s) (utok '_' <> eeib <> eric) it "CM343" $ let s = "_foo*\n" in s ~-> err (posN 4 s) (utok '*' <> etok '_' <> eric) it "CM344" $ let s = "*foo bar *\n" in s ~-> errFancy (posN 9 s) (nonFlanking "*") it "CM345" $ let s = "*foo bar\n*\n" in s ~-> errFancy (posN 9 s) (nonFlanking "*") it "CM346" $ let s = "*(*foo)\n" in s ~-> errFancy posI (nonFlanking "*") it "CM347" $ let s = "*(*foo*)*\n" in s ~-> errFancy posI (nonFlanking "*") it "CM348" $ let s = "*foo*bar\n" in s ~-> errFancy (posN 4 s) (nonFlanking "*") it "CM349" $ let s = "_foo bar _\n" in s ~-> errFancy (posN 9 s) (nonFlanking "_") it "CM350" $ let s = "_(_foo)\n" in s ~-> errFancy posI (nonFlanking "_") it "CM351" $ let s = "_(_foo_)_\n" in s ~-> errFancy posI (nonFlanking "_") it "CM352" $ let s = "_foo_bar\n" in s ~-> errFancy (posN 4 s) (nonFlanking "_") it "CM353" $ let s = "_пристаням_стремятся\n" in s ~-> errFancy (posN 10 s) (nonFlanking "_") it "CM354" $ let s = "_foo_bar_baz_\n" in s ~-> errFancy (posN 4 s) (nonFlanking "_") it "CM355" $ "_\\(bar\\)_.\n" ==-> "

(bar).

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

foo bar

\n" it "CM357" $ let s = "** foo bar**\n" in s ~-> errFancy (posN 1 s) (nonFlanking "*") it "CM358" $ let s = "a**\"foo\"**\n" in s ~-> err (posN 1 s) (utok '*' <> eeib <> eric) it "CM359" $ let s = "foo**bar**\n" in s ~-> err (posN 3 s) (utok '*' <> eeib <> eric) it "CM360" $ "__foo bar__" ==-> "

foo bar

\n" it "CM361" $ let s = "__ foo bar__\n" in s ~-> errFancy (posN 1 s) (nonFlanking "_") it "CM362" $ let s = "__\nfoo bar__\n" in s ~-> errFancy (posN 1 s) (nonFlanking "_") it "CM363" $ let s = "a__\"foo\"__\n" in s ~-> err (posN 1 s) (utok '_' <> eeib <> eric) it "CM364" $ let s = "foo__bar__\n" in s ~-> err (posN 3 s) (utok '_' <> eeib <> eric) it "CM365" $ let s = "5__6__78\n" in s ~-> err (posN 1 s) (utok '_' <> eeib <> eric) it "CM366" $ let s = "пристаням__стремятся__\n" in s ~-> err (posN 9 s) (utok '_' <> eeib <> eric) it "CM367" $ "__foo, __bar__, baz__" ==-> "

foo, bar, baz

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

foo-(bar)

\n" it "CM369" $ let s = "**foo bar **\n" in s ~-> errFancy (posN 11 s) (nonFlanking "*") it "CM370" $ let s = "**(**foo)\n" in s ~-> errFancy (posN 1 s) (nonFlanking "*") it "CM371" $ let s = "*(**foo**)*\n" in s ~-> errFancy posI (nonFlanking "*") xit "CM372" $ -- FIXME doesn't pass with current approach "**Gomphocarpus (*Gomphocarpus physocarpus*, syn.\n*Asclepias physocarpa*)**" ==-> "

Gomphocarpus (Gomphocarpus physocarpus, syn.\nAsclepias physocarpa)

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

foo "bar" foo

\n" it "CM374" $ let s = "**foo**bar\n" in s ~-> errFancy (posN 5 s) (nonFlanking "**") it "CM375" $ let s = "__foo bar __\n" in s ~-> errFancy (posN 11 s) (nonFlanking "_") it "CM376" $ let s = "__(__foo)\n" in s ~-> errFancy (posN 1 s) (nonFlanking "_") it "CM377" $ let s = "_(__foo__)_\n" in s ~-> errFancy posI (nonFlanking "_") it "CM378" $ let s = "__foo__bar\n" in s ~-> errFancy (posN 5 s) (nonFlanking "__") it "CM379" $ let s = "__пристаням__стремятся\n" in s ~-> errFancy (posN 11 s) (nonFlanking "__") it "CM380" $ "__foo\\_\\_bar\\_\\_baz__" ==-> "

foo__bar__baz

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

(bar).

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

foo bar

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

foo\nbar

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

foo bar baz

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

foo bar baz

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

foo bar

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

foo bar baz

\n" it "CM389" $ let s = "*foo**bar**baz*\n" in s ~-> err (posN 5 s) (utok '*' <> eeib) it "CM390" $ "***foo** bar*\n" ==-> "

foo bar

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

foo bar

\n" it "CM392" $ let s = "*foo**bar***\n" in s ~-> err (posN 5 s) (utok '*' <> elabel "end of inline block") it "CM393" $ "*foo **bar *baz* bim** bop*\n" ==-> "

foo bar baz bim bop

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

foo bar

\n" it "CM395" $ let s = "** is not an empty emphasis\n" in s ~-> errFancy (posN 1 s) (nonFlanking "*") it "CM396" $ let s = "**** is not an empty strong emphasis\n" in s ~-> errFancy (posN 3 s) (nonFlanking "*") it "CM397" $ "**foo [bar](/url)**" ==-> "

foo bar

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

foo\nbar

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

foo bar baz

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

foo bar baz

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

foo bar

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

foo bar

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

foo bar baz

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

foo bar

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

foo bar

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

foo bar baz\nbim bop

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

foo bar

\n" it "CM409" $ let s = "__ is not an empty emphasis\n" in s ~-> errFancy (posN 1 s) (nonFlanking "_") it "CM410" $ let s = "____ is not an empty strong emphasis\n" in s ~-> errFancy (posN 3 s) (nonFlanking "_") it "CM411" $ let s = "foo ***\n" in s ~-> errFancy (posN 6 s) (nonFlanking "*") it "CM412" $ "foo *\\**" ==-> "

foo *

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

foo _

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

foo *

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

foo _

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

foo _

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

foo *

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

foo _

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

foo *

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

foo

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

foo

\n" 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" $ let s = "*foo _bar* baz_\n" in s ~-> err (posN 9 s) (utok '*' <> etok '_' <> eric) it "CM445" $ let s = "*foo __bar *baz bim__ bam*\n" in s ~-> err (posN 19 s) (utok '_' <> etok '*' <> eric) it "CM446" $ let s = "**foo **bar baz**\n" in s ~-> err (posN 17 s) (ueib <> etoks "**" <> eic) it "CM447" $ let s = "*foo *bar baz*\n" in s ~-> err (posN 14 s) (ueib <> etok '*' <> eic) it "CM448" $ let s = "*[bar*](/url)\n" in s ~-> err (posN 5 s) (utok '*' <> etok ']' <> eric) it "CM449" $ let s = "_foo [bar_](/url)\n" in s ~-> err (posN 9 s) (utok '_' <> etok ']' <> eric) xit "CM450" $ -- FIXME pending HTML inlines "*" ==-> "

*

\n" xit "CM451" $ -- FIXME pending HTML inlines "**" ==-> "

**

\n" xit "CM452" $ "__\n" ==-> "

__

\n" it "CM453" $ "*a `*`*" ==-> "

a *

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

a _

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

link

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

link

\n" it "CM459" $ "[link]()" ==-> "

link

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

link

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

link))

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

link

\n" it "CM469" $ let s = "[link](foo\\)\\:)" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) it "CM470" $ "[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 "CM471" $ let s = "[link](foo\\bar)" in s ~-> err (posN 10 s) (utok '\\' <> etok '#' <> etok '/' <> etok '?' <> euri <> eppi) xit "CM472" $ -- FIXME pending entity references "[link](foo%20bä)" ==-> "

link

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

link\nlink\nlink

\n" xit "CM475" $ -- FIXME pending entity references "[link](/url \"title \\\""\")\n" ==-> "

link

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

link

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

link

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

link [bar

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

link foo bar #

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

\"moon\"

\n" it "CM487" $ let s = "[foo [bar](/uri)](/uri)\n" in s ~-> err (posN 5 s) (utok '[' <> etok ']' <> eic <> eric) it "CM488" $ let s = "[foo *[bar [baz](/uri)](/uri)*](/uri)\n" in s ~-> err (posN 11 s) (utok '[' <> etok ']' <> eic <> eric) it "CM489" $ let s = "![[[foo](uri1)](uri2)](uri3)" in s ~-> err (posN 3 s) (utoks "[foo" <> eeib <> eic) it "CM490" $ let s = "*[foo*](/uri)\n" in s ~-> err (posN 5 s) (utok '*' <> etok ']' <> eric) it "CM491" $ let s = "[foo *bar](baz*)\n" in s ~-> err (posN 9 s) (utok ']' <> etok '*' <> eic <> eric) it "CM492" $ let s = "*foo [bar* baz]\n" in s ~-> err (posN 9 s) (utok '*' <> etok ']' <> eric) xit "CM493" $ -- FIXME pending inline HTML let s = "[foo " in s ~-> err (posN 5 s) (utok '<' <> etok ']') it "CM494" $ let s = "[foo`](/uri)`\n" in s ~-> err (posN 13 s) (ueib <> etok ']' <> eic) it "CM495" $ "[foo" ==-> "

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

\n" context "6.6 Images" $ do it "CM541" $ "![foo](/url \"title\")" ==-> "

\"foo\"

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

\"foo

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

\"foo

\n" it "CM545" pending it "CM546" pending it "CM547" $ "![foo](train.jpg)" ==-> "

\"foo\"

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

My \"foo

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

\"foo\"

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

\n" it "CM551-CM562" pending -- pending reference-style stuff context "6.7 Autolinks" $ do it "CM563" $ "" ==-> "

http://foo.bar.baz/

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

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

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

irc://foo.bar:2233/baz

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

FOO@BAR.BAZ

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

a+b+c:d

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

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

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

<http://../>

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

localhost:5001/foo

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

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

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

<http://example.com/[>

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

foo@bar.example.com

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

foo+special@Bar.baz-bar0.com

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

<foo+@bar.example.com>

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

<>

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

< http://foo.bar >

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

m:abc

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

foo.bar.baz

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

http://example.com

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

foo@bar.example.com

\n" context "6.9 Hard line breaks" $ do -- NOTE We currently do not support hard line breaks represented in -- markup as space before newline. xit "CM603" $ "foo \nbaz" ==-> "

foo
\nbaz

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

foo
\nbaz

\n" xit "CM605" $ "foo \nbaz" ==-> "

foo
\nbaz

\n" xit "CM606" $ "foo \n bar" ==-> "

foo
\nbar

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

foo
\nbar

\n" xit "CM608" $ "*foo \nbar*" ==-> "

foo
\nbar

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

foo
\nbar

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

code span

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

code\\ span

\n" xit "CM612" $ "" ==-> "

\n" xit "CM613" $ -- FIXME pending HTML inlines "" ==-> "

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

foo\\

\n" xit "CM615" $ "foo " ==-> "

foo

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

foo\\

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

foo

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

foo\nbaz

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

foo\nbaz

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

hello $.;'there

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

Foo χρῆν

\n" it "CM622" $ "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 "multiple parse errors" $ do it "they are reported in correct order" $ do let s = "Foo `\n\nBar `.\n" pe = ueib <> etok '`' <> elabel "code span content" 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 '#' <> elabel "white space") , errFancy (posN 35 s) (nonFlanking "_") ] 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" $ it "returns the YAML section" $ do doc <- mkDoc "---\nx: 100\ny: 200\n---Here we go." let r = object [ "x" .= Number 100 , "y" .= Number 200 ] MMark.projectYaml doc `shouldBe` Just r context "when it is invalid" $ it "signal correct parse error" $ let s = "---\nx: 100\ny: x:\n---Here we go." in s ~-> errFancy (posN 15 s) (fancy . ErrorCustom . YamlParseError $ "mapping values are not allowed in this context") ---------------------------------------------------------------------------- -- 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 literal. euri :: Ord t => ET t euri = elabel "end of URI literal" -- | 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 rest of inline content. Eric! eric :: Ord t => ET t eric = elabel "the rest of inline content" -- | Create a 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