aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs132
1 files changed, 96 insertions, 36 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index b655ea1a9..eb9646df2 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -373,6 +373,7 @@ attributes = try $ do
attribute :: GenParser Char st ([Char], [[Char]], [([Char], [Char])])
attribute = identifierAttr <|> classAttr <|> keyValAttr
+
identifier :: GenParser Char st [Char]
identifier = do
first <- letter
@@ -912,9 +913,7 @@ inlineParsers = [ str
, note
, inlineNote
, link
-#ifdef _CITEPROC
- , inlineCitation
-#endif
+ , cite
, image
, math
, strikeout
@@ -1305,38 +1304,99 @@ rawHtmlInline' = do
else choice [htmlComment, anyHtmlInlineTag]
return $ HtmlInline result
-#ifdef _CITEPROC
-inlineCitation :: GenParser Char ParserState Inline
-inlineCitation = try $ do
+-- Citations
+
+cite :: GenParser Char ParserState Inline
+cite = do
failIfStrict
- cit <- citeMarker
- let citations = readWith parseCitation defaultParserState cit
- mr <- mapM chkCit citations
- if catMaybes mr /= []
- then return $ Cite citations []
- else fail "no citation found"
-
-chkCit :: Target -> GenParser Char ParserState (Maybe Target)
-chkCit t = do
+ textualCite <|> normalCite
+
+spnl :: GenParser Char st ()
+spnl = try $ skipSpaces >> optional newline >> skipSpaces >>
+ notFollowedBy (char '\n')
+
+textualCite :: GenParser Char ParserState Inline
+textualCite = try $ do
+ key <- citeKey
st <- getState
- case lookupKeySrc (stateKeys st) (Key [Str $ fst t]) of
- Just _ -> fail "This is a link"
- Nothing -> if elem (fst t) $ stateCitations st
- then return $ Just t
- else return $ Nothing
-
-citeMarker :: GenParser Char ParserState String
-citeMarker = char '[' >> manyTill ( noneOf "\n" <|> (newline >>~ notFollowedBy blankline) ) (char ']')
-
-parseCitation :: GenParser Char ParserState [(String,String)]
-parseCitation = try $ sepBy (parseLabel) (oneOf ";")
-
-parseLabel :: GenParser Char ParserState (String,String)
-parseLabel = try $ do
- res <- sepBy (skipSpaces >> optional newline >> skipSpaces >> many1 (noneOf "@;")) (oneOf "@")
- case res of
- [lab,loc] -> return (lab, loc)
- [lab] -> return (lab, "" )
- _ -> return ("" , "" )
-
-#endif
+ unless (key `elem` stateCitations st) $
+ fail "not a citation"
+ let first = Citation{ citationId = key
+ , citationPrefix = ""
+ , citationLocator = ""
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ option (Cite [first] []) $ try $ do
+ spnl
+ char '['
+ spnl
+ bareloc <- option "" locator
+ rest <- many $ try $ do
+ char ';'
+ spnl
+ citation
+ spnl
+ char ']'
+ let first' = if null bareloc
+ then first
+ else first{ citationLocator = bareloc
+ , citationMode = AuthorInText }
+ return $ Cite (first' : rest) []
+
+normalCite :: GenParser Char ParserState Inline
+normalCite = try $ do
+ cites <- citeList
+ return $ Cite cites []
+
+citeKey :: GenParser Char st String
+citeKey = try $ do
+ char '@'
+ first <- letter
+ rest <- many $ noneOf ",;]@ \t\n"
+ return (first:rest)
+
+locator :: GenParser Char st String
+locator = try $ do
+ optional $ char ','
+ spnl
+ -- TODO should eventually be list of inlines
+ many1 $ (char '\\' >> oneOf "];\n") <|> noneOf "];\n" <|>
+ (char '\n' >> notFollowedBy blankline >> return ' ')
+
+prefix :: GenParser Char st String
+prefix = try $ liftM removeLeadingTrailingSpace $
+ many $ (char '\\' >> anyChar) <|> noneOf "@]\n" <|>
+ (char '-' >> notFollowedBy (char '@') >> return '-') <|>
+ (char '\n' >> notFollowedBy blankline >> return ' ')
+
+citeList :: GenParser Char st [Citation]
+citeList = try $ do
+ char '['
+ spnl
+ first <- citation
+ spnl
+ rest <- many $ try $ do
+ char ';'
+ spnl
+ citation
+ spnl
+ char ']'
+ return (first:rest)
+
+citation :: GenParser Char st Citation
+citation = try $ do
+ suppress_auth <- option False (char '-' >> return True)
+ pref <- prefix
+ key <- citeKey
+ loc <- locator
+ return $ Citation{ citationId = key
+ , citationPrefix = pref
+ , citationLocator = loc
+ , citationMode = if suppress_auth
+ then SuppressAuthor
+ else NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }