aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-08-15 10:25:12 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-08-15 10:25:12 -0700
commit13dea94a9128a4caf3fb820bb21cd8176465c82e (patch)
tree96ec7405b1498d108cfcb04886b5d2e1c8ca148c /src
parent2ae82727546c1a989148b0ca34ae35fd2158cee6 (diff)
downloadpandoc-13dea94a9128a4caf3fb820bb21cd8176465c82e.tar.gz
Markdown reader: Use "tex" instead of "latex" for raw tex-ish content.
We can't always tell if it's LaTeX, ConTeXt, or plain TeX. Better just to use "tex" always. Also changed: ConTeXt writer: now outputs raw "tex" blocks as well as "context". (Closes #969). RST writer: uses ".. raw:: latex" for "tex" content. (RST doesn't support raw context anyway.) Note that if "context" or "latex" specifically is desired, you can still force that in a markdown document by using the raw attribute (see MANUAL.txt): ```{=latex} \foo ``` Note that this change may affect some filters, if they assume that raw tex parsed by the Markdown reader will be RawBlock (Format "latex"). In most cases it should be trivial to modify the filters to accept "tex" as well.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs10
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs15
-rw-r--r--src/Text/Pandoc/Writers/RST.hs1
3 files changed, 10 insertions, 16 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index c4e8a6524..a81942a9e 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1143,10 +1143,9 @@ rawTeXBlock :: PandocMonad m => MarkdownParser m (F Blocks)
rawTeXBlock = do
guardEnabled Ext_raw_tex
lookAhead $ try $ char '\\' >> letter
- result <- (B.rawBlock "context" . trim . concat <$>
- many1 ((++) <$> (rawConTeXtEnvironment <|> conTeXtCommand)
- <*> spnl'))
- <|> (B.rawBlock "latex" . trim . concat <$>
+ result <- (B.rawBlock "tex" . trim . concat <$>
+ many1 ((++) <$> rawConTeXtEnvironment <*> spnl'))
+ <|> (B.rawBlock "tex" . trim . concat <$>
many1 ((++) <$> rawLaTeXBlock <*> spnl'))
return $ case B.toList result of
[RawBlock _ cs]
@@ -1154,9 +1153,6 @@ rawTeXBlock = do
-- don't create a raw block for suppressed macro defs
_ -> return result
-conTeXtCommand :: PandocMonad m => MarkdownParser m String
-conTeXtCommand = oneOfStrings ["\\placeformula"]
-
rawHtmlBlocks :: PandocMonad m => MarkdownParser m (F Blocks)
rawHtmlBlocks = do
(TagOpen tagtype _, raw) <- htmlTag isBlockTag
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 10e996bdb..594812294 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -190,10 +190,9 @@ blockToConTeXt (BlockQuote lst) = do
blockToConTeXt (CodeBlock _ str) =
return $ flush ("\\starttyping" <> cr <> text str <> cr <> "\\stoptyping") $$ blankline
-- blankline because \stoptyping can't have anything after it, inc. '}'
-blockToConTeXt (RawBlock "context" str) = return $ text str <> blankline
-blockToConTeXt b@(RawBlock _ _ ) = do
- report $ BlockNotRendered b
- return empty
+blockToConTeXt b@(RawBlock f str)
+ | f == Format "context" || f == Format "tex" = return $ text str <> blankline
+ | otherwise = empty <$ report (BlockNotRendered b)
blockToConTeXt (Div (ident,_,kvs) bs) = do
let align dir txt = "\\startalignment[" <> dir <> "]" $$ txt $$ "\\stopalignment"
mblang <- fromBCP47 (lookup "lang" kvs)
@@ -401,11 +400,9 @@ inlineToConTeXt (Math InlineMath str) =
return $ char '$' <> text str <> char '$'
inlineToConTeXt (Math DisplayMath str) =
return $ text "\\startformula " <> text str <> text " \\stopformula" <> space
-inlineToConTeXt (RawInline "context" str) = return $ text str
-inlineToConTeXt (RawInline "tex" str) = return $ text str
-inlineToConTeXt il@(RawInline _ _) = do
- report $ InlineNotRendered il
- return empty
+inlineToConTeXt il@(RawInline f str)
+ | f == Format "tex" || f == Format "context" = return $ text str
+ | otherwise = empty <$ report (InlineNotRendered il)
inlineToConTeXt LineBreak = return $ text "\\crlf" <> cr
inlineToConTeXt SoftBreak = do
wrapText <- gets (writerWrapText . stOptions)
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 005db5e77..b416eca59 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -253,6 +253,7 @@ blockToRST (LineBlock lns) =
linesToLineBlock lns
blockToRST (RawBlock f@(Format f') str)
| f == "rst" = return $ text str
+ | f == "tex" = blockToRST (RawBlock (Format "latex") str)
| otherwise = return $ blankline <> ".. raw:: " <>
text (map toLower f') $+$
nest 3 (text str) $$ blankline