aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2023-12-18 23:27:40 -0800
committerJohn MacFarlane <[email protected]>2023-12-18 23:27:40 -0800
commit0e86a84e3323980dd8a0071d6ad901179cdc4a35 (patch)
treed4c8e47b0efa8b9c90851de664be293c270a2bdd
parent2f6a66feb149753e5298e2acb795196f1cc8b821 (diff)
LaTeX writer: omit superfluous page locator label...
when used with `--natbib` or `--biblatex`. These will treat a bare number as a page locator, and they will be able to localize it. We borrow the code for stripping the locator label from the suffix from Citeproc code. Note that the recognition of the locator label is locale-sensitive; if `lang` is `de`, then `S. 33` is a page reference, and `p. 33` is not! Closes #9275.
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs17
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Citation.hs36
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Types.hs3
-rw-r--r--test/command/9275.md18
4 files changed, 59 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 6173e2a23..943f50ef9 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -127,6 +127,13 @@ pandocToLaTeX options (Pandoc meta blocks) = do
let colwidth = if writerWrapText options == WrapAuto
then Just $ writerColumns options
else Nothing
+ docLangs <- catMaybes <$>
+ mapM (toLang . Just) (nubOrd (query (extract "lang") blocks))
+ mblang <- toLang $ case getLang options meta of
+ Just l -> Just l
+ Nothing | null docLangs -> Nothing
+ | otherwise -> Just "en"
+ modify $ \s -> s{ stLang = mblang }
metadata <- metaToContext options
blockListToLaTeX
(fmap chomp . inlineListToLaTeX)
@@ -167,8 +174,8 @@ pandocToLaTeX options (Pandoc meta blocks) = do
st <- get
titleMeta <- stringToLaTeX TextString $ stringify $ docTitle meta
authorsMeta <- mapM (stringToLaTeX TextString . stringify) $ docAuthors meta
- docLangs <- catMaybes <$>
- mapM (toLang . Just) (nubOrd (query (extract "lang") blocks))
+ -- we need a default here since lang is used in template conditionals
+ let otherLangs = [l | l <- docLangs, mblang /= Just l]
let hasStringValue x = isJust (getField x metadata :: Maybe (Doc Text))
let geometryFromMargins = mconcat $ intersperse ("," :: Doc Text) $
mapMaybe (\(x,y) ->
@@ -178,12 +185,6 @@ pandocToLaTeX options (Pandoc meta blocks) = do
,("tmargin","margin-top")
,("bmargin","margin-bottom")
]
- mblang <- toLang $ case getLang options meta of
- Just l -> Just l
- Nothing | null docLangs -> Nothing
- | otherwise -> Just "en"
- -- we need a default here since lang is used in template conditionals
- let otherLangs = [l | l <- docLangs, mblang /= Just l]
let dirs = query (extract "dir") blocks
diff --git a/src/Text/Pandoc/Writers/LaTeX/Citation.hs b/src/Text/Pandoc/Writers/LaTeX/Citation.hs
index 8a586ae6f..c4cf1097b 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Citation.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Citation.hs
@@ -15,6 +15,8 @@ module Text.Pandoc.Writers.LaTeX.Citation
import Data.Text (Text)
import Data.Char (isPunctuation)
+import Control.Monad.State (gets)
+import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
@@ -22,7 +24,11 @@ import Data.List (foldl')
import Text.DocLayout (Doc, brackets, empty, (<+>), text, isEmpty, literal,
braces)
import Text.Pandoc.Walk
-import Text.Pandoc.Writers.LaTeX.Types ( LW )
+import Text.Pandoc.Writers.LaTeX.Types ( LW, WriterState(stLang) )
+import Text.Pandoc.Citeproc.Locator (parseLocator, LocatorInfo(..),
+ toLocatorMap)
+import Citeproc.Types (Lang(..))
+import Citeproc.Locale (getLocale)
citationsToNatbib :: PandocMonad m
=> ([Inline] -> LW m (Doc Text))
@@ -101,11 +107,9 @@ citeArgumentsList :: PandocMonad m
-> LW m (Doc Text)
citeArgumentsList _inlineListToLaTeX (CiteGroup _ _ []) = return empty
citeArgumentsList inlineListToLaTeX (CiteGroup pfxs sfxs ids) = do
- pdoc <- inlineListToLaTeX pfxs
- sdoc <- inlineListToLaTeX sfxs'
- return $ optargs pdoc sdoc <>
- braces (literal (T.intercalate "," (reverse ids)))
- where sfxs' = stripLocatorBraces $ case sfxs of
+ mblang <- gets stLang
+ let sfxs' = removePageLabel mblang $
+ stripLocatorBraces $ case sfxs of
(Str t : r) -> case T.uncons t of
Just (x, xs)
| T.null xs
@@ -113,10 +117,14 @@ citeArgumentsList inlineListToLaTeX (CiteGroup pfxs sfxs ids) = do
| isPunctuation x -> Str xs : r
_ -> sfxs
_ -> sfxs
- optargs pdoc sdoc = case (isEmpty pdoc, isEmpty sdoc) of
+ optargs pdoc sdoc = case (isEmpty pdoc, isEmpty sdoc) of
(True, True ) -> empty
(True, False) -> brackets sdoc
(_ , _ ) -> brackets pdoc <> brackets sdoc
+ pdoc <- inlineListToLaTeX pfxs
+ sdoc <- inlineListToLaTeX sfxs'
+ return $ optargs pdoc sdoc <>
+ braces (literal (T.intercalate "," (reverse ids)))
citeArguments :: PandocMonad m
=> ([Inline] -> LW m (Doc Text))
@@ -180,3 +188,17 @@ citationsToBiblatex inlineListToLaTeX (c:cs)
cid = citationId cit
citationsToBiblatex _ _ = return empty
+
+-- | In natbib and biblatex, the label p. or pp. can be
+-- omitted; ranges will be treated as page ranges by default.
+-- See #9275.
+removePageLabel :: Maybe Lang -> [Inline] -> [Inline]
+removePageLabel mblang ils =
+ case mbLocinfo of
+ Just locinfo | locatorLabel locinfo == "page"
+ -> Str (locatorLoc locinfo) : ils'
+ _ -> ils
+ where
+ (mbLocinfo, ils') = parseLocator (toLocatorMap locale) ils
+ lang = fromMaybe (Lang "en" Nothing (Just "US") [] [] []) mblang
+ locale = either mempty id $ getLocale lang
diff --git a/src/Text/Pandoc/Writers/LaTeX/Types.hs b/src/Text/Pandoc/Writers/LaTeX/Types.hs
index 0e0582948..fa27b9e52 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Types.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Types.hs
@@ -11,6 +11,7 @@ import Text.Pandoc.Options
( WriterOptions (writerIncremental, writerTopLevelDivision)
, TopLevelDivision (..)
)
+import Citeproc.Types (Lang)
-- | LaTeX writer type. The type constructor @m@ will typically be an
-- instance of PandocMonad.
@@ -50,6 +51,7 @@ data WriterState =
, stEmptyLine :: Bool -- ^ true if no content on line
, stHasCslRefs :: Bool -- ^ has a Div with class refs
, stIsFirstInDefinition :: Bool -- ^ first block in a defn list
+ , stLang :: Maybe Lang -- ^ lang specified in metadata
}
startingState :: WriterOptions -> WriterState
@@ -88,4 +90,5 @@ startingState options =
, stEmptyLine = True
, stHasCslRefs = False
, stIsFirstInDefinition = False
+ , stLang = Nothing
}
diff --git a/test/command/9275.md b/test/command/9275.md
new file mode 100644
index 000000000..c76886624
--- /dev/null
+++ b/test/command/9275.md
@@ -0,0 +1,18 @@
+```
+% pandoc -t latex --biblatex
+[@scott2000, p. 33]
+[@scott2000, pp. 33-34 and elsewhere; @scott2001, ch. 4]
+^D
+\autocite[33]{scott2000} \autocites[33-34 and
+elsewhere]{scott2000}[ch.~4]{scott2001}
+
+```
+
+```
+% pandoc -t latex --biblatex -Mlang=de
+[@scott2000, p. 33]
+[@scott2000, S. 33]
+^D
+\autocite[p.~33]{scott2000} \autocite[33]{scott2000}
+
+```