diff options
author | Konstantin Zudov <konstantin@anche.no> | 2015-03-03 03:28:56 +0200 |
---|---|---|
committer | Konstantin Zudov <konstantin@anche.no> | 2015-03-10 20:32:24 +0200 |
commit | b9f77ed03d0e4a0651d7508d563e880556690fcf (patch) | |
tree | 41f95866036702b3c78289bab0b83f6089ca2524 /tests | |
parent | 4f0c5c30809f09bd700cd47035f86a3db1c64669 (diff) | |
download | pandoc-b9f77ed03d0e4a0651d7508d563e880556690fcf.tar.gz |
Support shortcut reference links in markdown writer
Issue #1977
Most markdown processors support the [shortcut format] for reference links.
Pandoc's markdown reader parsed this shortcuts unoptionally.
Pandoc's markdown writer (with --reference-links option) never shortcutted links.
This commit adds an extension `shortcut_reference_links`. The extension is
enabled by default for those markdown flavors that support reading shortcut
reference links, namely:
- pandoc
- strict pandoc
- github flavoured
- PHPmarkdown
If extension is enabled, reader parses the shortcuts in the same way as
it preveously did. Otherwise it would parse them as normal text.
If extension is enabled, writer outputs shortcut reference links unless
doing so would cause problems (see test cases in `tests/Tests/Writers/Markdown.hs`).
Diffstat (limited to 'tests')
-rw-r--r-- | tests/Tests/Writers/Markdown.hs | 91 |
1 files changed, 90 insertions, 1 deletions
diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index c2a8f5903..dce40ddcb 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Tests.Writers.Markdown (tests) where import Test.Framework @@ -35,4 +36,92 @@ tests = [ "indented code after list" =: bulletList [ plain "foo" <> bulletList [ plain "bar" ], plain "baz" ] =?> "- foo\n - bar\n- baz\n" - ] + ] ++ [shortcutLinkRefsTests] + +shortcutLinkRefsTests :: Test +shortcutLinkRefsTests = + let infix 4 =: + (=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test + (=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc) + in testGroup "Shortcut reference links" + [ "Simple link (shortcutable)" + =: (para (link "/url" "title" "foo")) + =?> "[foo]\n\n [foo]: /url \"title\"" + , "Followed by another link (unshortcutable)" + =: (para ((link "/url1" "title1" "first") + <> (link "/url2" "title2" "second"))) + =?> unlines [ "[first][][second]" + , "" + , " [first]: /url1 \"title1\"" + , " [second]: /url2 \"title2\"" + ] + , "Followed by space and another link (unshortcutable)" + =: (para ((link "/url1" "title1" "first") <> " " + <> (link "/url2" "title2" "second"))) + =?> unlines [ "[first][] [second]" + , "" + , " [first]: /url1 \"title1\"" + , " [second]: /url2 \"title2\"" + ] + , "Reference link is used multiple times (unshortcutable)" + =: (para ((link "/url1" "" "foo") <> (link "/url2" "" "foo") + <> (link "/url3" "" "foo"))) + =?> unlines [ "[foo][][foo][1][foo][2]" + , "" + , " [foo]: /url1" + , " [1]: /url2" + , " [2]: /url3" + ] + , "Reference link is used multiple times (unshortcutable)" + =: (para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo") + <> " " <> (link "/url3" "" "foo"))) + =?> unlines [ "[foo][] [foo][1] [foo][2]" + , "" + , " [foo]: /url1" + , " [1]: /url2" + , " [2]: /url3" + ] + , "Reference link is followed by text in brackets" + =: (para ((link "/url" "" "link") <> "[text in brackets]")) + =?> unlines [ "[link][][text in brackets]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and text in brackets" + =: (para ((link "/url" "" "link") <> " [text in brackets]")) + =?> unlines [ "[link][] [text in brackets]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by RawInline" + =: (para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]")) + =?> unlines [ "[link][][rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and RawInline" + =: (para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]")) + =?> unlines [ "[link][] [rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by RawInline with space" + =: (para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]")) + =?> unlines [ "[link][] [rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by citation" + =: (para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))) + =?> unlines [ "[link][][@author]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and citation" + =: (para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))) + =?> unlines [ "[link][] [@author]" + , "" + , " [link]: /url" + ] + ] |