Merge branch 'altcite'
This commit is contained in:
commit
b1d08a8aa8
7 changed files with 106 additions and 71 deletions
|
@ -55,7 +55,10 @@ processBiblio (Just style) r p =
|
||||||
cits_map = M.fromList $ zip grps (citations result)
|
cits_map = M.fromList $ zip grps (citations result)
|
||||||
biblioList = map (renderPandoc' style) (bibliography result)
|
biblioList = map (renderPandoc' style) (bibliography result)
|
||||||
Pandoc m b = bottomUp mvPunct . deNote . topDown (processCite style cits_map) $ p'
|
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.
|
-- | Substitute 'Cite' elements with formatted citations.
|
||||||
processCite :: Style -> M.Map [Citation] [FormattedOutput] -> Inline -> Inline
|
processCite :: Style -> M.Map [Citation] [FormattedOutput] -> Inline -> Inline
|
||||||
|
|
|
@ -55,7 +55,6 @@ import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
|
||||||
import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,
|
import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,
|
||||||
isTextTag, isCommentTag )
|
isTextTag, isCommentTag )
|
||||||
import Text.Pandoc.Biblio (processBiblio)
|
import Text.Pandoc.Biblio (processBiblio)
|
||||||
import qualified Text.CSL as CSL
|
|
||||||
import Data.Monoid (mconcat, mempty)
|
import Data.Monoid (mconcat, mempty)
|
||||||
import Control.Applicative ((<$>), (<*), (*>), (<$))
|
import Control.Applicative ((<$>), (<*), (*>), (<$))
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
@ -1797,11 +1796,13 @@ rawHtmlInline = do
|
||||||
cite :: MarkdownParser (F Inlines)
|
cite :: MarkdownParser (F Inlines)
|
||||||
cite = do
|
cite = do
|
||||||
guardEnabled Ext_citations
|
guardEnabled Ext_citations
|
||||||
getOption readerReferences >>= guard . not . null
|
citations <- textualCite <|> (fmap (flip B.cite unknownC) <$> normalCite)
|
||||||
citations <- textualCite <|> normalCite
|
return citations
|
||||||
return $ flip B.cite mempty <$> citations
|
|
||||||
|
|
||||||
textualCite :: MarkdownParser (F [Citation])
|
unknownC :: Inlines
|
||||||
|
unknownC = B.str "???"
|
||||||
|
|
||||||
|
textualCite :: MarkdownParser (F Inlines)
|
||||||
textualCite = try $ do
|
textualCite = try $ do
|
||||||
(_, key) <- citeKey
|
(_, key) <- citeKey
|
||||||
let first = Citation{ citationId = key
|
let first = Citation{ citationId = key
|
||||||
|
@ -1813,8 +1814,12 @@ textualCite = try $ do
|
||||||
}
|
}
|
||||||
mbrest <- option Nothing $ try $ spnl >> Just <$> normalCite
|
mbrest <- option Nothing $ try $ spnl >> Just <$> normalCite
|
||||||
case mbrest of
|
case mbrest of
|
||||||
Just rest -> return $ (first:) <$> rest
|
Just rest -> return $ (flip B.cite unknownC . (first:)) <$> rest
|
||||||
Nothing -> option (return [first]) $ bareloc first
|
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 :: Citation -> MarkdownParser (F [Citation])
|
||||||
bareloc c = try $ do
|
bareloc c = try $ do
|
||||||
|
@ -1846,8 +1851,6 @@ citeKey = try $ do
|
||||||
let internal p = try $ p >>~ lookAhead (letter <|> digit)
|
let internal p = try $ p >>~ lookAhead (letter <|> digit)
|
||||||
rest <- many $ letter <|> digit <|> internal (oneOf ":.#$%&-_+?<>~/")
|
rest <- many $ letter <|> digit <|> internal (oneOf ":.#$%&-_+?<>~/")
|
||||||
let key = first:rest
|
let key = first:rest
|
||||||
citations' <- map CSL.refId <$> getOption readerReferences
|
|
||||||
guard $ key `elem` citations'
|
|
||||||
return (suppress_author, key)
|
return (suppress_author, key)
|
||||||
|
|
||||||
suffix :: MarkdownParser (F Inlines)
|
suffix :: MarkdownParser (F Inlines)
|
||||||
|
|
|
@ -186,7 +186,12 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
|
||||||
let toc = if writerTableOfContents opts
|
let toc = if writerTableOfContents opts
|
||||||
then tableOfContents opts headerBlocks
|
then tableOfContents opts headerBlocks
|
||||||
else empty
|
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
|
st <- get
|
||||||
notes' <- notesToMarkdown opts (reverse $ stNotes st)
|
notes' <- notesToMarkdown opts (reverse $ stNotes st)
|
||||||
st' <- get -- note that the notes may contain refs
|
st' <- get -- note that the notes may contain refs
|
||||||
|
@ -304,10 +309,10 @@ blockToMarkdown _ Null = return empty
|
||||||
blockToMarkdown opts (Div attrs ils) = do
|
blockToMarkdown opts (Div attrs ils) = do
|
||||||
isPlain <- gets stPlain
|
isPlain <- gets stPlain
|
||||||
contents <- blockListToMarkdown opts ils
|
contents <- blockListToMarkdown opts ils
|
||||||
return $ if isPlain
|
return $ if isPlain || not (isEnabled Ext_markdown_in_html_blocks opts)
|
||||||
then contents <> blankline
|
then contents <> blankline
|
||||||
else tagWithAttrs "div" attrs <> blankline <>
|
else tagWithAttrs "div" attrs <> blankline <>
|
||||||
contents <> blankline <> "</div>" <> blankline
|
contents <> blankline <> "</div>" <> blankline
|
||||||
blockToMarkdown opts (Plain inlines) = do
|
blockToMarkdown opts (Plain inlines) = do
|
||||||
contents <- inlineListToMarkdown opts inlines
|
contents <- inlineListToMarkdown opts inlines
|
||||||
return $ contents <> cr
|
return $ contents <> cr
|
||||||
|
@ -711,17 +716,20 @@ inlineToMarkdown opts (LineBreak)
|
||||||
| isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr
|
| isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr
|
||||||
| otherwise = return $ " " <> cr
|
| otherwise = return $ " " <> cr
|
||||||
inlineToMarkdown _ Space = return space
|
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
|
| not (isEnabled Ext_citations opts) = inlineListToMarkdown opts lst
|
||||||
| citationMode c == AuthorInText = do
|
| otherwise =
|
||||||
suffs <- inlineListToMarkdown opts $ citationSuffix c
|
if citationMode c == AuthorInText
|
||||||
rest <- mapM convertOne cs
|
then do
|
||||||
let inbr = suffs <+> joincits rest
|
suffs <- inlineListToMarkdown opts $ citationSuffix c
|
||||||
br = if isEmpty inbr then empty else char '[' <> inbr <> char ']'
|
rest <- mapM convertOne cs
|
||||||
return $ text ("@" ++ citationId c) <+> br
|
let inbr = suffs <+> joincits rest
|
||||||
| otherwise = do
|
br = if isEmpty inbr then empty else char '[' <> inbr <> char ']'
|
||||||
cits <- mapM convertOne (c:cs)
|
return $ text ("@" ++ citationId c) <+> br
|
||||||
return $ text "[" <> joincits cits <> text "]"
|
else do
|
||||||
|
cits <- mapM convertOne (c:cs)
|
||||||
|
return $ text "[" <> joincits cits <> text "]"
|
||||||
where
|
where
|
||||||
joincits = hcat . intersperse (text "; ") . filter (not . isEmpty)
|
joincits = hcat . intersperse (text "; ") . filter (not . isEmpty)
|
||||||
convertOne Citation { citationId = k
|
convertOne Citation { citationId = k
|
||||||
|
@ -738,7 +746,6 @@ inlineToMarkdown opts (Cite (c:cs) lst@[RawInline "latex" _])
|
||||||
return $ pdoc <+> r
|
return $ pdoc <+> r
|
||||||
modekey SuppressAuthor = "-"
|
modekey SuppressAuthor = "-"
|
||||||
modekey _ = ""
|
modekey _ = ""
|
||||||
inlineToMarkdown opts (Cite _ lst) = inlineListToMarkdown opts lst
|
|
||||||
inlineToMarkdown opts (Link txt (src, tit)) = do
|
inlineToMarkdown opts (Link txt (src, tit)) = do
|
||||||
linktext <- inlineListToMarkdown opts txt
|
linktext <- inlineListToMarkdown opts txt
|
||||||
let linktitle = if null tit
|
let linktitle = if null tit
|
||||||
|
|
|
@ -196,7 +196,7 @@ markdownCitationTests
|
||||||
++ [test "natbib" wopts "markdown-citations.txt"
|
++ [test "natbib" wopts "markdown-citations.txt"
|
||||||
"markdown-citations.txt"]
|
"markdown-citations.txt"]
|
||||||
where
|
where
|
||||||
ropts = ["-r", "markdown", "-w", "markdown", "--bibliography",
|
ropts = ["-r", "markdown", "-w", "markdown-citations", "--bibliography",
|
||||||
"biblio.bib", "--no-wrap"]
|
"biblio.bib", "--no-wrap"]
|
||||||
wopts = ["-r", "markdown", "-w", "markdown", "--no-wrap", "--natbib"]
|
wopts = ["-r", "markdown", "-w", "markdown", "--no-wrap", "--natbib"]
|
||||||
styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"])
|
styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"])
|
||||||
|
|
|
@ -1,9 +1,9 @@
|
||||||
Pandoc with citeproc-hs
|
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.
|
- Doe (2005) says blah.
|
||||||
|
|
||||||
|
@ -29,15 +29,21 @@ Pandoc with citeproc-hs
|
||||||
|
|
||||||
- With some markup (*see* Doe 2005, 32).
|
- With some markup (*see* Doe 2005, 32).
|
||||||
|
|
||||||
|
<div class="references">
|
||||||
|
|
||||||
References
|
References
|
||||||
==========
|
==========
|
||||||
|
|
||||||
|
“Nonexistent Not Found!”
|
||||||
|
|
||||||
Doe, John. 2005. *First Book*. Cambridge: Cambridge University Press.
|
Doe, John. 2005. *First Book*. Cambridge: Cambridge University Press.
|
||||||
|
|
||||||
———. 2006. “Article.” *Journal of Generic Studies* 6: 33–34.
|
———. 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.
|
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).
|
[^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).
|
[^2]: Some citations (see Doe 2005, chap. 3; Doe and Roe 2007; Doe 2006).
|
||||||
|
|
|
@ -1,45 +1,51 @@
|
||||||
Pandoc with citeproc-hs
|
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]
|
- 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]
|
- 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]
|
- Now some modifiers.[^3]
|
||||||
|
|
||||||
- With some markup [1].
|
- With some markup [2].
|
||||||
|
|
||||||
|
<div class="references">
|
||||||
|
|
||||||
References
|
References
|
||||||
==========
|
==========
|
||||||
|
|
||||||
[1] J. Doe, *First Book*. Cambridge: Cambridge University Press, 2005.
|
[1]“nonexistent not found!” .
|
||||||
|
|
||||||
[2] J. Doe, “Article,” *Journal of Generic Studies*, vol. 6, pp. 33–34, 2006.
|
[2] J. Doe, *First Book*. Cambridge: Cambridge University Press, 2005.
|
||||||
|
|
||||||
[3] J. Doe and J. Roe, “Why Water Is Wet,” in *Third Book*, S. Smith, Ed. Oxford: Oxford University Press, 2007.
|
[3] J. Doe, “Article,” *Journal of Generic Studies*, vol. 6, pp. 33–34, 2006.
|
||||||
|
|
||||||
[^1]: Reference 3 and a citation without locators [3].
|
[4] J. Doe and J. Roe, “Why Water Is Wet,” in *Third Book*, S. Smith, Ed. Oxford: Oxford University Press, 2007.
|
||||||
|
|
||||||
[^2]: Some citations [1–3].
|
</div>
|
||||||
|
|
||||||
[^3]: Like a citation without author: [1], and now Doe with a locator [2].
|
[^1]: Reference 4 and a citation without locators [4].
|
||||||
|
|
||||||
|
[^2]: Some citations [2–4].
|
||||||
|
|
||||||
|
[^3]: Like a citation without author: [2], and now Doe with a locator [3].
|
||||||
|
|
|
@ -1,33 +1,35 @@
|
||||||
Pandoc with citeproc-hs
|
Pandoc with citeproc-hs
|
||||||
=======================
|
=======================
|
||||||
|
|
||||||
- [@nonexistent]
|
- [^1]
|
||||||
|
|
||||||
- @nonexistent
|
- [^2]
|
||||||
|
|
||||||
- John Doe[^1] says blah.
|
- John Doe[^3] says blah.
|
||||||
|
|
||||||
- Doe[^2] says blah.
|
|
||||||
|
|
||||||
- Doe[^3] says blah.
|
|
||||||
|
|
||||||
- Doe[^4] says blah.
|
- Doe[^4] says blah.
|
||||||
|
|
||||||
- In a note.[^5]
|
- Doe[^5] says blah.
|
||||||
|
|
||||||
- A citation group.[^6]
|
- Doe[^6] says blah.
|
||||||
|
|
||||||
- Another one.[^7]
|
- In a note.[^7]
|
||||||
|
|
||||||
- And another one in a note.[^8]
|
- A citation group.[^8]
|
||||||
|
|
||||||
- Citation with a suffix and locator.[^9]
|
- Another one.[^9]
|
||||||
|
|
||||||
- Citation with suffix only.[^10]
|
- And another one in a note.[^10]
|
||||||
|
|
||||||
- Now some modifiers.[^11]
|
- Citation with a suffix and locator.[^11]
|
||||||
|
|
||||||
- With some markup.[^12]
|
- Citation with suffix only.[^12]
|
||||||
|
|
||||||
|
- Now some modifiers.[^13]
|
||||||
|
|
||||||
|
- With some markup.[^14]
|
||||||
|
|
||||||
|
<div class="references">
|
||||||
|
|
||||||
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).
|
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!’.
|
||||||
|
|
||||||
[^2]: *First Book*, p. 30.
|
</div>
|
||||||
|
|
||||||
[^3]: *First Book*, p. 30, with suffix.
|
[^1]: [CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.].
|
||||||
|
|
||||||
[^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).
|
[^2]: [CSL STYLE ERROR: reference with no printed form.].
|
||||||
|
|
||||||
[^5]: Doe and Roe, p. 12 and a citation without locators Doe and Roe.
|
[^3]: *First Book* (Cambridge: Cambridge University Press, 2005).
|
||||||
|
|
||||||
[^6]: See Doe, *First Book*, chap. 3; also Doe and Roe, pp. 34–35.
|
[^4]: *First Book*, p. 30.
|
||||||
|
|
||||||
[^7]: See Doe, *First Book*, pp. 34–35.
|
[^5]: *First Book*, p. 30, with suffix.
|
||||||
|
|
||||||
[^8]: Some citations see Doe, *First Book*, chap. 3; Doe and Roe; Doe, ‘Article’, 33–34.
|
[^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).
|
||||||
|
|
||||||
[^9]: Doe, *First Book*, pp. 33, 35–37, and nowhere else.
|
[^7]: Doe and Roe, p. 12 and a citation without locators Doe and Roe.
|
||||||
|
|
||||||
[^10]: Doe, *First Book* and nowhere else.
|
[^8]: See Doe, *First Book*, chap. 3; also Doe and Roe, pp. 34–35.
|
||||||
|
|
||||||
[^11]: Like a citation without author: *First Book*, and now Doe with a locator ‘Article’, 33–34 (p. 44).
|
[^9]: See Doe, *First Book*, pp. 34–35.
|
||||||
|
|
||||||
[^12]: *See* Doe, *First Book*, p. 32.
|
[^10]: Some citations see Doe, *First Book*, chap. 3; Doe and Roe; Doe, ‘Article’, 33–34.
|
||||||
|
|
||||||
|
[^11]: Doe, *First Book*, pp. 33, 35–37, and nowhere else.
|
||||||
|
|
||||||
|
[^12]: Doe, *First Book* and nowhere else.
|
||||||
|
|
||||||
|
[^13]: Like a citation without author: *First Book*, and now Doe with a locator ‘Article’, 33–34 (p. 44).
|
||||||
|
|
||||||
|
[^14]: *See* Doe, *First Book*, p. 32.
|
||||||
|
|
Loading…
Add table
Reference in a new issue