aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2010-11-16 20:31:22 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2010-11-16 20:31:22 -0800
commitce9fc2a37d51e65bbfb25eed01cd400e183fb8d9 (patch)
tree6e9a7b20c5c037a3ca5a160a01117fa64663b194 /src/Text
parent55e991614d2e510cf9917b16e58ea1da0cc279ea (diff)
downloadpandoc-ce9fc2a37d51e65bbfb25eed01cd400e183fb8d9.tar.gz
Updated for changes in Citaiton type.
citationPrefix now [Inline] rather than String; citationSuffix added. This change presupposes no changes in citeproc-hs. It passes a string for these values to citeproc-hs. Eventually, citeproc-hs should use an [Inline] for these as well.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Biblio.hs29
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs7
2 files changed, 24 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs
index 05cc296c1..60e059175 100644
--- a/src/Text/Pandoc/Biblio.hs
+++ b/src/Text/Pandoc/Biblio.hs
@@ -99,8 +99,8 @@ getNoteCitations needNote
in queryWith getCitation . getCits
setHash :: Citation -> IO Citation
-setHash (Citation i p l cm nn _)
- = hashUnique `fmap` newUnique >>= return . Citation i p l cm nn
+setHash (Citation i p s l cm nn _)
+ = hashUnique `fmap` newUnique >>= return . Citation i p s l cm nn
generateNotes :: [Inline] -> Pandoc -> Pandoc
generateNotes needNote = processWith (mvCiteInNote needNote)
@@ -150,19 +150,30 @@ setCiteNoteNum _ _ = []
setCitationNoteNum :: Int -> [Citation] -> [Citation]
setCitationNoteNum i = map $ \c -> c { citationNoteNum = i}
+-- a temporary function to tide us over until citeproc is
+-- changed to use Inline lists for prefixes and suffixes...
+stringify :: [Inline] -> String
+stringify = queryWith go
+ where go :: Inline -> [Char]
+ go Space = " "
+ go (Str x) = x
+ go (Code x) = x
+ go _ = ""
+
toCslCite :: Citation -> CSL.Cite
-toCslCite (Citation i p l cm nn h)
- = let (la,lo) = parseLocator l
- citMode = case cm of
+toCslCite c
+ = let (la,lo) = parseLocator $ citationLocator c
+ citMode = case citationMode c of
AuthorInText -> (True, False)
SuppressAuthor -> (False,True )
NormalCitation -> (False,False)
- in emptyCite { CSL.citeId = i
- , CSL.citePrefix = p
+ in emptyCite { CSL.citeId = citationId c
+ , CSL.citePrefix = stringify $ citationPrefix c
+ , CSL.citeSuffix = stringify $ citationSuffix c
, CSL.citeLabel = la
, CSL.citeLocator = lo
- , CSL.citeNoteNumber = show nn
+ , CSL.citeNoteNumber = show $ citationNoteNum c
, CSL.authorInText = fst citMode
, CSL.suppressAuthor = snd citMode
- , CSL.citeHash = h
+ , CSL.citeHash = citationHash c
}
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 0d0e850bc..8101d3098 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1322,7 +1322,8 @@ textualCite = try $ do
unless (key `elem` stateCitations st) $
fail "not a citation"
let first = Citation{ citationId = key
- , citationPrefix = ""
+ , citationPrefix = []
+ , citationSuffix = []
, citationLocator = ""
, citationMode = AuthorInText
, citationNoteNum = 0
@@ -1361,7 +1362,6 @@ 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 ' ')
@@ -1392,7 +1392,8 @@ citation = try $ do
key <- citeKey
loc <- option "" locator
return $ Citation{ citationId = key
- , citationPrefix = pref
+ , citationPrefix = [Str pref]
+ , citationSuffix = []
, citationLocator = loc
, citationMode = if suppress_auth
then SuppressAuthor