Markdown writer: New approach for citations.
* Reverts 1.11 change that caused citations to be rendered as markdown citations, even if `--biblio` was specified, unless `citation` extension is disabled. Now, formatted citations are always printed if `--biblio` was specified. If you want to reformat markdown keeping pandoc markdown citations intact, just don't specify `--biblio`. * Reverted now unnecessary changes to Text.Pandoc.Biblio adding the raw block to mark the bibliography, and to Text.Pandoc.Writers.Markdown to remove the bibliography if `citations` not specified. * If the content of a `Cite` inline is a `RawInline "latex"`, which means that a LaTeX citation command was parsed and `--biblio` wasn't specified, then render it as a pandoc markdown citation. This means that `pandoc -f latex -t markdown`, without `--biblio`, will convert LaTeX citation commands to pandoc markdown citations.
This commit is contained in:
parent
8ca5198b8e
commit
835deee58b
3 changed files with 6 additions and 16 deletions
|
@ -54,7 +54,7 @@ processBiblio (Just style) r p =
|
|||
cits_map = M.fromList $ zip grps (citations result)
|
||||
biblioList = map (renderPandoc' style) (bibliography result)
|
||||
Pandoc m b = bottomUp mvPunct . deNote . bottomUp (processCite style cits_map) $ p'
|
||||
in Pandoc m $ b ++ (RawBlock "pandoc" "references" : biblioList)
|
||||
in Pandoc m $ b ++ biblioList
|
||||
|
||||
-- | Substitute 'Cite' elements with formatted citations.
|
||||
processCite :: Style -> M.Map [Citation] [FormattedOutput] -> Inline -> Inline
|
||||
|
|
|
@ -61,8 +61,7 @@ writeMarkdown opts document =
|
|||
evalState (pandocToMarkdown opts{
|
||||
writerWrapText = writerWrapText opts &&
|
||||
not (isEnabled Ext_hard_line_breaks opts) }
|
||||
document') def
|
||||
where document' = maybeRemoveBiblio opts document
|
||||
document) def
|
||||
|
||||
-- | Convert Pandoc to plain text (like markdown, but without links,
|
||||
-- pictures, or inline formatting).
|
||||
|
@ -72,16 +71,7 @@ writePlain opts document =
|
|||
writerExtensions = Set.delete Ext_escaped_line_breaks $
|
||||
writerExtensions opts }
|
||||
document') def{ stPlain = True }
|
||||
where document' = plainify $ maybeRemoveBiblio opts document
|
||||
|
||||
-- If we're rendering citations as pandoc markdown citations,
|
||||
-- then we don't want to include a bibliography.
|
||||
maybeRemoveBiblio :: WriterOptions -> Pandoc -> Pandoc
|
||||
maybeRemoveBiblio opts (Pandoc meta bs) = Pandoc meta bs'
|
||||
where bs' = if isEnabled Ext_citations opts
|
||||
then takeWhile
|
||||
(/= RawBlock "pandoc" "references") bs
|
||||
else bs
|
||||
where document' = plainify document
|
||||
|
||||
plainify :: Pandoc -> Pandoc
|
||||
plainify = bottomUp go
|
||||
|
@ -653,7 +643,7 @@ inlineToMarkdown opts (LineBreak)
|
|||
| isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr
|
||||
| otherwise = return $ " " <> cr
|
||||
inlineToMarkdown _ Space = return space
|
||||
inlineToMarkdown opts (Cite (c:cs) lst)
|
||||
inlineToMarkdown opts (Cite (c:cs) lst@[RawInline "latex" _])
|
||||
| not (isEnabled Ext_citations opts) = inlineListToMarkdown opts lst
|
||||
| citationMode c == AuthorInText = do
|
||||
suffs <- inlineListToMarkdown opts $ citationSuffix c
|
||||
|
@ -680,7 +670,7 @@ inlineToMarkdown opts (Cite (c:cs) lst)
|
|||
return $ pdoc <+> r
|
||||
modekey SuppressAuthor = "-"
|
||||
modekey _ = ""
|
||||
inlineToMarkdown _ (Cite _ _) = return $ text ""
|
||||
inlineToMarkdown opts (Cite _ lst) = inlineListToMarkdown opts lst
|
||||
inlineToMarkdown opts (Link txt (src, tit)) = do
|
||||
linktext <- inlineListToMarkdown opts txt
|
||||
let linktitle = if null tit
|
||||
|
|
|
@ -186,7 +186,7 @@ markdownCitationTests
|
|||
++ [test "natbib" wopts "markdown-citations.txt"
|
||||
"markdown-citations.txt"]
|
||||
where
|
||||
ropts = ["-r", "markdown", "-w", "markdown-citations", "--bibliography",
|
||||
ropts = ["-r", "markdown", "-w", "markdown", "--bibliography",
|
||||
"biblio.bib", "--no-wrap"]
|
||||
wopts = ["-r", "markdown", "-w", "markdown", "--no-wrap", "--natbib"]
|
||||
styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"])
|
||||
|
|
Loading…
Reference in a new issue