diff options
-rw-r--r-- | src/Text/Pandoc/Biblio.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 21 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 35 | ||||
-rw-r--r-- | tests/Tests/Old.hs | 2 | ||||
-rw-r--r-- | tests/markdown-citations.chicago-author-date.txt | 10 | ||||
-rw-r--r-- | tests/markdown-citations.ieee.txt | 40 | ||||
-rw-r--r-- | tests/markdown-citations.mhra.txt | 62 |
7 files changed, 105 insertions, 70 deletions
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs index 206b38530..1c0975f11 100644 --- a/src/Text/Pandoc/Biblio.hs +++ b/src/Text/Pandoc/Biblio.hs @@ -55,7 +55,10 @@ 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 . topDown (processCite style cits_map) $ p' - in Pandoc m $ b ++ biblioList + (bs, lastb) = case reverse b of + x@(Header _ _ _) : xs -> (reverse xs, [x]) + _ -> (b, []) + in Pandoc m $ bs ++ [Div ("",["references"],[]) (lastb ++ biblioList)] -- | Substitute 'Cite' elements with formatted citations. processCite :: Style -> M.Map [Citation] [FormattedOutput] -> Inline -> Inline diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index a653c2e98..05662d9b5 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -55,7 +55,6 @@ import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock ) import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag, isTextTag, isCommentTag ) import Text.Pandoc.Biblio (processBiblio) -import qualified Text.CSL as CSL import Data.Monoid (mconcat, mempty) import Control.Applicative ((<$>), (<*), (*>), (<$)) import Control.Monad @@ -1797,11 +1796,13 @@ rawHtmlInline = do cite :: MarkdownParser (F Inlines) cite = do guardEnabled Ext_citations - getOption readerReferences >>= guard . not . null - citations <- textualCite <|> normalCite - return $ flip B.cite mempty <$> citations + citations <- textualCite <|> (fmap (flip B.cite unknownC) <$> normalCite) + return citations + +unknownC :: Inlines +unknownC = B.str "???" -textualCite :: MarkdownParser (F [Citation]) +textualCite :: MarkdownParser (F Inlines) textualCite = try $ do (_, key) <- citeKey let first = Citation{ citationId = key @@ -1813,8 +1814,12 @@ textualCite = try $ do } mbrest <- option Nothing $ try $ spnl >> Just <$> normalCite case mbrest of - Just rest -> return $ (first:) <$> rest - Nothing -> option (return [first]) $ bareloc first + Just rest -> return $ (flip B.cite unknownC . (first:)) <$> rest + Nothing -> (fmap (flip B.cite unknownC) <$> bareloc first) <|> + return (do st <- askF + return $ case M.lookup key (stateExamples st) of + Just n -> B.str (show n) + _ -> B.cite [first] unknownC) bareloc :: Citation -> MarkdownParser (F [Citation]) bareloc c = try $ do @@ -1846,8 +1851,6 @@ citeKey = try $ do let internal p = try $ p >>~ lookAhead (letter <|> digit) rest <- many $ letter <|> digit <|> internal (oneOf ":.#$%&-_+?<>~/") let key = first:rest - citations' <- map CSL.refId <$> getOption readerReferences - guard $ key `elem` citations' return (suppress_author, key) suffix :: MarkdownParser (F Inlines) diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 623c445df..d617954dd 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -186,7 +186,12 @@ pandocToMarkdown opts (Pandoc meta blocks) = do let toc = if writerTableOfContents opts then tableOfContents opts headerBlocks else empty - body <- blockListToMarkdown opts blocks + -- Strip off final 'references' header if markdown citations enabled + let blocks' = case reverse blocks of + (Div (_,["references"],_) _):xs + | isEnabled Ext_citations opts -> reverse xs + _ -> blocks + body <- blockListToMarkdown opts blocks' st <- get notes' <- notesToMarkdown opts (reverse $ stNotes st) st' <- get -- note that the notes may contain refs @@ -304,10 +309,10 @@ blockToMarkdown _ Null = return empty blockToMarkdown opts (Div attrs ils) = do isPlain <- gets stPlain contents <- blockListToMarkdown opts ils - return $ if isPlain + return $ if isPlain || not (isEnabled Ext_markdown_in_html_blocks opts) then contents <> blankline else tagWithAttrs "div" attrs <> blankline <> - contents <> blankline <> "</div>" <> blankline + contents <> blankline <> "</div>" <> blankline blockToMarkdown opts (Plain inlines) = do contents <- inlineListToMarkdown opts inlines return $ contents <> cr @@ -711,17 +716,20 @@ inlineToMarkdown opts (LineBreak) | isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr | otherwise = return $ " " <> cr inlineToMarkdown _ Space = return space -inlineToMarkdown opts (Cite (c:cs) lst@[RawInline "latex" _]) +inlineToMarkdown opts (Cite [] lst) = inlineListToMarkdown opts lst +inlineToMarkdown opts (Cite (c:cs) lst) | not (isEnabled Ext_citations opts) = 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 char '[' <> inbr <> char ']' - return $ text ("@" ++ citationId c) <+> br - | otherwise = do - cits <- mapM convertOne (c:cs) - return $ text "[" <> joincits cits <> text "]" + | otherwise = + if citationMode c == AuthorInText + then do + suffs <- inlineListToMarkdown opts $ citationSuffix c + rest <- mapM convertOne cs + let inbr = suffs <+> joincits rest + br = if isEmpty inbr then empty else char '[' <> inbr <> char ']' + return $ text ("@" ++ citationId c) <+> br + else do + cits <- mapM convertOne (c:cs) + return $ text "[" <> joincits cits <> text "]" where joincits = hcat . intersperse (text "; ") . filter (not . isEmpty) convertOne Citation { citationId = k @@ -738,7 +746,6 @@ inlineToMarkdown opts (Cite (c:cs) lst@[RawInline "latex" _]) return $ pdoc <+> r modekey SuppressAuthor = "-" modekey _ = "" -inlineToMarkdown opts (Cite _ lst) = inlineListToMarkdown opts lst inlineToMarkdown opts (Link txt (src, tit)) = do linktext <- inlineListToMarkdown opts txt let linktitle = if null tit diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 0ba240084..8609781d0 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -196,7 +196,7 @@ markdownCitationTests ++ [test "natbib" wopts "markdown-citations.txt" "markdown-citations.txt"] where - ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", + ropts = ["-r", "markdown", "-w", "markdown-citations", "--bibliography", "biblio.bib", "--no-wrap"] wopts = ["-r", "markdown", "-w", "markdown", "--no-wrap", "--natbib"] styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"]) diff --git a/tests/markdown-citations.chicago-author-date.txt b/tests/markdown-citations.chicago-author-date.txt index de242300d..81d7482cb 100644 --- a/tests/markdown-citations.chicago-author-date.txt +++ b/tests/markdown-citations.chicago-author-date.txt @@ -1,9 +1,9 @@ Pandoc with citeproc-hs ======================= -- [@nonexistent] +- ([CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.]) -- @nonexistent +- ([CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.]) - Doe (2005) says blah. @@ -29,15 +29,21 @@ Pandoc with citeproc-hs - With some markup (*see* Doe 2005, 32). +<div class="references"> + References ========== +“Nonexistent Not Found!” + Doe, John. 2005. *First Book*. Cambridge: Cambridge University Press. ———. 2006. “Article.” *Journal of Generic Studies* 6: 33–34. Doe, John, and Jenny Roe. 2007. “Why Water Is Wet.” In *Third Book*, edited by Sam Smith. Oxford: Oxford University Press. +</div> + [^1]: Doe and Roe (2007, 12) and a citation without locators (Doe and Roe 2007). [^2]: Some citations (see Doe 2005, chap. 3; Doe and Roe 2007; Doe 2006). diff --git a/tests/markdown-citations.ieee.txt b/tests/markdown-citations.ieee.txt index a397e3f38..4085a7c63 100644 --- a/tests/markdown-citations.ieee.txt +++ b/tests/markdown-citations.ieee.txt @@ -1,45 +1,51 @@ Pandoc with citeproc-hs ======================= -- [@nonexistent] +- [] -- @nonexistent +- -- Reference 1 says blah. +- Reference 2 says blah. -- Reference 1 says blah. +- Reference 2 says blah. -- Reference 1 says blah. +- Reference 2 says blah. -- Reference 1 [3] says blah. +- Reference 2 [4] says blah. - In a note.[^1] -- A citation group [1], [3]. +- A citation group [2], [4]. -- Another one [1]. +- Another one [2]. - And another one in a note.[^2] -- Citation with a suffix and locator [1]. +- Citation with a suffix and locator [2]. -- Citation with suffix only [1]. +- Citation with suffix only [2]. - Now some modifiers.[^3] -- With some markup [1]. +- With some markup [2]. + +<div class="references"> References ========== -[1] J. Doe, *First Book*. Cambridge: Cambridge University Press, 2005. +[1]“nonexistent not found!” . + +[2] J. Doe, *First Book*. Cambridge: Cambridge University Press, 2005. + +[3] J. Doe, “Article,” *Journal of Generic Studies*, vol. 6, pp. 33–34, 2006. -[2] J. Doe, “Article,” *Journal of Generic Studies*, vol. 6, pp. 33–34, 2006. +[4] J. Doe and J. Roe, “Why Water Is Wet,” in *Third Book*, S. Smith, Ed. Oxford: Oxford University Press, 2007. -[3] J. Doe and J. Roe, “Why Water Is Wet,” in *Third Book*, S. Smith, Ed. Oxford: Oxford University Press, 2007. +</div> -[^1]: Reference 3 and a citation without locators [3]. +[^1]: Reference 4 and a citation without locators [4]. -[^2]: Some citations [1–3]. +[^2]: Some citations [2–4]. -[^3]: Like a citation without author: [1], and now Doe with a locator [2]. +[^3]: Like a citation without author: [2], and now Doe with a locator [3]. diff --git a/tests/markdown-citations.mhra.txt b/tests/markdown-citations.mhra.txt index d33a1b94b..01d9c45ca 100644 --- a/tests/markdown-citations.mhra.txt +++ b/tests/markdown-citations.mhra.txt @@ -1,33 +1,35 @@ Pandoc with citeproc-hs ======================= -- [@nonexistent] +- [^1] -- @nonexistent +- [^2] -- John Doe[^1] says blah. +- John Doe[^3] says blah. -- Doe[^2] says blah. +- Doe[^4] says blah. -- Doe[^3] says blah. +- Doe[^5] says blah. -- Doe[^4] says blah. +- Doe[^6] says blah. -- In a note.[^5] +- In a note.[^7] -- A citation group.[^6] +- A citation group.[^8] -- Another one.[^7] +- Another one.[^9] -- And another one in a note.[^8] +- And another one in a note.[^10] -- Citation with a suffix and locator.[^9] +- Citation with a suffix and locator.[^11] -- Citation with suffix only.[^10] +- Citation with suffix only.[^12] -- Now some modifiers.[^11] +- Now some modifiers.[^13] -- With some markup.[^12] +- With some markup.[^14] + +<div class="references"> References ========== @@ -38,26 +40,34 @@ Doe, John, ‘Article’, *Journal of Generic Studies*, 6 (2006), 33–34. Doe, John, and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed. by Sam Smith (Oxford: Oxford University Press, 2007). -[^1]: *First Book* (Cambridge: Cambridge University Press, 2005). +‘Nonexistent Not Found!’. + +</div> + +[^1]: [CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.]. + +[^2]: [CSL STYLE ERROR: reference with no printed form.]. + +[^3]: *First Book* (Cambridge: Cambridge University Press, 2005). -[^2]: *First Book*, p. 30. +[^4]: *First Book*, p. 30. -[^3]: *First Book*, p. 30, with suffix. +[^5]: *First Book*, p. 30, with suffix. -[^4]: *First Book*; ‘Article’, *Journal of Generic Studies*, 6 (2006), 33–34 (p. 30); see also John Doe and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed. by Sam Smith (Oxford: Oxford University Press, 2007). +[^6]: *First Book*; ‘Article’, *Journal of Generic Studies*, 6 (2006), 33–34 (p. 30); see also John Doe and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed. by Sam Smith (Oxford: Oxford University Press, 2007). -[^5]: Doe and Roe, p. 12 and a citation without locators Doe and Roe. +[^7]: Doe and Roe, p. 12 and a citation without locators Doe and Roe. -[^6]: See Doe, *First Book*, chap. 3; also Doe and Roe, pp. 34–35. +[^8]: See Doe, *First Book*, chap. 3; also Doe and Roe, pp. 34–35. -[^7]: See Doe, *First Book*, pp. 34–35. +[^9]: See Doe, *First Book*, pp. 34–35. -[^8]: Some citations see Doe, *First Book*, chap. 3; Doe and Roe; Doe, ‘Article’, 33–34. +[^10]: Some citations see Doe, *First Book*, chap. 3; Doe and Roe; Doe, ‘Article’, 33–34. -[^9]: Doe, *First Book*, pp. 33, 35–37, and nowhere else. +[^11]: Doe, *First Book*, pp. 33, 35–37, and nowhere else. -[^10]: Doe, *First Book* and nowhere else. +[^12]: Doe, *First Book* and nowhere else. -[^11]: Like a citation without author: *First Book*, and now Doe with a locator ‘Article’, 33–34 (p. 44). +[^13]: Like a citation without author: *First Book*, and now Doe with a locator ‘Article’, 33–34 (p. 44). -[^12]: *See* Doe, *First Book*, p. 32. +[^14]: *See* Doe, *First Book*, p. 32. |