diff options
| -rw-r--r-- | src/Text/Pandoc/Biblio.hs | 38 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 38 | 
2 files changed, 36 insertions, 40 deletions
| diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs index 921cf54c5..bf1624bb4 100644 --- a/src/Text/Pandoc/Biblio.hs +++ b/src/Text/Pandoc/Biblio.hs @@ -31,6 +31,7 @@ module Text.Pandoc.Biblio ( processBiblio ) where  import Data.List  import Data.Unique +import Data.Char ( isDigit )  import qualified Data.Map as M  import Text.CSL hiding ( Cite(..), Citation(..) )  import qualified Text.CSL as CSL ( Cite(..) ) @@ -97,8 +98,8 @@ getNoteCitations needNote        in  queryWith getCitation . getCits  setHash :: Citation -> IO Citation -setHash (Citation i p s l cm nn _) -    = hashUnique `fmap` newUnique >>= return . Citation i p s l cm nn +setHash (Citation i p s cm nn _) +    = hashUnique `fmap` newUnique >>= return . Citation i p s cm nn  generateNotes :: [Inline] -> Pandoc -> Pandoc  generateNotes needNote = processWith (mvCiteInNote needNote) @@ -150,14 +151,15 @@ setCitationNoteNum i = map $ \c -> c { citationNoteNum = i}  toCslCite :: Citation -> CSL.Cite  toCslCite c -    = let (la,lo) = parseLocator $ citationLocator c +    = let (l, s)  = locatorWords $ citationSuffix c +          (la,lo) = parseLocator $ unwords l            citMode = case citationMode c of                        AuthorInText   -> (True, False)                        SuppressAuthor -> (False,True )                        NormalCitation -> (False,False)        in   emptyCite { CSL.citeId         = citationId c                       , CSL.citePrefix     = PandocText $ citationPrefix c -                     , CSL.citeSuffix     = PandocText $ citationSuffix c +                     , CSL.citeSuffix     = PandocText $ s                       , CSL.citeLabel      = la                       , CSL.citeLocator    = lo                       , CSL.citeNoteNumber = show $ citationNoteNum c @@ -165,3 +167,31 @@ toCslCite c                       , CSL.suppressAuthor = snd citMode                       , CSL.citeHash       = citationHash c                       } + +locatorWords :: [Inline] -> ([String], [Inline]) +locatorWords (Space : t) = locatorWords t +locatorWords (Str "" : t) = locatorWords t +locatorWords a@(Str (',' : s) : t) +    = if ws /= [] then (ws, t') else ([], a) +    where +        (ws, t') = locatorWords (Str s:t) +locatorWords i +    = if any isDigit w then (w':ws, s'') else ([], i) +    where +        (w, s')   = locatorWord i +        (ws, s'') = locatorWords s' +        w'        = if ws == [] then w else w ++ "," + +locatorWord :: [Inline] -> (String, [Inline]) +locatorWord (Space : r) = (" " ++ ts, r') +    where +        (ts, r') = locatorWord r +locatorWord (Str t : r) +    | t' /= ""  = (w      , Str t' : r) +    | otherwise = (t ++ ts, r'        ) +    where +        w  = takeWhile (/= ',') t +        t' = dropWhile (/= ',') t +        (ts, r') = locatorWord r +locatorWord i = ("", i) + diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 2d3ad1199..1b3900798 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -34,7 +34,7 @@ module Text.Pandoc.Readers.Markdown (  import Data.List ( transpose, isSuffixOf, sortBy, findIndex, intercalate )  import qualified Data.Map as M  import Data.Ord ( comparing ) -import Data.Char ( isAlphaNum, isDigit ) +import Data.Char ( isAlphaNum )  import Data.Maybe  import Text.Pandoc.Definition  import Text.Pandoc.Shared @@ -1319,23 +1319,12 @@ spnl = try $ do    skipSpaces    notFollowedBy (char '\n') -blankSpace :: GenParser Char st () -blankSpace = try $ do -  res <- many1 $ oneOf " \t\n" -  guard $ length res > 0 -  guard $ length (filter (=='\n') res) <= 1 - -noneOfUnlessEscaped :: [Char] -> GenParser Char st Char -noneOfUnlessEscaped cs = -  try (char '\\' >> oneOf cs) <|> noneOf cs -  textualCite :: GenParser Char ParserState [Citation]  textualCite = try $ do    (_, key) <- citeKey    let first = Citation{ citationId      = key                        , citationPrefix  = []                        , citationSuffix  = [] -                      , citationLocator = ""                        , citationMode    = AuthorInText                        , citationNoteNum = 0                        , citationHash    = 0 @@ -1349,12 +1338,11 @@ bareloc :: Citation -> GenParser Char ParserState [Citation]  bareloc c = try $ do    spnl    char '[' -  loc <- locator    suff <- suffix    rest <- option [] $ try $ char ';' >> citeList    spnl    char ']' -  return $ c{ citationLocator = loc, citationSuffix = suff } : rest +  return $ c{ citationSuffix = suff } : rest  normalCite :: GenParser Char ParserState [Citation]  normalCite = try $ do @@ -1376,26 +1364,6 @@ citeKey = try $ do    guard $ key `elem` stateCitations st    return (suppress_author, key) -locator :: GenParser Char st String -locator = try $ do -  spnl -  w  <- many1 (noneOf " \t\n;,]") -  ws <- many (locatorWord <|> locatorComma) -  return $ unwords $ w:ws - -locatorWord :: GenParser Char st String -locatorWord = try $ do -  spnl -  wd <- many1 $ noneOfUnlessEscaped "];, \t\n" -  guard $ any isDigit wd -  return wd - -locatorComma :: GenParser Char st String -locatorComma = try $ do -  char ',' -  lookAhead $ locatorWord -  return "," -  suffix :: GenParser Char ParserState [Inline]  suffix = try $ do    spnl @@ -1412,12 +1380,10 @@ citation :: GenParser Char ParserState Citation  citation = try $ do    pref <- prefix    (suppress_author, key) <- citeKey -  loc <- option "" $ try $ blankSpace >> locator    suff <- suffix    return $ Citation{ citationId        = key                       , citationPrefix  = pref                       , citationSuffix  = suff -                     , citationLocator = loc                       , citationMode    = if suppress_author                                              then SuppressAuthor                                              else NormalCitation | 
