RST reader: Partial support for labeled footnotes.
Also made simpleReferenceName parser more accurate, which affects several other parsers.
This commit is contained in:
parent
310697ce7e
commit
35cef01659
1 changed files with 20 additions and 7 deletions
|
@ -34,7 +34,7 @@ import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import Text.Pandoc.Parsing
|
import Text.Pandoc.Parsing
|
||||||
import Text.ParserCombinators.Parsec
|
import Text.ParserCombinators.Parsec
|
||||||
import Control.Monad ( when )
|
import Control.Monad ( when, liftM )
|
||||||
import Data.List ( findIndex, intercalate, transpose, sort, deleteFirstsBy )
|
import Data.List ( findIndex, intercalate, transpose, sort, deleteFirstsBy )
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Text.Printf ( printf )
|
import Text.Printf ( printf )
|
||||||
|
@ -540,7 +540,13 @@ noteBlock = try $ do
|
||||||
return $ replicate (sourceLine endPos - sourceLine startPos) '\n'
|
return $ replicate (sourceLine endPos - sourceLine startPos) '\n'
|
||||||
|
|
||||||
noteMarker :: GenParser Char ParserState [Char]
|
noteMarker :: GenParser Char ParserState [Char]
|
||||||
noteMarker = char '[' >> (many1 digit <|> count 1 (oneOf "#*")) >>~ char ']'
|
noteMarker = do
|
||||||
|
char '['
|
||||||
|
res <- many1 digit
|
||||||
|
<|> (try $ char '#' >> liftM ('#':) simpleReferenceName')
|
||||||
|
<|> count 1 (oneOf "#*")
|
||||||
|
char ']'
|
||||||
|
return res
|
||||||
|
|
||||||
--
|
--
|
||||||
-- reference key
|
-- reference key
|
||||||
|
@ -557,13 +563,20 @@ unquotedReferenceName = try $ do
|
||||||
label' <- many1Till inline (lookAhead $ char ':')
|
label' <- many1Till inline (lookAhead $ char ':')
|
||||||
return label'
|
return label'
|
||||||
|
|
||||||
isolated :: Char -> GenParser Char st Char
|
-- Simple reference names are single words consisting of alphanumerics
|
||||||
isolated ch = try $ char ch >>~ notFollowedBy (char ch)
|
-- plus isolated (no two adjacent) internal hyphens, underscores,
|
||||||
|
-- periods, colons and plus signs; no whitespace or other characters
|
||||||
|
-- are allowed.
|
||||||
|
simpleReferenceName' :: GenParser Char st String
|
||||||
|
simpleReferenceName' = do
|
||||||
|
x <- alphaNum
|
||||||
|
xs <- many $ alphaNum
|
||||||
|
<|> (try $ oneOf "-_:+." >> lookAhead alphaNum)
|
||||||
|
return (x:xs)
|
||||||
|
|
||||||
simpleReferenceName :: GenParser Char st [Inline]
|
simpleReferenceName :: GenParser Char st [Inline]
|
||||||
simpleReferenceName = do
|
simpleReferenceName = do
|
||||||
raw <- many1 (alphaNum <|> isolated '-' <|> isolated '.' <|>
|
raw <- simpleReferenceName'
|
||||||
(try $ char '_' >>~ lookAhead alphaNum))
|
|
||||||
return [Str raw]
|
return [Str raw]
|
||||||
|
|
||||||
referenceName :: GenParser Char ParserState [Inline]
|
referenceName :: GenParser Char ParserState [Inline]
|
||||||
|
|
Loading…
Add table
Reference in a new issue