aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-06-07 21:30:14 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-06-07 21:30:14 -0700
commitc1ae8d00ee0c021592900adaf8225a0c65c9fd42 (patch)
tree5b612b39046fc692d980485ffdd627c3a8ab9614 /src/Text
parent905dee6ee3c96560d67e82f6786b8f248b5c83c8 (diff)
downloadpandoc-c1ae8d00ee0c021592900adaf8225a0c65c9fd42.tar.gz
LaTeX writer: properly handle footnotes in table captions.
Refactored code from figure captions to use in both places. Closes #4683.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs39
1 files changed, 22 insertions, 17 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 4c791aa44..dde4fe86d 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -517,25 +517,15 @@ blockToLaTeX (Plain lst) =
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
-- title beginning with fig: indicates that the image is a figure
blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,'f':'i':'g':':':tit)]) = do
- inNote <- gets stInNote
- inMinipage <- gets stInMinipage
- modify $ \st -> st{ stInMinipage = True, stNotes = [] }
- capt <- inlineListToLaTeX txt
- notes <- gets stNotes
- modify $ \st -> st{ stInMinipage = False, stNotes = [] }
-
- -- We can't have footnotes in the list of figures, so remove them:
- captForLof <- if null notes
- then return empty
- else brackets <$> inlineListToLaTeX (walk deNote txt)
- img <- inlineToLaTeX (Image attr txt (src,tit))
- let footnotes = notesToLaTeX notes
+ (capt, captForLof, footnotes) <- getCaption txt
lab <- labelFor ident
let caption = "\\caption" <> captForLof <> braces capt <> lab
+ img <- inlineToLaTeX (Image attr txt (src,tit))
innards <- hypertarget True ident $
"\\centering" $$ img $$ caption <> cr
let figure = cr <> "\\begin{figure}" $$ innards $$ "\\end{figure}"
- return $ if inNote || inMinipage
+ st <- get
+ return $ if stInNote st || stInMinipage st
-- can't have figures in notes or minipage (here, table cell)
-- http://www.tex.ac.uk/FAQ-ouparmd.html
then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}"
@@ -714,11 +704,11 @@ blockToLaTeX (Header level (id',classes,_) lst) = do
modify $ \s -> s{stInHeading = False}
return hdr
blockToLaTeX (Table caption aligns widths heads rows) = do
+ (captionText, captForLof, footnotes) <- getCaption caption
let toHeaders hs = do contents <- tableRowToLaTeX True aligns widths hs
return ("\\toprule" $$ contents $$ "\\midrule")
let removeNote (Note _) = Span ("", [], []) []
removeNote x = x
- captionText <- inlineListToLaTeX caption
firsthead <- if isEmpty captionText || all null heads
then return empty
else ($$ text "\\endfirsthead") <$> toHeaders heads
@@ -730,8 +720,8 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
else walk removeNote heads)
let capt = if isEmpty captionText
then empty
- else text "\\caption" <>
- braces captionText <> "\\tabularnewline"
+ else "\\caption" <> captForLof <> braces captionText
+ <> "\\tabularnewline"
rows' <- mapM (tableRowToLaTeX False aligns widths) rows
let colDescriptors = text $ concatMap toColDescriptor aligns
modify $ \s -> s{ stTable = True }
@@ -745,6 +735,21 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
$$ vcat rows'
$$ "\\bottomrule"
$$ "\\end{longtable}"
+ $$ footnotes
+
+getCaption :: PandocMonad m => [Inline] -> LW m (Doc, Doc, Doc)
+getCaption txt = do
+ inMinipage <- gets stInMinipage
+ modify $ \st -> st{ stInMinipage = True, stNotes = [] }
+ capt <- inlineListToLaTeX txt
+ notes <- gets stNotes
+ modify $ \st -> st{ stInMinipage = inMinipage, stNotes = [] }
+ -- We can't have footnotes in the list of figures/tables, so remove them:
+ captForLof <- if null notes
+ then return empty
+ else brackets <$> inlineListToLaTeX (walk deNote txt)
+ let footnotes = notesToLaTeX notes
+ return (capt, captForLof, footnotes)
toColDescriptor :: Alignment -> String
toColDescriptor align =