aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorTuongNM <[email protected]>2025-09-15 10:28:57 +0200
committerGitHub <[email protected]>2025-09-15 10:28:57 +0200
commite2f088f4e5ea1543757b064b3871b483109bda42 (patch)
treea5c2f93c9986355538ef66624938df9678190afd /src
parent4be17f77b77815c32ab9ffbae6ece72cc1e36221 (diff)
LaTeX writer: Protect VERB in caption (#11139)
Also apply hlint suggestions for fewer imports and moving brackets to avoid $.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs15
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Caption.hs4
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Types.hs2
3 files changed, 16 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index eb4671c18..24ed4bebc 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -32,7 +32,7 @@ import Control.Monad
unless )
import Crypto.Hash (hashWith, MD5(MD5))
import Data.Containers.ListUtils (nubOrd)
-import Data.Char (isDigit, isAscii)
+import Data.Char (isDigit, isAscii, isLetter)
import Data.List (intersperse, (\\))
import Data.Maybe (catMaybes, fromMaybe, isJust, mapMaybe, isNothing)
import Data.Monoid (Any (..))
@@ -68,7 +68,6 @@ import Text.Pandoc.Writers.Shared
import qualified Data.Attoparsec.Text as A
import qualified Text.Pandoc.UTF8 as UTF8
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
-import Data.Char (isLetter)
import Control.Applicative ((<|>))
-- Work around problems with notes inside emphasis (see #8982)
@@ -677,7 +676,7 @@ blockToLaTeX (Figure (ident, _, kvs) captnode body) = do
, stSubfigure = stSubfigure st || isSubfigure
}
- let containsTable = getAny . (query $ \case
+ let containsTable = getAny . query (\case
Table {} -> Any True
_ -> Any False)
st <- get
@@ -948,6 +947,7 @@ inlineToLaTeX (Code (_,classes,kvs) str) = do
inHeading <- gets stInHeading
inItem <- gets stInItem
inSoul <- gets stInSoulCommand
+ inCaption <- gets stInCaption
let listingsCode = do
let listingsopts = (case getListingsLanguage classes of
Just l -> (("language", mbBraced l):)
@@ -1000,7 +1000,14 @@ inlineToLaTeX (Code (_,classes,kvs) str) = do
-- (see #1294). with regular texttt we don't get an error, but we get
-- incorrect results if there is a space (see #5529).
let inMbox x = "\\mbox" <> braces x
- (if inSoul then inMbox else id) <$>
+
+ -- for captions we need to protect VERB with \protect (see #6821)
+ let protect x = "\\protect" <> x
+
+ let optionalProtect = case () of _ | inSoul -> inMbox
+ | inCaption -> protect
+ | otherwise -> id
+ optionalProtect <$>
case writerHighlightMethod opts of
_ | inHeading || inItem -> rawCode -- see #5574
IdiomaticHighlighting -> listingsCode
diff --git a/src/Text/Pandoc/Writers/LaTeX/Caption.hs b/src/Text/Pandoc/Writers/LaTeX/Caption.hs
index 2efbfa86e..9a63fee3c 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Caption.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Caption.hs
@@ -23,7 +23,7 @@ import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Text.Pandoc.Writers.LaTeX.Notes (notesToLaTeX)
import Text.Pandoc.Writers.LaTeX.Types
- ( LW, WriterState (stExternalNotes, stNotes) )
+ ( LW, WriterState (stExternalNotes, stNotes, stInCaption) )
-- | Produces the components of a LaTeX 'caption' command. Returns a triple
@@ -35,6 +35,7 @@ getCaption :: PandocMonad m
-> Caption
-> LW m (Doc Text, Doc Text, Doc Text)
getCaption inlineListToLaTeX externalNotes (Caption maybeShort long) = do
+ modify $ \st -> st{ stInCaption = True }
let long' = blocksToInlines long
oldExternalNotes <- gets stExternalNotes
modify $ \st -> st{ stExternalNotes = externalNotes, stNotes = [] }
@@ -53,4 +54,5 @@ getCaption inlineListToLaTeX externalNotes (Caption maybeShort long) = do
then toShortCapt long'
else return empty
Just short -> toShortCapt short
+ modify $ \st -> st{ stInCaption = False }
return (capt, captForLof, footnotes)
diff --git a/src/Text/Pandoc/Writers/LaTeX/Types.hs b/src/Text/Pandoc/Writers/LaTeX/Types.hs
index 1295d2d01..4906026ed 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Types.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Types.hs
@@ -54,6 +54,7 @@ data WriterState =
, stLang :: Maybe Lang -- ^ lang specified in metadata
, stInSoulCommand :: Bool -- ^ in a soul command like ul
, stCancel :: Bool -- ^ true if document uses \cancel
+ , stInCaption :: Bool -- ^ true if in a caption
}
startingState :: WriterOptions -> WriterState
@@ -95,4 +96,5 @@ startingState options =
, stLang = Nothing
, stInSoulCommand = False
, stCancel = False
+ , stInCaption = False
}