aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Markdown.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Markdown.hs')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs40
1 files changed, 24 insertions, 16 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index b655ea1a9..b7c5220d1 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -912,9 +912,7 @@ inlineParsers = [ str
, note
, inlineNote
, link
-#ifdef _CITEPROC
, inlineCitation
-#endif
, image
, math
, strikeout
@@ -1305,7 +1303,6 @@ rawHtmlInline' = do
else choice [htmlComment, anyHtmlInlineTag]
return $ HtmlInline result
-#ifdef _CITEPROC
inlineCitation :: GenParser Char ParserState Inline
inlineCitation = try $ do
failIfStrict
@@ -1316,27 +1313,38 @@ inlineCitation = try $ do
then return $ Cite citations []
else fail "no citation found"
-chkCit :: Target -> GenParser Char ParserState (Maybe Target)
+chkCit :: Citation -> GenParser Char ParserState (Maybe Citation)
chkCit t = do
st <- getState
- case lookupKeySrc (stateKeys st) (Key [Str $ fst t]) of
+ case lookupKeySrc (stateKeys st) (Key [Str $ citationId t]) of
Just _ -> fail "This is a link"
- Nothing -> if elem (fst t) $ stateCitations st
+ Nothing -> if elem (citationId 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 ";")
+parseCitation :: GenParser Char ParserState [Citation]
+parseCitation = try $ sepBy (parseLabel) (skipMany1 $ char ';')
-parseLabel :: GenParser Char ParserState (String,String)
+parseLabel :: GenParser Char ParserState Citation
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
+ r <- many (noneOf ";")
+ let t' s = if s /= [] then tail s else []
+ trim = unwords . words
+ pref = takeWhile (/= '@') r
+ rest = t' $ dropWhile (/= '@') r
+ cit = takeWhile (/= ',') rest
+ loc = t' $ dropWhile (/= ',') rest
+ (p,na) = if pref /= [] && last pref == '-'
+ then (init pref, True )
+ else (pref , False)
+ (p',o) = if p /= [] && last p == '+'
+ then (init p , True )
+ else (p , False)
+ mode = case (na,o) of
+ (True, False) -> SuppressAuthor
+ (False,True ) -> AuthorOnly
+ _ -> NormalCitation
+ return $ Citation cit (trim p') (trim loc) mode 0 0