aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Extensions.hs3
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs25
-rw-r--r--test/Tests/Readers/Markdown.hs30
3 files changed, 0 insertions, 58 deletions
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 69257ecc8..39c2a0489 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -118,7 +118,6 @@ data Extension =
| Ext_literate_haskell -- ^ Enable literate Haskell conventions
| Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown iff
-- container has attribute 'markdown'
- | Ext_wikilinks -- ^ Interpret a markdown wiki link
| Ext_markdown_in_html_blocks -- ^ Interpret as markdown inside HTML blocks
| Ext_mmd_header_identifiers -- ^ Multimarkdown style header identifiers [myid]
| Ext_mmd_link_attributes -- ^ MMD style reference link attributes
@@ -259,7 +258,6 @@ githubMarkdownExtensions = extensionsFromList
, Ext_emoji
, Ext_fenced_code_blocks
, Ext_backtick_code_blocks
- , Ext_wikilinks
]
-- | Extensions to be used with multimarkdown.
@@ -446,7 +444,6 @@ getAllExtensions f = universalExtensions <> getAll f
, Ext_tex_math_single_backslash
, Ext_tex_math_double_backslash
, Ext_markdown_attribute
- , Ext_wikilinks
, Ext_mmd_title_block
, Ext_abbreviations
, Ext_autolink_bare_uris
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 8fd0b68e2..5c3a21bb7 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -21,7 +21,6 @@ module Text.Pandoc.Readers.Markdown (
import Control.Monad
import Control.Monad.Except (throwError)
import Data.Char (isAlphaNum, isPunctuation, isSpace)
-import Data.Functor (($>))
import Data.List (transpose, elemIndex, sortOn)
import qualified Data.Map as M
import Data.Maybe
@@ -1486,7 +1485,6 @@ inline = choice [ whitespace
, note
, cite
, bracketedSpan
- , githubWikiLink
, link
, image
, math
@@ -1782,29 +1780,6 @@ source = do
linkTitle :: PandocMonad m => MarkdownParser m Text
linkTitle = quotedTitle '"' <|> quotedTitle '\''
--- Github wiki style link, with optional title
--- syntax documented under https://help.github.com/en/github/building-a-strong-community/editing-wiki-content
-githubWikiLink :: PandocMonad m => MarkdownParser m (F Inlines)
-githubWikiLink = try $ guardEnabled Ext_wikilinks >> wikilink
- where
- wikilink = try $ do
- string "[["
- firstPart <- fmap mconcat . sequence <$> wikiText
- (char '|' *> complexWikilink firstPart)
- <|> (string "]]" $> (B.link
- <$> (stringify <$> firstPart)
- <*> return "wikilink"
- <*> firstPart))
-
- complexWikilink firstPart = do
- url <- fmap stringify . sequence <$> wikiText
- string "]]"
- return $ B.link <$> url
- <*> return "wikilink"
- <*> firstPart
-
- wikiText = many (whitespace <|> bareURL <|> str <|> endline <|> escapedChar)
-
link :: PandocMonad m => MarkdownParser m (F Inlines)
link = try $ do
st <- getState
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index a2abcb143..18f909583 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -307,36 +307,6 @@ tests = [ testGroup "inline code"
"[https://example.org(](url)" =?>
para (link "url" "" (text "https://example.org("))
]
- , testGroup "Github wiki links"
- [ test markdownGH "autolink" $
- "[[https://example.org]]" =?>
- para (link "https://example.org" "wikilink" (text "https://example.org"))
- , test markdownGH "link with title" $
- "[[title|https://example.org]]" =?>
- para (link "https://example.org" "wikilink" (text "title"))
- , test markdownGH "bad link with title" $
- "[[title|random string]]" =?>
- para (link "random-string" "wikilink" (text "title"))
- , test markdownGH "autolink not being a link" $
- "[[Name of page]]" =?>
- para (link "Name-of-page" "wikilink" (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"))
- , test markdownGH "formatting (strong and emphasis) should not be interpreted" $
- "[[***a**b **c**d*|https://example.org]]" =?>
- para (text "[[" <> emph (strong (str "a") <> str "b" <> space
- <> strong (str "c") <> str "d") <> text "|https://example.org]]")
- , test markdownGH "inlined code should not make a link" $
- "[[ti`|`le|https://example.org]]" =?>
- para (text "[[ti" <> code "|" <> text "le|https://example.org]]")
- , test markdownGH "link with title and a cut should take the middle part as link" $
- "[[tit|le|https://example.org]]" =?>
- para (link "le" "wikilink" (text "tit"))
- , test markdownGH "link with inline start should be a link" $
- "[[t`i*t_le|https://example.org]]" =?>
- para (link "https://example.org" "wikilink" (text "t`i*t_le"))
- ]
, testGroup "Headers"
[ "blank line before header" =:
"\n# Header\n"