LaTeX writer: properly handle footnotes in captions.

Closes #1506.
This commit is contained in:
John MacFarlane 2015-11-01 15:30:05 -08:00
parent c4ea64203a
commit 411a25306c

View file

@ -394,18 +394,23 @@ blockToLaTeX (Plain lst) =
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
inNote <- gets stInNote inNote <- gets stInNote
modify $ \st -> st{ stInMinipage = True, stNotes = [] }
capt <- inlineListToLaTeX txt 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: -- We can't have footnotes in the list of figures, so remove them:
captForLof <- if null (query queryNote txt) captForLof <- if null notes
then return empty then return empty
else brackets <$> inlineListToLaTeX (walk deNote txt) else brackets <$> inlineListToLaTeX (walk deNote txt)
img <- inlineToLaTeX (Image txt (src,tit)) img <- inlineToLaTeX (Image txt (src,tit))
let footnotes = notesToLaTeX notes
return $ if inNote return $ if inNote
-- can't have figures in notes -- can't have figures in notes
then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}" then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}"
else "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ else "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$
("\\caption" <> captForLof <> braces capt) $$ ("\\caption" <> captForLof <> braces capt) $$
"\\end{figure}" "\\end{figure}" $$
footnotes
-- . . . indicates pause in beamer slides -- . . . indicates pause in beamer slides
blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do
beamer <- writerBeamer `fmap` gets stOptions beamer <- writerBeamer `fmap` gets stOptions
@ -647,19 +652,21 @@ tableCellToLaTeX header (width, align, blocks) = do
return $ ("\\begin{minipage}" <> valign <> return $ ("\\begin{minipage}" <> valign <>
braces (text (printf "%.2f\\columnwidth" width)) <> braces (text (printf "%.2f\\columnwidth" width)) <>
(halign <> "\\strut" <> cr <> cellContents <> cr) <> (halign <> "\\strut" <> cr <> cellContents <> cr) <>
"\\strut\\end{minipage}") "\\strut\\end{minipage}") $$
$$ case notes of notesToLaTeX notes
[] -> empty
ns -> (case length ns of notesToLaTeX :: [Doc] -> Doc
notesToLaTeX [] = empty
notesToLaTeX ns = (case length ns of
n | n > 1 -> "\\addtocounter" <> n | n > 1 -> "\\addtocounter" <>
braces "footnote" <> braces "footnote" <>
braces (text $ show $ 1 - n) braces (text $ show $ 1 - n)
| otherwise -> empty) | otherwise -> empty)
$$ $$
vcat (intersperse vcat (intersperse
("\\addtocounter" <> braces "footnote" <> braces "1") ("\\addtocounter" <> braces "footnote" <> braces "1")
$ map (\x -> "\\footnotetext" <> braces x) $ map (\x -> "\\footnotetext" <> braces x)
$ reverse ns) $ reverse ns)
listItemToLaTeX :: [Block] -> State WriterState Doc listItemToLaTeX :: [Block] -> State WriterState Doc
listItemToLaTeX lst listItemToLaTeX lst
@ -1208,10 +1215,6 @@ commonFromBcp47 x = fromIso $ head x
fromIso "vi" = "vietnamese" fromIso "vi" = "vietnamese"
fromIso _ = "" fromIso _ = ""
queryNote :: Inline -> [Inline]
queryNote (Note xs) = [Note xs]
queryNote _ = []
deNote :: Inline -> Inline deNote :: Inline -> Inline
deNote (Note _) = RawInline (Format "latex") "" deNote (Note _) = RawInline (Format "latex") ""
deNote x = x deNote x = x