From 136bf901aa088eaf4e5c996c71e0a36c171f1587 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 19 Sep 2018 14:49:46 -0700 Subject: [PATCH] Markdown reader: distinguish autolinks in the AST. With this change, autolinks are parsed as Links with the `uri` class. (The same is true for bare links, if the `autolink_bare_uris` extension is enabled.) Email autolinks are parsed as Links with the `email` class. This allows the distinction to be represented in the URI. Formerly the `uri` class was added to autolinks by the HTML writer, but it had to guess what was an autolink and could not distinguish `[http://example.com](http://example.com)` from ``. It also incorrectly recognized `[pandoc](pandoc)` as an autolink. Now the HTML writer simply passes through the `uri` attribute if it is present, but does not add anything. The Textile writer has been modified so that the `uri` class is not explicitly added for autolinks, even if it is present. Closes #4913. --- src/Text/Pandoc/Readers/Markdown.hs | 12 +++++----- src/Text/Pandoc/Writers/HTML.hs | 7 ++---- src/Text/Pandoc/Writers/Textile.hs | 6 ++--- test/Tests/Readers/Markdown.hs | 8 ++++--- test/command/3716.md | 2 +- test/command/4913.md | 34 +++++++++++++++++++++++++++++ test/markdown-reader-more.native | 8 +++---- test/testsuite.native | 8 +++---- test/writer.docbook4 | 6 ++--- test/writer.docbook5 | 6 ++--- test/writer.html4 | 2 +- test/writer.html5 | 2 +- test/writer.native | 8 +++---- test/writer.textile | 2 +- 14 files changed, 73 insertions(+), 38 deletions(-) create mode 100644 test/command/4913.md diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 5f6788887..d1ea7a1a5 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1,6 +1,7 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RelaxedPolyRec #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TupleSections #-} {- Copyright (C) 2006-2018 John MacFarlane @@ -1879,23 +1880,24 @@ bareURL :: PandocMonad m => MarkdownParser m (F Inlines) bareURL = try $ do guardEnabled Ext_autolink_bare_uris getState >>= guard . stateAllowLinks - (orig, src) <- uri <|> emailAddress + (cls, (orig, src)) <- (("uri",) <$> uri) <|> (("email",) <$> emailAddress) notFollowedBy $ try $ spaces >> htmlTag (~== TagClose "a") - return $ return $ B.link src "" (B.str orig) + return $ return $ B.linkWith ("",[cls],[]) src "" (B.str orig) autoLink :: PandocMonad m => MarkdownParser m (F Inlines) autoLink = try $ do getState >>= guard . stateAllowLinks char '<' - (orig, src) <- uri <|> emailAddress + (cls, (orig, src)) <- (("uri",) <$> uri) <|> (("email",) <$> emailAddress) -- in rare cases, something may remain after the uri parser -- is finished, because the uri parser tries to avoid parsing -- final punctuation. for example: in ``, -- the URI parser will stop before the dashes. extra <- fromEntities <$> manyTill nonspaceChar (char '>') - attr <- option nullAttr $ try $ + attr <- option ("", [cls], []) $ try $ guardEnabled Ext_link_attributes >> attributes - return $ return $ B.linkWith attr (src ++ escapeURI extra) "" (B.str $ orig ++ extra) + return $ return $ B.linkWith attr (src ++ escapeURI extra) "" + (B.str $ orig ++ extra) image :: PandocMonad m => MarkdownParser m (F Inlines) image = try $ do diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index a0b622c83..851b48956 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -56,7 +56,7 @@ import Data.String (fromString) import Data.Text (Text) import qualified Data.Text.Lazy as TL import Network.HTTP (urlEncode) -import Network.URI (URI (..), parseURIReference, unEscapeString) +import Network.URI (URI (..), parseURIReference) import Numeric (showHex) import Text.Blaze.Internal (customLeaf, customParent, MarkupM(Empty)) #if MIN_VERSION_blaze_markup(0,6,3) @@ -1084,10 +1084,7 @@ inlineToHtml opts inline = do in '#' : prefix ++ xs _ -> s let link = H.a ! A.href (toValue s') $ linkText - let attr = if txt == [Str (unEscapeString s)] - then (ident, "uri" : classes, kvs) - else (ident, classes, kvs) - link' <- addAttrs opts attr link + link' <- addAttrs opts (ident, classes, kvs) link return $ if null tit then link' else link' ! A.title (toValue tit) diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index d1724f438..c7d96454a 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -463,15 +463,15 @@ inlineToTextile _ SoftBreak = return " " inlineToTextile _ Space = return " " inlineToTextile opts (Link (_, cls, _) txt (src, _)) = do - let classes = if null cls - then "" - else "(" ++ unwords cls ++ ")" label <- case txt of [Code _ s] | s == src -> return "$" [Str s] | s == src -> return "$" _ -> inlineListToTextile opts txt + let classes = if null cls || cls == ["uri"] && label == "$" + then "" + else "(" ++ unwords cls ++ ")" return $ "\"" ++ classes ++ label ++ "\":" ++ src inlineToTextile opts (Image attr@(_, cls, _) alt (source, tit)) = do diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index bc8e55615..be89e708e 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -39,7 +39,7 @@ testBareLink (inp, ils) = (unpack inp) (inp, doc $ para ils) autolink :: String -> Inlines -autolink = autolinkWith nullAttr +autolink = autolinkWith ("",["uri"],[]) autolinkWith :: Attr -> String -> Inlines autolinkWith attr s = linkWith attr s "" (str s) @@ -72,10 +72,12 @@ bareLinkTests = , ("http://en.wikipedia.org/wiki/Sprite_(computer_graphics)", autolink "http://en.wikipedia.org/wiki/Sprite_(computer_graphics)") , ("http://en.wikipedia.org/wiki/Sprite_[computer_graphics]", - link "http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" "" + linkWith ("",["uri"],[]) + "http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" "" (str "http://en.wikipedia.org/wiki/Sprite_[computer_graphics]")) , ("http://en.wikipedia.org/wiki/Sprite_{computer_graphics}", - link "http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" "" + linkWith ("",["uri"],[]) + "http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" "" (str "http://en.wikipedia.org/wiki/Sprite_{computer_graphics}")) , ("http://example.com/Notification_Center-GitHub-20101108-140050.jpg", autolink "http://example.com/Notification_Center-GitHub-20101108-140050.jpg") diff --git a/test/command/3716.md b/test/command/3716.md index 7e00819da..81e4a9568 100644 --- a/test/command/3716.md +++ b/test/command/3716.md @@ -2,5 +2,5 @@ % pandoc {.foo} ^D -

http://example.com

+

http://example.com

``` diff --git a/test/command/4913.md b/test/command/4913.md new file mode 100644 index 000000000..6492b80ce --- /dev/null +++ b/test/command/4913.md @@ -0,0 +1,34 @@ +``` +% pandoc -f markdown -t html +[https://pandoc.org](https://pandoc.org) +^D +

https://pandoc.org

+``` + +``` +% pandoc -f markdown -t markdown +[https://pandoc.org](https://pandoc.org) +^D + +``` + +``` +% pandoc -f markdown -t html + +^D +

https://pandoc.org

+``` + +``` +% pandoc -f markdown -t html +{.foo} +^D +

https://pandoc.org

+``` + +``` +% pandoc -f markdown -t html + +^D +

+``` diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native index 799f4ffa7..9c128ab94 100644 --- a/test/markdown-reader-more.native +++ b/test/markdown-reader-more.native @@ -45,9 +45,9 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S ,Para [Str "`hi"] ,Para [Str "there`"] ,Header 2 ("multilingual-urls",[],[]) [Str "Multilingual",Space,Str "URLs"] -,Para [Link ("",[],[]) [Str "http://\27979.com?\27979=\27979"] ("http://\27979.com?\27979=\27979","")] +,Para [Link ("",["uri"],[]) [Str "http://\27979.com?\27979=\27979"] ("http://\27979.com?\27979=\27979","")] ,Para [Link ("",[],[]) [Str "foo"] ("/bar/\27979?x=\27979","title")] -,Para [Link ("",[],[]) [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")] +,Para [Link ("",["email"],[]) [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")] ,Header 2 ("numbered-examples",[],[]) [Str "Numbered",Space,Str "examples"] ,OrderedList (1,Example,TwoParens) [[Plain [Str "First",Space,Str "example."]] @@ -176,8 +176,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S ,[]]] ,Header 2 ("entities-in-links-and-titles",[],[]) [Str "Entities",Space,Str "in",Space,Str "links",Space,Str "and",Space,Str "titles"] ,Para [Link ("",[],[]) [Str "link"] ("/\252rl","\246\246!")] -,Para [Link ("",[],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")] -,Para [Link ("",[],[]) [Str "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")] +,Para [Link ("",["uri"],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")] +,Para [Link ("",["email"],[]) [Str "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")] ,Para [Link ("",[],[]) [Str "foobar"] ("/\252rl","\246\246!")] ,Header 2 ("parentheses-in-urls",[],[]) [Str "Parentheses",Space,Str "in",Space,Str "URLs"] ,Para [Link ("",[],[]) [Str "link"] ("/hi(there)","")] diff --git a/test/testsuite.native b/test/testsuite.native index fcd189eb0..73fcc0633 100644 --- a/test/testsuite.native +++ b/test/testsuite.native @@ -384,14 +384,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"] -,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] +,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",["uri"],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,BulletList [[Plain [Str "In",Space,Str "a",Space,Str "list?"]] - ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]] + ,[Plain [Link ("",["uri"],[]) [Str "http://example.com/"] ("http://example.com/","")]] ,[Plain [Str "It",Space,Str "should."]]] -,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] +,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",["email"],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,BlockQuote - [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]] + [Para [Str "Blockquoted:",Space,Link ("",["uri"],[]) [Str "http://example.com/"] ("http://example.com/","")]] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,HorizontalRule diff --git a/test/writer.docbook4 b/test/writer.docbook4 index 163255974..38b3cc1ee 100644 --- a/test/writer.docbook4 +++ b/test/writer.docbook4 @@ -1298,7 +1298,7 @@ These should not be escaped: \$ \\ \> \[ \{ Autolinks With an ampersand: - http://example.com/?foo=1&bar=2 + http://example.com/?foo=1&bar=2 @@ -1308,7 +1308,7 @@ These should not be escaped: \$ \\ \> \[ \{ - http://example.com/ + http://example.com/ @@ -1323,7 +1323,7 @@ These should not be escaped: \$ \\ \> \[ \{
Blockquoted: - http://example.com/ + http://example.com/
diff --git a/test/writer.docbook5 b/test/writer.docbook5 index 992cd8b63..9a9eff0c5 100644 --- a/test/writer.docbook5 +++ b/test/writer.docbook5 @@ -1273,7 +1273,7 @@ These should not be escaped: \$ \\ \> \[ \{ Autolinks With an ampersand: - http://example.com/?foo=1&bar=2 + http://example.com/?foo=1&bar=2 @@ -1283,7 +1283,7 @@ These should not be escaped: \$ \\ \> \[ \{ - http://example.com/ + http://example.com/ @@ -1298,7 +1298,7 @@ These should not be escaped: \$ \\ \> \[ \{
Blockquoted: - http://example.com/ + http://example.com/
diff --git a/test/writer.html4 b/test/writer.html4 index dc889f07a..bed6617a0 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -508,7 +508,7 @@ Blah
  • http://example.com/
  • It should.
  • -

    An e-mail address: nobody@nowhere.net

    +

    An e-mail address:

    Blockquoted: http://example.com/

    diff --git a/test/writer.html5 b/test/writer.html5 index 4f80231db..46105d0a6 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -511,7 +511,7 @@ Blah
  • http://example.com/
  • It should.
  • -

    An e-mail address: nobody@nowhere.net

    +

    An e-mail address:

    Blockquoted: http://example.com/

    diff --git a/test/writer.native b/test/writer.native index fcd189eb0..73fcc0633 100644 --- a/test/writer.native +++ b/test/writer.native @@ -384,14 +384,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"] -,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] +,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",["uri"],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,BulletList [[Plain [Str "In",Space,Str "a",Space,Str "list?"]] - ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]] + ,[Plain [Link ("",["uri"],[]) [Str "http://example.com/"] ("http://example.com/","")]] ,[Plain [Str "It",Space,Str "should."]]] -,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] +,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",["email"],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,BlockQuote - [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]] + [Para [Str "Blockquoted:",Space,Link ("",["uri"],[]) [Str "http://example.com/"] ("http://example.com/","")]] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,HorizontalRule diff --git a/test/writer.textile b/test/writer.textile index d19b698f9..78e659091 100644 --- a/test/writer.textile +++ b/test/writer.textile @@ -660,7 +660,7 @@ With an ampersand: "$":http://example.com/?foo=1&bar=2 * "$":http://example.com/ * It should. -An e-mail address: "nobody@nowhere.net":mailto:nobody@nowhere.net +An e-mail address: "(email)nobody@nowhere.net":mailto:nobody@nowhere.net bq. Blockquoted: "$":http://example.com/