RST reader: support RST-style citations.

The citations appear at the end of the document as a definition
list in a special div with id `citations`.

Citations link to the definitions.

Added stateCitations to ParserState.

Closes #853.
This commit is contained in:
John MacFarlane 2017-03-03 22:23:01 +01:00
parent d18a1c1c9e
commit fb47d1d909
3 changed files with 74 additions and 14 deletions

View file

@ -923,6 +923,7 @@ data ParserState = ParserState
stateNotes' :: NoteTable', -- ^ List of notes (parsed bodies) stateNotes' :: NoteTable', -- ^ List of notes (parsed bodies)
stateMeta :: Meta, -- ^ Document metadata stateMeta :: Meta, -- ^ Document metadata
stateMeta' :: F Meta, -- ^ Document metadata stateMeta' :: F Meta, -- ^ Document metadata
stateCitations :: M.Map String String, -- ^ RST-style citations
stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used
stateHeaders :: M.Map Inlines String, -- ^ List of headers and ids (used for implicit ref links) stateHeaders :: M.Map Inlines String, -- ^ List of headers and ids (used for implicit ref links)
stateIdentifiers :: Set.Set String, -- ^ Header identifiers used stateIdentifiers :: Set.Set String, -- ^ Header identifiers used
@ -1030,6 +1031,7 @@ defaultParserState =
stateNotes' = [], stateNotes' = [],
stateMeta = nullMeta, stateMeta = nullMeta,
stateMeta' = return nullMeta, stateMeta' = return nullMeta,
stateCitations = M.empty,
stateHeaderTable = [], stateHeaderTable = [],
stateHeaders = M.empty, stateHeaders = M.empty,
stateIdentifiers = Set.empty, stateIdentifiers = Set.empty,

View file

@ -158,8 +158,8 @@ parseRST = do
-- go through once just to get list of reference keys and notes -- go through once just to get list of reference keys and notes
-- docMinusKeys is the raw document with blanks where the keys were... -- docMinusKeys is the raw document with blanks where the keys were...
docMinusKeys <- concat <$> docMinusKeys <- concat <$>
manyTill (referenceKey <|> noteBlock <|> headerBlock <|> manyTill (referenceKey <|> noteBlock <|> citationBlock <|>
lineClump) eof headerBlock <|> lineClump) eof
setInput docMinusKeys setInput docMinusKeys
setPosition startPos setPosition startPos
st' <- getState st' <- getState
@ -169,6 +169,12 @@ parseRST = do
, stateIdentifiers = mempty } , stateIdentifiers = mempty }
-- now parse it for real... -- now parse it for real...
blocks <- B.toList <$> parseBlocks blocks <- B.toList <$> parseBlocks
citations <- (sort . M.toList . stateCitations) <$> getState
citationItems <- mapM parseCitation citations
let refBlock = if null citationItems
then []
else [Div ("citations",[],[]) $
B.toList $ B.definitionList citationItems]
standalone <- getOption readerStandalone standalone <- getOption readerStandalone
state <- getState state <- getState
let meta = stateMeta state let meta = stateMeta state
@ -176,7 +182,15 @@ parseRST = do
then titleTransform (blocks, meta) then titleTransform (blocks, meta)
else (blocks, meta) else (blocks, meta)
reportLogMessages reportLogMessages
return $ Pandoc meta' blocks' return $ Pandoc meta' (blocks' ++ refBlock)
parseCitation :: PandocMonad m
=> (String, String) -> RSTParser m (Inlines, [Blocks])
parseCitation (ref, raw) = do
contents <- parseFromString parseBlocks raw
return $ (B.spanWith (ref, ["citation-label"], []) (B.str ref),
[contents])
-- --
-- parsing blocks -- parsing blocks
@ -860,22 +874,43 @@ codeblock classes numberLines lang body =
noteBlock :: Monad m => RSTParser m [Char] noteBlock :: Monad m => RSTParser m [Char]
noteBlock = try $ do noteBlock = try $ do
(ref, raw, replacement) <- noteBlock' noteMarker
updateState $ \s -> s { stateNotes = (ref, raw) : stateNotes s }
-- return blanks so line count isn't affected
return replacement
citationBlock :: Monad m => RSTParser m [Char]
citationBlock = try $ do
(ref, raw, replacement) <- noteBlock' citationMarker
updateState $ \s ->
s { stateCitations = M.insert ref raw (stateCitations s),
stateKeys = M.insert (toKey ref) (('#':ref,""), ("",["citation"],[]))
(stateKeys s) }
-- return blanks so line count isn't affected
return replacement
noteBlock' :: Monad m
=> RSTParser m String -> RSTParser m (String, String, String)
noteBlock' marker = try $ do
startPos <- getPosition startPos <- getPosition
string ".." string ".."
spaceChar >> skipMany spaceChar spaceChar >> skipMany spaceChar
ref <- noteMarker ref <- marker
first <- (spaceChar >> skipMany spaceChar >> anyLine) first <- (spaceChar >> skipMany spaceChar >> anyLine)
<|> (newline >> return "") <|> (newline >> return "")
blanks <- option "" blanklines blanks <- option "" blanklines
rest <- option "" indentedBlock rest <- option "" indentedBlock
endPos <- getPosition endPos <- getPosition
let raw = first ++ "\n" ++ blanks ++ rest ++ "\n" let raw = first ++ "\n" ++ blanks ++ rest ++ "\n"
let newnote = (ref, raw) let replacement =replicate (sourceLine endPos - sourceLine startPos) '\n'
st <- getState return (ref, raw, replacement)
let oldnotes = stateNotes st
updateState $ \s -> s { stateNotes = newnote : oldnotes } citationMarker :: Monad m => RSTParser m [Char]
-- return blanks so line count isn't affected citationMarker = do
return $ replicate (sourceLine endPos - sourceLine startPos) '\n' char '['
res <- simpleReferenceName'
char ']'
return res
noteMarker :: Monad m => RSTParser m [Char] noteMarker :: Monad m => RSTParser m [Char]
noteMarker = do noteMarker = do
@ -913,9 +948,7 @@ simpleReferenceName' = do
return (x:xs) return (x:xs)
simpleReferenceName :: Monad m => ParserT [Char] st m Inlines simpleReferenceName :: Monad m => ParserT [Char] st m Inlines
simpleReferenceName = do simpleReferenceName = B.str <$> simpleReferenceName'
raw <- simpleReferenceName'
return $ B.str raw
referenceName :: PandocMonad m => RSTParser m Inlines referenceName :: PandocMonad m => RSTParser m Inlines
referenceName = quotedReferenceName <|> referenceName = quotedReferenceName <|>
@ -1290,9 +1323,16 @@ explicitLink = try $ do
_ -> return ((src, ""), nullAttr) _ -> return ((src, ""), nullAttr)
return $ B.linkWith attr (escapeURI src') tit label'' return $ B.linkWith attr (escapeURI src') tit label''
citationName :: PandocMonad m => RSTParser m Inlines
citationName = do
raw <- citationMarker
return $ B.str $ "[" ++ raw ++ "]"
referenceLink :: PandocMonad m => RSTParser m Inlines referenceLink :: PandocMonad m => RSTParser m Inlines
referenceLink = try $ do referenceLink = try $ do
(label',ref) <- withRaw (quotedReferenceName <|> simpleReferenceName) <* (label',ref) <- withRaw (quotedReferenceName
<|> simpleReferenceName
<|> citationName) <*
char '_' char '_'
let isAnonKey (Key ('_':_)) = True let isAnonKey (Key ('_':_)) = True
isAnonKey _ = False isAnonKey _ = False

18
test/command/853.md Normal file
View file

@ -0,0 +1,18 @@
reStructuredText citations.
```
% pandoc -f rst
Here is a citation reference: [CIT2002]_.
.. [CIT2002] This is the citation. It's just like a footnote,
except the label is textual.
^D
<p>Here is a citation reference: <a href="#CIT2002" class="citation">[CIT2002]</a>.</p>
<div id="citations">
<dl>
<dt><span id="CIT2002" class="citation-label">CIT2002</span></dt>
<dd><p>This is the citation. It's just like a footnote, except the label is textual.</p>
</dd>
</dl>
</div>
```