diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 3d4c5da455d1..a0fd682df78c 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1859,6 +1859,7 @@ wikilink :: PandocMonad m => (Attr -> Text -> Text -> Inlines -> Inlines) -> MarkdownParser m (F Inlines) wikilink constructor = do + let attr = (mempty, ["wikilink"], mempty) titleAfter <- (True <$ guardEnabled Ext_wikilinks_title_after_pipe) <|> (False <$ guardEnabled Ext_wikilinks_title_before_pipe) @@ -1871,7 +1872,7 @@ wikilink constructor = do | titleAfter -> (T.drop 1 after, before) | otherwise -> (before, T.drop 1 after) guard $ T.all (`notElem` ['\n','\r','\f','\t']) url - return . pure . constructor nullAttr url "wikilink" $ + return . pure . constructor attr url "" $ B.text $ fromEntities title link :: PandocMonad m => MarkdownParser m (F Inlines) diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index e7d6ea4cbf8d..628aaa5dca02 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -667,7 +667,7 @@ internalLink = try $ do sym "]]" -- see #8525: linktrail <- B.text <$> manyChar (satisfy (\c -> isLetter c && not (isCJK c))) - let link = B.link (addUnderscores pagename) "wikilink" (label <> linktrail) + let link = B.linkWith (mempty, ["wikilink"], mempty) (addUnderscores pagename) (stringify label) (label <> linktrail) if "Category:" `T.isPrefixOf` pagename then do updateState $ \st -> st{ mwCategoryLinks = link : mwCategoryLinks st } @@ -699,7 +699,7 @@ inlinesBetween start end = emph :: PandocMonad m => MWParser m Inlines emph = B.emph <$> inlinesBetween start end where start = sym "''" - end = try $ notFollowedBy' (() <$ strong) >> sym "''" + end = try $ notFollowedBy' (() <$ strong) >> ((sym "''") <|> void newline) strong :: PandocMonad m => MWParser m Inlines strong = B.strong <$> inlinesBetween start end diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs index e8be03c2893d..818f5b601b4d 100644 --- a/src/Text/Pandoc/Readers/Vimwiki.hs +++ b/src/Text/Pandoc/Readers/Vimwiki.hs @@ -56,15 +56,7 @@ import Data.Text (Text) import qualified Data.Text as T import Safe (lastMay) import Text.Pandoc.Builder (Blocks, Inlines, fromList, toList, trimInlines) -import qualified Text.Pandoc.Builder as B (blockQuote, bulletList, code, - codeBlockWith, definitionList, - displayMath, divWith, emph, - headerWith, horizontalRule, image, - imageWith, link, math, orderedList, - para, plain, setMeta, simpleTable, - softbreak, space, spanWith, str, - strikeout, strong, subscript, - superscript) +import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class.PandocMonad (PandocMonad (..)) import Text.Pandoc.Definition (Attr, Block (BulletList, OrderedList), Inline (Space), ListNumberDelim (..), @@ -555,17 +547,14 @@ link = try $ do then do url <- manyTillChar anyChar $ char '|' lab <- mconcat <$> manyTill inline (string "]]") - let tit = if isURI url - then "" - else "wikilink" - return $ B.link (procLink url) tit lab + return $ B.linkWith (attr url) (procLink url) "" lab else do manyTill anyChar (string "]]") -- not using try here because [[hell]o]] is not rendered as a link in vimwiki - let tit = if isURI contents - then "" - else "wikilink" - return $ B.link (procLink contents) tit (B.str contents) + return $ B.linkWith (attr contents) (procLink contents) "" (B.str contents) + where + attr t | isURI t = B.nullAttr + | otherwise = (mempty, ["wikilink"], mempty) image :: PandocMonad m => VwParser m Inlines image = try $ do diff --git a/src/Text/Pandoc/Writers/Markdown/Inline.hs b/src/Text/Pandoc/Writers/Markdown/Inline.hs index 948932fc5fca..da04e4b5efe6 100644 --- a/src/Text/Pandoc/Writers/Markdown/Inline.hs +++ b/src/Text/Pandoc/Writers/Markdown/Inline.hs @@ -649,7 +649,7 @@ inlineToMarkdown opts lnk@(Link attr@(ident,classes,kvs) txt (src, tit)) = do case txt of [Str s] | escapeURI s == srcSuffix -> True _ -> False - let useWikilink = tit == "wikilink" && + let useWikilink = "wikilink" `elem` classes && (isEnabled Ext_wikilinks_title_after_pipe opts || isEnabled Ext_wikilinks_title_before_pipe opts) let useRefLinks = writerReferenceLinks opts && not useAuto diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index 3a6ffd0d3068..aded6c663ef9 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -58,6 +58,9 @@ autolinkWith :: Attr -> String -> Inlines autolinkWith attr s = linkWith attr s' "" (str s') where s' = T.pack s +wikilink :: Attr +wikilink = (mempty, ["wikilink"], mempty) + bareLinkTests :: [(Text, Inlines)] bareLinkTests = [ ("http://google.com is a search engine.", @@ -312,22 +315,22 @@ tests = [ testGroup "inline code" , testGroup "Github wiki links" [ test markdownGH "autolink" $ "[[https://example.org]]" =?> - para (link "https://example.org" "wikilink" (str "https://example.org")) + para (linkWith wikilink "https://example.org" "" (str "https://example.org")) , test markdownGH "link with title" $ "[[title|https://example.org]]" =?> - para (link "https://example.org" "wikilink" (str "title")) + para (linkWith wikilink "https://example.org" "" (str "title")) , test markdownGH "bad link with title" $ "[[title|random string]]" =?> - para (link "random string" "wikilink" (str "title")) + para (linkWith wikilink "random string" "" (str "title")) , test markdownGH "autolink not being a link" $ "[[Name of page]]" =?> - para (link "Name of page" "wikilink" (text "Name of page")) + para (linkWith wikilink "Name of page" "" (text "Name of page")) , test markdownGH "autolink not being a link with a square bracket" $ "[[Name of ]page]]" =?> - para (link "Name of ]page" "wikilink" (text "Name of ]page")) + para (linkWith wikilink "Name of ]page" "" (text "Name of ]page")) , test markdownGH "link with inline start should be a link" $ "[[t`i*t_le|https://example.org]]" =?> - para (link "https://example.org" "wikilink" (str "t`i*t_le")) + para (linkWith wikilink "https://example.org" "" (str "t`i*t_le")) ] , testGroup "Headers" [ "blank line before header" =: diff --git a/test/command/2649.md b/test/command/2649.md index 8258b9c10bea..ae825d059aee 100644 --- a/test/command/2649.md +++ b/test/command/2649.md @@ -90,19 +90,20 @@
1
78
2
38
10
18
hi and
hi and