aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorNathan Gass <gass@search.ch>2010-12-13 21:27:18 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2010-12-13 20:42:58 -0800
commitc81495a07afc61cf39af51e1517586d1131c203a (patch)
treed5f71ffda5fb4122932cf934da78ce972f25d7b0
parent48600fd5473d1a3c596c6ac8c29f1d7b17f1dc92 (diff)
downloadpandoc-c81495a07afc61cf39af51e1517586d1131c203a.tar.gz
Added option to write citation markup in markdown writer.
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs30
-rw-r--r--src/pandoc.hs2
2 files changed, 30 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 1b612006b..012889552 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -77,6 +77,7 @@ plainify = processWith go
go (HtmlInline _ : ys) = Str "" : go ys
go (Link xs _ : ys) = go xs ++ go ys
go (Image _ _ : ys) = go ys
+ go (Cite _ cits : ys) = go cits ++ go ys
go (x : ys) = x : go ys
go [] = []
@@ -400,7 +401,34 @@ inlineToMarkdown _ (TeX str) = return $ text str
inlineToMarkdown _ (HtmlInline str) = return $ text str
inlineToMarkdown _ (LineBreak) = return $ text " \n"
inlineToMarkdown _ Space = return $ char ' '
-inlineToMarkdown opts (Cite _ cits) = inlineListToMarkdown opts cits
+inlineToMarkdown opts (Cite (c:cs) lst)
+ | writerCiteMethod opts == Citeproc = inlineListToMarkdown opts lst
+ | citationMode c == AuthorInText = do
+ suffs <- inlineListToMarkdown opts $ citationSuffix c
+ rest <- mapM convertOne cs
+ let inbr = suffs <+> joincits rest
+ br = if isEmpty inbr then empty else brackets inbr
+ return $ text ("@" ++ citationId c) <+> br
+ | otherwise = do
+ cits <- mapM convertOne (c:cs)
+ return $ text "[" <> joincits cits <> text "]"
+ where
+ joincits = hcat . punctuate (text "; ") . filter (not . isEmpty)
+ convertOne Citation { citationId = k
+ , citationPrefix = pinlines
+ , citationSuffix = sinlines
+ , citationMode = m }
+ = do
+ pdoc <- inlineListToMarkdown opts pinlines
+ sdoc <- inlineListToMarkdown opts sinlines
+ let k' = text (modekey m ++ "@" ++ k)
+ r = case sinlines of
+ Str (y:_):_ | y `elem` ",;]@" -> k' <> sdoc
+ _ -> k' <+> sdoc
+ return $ pdoc <+> r
+ modekey SuppressAuthor = "-"
+ modekey _ = ""
+inlineToMarkdown _ (Cite _ _) = return $ text ""
inlineToMarkdown opts (Link txt (src', tit)) = do
linktext <- inlineListToMarkdown opts txt
let linktitle = if null tit then empty else text $ " \"" ++ tit ++ "\""
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 87e72298a..59390fe6c 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -463,7 +463,7 @@ options =
(\arg opt -> return opt { optCslFile = arg })
"FILENAME")
""
- , Option "" ["natbib"]
+ , Option "" ["natbib", "no-citeproc"]
(NoArg
(\opt -> return opt { optCiteMethod = Natbib }))
"" -- "Use natbib cite commands in LaTeX output"