From c841bcf3b01548b2f9b462b39d8edda4c10be534 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Sat, 16 Jan 2021 16:22:04 -0800
Subject: Revert "Markdown reader: support GitHub wiki's internal links (#2923)
 (#6458)"

This reverts commit 6efd3460a776620fdb93812daa4f6831e6c332ce.

Since this extension is designed to be used with
GitHub markdown (gfm), we need to implement the parser
as a commonmark extension (commonmark-extensions),
rather than in pandoc's markdown reader.  When that is
done, we can add it here.
---
 src/Text/Pandoc/Extensions.hs       |  3 ---
 src/Text/Pandoc/Readers/Markdown.hs | 25 -------------------------
 2 files changed, 28 deletions(-)

(limited to 'src/Text/Pandoc')

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
-- 
cgit v1.2.3