diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-01-08 11:36:33 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-01-08 11:36:33 -0800 |
commit | 8673eb079bc389f340bafd4c191c642afc7e1603 (patch) | |
tree | a1111e65028c23488ff5d4652a60bdb27feb4153 /src/Text/Pandoc/Readers | |
parent | 230e07ddfce31ba89a12e39ecf995577d0bb67a8 (diff) | |
download | pandoc-8673eb079bc389f340bafd4c191c642afc7e1603.tar.gz |
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.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 11 |
3 files changed, 7 insertions, 11 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 '-') |