From 8673eb079bc389f340bafd4c191c642afc7e1603 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Tue, 8 Jan 2019 11:36:33 -0800
Subject: [PATCH] Removed superfluous sourceCode class on code blocks.

* These were added by the RST reader and, for literate Haskell,
  by the Markdown and LaTeX readers.  There is no point to
  this class, and it is not applied consistently by all readers.
  See #5047.

* Reverse order of `literate` and `haskell` classes on code blocks
  when parsing literate Haskell. Better if `haskell` comes first.
---
 src/Text/Pandoc/Readers/LaTeX.hs    |  3 +--
 src/Text/Pandoc/Readers/Markdown.hs |  4 ++--
 src/Text/Pandoc/Readers/RST.hs      | 11 ++++-------
 test/Tests/Readers/Markdown.hs      |  4 ++--
 test/Tests/Readers/RST.hs           | 12 ++++++------
 test/command/4811.md                |  2 +-
 test/lhs-test-markdown.native       |  2 +-
 test/lhs-test.html                  |  2 +-
 test/lhs-test.html+lhs              |  2 +-
 test/lhs-test.markdown              |  2 +-
 test/lhs-test.native                |  2 +-
 test/rst-reader.native              |  8 ++++----
 12 files changed, 25 insertions(+), 29 deletions(-)

diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 147527d2b..f0669164c 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1823,8 +1823,7 @@ environments = M.fromList
    , ("enumerate", orderedList')
    , ("alltt", alltt <$> env "alltt" blocks)
    , ("code", guardEnabled Ext_literate_haskell *>
-       (codeBlockWith ("",["sourceCode","literate","haskell"],[]) <$>
-         verbEnv "code"))
+       (codeBlockWith ("",["haskell","literate"],[]) <$> verbEnv "code"))
    , ("comment", mempty <$ verbEnv "comment")
    , ("verbatim", codeBlock <$> verbEnv "verbatim")
    , ("Verbatim", fancyverbEnv "Verbatim")
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index dd1bedc91..b463898a0 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -748,9 +748,9 @@ codeBlockIndented = do
 lhsCodeBlock :: PandocMonad m => MarkdownParser m (F Blocks)
 lhsCodeBlock = do
   guardEnabled Ext_literate_haskell
-  (return . B.codeBlockWith ("",["sourceCode","literate","haskell"],[]) <$>
+  (return . B.codeBlockWith ("",["haskell","literate"],[]) <$>
           (lhsCodeBlockBird <|> lhsCodeBlockLaTeX))
-    <|> (return . B.codeBlockWith ("",["sourceCode","haskell"],[]) <$>
+    <|> (return . B.codeBlockWith ("",["haskell"],[]) <$>
           lhsCodeBlockInverseBird)
 
 lhsCodeBlockLaTeX :: PandocMonad m => MarkdownParser m String
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 4e16554be..ee2c2e904 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -39,7 +39,7 @@ import Control.Monad.Except (throwError)
 import Control.Monad.Identity (Identity (..))
 import Data.Char (isHexDigit, isSpace, toLower, toUpper, isAlphaNum)
 import Data.List (deleteFirstsBy, elemIndex, intercalate, isInfixOf, isSuffixOf,
-                  nub, sort, transpose, union)
+                  nub, sort, transpose)
 import qualified Data.Map as M
 import Data.Maybe (fromMaybe, isJust)
 import Data.Sequence (ViewR (..), viewr)
@@ -421,7 +421,7 @@ lhsCodeBlock = try $ do
   optional codeBlockStart
   lns <- latexCodeBlock <|> birdCodeBlock
   blanklines
-  return $ B.codeBlockWith ("", ["sourceCode", "literate", "haskell"], [])
+  return $ B.codeBlockWith ("", ["haskell","literate"], [])
          $ intercalate "\n" lns
 
 latexCodeBlock :: Monad m => ParserT [Char] st m [[Char]]
@@ -995,7 +995,7 @@ codeblock :: String -> [String] -> Maybe String -> String -> String
 codeblock ident classes numberLines lang body =
   return $ B.codeBlockWith attribs $ stripTrailingNewlines body
     where attribs = (ident, classes', kvs)
-          classes' = "sourceCode" : lang
+          classes' = lang
                     : maybe [] (const ["numberLines"]) numberLines
                     ++ classes
           kvs     = case numberLines of
@@ -1414,7 +1414,7 @@ renderRole contents fmt role attr = case role of
     "title-reference" -> titleRef contents
     "title" -> titleRef contents
     "t" -> titleRef contents
-    "code" -> return $ B.codeWith (addClass "sourceCode" attr) contents
+    "code" -> return $ B.codeWith attr contents
     "span" -> return $ B.spanWith attr $ treatAsText contents
     "raw" -> return $ B.rawInline (fromMaybe "" fmt) contents
     custom -> do
@@ -1438,9 +1438,6 @@ renderRole contents fmt role attr = case role of
    handleEscapes ('\\':c:cs) = c : handleEscapes cs
    handleEscapes (c:cs) = c : handleEscapes cs
 
-addClass :: String -> Attr -> Attr
-addClass c (ident, classes, keyValues) = (ident, classes `union` [c], keyValues)
-
 roleName :: PandocMonad m => RSTParser m String
 roleName = many1 (letter <|> char '-')
 
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index be89e708e..75401fb91 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -319,9 +319,9 @@ tests = [ testGroup "inline code"
                        Ext_literate_haskell pandocExtensions })
               "inverse bird tracks and html" $
               "> a\n\n< b\n\n<div>\n"
-              =?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a"
+              =?> codeBlockWith ("",["haskell","literate"],[]) "a"
                   <>
-                  codeBlockWith ("",["sourceCode","haskell"],[]) "b"
+                  codeBlockWith ("",["haskell"],[]) "b"
                   <>
                   rawBlock "html" "<div>\n\n"
           ]
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index 963e7530d..d69440843 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -106,7 +106,7 @@ tests = [ "line block with blank line" =:
             ]  =?>
               doc (codeBlockWith
                   ( ""
-                  , ["sourceCode", "python", "numberLines", "class1", "class2", "class3"]
+                  , ["python", "numberLines", "class1", "class2", "class3"]
                   , [ ("startFrom", "34") ]
                   )
                   "def func(x):\n  return y")
@@ -119,7 +119,7 @@ tests = [ "line block with blank line" =:
             ]  =?>
               doc (codeBlockWith
                   ( ""
-                  , ["sourceCode", "python", "numberLines"]
+                  , ["python", "numberLines"]
                   , [ ("startFrom", "") ]
                   )
                   "def func(x):\n  return y")
@@ -164,18 +164,18 @@ tests = [ "line block with blank line" =:
           [ "literal role prefix" =: ":literal:`a`" =?> para (code "a")
           , "literal role postfix" =: "`a`:literal:" =?> para (code "a")
           , "literal text" =: "``text``" =?> para (code "text")
-          , "code role" =: ":code:`a`" =?> para (codeWith ("", ["sourceCode"], []) "a")
+          , "code role" =: ":code:`a`" =?> para (codeWith ("", [], []) "a")
           , "inherited code role" =: ".. role:: codeLike(code)\n\n:codeLike:`a`"
-            =?> para (codeWith ("", ["codeLike", "sourceCode"], []) "a")
+            =?> para (codeWith ("", ["codeLike"], []) "a")
           , "custom code role with language field"
             =: ".. role:: lhs(code)\n    :language: haskell\n\n:lhs:`a`"
-            =?> para (codeWith ("", ["lhs", "haskell","sourceCode"], []) "a")
+            =?> para (codeWith ("", ["lhs", "haskell"], []) "a")
           , "custom role with unspecified parent role"
             =: ".. role:: classy\n\n:classy:`text`"
             =?> para (spanWith ("", ["classy"], []) "text")
           , "role with recursive inheritance"
             =: ".. role:: haskell(code)\n.. role:: lhs(haskell)\n\n:lhs:`text`"
-            =?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text")
+            =?> para (codeWith ("", ["lhs", "haskell"], []) "text")
           , "unknown role" =: ":unknown:`text`" =?>
               para (codeWith ("",["interpreted-text"],[("role","unknown")]) "text")
           ]
diff --git a/test/command/4811.md b/test/command/4811.md
index 9c8bea7ce..81a60d78d 100644
--- a/test/command/4811.md
+++ b/test/command/4811.md
@@ -19,7 +19,7 @@ Backslash escape behaves properly in interpreted roles:
 `hi\ there`:code:
 ^D
 [Para [Superscript [Str "hithere"]]
-,Para [Code ("",["sourceCode"],[]) "hi\\ there"]]
+,Para [Code ("",[],[]) "hi\\ there"]]
 ```
 
 Backtick followed by alphanumeric doesn't end the span:
diff --git a/test/lhs-test-markdown.native b/test/lhs-test-markdown.native
index b6d908339..7a423b1ab 100644
--- a/test/lhs-test-markdown.native
+++ b/test/lhs-test-markdown.native
@@ -1,6 +1,6 @@
 [Header 1 ("lhs-test",[],[]) [Str "lhs",Space,Str "test"]
 ,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",SoftBreak,Str "return",Space,Str "a",Space,Str "single",Space,Str "value:"]
-,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n          -- arr (\\op (x,y) -> x `op` y)"
+,CodeBlock ("",["haskell","literate"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n          -- arr (\\op (x,y) -> x `op` y)"
 ,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",SoftBreak,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",SoftBreak,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)."]
 ,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
 ,Para [Str "Block",Space,Str "quote:"]
diff --git a/test/lhs-test.html b/test/lhs-test.html
index efe9d8e29..03dd347ff 100644
--- a/test/lhs-test.html
+++ b/test/lhs-test.html
@@ -82,7 +82,7 @@ code span.wa { color: #60a0b0; font-weight: bold; font-style: italic; } /* Warni
 <h1 id="lhs-test">lhs test</h1>
 <p><code>unsplit</code> is an arrow that takes a pair of values and combines them to
 return a single value:</p>
-<div class="sourceCode" id="cb1"><pre class="sourceCode literate haskell"><code class="sourceCode haskell"><a class="sourceLine" id="cb1-1" title="1"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d</a>
+<div class="sourceCode" id="cb1"><pre class="sourceCode haskell literate"><code class="sourceCode haskell"><a class="sourceLine" id="cb1-1" title="1"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d</a>
 <a class="sourceLine" id="cb1-2" title="2">unsplit <span class="fu">=</span> arr <span class="fu">.</span> <span class="fu">uncurry</span></a>
 <a class="sourceLine" id="cb1-3" title="3">          <span class="co">-- arr (\op (x,y) -&gt; x `op` y)</span></a></code></pre></div>
 <p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a
diff --git a/test/lhs-test.html+lhs b/test/lhs-test.html+lhs
index 88f7b8834..ee0d8a299 100644
--- a/test/lhs-test.html+lhs
+++ b/test/lhs-test.html+lhs
@@ -82,7 +82,7 @@ code span.wa { color: #60a0b0; font-weight: bold; font-style: italic; } /* Warni
 <h1 id="lhs-test">lhs test</h1>
 <p><code>unsplit</code> is an arrow that takes a pair of values and combines them to
 return a single value:</p>
-<div class="sourceCode" id="cb1"><pre class="sourceCode literate literatehaskell"><code class="sourceCode literatehaskell"><a class="sourceLine" id="cb1-1" title="1"><span class="ot">&gt; unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d</a>
+<div class="sourceCode" id="cb1"><pre class="sourceCode literatehaskell literate"><code class="sourceCode literatehaskell"><a class="sourceLine" id="cb1-1" title="1"><span class="ot">&gt; unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=&gt;</span> (b <span class="ot">-&gt;</span> c <span class="ot">-&gt;</span> d) <span class="ot">-&gt;</span> a (b, c) d</a>
 <a class="sourceLine" id="cb1-2" title="2"><span class="ot">&gt;</span> unsplit <span class="fu">=</span> arr <span class="fu">.</span> <span class="fu">uncurry</span></a>
 <a class="sourceLine" id="cb1-3" title="3"><span class="ot">&gt;</span>           <span class="co">-- arr (\op (x,y) -&gt; x `op` y)</span></a></code></pre></div>
 <p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a
diff --git a/test/lhs-test.markdown b/test/lhs-test.markdown
index 20949b75c..0ddf24a98 100644
--- a/test/lhs-test.markdown
+++ b/test/lhs-test.markdown
@@ -4,7 +4,7 @@ lhs test
 `unsplit` is an arrow that takes a pair of values and combines them to
 return a single value:
 
-``` {.sourceCode .literate .haskell}
+``` {.haskell .literate}
 unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
 unsplit = arr . uncurry
           -- arr (\op (x,y) -> x `op` y)
diff --git a/test/lhs-test.native b/test/lhs-test.native
index b6d908339..7a423b1ab 100644
--- a/test/lhs-test.native
+++ b/test/lhs-test.native
@@ -1,6 +1,6 @@
 [Header 1 ("lhs-test",[],[]) [Str "lhs",Space,Str "test"]
 ,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",SoftBreak,Str "return",Space,Str "a",Space,Str "single",Space,Str "value:"]
-,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n          -- arr (\\op (x,y) -> x `op` y)"
+,CodeBlock ("",["haskell","literate"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n          -- arr (\\op (x,y) -> x `op` y)"
 ,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",SoftBreak,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",SoftBreak,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)."]
 ,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
 ,Para [Str "Block",Space,Str "quote:"]
diff --git a/test/rst-reader.native b/test/rst-reader.native
index 89dde7396..cd1437ac8 100644
--- a/test/rst-reader.native
+++ b/test/rst-reader.native
@@ -38,7 +38,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
 ,Para [Str "And:"]
 ,CodeBlock ("",[],[]) "this block is indented by two tabs\n\nThese should not be escaped:  \\$ \\\\ \\> \\[ \\{"
 ,Para [Str "And:"]
-,CodeBlock ("",["sourceCode","python"],[]) "def my_function(x):\n    return x + 1"
+,CodeBlock ("",["python"],[]) "def my_function(x):\n    return x + 1"
 ,Header 1 ("lists",[],[]) [Str "Lists"]
 ,Header 2 ("unordered",[],[]) [Str "Unordered"]
 ,Para [Str "Asterisks",Space,Str "tight:"]
@@ -328,8 +328,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
 ,Para [Str "Reset",Space,Str "default-role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default."]
 ,Para [Str "And",Space,Str "now",Space,Span ("",["title-ref"],[]) [Str "some-invalid-string-3231231"],Space,Str "is",Space,Str "nonsense."]
 ,Para [Str "And",Space,Str "now",Space,Str "with",Space,RawInline (Format "html") "<b>inline</b> <span id=\"test\">HTML</span>",Str "."]
-,Para [Str "And",Space,Str "some",Space,Str "inline",Space,Str "haskell",Space,Code ("",["haskell","sourceCode"],[]) "fmap id [1,2..10]",Str "."]
-,Para [Str "Indirect",Space,Str "python",Space,Str "role",Space,Code ("",["py","python","indirect","sourceCode"],[]) "[x*x for x in [1,2,3,4,5]]",Str "."]
-,Para [Str "Different",Space,Str "indirect",Space,Str "C",Space,Code ("",["c","different-indirect","sourceCode"],[]) "int x = 15;",Str "."]
+,Para [Str "And",Space,Str "some",Space,Str "inline",Space,Str "haskell",Space,Code ("",["haskell"],[]) "fmap id [1,2..10]",Str "."]
+,Para [Str "Indirect",Space,Str "python",Space,Str "role",Space,Code ("",["py","python","indirect"],[]) "[x*x for x in [1,2,3,4,5]]",Str "."]
+,Para [Str "Different",Space,Str "indirect",Space,Str "C",Space,Code ("",["c","different-indirect"],[]) "int x = 15;",Str "."]
 ,Header 2 ("literal-symbols",[],[]) [Str "Literal",Space,Str "symbols"]
 ,Para [Str "2*2",Space,Str "=",Space,Str "4*1"]]