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.
This commit is contained in:
John MacFarlane 2010-11-16 20:31:22 -08:00
parent 55e991614d
commit ce9fc2a37d
2 changed files with 24 additions and 12 deletions

View file

@ -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
}

View file

@ -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