aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-02-10 21:47:36 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-02-10 21:48:42 -0800
commitf59e33dd1a49e3f3229c4c26d50c9d002343221d (patch)
treef94af345fdc4a47473d267de13b88c94ceb8e96a /src/Text/Pandoc
parentfe3d8ea4185faee8e1b2aaafa530f598d8b96e85 (diff)
downloadpandoc-f59e33dd1a49e3f3229c4c26d50c9d002343221d.tar.gz
LaTeX reader: Add ", " to suffix...
if it doesn't start w space or punctuation. Otherwise we get no space between the year and the suffix in author-date styles.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs22
1 files changed, 13 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 29aeb1f6f..5e69347b6 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -41,7 +41,7 @@ import qualified Text.Pandoc.UTF8 as UTF8
import Data.Char ( chr, ord )
import Control.Monad
import Text.Pandoc.Builder
-import Data.Char (isLetter)
+import Data.Char (isLetter, isPunctuation, isSpace)
import Control.Applicative
import Data.Monoid
import System.FilePath (replaceExtension)
@@ -800,20 +800,24 @@ preamble = mempty <$> manyTill preambleBlock beginDoc
-- citations
-addPrefix :: Inlines -> [Citation] -> [Citation]
-addPrefix p (k:ks) = k {citationPrefix = toList p ++ citationPrefix k} : ks
+addPrefix :: [Inline] -> [Citation] -> [Citation]
+addPrefix p (k:ks) = k {citationPrefix = p ++ citationPrefix k} : ks
addPrefix _ _ = []
-addSuffix :: Inlines -> [Citation] -> [Citation]
+addSuffix :: [Inline] -> [Citation] -> [Citation]
addSuffix s ks@(_:_) =
- let k = last ks
- in init ks ++ [k {citationSuffix = citationSuffix k ++ toList s}]
+ let k = last ks
+ s' = case s of
+ (Str (c:_):_)
+ | not (isPunctuation c || isSpace c) -> Str "," : Space : s
+ _ -> s
+ in init ks ++ [k {citationSuffix = citationSuffix k ++ s'}]
addSuffix _ _ = []
simpleCiteArgs :: LP [Citation]
simpleCiteArgs = try $ do
- first <- optionMaybe opt
- second <- optionMaybe opt
+ first <- optionMaybe $ toList <$> opt
+ second <- optionMaybe $ toList <$> opt
char '{'
keys <- manyTill citationLabel (char '}')
let (pre, suf) = case (first , second ) of
@@ -850,7 +854,7 @@ citation name mode multi = do
complexNatbibCitation :: CitationMode -> LP Inlines
complexNatbibCitation mode = try $ do
- let ils = (trimInlines . mconcat) <$>
+ let ils = (toList . trimInlines . mconcat) <$>
many (notFollowedBy (oneOf "\\};") >> inline)
let parseOne = try $ do
skipSpaces