LaTeX writer: Modified to use Pretty.

Improved footnote formatting, removed spurious blank lines.
This commit is contained in:
John MacFarlane 2010-12-19 10:13:55 -08:00
parent 09aec9f3e3
commit 99a58e51f5
2 changed files with 65 additions and 106 deletions

View file

@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{- {-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu> Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
@ -32,10 +33,10 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Text.Pandoc.Templates import Text.Pandoc.Templates
import Text.Printf ( printf ) import Text.Printf ( printf )
import Data.List ( (\\), isSuffixOf, isPrefixOf, intersperse, intercalate ) import Data.List ( (\\), isSuffixOf, isPrefixOf, intercalate )
import Data.Char ( toLower, isPunctuation ) import Data.Char ( toLower, isPunctuation )
import Control.Monad.State import Control.Monad.State
import Text.PrettyPrint.HughesPJ hiding ( Str ) import Text.Pandoc.Pretty
import System.FilePath (dropExtension) import System.FilePath (dropExtension)
data WriterState = data WriterState =
@ -71,17 +72,21 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
"{report}" `isSuffixOf` x) "{report}" `isSuffixOf` x)
when (any usesBookClass (lines template)) $ when (any usesBookClass (lines template)) $
modify $ \s -> s{stBook = True} modify $ \s -> s{stBook = True}
titletext <- liftM render $ inlineListToLaTeX title opts <- liftM stOptions get
authorsText <- mapM (liftM render . inlineListToLaTeX) authors let colwidth = if writerWrapText opts
dateText <- liftM render $ inlineListToLaTeX date then Just $ writerColumns opts
else Nothing
titletext <- liftM (render colwidth) $ inlineListToLaTeX title
authorsText <- mapM (liftM (render colwidth) . inlineListToLaTeX) authors
dateText <- liftM (render colwidth) $ inlineListToLaTeX date
let (blocks', lastHeader) = if writerCiteMethod options == Citeproc then let (blocks', lastHeader) = if writerCiteMethod options == Citeproc then
(blocks, []) (blocks, [])
else case last blocks of else case last blocks of
Header 1 il -> (init blocks, il) Header 1 il -> (init blocks, il)
_ -> (blocks, []) _ -> (blocks, [])
body <- blockListToLaTeX blocks' body <- blockListToLaTeX blocks'
biblioTitle <- liftM render $ inlineListToLaTeX lastHeader biblioTitle <- liftM (render colwidth) $ inlineListToLaTeX lastHeader
let main = render body let main = render colwidth body
st <- get st <- get
let biblioFiles = intercalate "," $ map dropExtension $ writerBiblioFiles options let biblioFiles = intercalate "," $ map dropExtension $ writerBiblioFiles options
citecontext = case writerCiteMethod options of citecontext = case writerCiteMethod options of
@ -152,20 +157,15 @@ deVerb (other:rest) = other:(deVerb rest)
blockToLaTeX :: Block -- ^ Block to convert blockToLaTeX :: Block -- ^ Block to convert
-> State WriterState Doc -> State WriterState Doc
blockToLaTeX Null = return empty blockToLaTeX Null = return empty
blockToLaTeX (Plain lst) = do blockToLaTeX (Plain lst) = inlineListToLaTeX lst
st <- get
let opts = stOptions st
wrapTeXIfNeeded opts True inlineListToLaTeX lst
blockToLaTeX (Para [Image txt (src,tit)]) = do blockToLaTeX (Para [Image txt (src,tit)]) = do
capt <- inlineListToLaTeX txt capt <- inlineListToLaTeX txt
img <- inlineToLaTeX (Image txt (src,tit)) img <- inlineToLaTeX (Image txt (src,tit))
return $ text "\\begin{figure}[htb]" $$ text "\\centering" $$ img $$ return $ text "\\begin{figure}[htb]" $$ text "\\centering" $$ img $$
(text "\\caption{" <> capt <> char '}') $$ text "\\end{figure}\n" (text "\\caption{" <> capt <> char '}') $$ text "\\end{figure}" $$ blankline
blockToLaTeX (Para lst) = do blockToLaTeX (Para lst) = do
st <- get result <- inlineListToLaTeX lst
let opts = stOptions st return $ result <> blankline
result <- wrapTeXIfNeeded opts True inlineListToLaTeX lst
return $ result <> char '\n'
blockToLaTeX (BlockQuote lst) = do blockToLaTeX (BlockQuote lst) = do
contents <- blockListToLaTeX lst contents <- blockListToLaTeX lst
return $ text "\\begin{quote}" $$ contents $$ text "\\end{quote}" return $ text "\\begin{quote}" $$ contents $$ text "\\end{quote}"
@ -181,8 +181,8 @@ blockToLaTeX (CodeBlock (_,classes,_) str) = do
modify $ \s -> s{ stVerbInNote = True } modify $ \s -> s{ stVerbInNote = True }
return "Verbatim" return "Verbatim"
else return "verbatim" else return "verbatim"
return $ text ("\\begin{" ++ env ++ "}\n") <> text str <> return $ "\\begin{" <> text env <> "}" $$ flush (text str) $$
text ("\n\\end{" ++ env ++ "}") "\\end{" <> text env <> "}" $$ cr -- final cr needed because of footnotes
blockToLaTeX (RawHtml _) = return empty blockToLaTeX (RawHtml _) = return empty
blockToLaTeX (BulletList lst) = do blockToLaTeX (BulletList lst) = do
items <- mapM listItemToLaTeX lst items <- mapM listItemToLaTeX lst
@ -211,8 +211,8 @@ blockToLaTeX (DefinitionList lst) = do
items <- mapM defListItemToLaTeX lst items <- mapM defListItemToLaTeX lst
return $ text "\\begin{description}" $$ vcat items $$ return $ text "\\begin{description}" $$ vcat items $$
text "\\end{description}" text "\\end{description}"
blockToLaTeX HorizontalRule = return $ text $ blockToLaTeX HorizontalRule = return $
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}\n" "\\begin{center}\\rule{3in}{0.4pt}\\end{center}" $$ blankline
blockToLaTeX (Header level lst) = do blockToLaTeX (Header level lst) = do
let lst' = deVerb lst let lst' = deVerb lst
txt <- inlineListToLaTeX lst' txt <- inlineListToLaTeX lst'
@ -229,7 +229,7 @@ blockToLaTeX (Header level lst) = do
let stuffing = optional <> char '{' <> txt <> char '}' let stuffing = optional <> char '{' <> txt <> char '}'
book <- liftM stBook get book <- liftM stBook get
let level' = if book then level - 1 else level let level' = if book then level - 1 else level
let headerWith x y = text x <> y <> char '\n' let headerWith x y = text x <> y $$ blankline
return $ case level' of return $ case level' of
0 -> headerWith "\\chapter" stuffing 0 -> headerWith "\\chapter" stuffing
1 -> headerWith "\\section" stuffing 1 -> headerWith "\\section" stuffing
@ -237,7 +237,7 @@ blockToLaTeX (Header level lst) = do
3 -> headerWith "\\subsubsection" stuffing 3 -> headerWith "\\subsubsection" stuffing
4 -> headerWith "\\paragraph" stuffing 4 -> headerWith "\\paragraph" stuffing
5 -> headerWith "\\subparagraph" stuffing 5 -> headerWith "\\subparagraph" stuffing
_ -> txt <> char '\n' _ -> txt $$ blankline
blockToLaTeX (Table caption aligns widths heads rows) = do blockToLaTeX (Table caption aligns widths heads rows) = do
headers <- if all null heads headers <- if all null heads
then return empty then return empty
@ -246,13 +246,13 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
rows' <- mapM tableRowToLaTeX rows rows' <- mapM tableRowToLaTeX rows
let colDescriptors = concat $ zipWith toColDescriptor widths aligns let colDescriptors = concat $ zipWith toColDescriptor widths aligns
let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$ let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$
headers $$ vcat rows' $$ text "\\end{tabular}" headers $$ vcat rows' $$ text "\\end{tabular}"
let centered txt = text "\\begin{center}" $$ txt $$ text "\\end{center}" let centered txt = text "\\begin{center}" $$ txt $$ text "\\end{center}"
modify $ \s -> s{ stTable = True } modify $ \s -> s{ stTable = True }
return $ if isEmpty captionText return $ if isEmpty captionText
then centered tableBody <> char '\n' then centered tableBody $$ blankline
else text "\\begin{table}[h]" $$ centered tableBody $$ else text "\\begin{table}[h]" $$ centered tableBody $$
inCmd "caption" captionText $$ text "\\end{table}\n" inCmd "caption" captionText $$ text "\\end{table}" $$ blankline
toColDescriptor :: Double -> Alignment -> String toColDescriptor :: Double -> Alignment -> String
toColDescriptor 0 align = toColDescriptor 0 align =
@ -285,7 +285,7 @@ listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc
defListItemToLaTeX (term, defs) = do defListItemToLaTeX (term, defs) = do
term' <- inlineListToLaTeX $ deVerb term term' <- inlineListToLaTeX $ deVerb term
def' <- liftM (vcat . intersperse (text "")) $ mapM blockListToLaTeX defs def' <- liftM vsep $ mapM blockListToLaTeX defs
return $ text "\\item[" <> term' <> text "]" $$ def' return $ text "\\item[" <> term' <> text "]" $$ def'
-- | Convert list of inline elements to LaTeX. -- | Convert list of inline elements to LaTeX.
@ -360,7 +360,7 @@ inlineToLaTeX (Math DisplayMath str) = return $ text "\\[" <> text str <> text "
inlineToLaTeX (TeX str) = return $ text str inlineToLaTeX (TeX str) = return $ text str
inlineToLaTeX (HtmlInline _) = return empty inlineToLaTeX (HtmlInline _) = return empty
inlineToLaTeX (LineBreak) = return $ text "\\\\" inlineToLaTeX (LineBreak) = return $ text "\\\\"
inlineToLaTeX Space = return $ char ' ' inlineToLaTeX Space = return space
inlineToLaTeX (Link txt (src, _)) = inlineToLaTeX (Link txt (src, _)) =
case txt of case txt of
[Code x] | x == src -> -- autolink [Code x] | x == src -> -- autolink
@ -373,15 +373,11 @@ inlineToLaTeX (Image _ (source, _)) = do
modify $ \s -> s{ stGraphics = True } modify $ \s -> s{ stGraphics = True }
return $ text $ "\\includegraphics{" ++ source ++ "}" return $ text $ "\\includegraphics{" ++ source ++ "}"
inlineToLaTeX (Note contents) = do inlineToLaTeX (Note contents) = do
st <- get modify (\s -> s{stInNote = True})
put (st {stInNote = True})
contents' <- blockListToLaTeX contents contents' <- blockListToLaTeX contents
modify (\s -> s {stInNote = False}) modify (\s -> s {stInNote = False})
let rawnote = stripTrailingNewlines $ render contents'
-- note: a \n before } is needed when note ends with a Verbatim environment -- note: a \n before } is needed when note ends with a Verbatim environment
let optNewline = "\\end{Verbatim}" `isSuffixOf` rawnote return $ text "\\footnote{" <> nest 2 contents' <> char '}'
return $ text "\\footnote{" <>
text rawnote <> (if optNewline then char '\n' else empty) <> char '}'
citationsToNatbib :: [Citation] -> State WriterState Doc citationsToNatbib :: [Citation] -> State WriterState Doc

View file

@ -36,8 +36,8 @@
\begin{document} \begin{document}
\maketitle \maketitle
This is a set of tests for pandoc. Most of them are adapted from This is a set of tests for pandoc. Most of them are adapted from John Gruber's
John Gruber's markdown test suite. markdown test suite.
\begin{center}\rule{3in}{0.4pt}\end{center} \begin{center}\rule{3in}{0.4pt}\end{center}
@ -69,9 +69,9 @@ with no blank line
Here's a regular paragraph. Here's a regular paragraph.
In Markdown 1.0.0 and earlier. Version 8. This line turns into a In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item.
list item. Because a hard-wrapped line in the middle of a paragraph Because a hard-wrapped line in the middle of a paragraph looked like a list
looked like a list item. item.
Here's one with a bullet. * criminey. Here's one with a bullet. * criminey.
@ -161,13 +161,10 @@ Asterisks loose:
\begin{itemize} \begin{itemize}
\item \item
asterisk 1 asterisk 1
\item \item
asterisk 2 asterisk 2
\item \item
asterisk 3 asterisk 3
\end{itemize} \end{itemize}
Pluses tight: Pluses tight:
@ -184,13 +181,10 @@ Pluses loose:
\begin{itemize} \begin{itemize}
\item \item
Plus 1 Plus 1
\item \item
Plus 2 Plus 2
\item \item
Plus 3 Plus 3
\end{itemize} \end{itemize}
Minuses tight: Minuses tight:
@ -207,13 +201,10 @@ Minuses loose:
\begin{itemize} \begin{itemize}
\item \item
Minus 1 Minus 1
\item \item
Minus 2 Minus 2
\item \item
Minus 3 Minus 3
\end{itemize} \end{itemize}
\subsection{Ordered} \subsection{Ordered}
@ -242,26 +233,20 @@ Loose using tabs:
\begin{enumerate}[1.] \begin{enumerate}[1.]
\item \item
First First
\item \item
Second Second
\item \item
Third Third
\end{enumerate} \end{enumerate}
and using spaces: and using spaces:
\begin{enumerate}[1.] \begin{enumerate}[1.]
\item \item
One One
\item \item
Two Two
\item \item
Three Three
\end{enumerate} \end{enumerate}
Multiple paragraphs: Multiple paragraphs:
@ -269,15 +254,11 @@ Multiple paragraphs:
\item \item
Item 1, graf one. Item 1, graf one.
Item 1. graf two. The quick brown fox jumped over the lazy dog's Item 1. graf two. The quick brown fox jumped over the lazy dog's back.
back.
\item \item
Item 2. Item 2.
\item \item
Item 3. Item 3.
\end{enumerate} \end{enumerate}
\subsection{Nested} \subsection{Nested}
@ -316,7 +297,6 @@ Same thing but with paragraphs:
\begin{enumerate}[1.] \begin{enumerate}[1.]
\item \item
First First
\item \item
Second: Second:
@ -330,24 +310,20 @@ Same thing but with paragraphs:
\end{itemize} \end{itemize}
\item \item
Third Third
\end{enumerate} \end{enumerate}
\subsection{Tabs and spaces} \subsection{Tabs and spaces}
\begin{itemize} \begin{itemize}
\item \item
this is a list item indented with tabs this is a list item indented with tabs
\item \item
this is a list item indented with spaces this is a list item indented with spaces
\begin{itemize} \begin{itemize}
\item \item
this is an example list item indented with tabs this is an example list item indented with tabs
\item \item
this is an example list item indented with spaces this is an example list item indented with spaces
\end{itemize} \end{itemize}
\end{itemize} \end{itemize}
\subsection{Fancy list markers} \subsection{Fancy list markers}
@ -487,13 +463,11 @@ Multiple definitions, loose:
\item[apple] \item[apple]
red fruit red fruit
computer computer
\item[orange] \item[orange]
orange fruit orange fruit
bank bank
\end{description} \end{description}
@ -503,7 +477,6 @@ Blank line after term, indented marker, alternate markers:
\item[apple] \item[apple]
red fruit red fruit
computer computer
\item[orange] \item[orange]
@ -583,20 +556,17 @@ So is \textbf{\emph{this}} word.
So is \textbf{\emph{this}} word. So is \textbf{\emph{this}} word.
This is code: \verb!>!, \verb!$!, \verb!\!, \verb!\$!, This is code: \verb!>!, \verb!$!, \verb!\!, \verb!\$!, \verb!<html>!.
\verb!<html>!.
\sout{This is \emph{strikeout}.} \sout{This is \emph{strikeout}.}
Superscripts: a\textsuperscript{bc}d Superscripts: a\textsuperscript{bc}d a\textsuperscript{\emph{hello}}
a\textsuperscript{\emph{hello}} a\textsuperscript{hello~there}. a\textsuperscript{hello~there}.
Subscripts: H\textsubscr{2}O, H\textsubscr{23}O, Subscripts: H\textsubscr{2}O, H\textsubscr{23}O, H\textsubscr{many~of~them}O.
H\textsubscr{many~of~them}O.
These should not be superscripts or subscripts, because of the These should not be superscripts or subscripts, because of the unescaped
unescaped spaces: a\^{}b c\^{}d, a\ensuremath{\sim}b spaces: a\^{}b c\^{}d, a\ensuremath{\sim}b c\ensuremath{\sim}d.
c\ensuremath{\sim}d.
\begin{center}\rule{3in}{0.4pt}\end{center} \begin{center}\rule{3in}{0.4pt}\end{center}
@ -640,8 +610,7 @@ Ellipses\ldots{}and\ldots{}and\ldots{}.
Here's some display math: Here's some display math:
\[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\] \[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\]
\item \item
Here's one that has a line break in it: Here's one that has a line break in it: $\alpha + \omega \times x^2$.
$\alpha + \omega \times x^2$.
\end{itemize} \end{itemize}
These shouldn't be math: These shouldn't be math:
@ -649,8 +618,8 @@ These shouldn't be math:
\item \item
To get the famous equation, write \verb!$e = mc^2$!. To get the famous equation, write \verb!$e = mc^2$!.
\item \item
\$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if \$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if ``lot'' is
``lot'' is emphasized.) emphasized.)
\item \item
Shoes (\$20) and socks (\$5). Shoes (\$20) and socks (\$5).
\item \item
@ -777,16 +746,15 @@ Foo \href{/url/}{biz}.
\subsection{With ampersands} \subsection{With ampersands}
Here's a Here's a \href{http://example.com/?foo=1&bar=2}{link with an ampersand in the
\href{http://example.com/?foo=1&bar=2}{link with an ampersand in the URL}. URL}.
Here's a link with an amersand in the link text: Here's a link with an amersand in the link text:
\href{http://att.com/}{AT\&T}. \href{http://att.com/}{AT\&T}.
Here's an \href{/script?foo=1&bar=2}{inline link}. Here's an \href{/script?foo=1&bar=2}{inline link}.
Here's an Here's an \href{/script?foo=1&bar=2}{inline link in pointy braces}.
\href{/script?foo=1&bar=2}{inline link in pointy braces}.
\subsection{Autolinks} \subsection{Autolinks}
@ -830,37 +798,32 @@ Here is a movie \includegraphics{movie.jpg} icon.
\section{Footnotes} \section{Footnotes}
Here is a footnote reference,% Here is a footnote reference,\footnote{Here is the footnote. It can go
\footnote{Here is the footnote. It can go anywhere after the footnote anywhere after the footnote reference. It need not be placed at the end of
reference. It need not be placed at the end of the document.} the document.} and another.\footnote{Here's the long note. This one contains
and another.% multiple blocks.
\footnote{Here's the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the Subsequent blocks are indented to show that they belong to the footnote (as
footnote (as with list items). with list items).
\begin{Verbatim} \begin{Verbatim}
{ <code> } { <code> }
\end{Verbatim} \end{Verbatim}
If you want, you can indent every line, but you can also be lazy If you want, you can indent every line, but you can also be lazy and just
and just indent the first line of each block.} indent the first line of each block.} This should \emph{not} be a footnote
This should \emph{not} be a footnote reference, because it contains reference, because it contains a space.{[}\^{}my note{]} Here is an inline
a space.{[}\^{}my note{]} Here is an inline note.% note.\footnote{This is \emph{easier} to type. Inline notes may contain
\footnote{This is \emph{easier} to type. Inline notes may contain \href{http://google.com}{links} and \verb!]! verbatim characters, as well as
\href{http://google.com}{links} and \verb!]! verbatim characters, {[}bracketed text{]}.}
as well as {[}bracketed text{]}.}
\begin{quote} \begin{quote}
Notes can go in quotes.% Notes can go in quotes.\footnote{In quote.}
\footnote{In quote.}
\end{quote} \end{quote}
\begin{enumerate}[1.] \begin{enumerate}[1.]
\item \item
And in list items.% And in list items.\footnote{In list.}
\footnote{In list.}
\end{enumerate} \end{enumerate}
This paragraph should not be part of the note, as it is not This paragraph should not be part of the note, as it is not indented.
indented.
\end{document} \end{document}