LaTeX writer: Use \texttt and escapes instead of \verb!..!.

\verb is simply too fragile; it doesn't work inside command
arguments.
This commit is contained in:
John MacFarlane 2011-07-22 12:19:34 -07:00
parent e3e9225ab3
commit 0cf2a631e8
4 changed files with 34 additions and 38 deletions

View file

@ -152,21 +152,13 @@ stringToLaTeX = escapeStringUsing latexEscapes
inCmd :: String -> Doc -> Doc inCmd :: String -> Doc -> Doc
inCmd cmd contents = char '\\' <> text cmd <> braces contents inCmd cmd contents = char '\\' <> text cmd <> braces contents
-- | Remove all code elements from list of inline elements
-- (because it's illegal to have verbatim inside some command arguments)
deVerb :: [Inline] -> [Inline]
deVerb [] = []
deVerb ((Code _ str):rest) =
(RawInline "latex" $ "\\texttt{" ++ stringToLaTeX str ++ "}"):(deVerb rest)
deVerb (other:rest) = other:(deVerb rest)
-- | Convert Pandoc block element to LaTeX. -- | Convert Pandoc block element to LaTeX.
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) = inlineListToLaTeX lst blockToLaTeX (Plain lst) = inlineListToLaTeX lst
blockToLaTeX (Para [Image txt (src,tit)]) = do blockToLaTeX (Para [Image txt (src,tit)]) = do
capt <- inlineListToLaTeX $ deVerb txt capt <- inlineListToLaTeX txt
img <- inlineToLaTeX (Image txt (src,tit)) img <- inlineToLaTeX (Image txt (src,tit))
return $ "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ return $ "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$
("\\caption{" <> capt <> char '}') $$ "\\end{figure}" $$ blankline ("\\caption{" <> capt <> char '}') $$ "\\end{figure}" $$ blankline
@ -250,14 +242,13 @@ blockToLaTeX (DefinitionList lst) = do
blockToLaTeX HorizontalRule = return $ blockToLaTeX HorizontalRule = return $
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}" $$ blankline "\\begin{center}\\rule{3in}{0.4pt}\\end{center}" $$ blankline
blockToLaTeX (Header level lst) = do blockToLaTeX (Header level lst) = do
let lst' = deVerb lst txt <- inlineListToLaTeX lst
txt <- inlineListToLaTeX lst'
let noNote (Note _) = Str "" let noNote (Note _) = Str ""
noNote x = x noNote x = x
let lstNoNotes = bottomUp noNote lst' let lstNoNotes = bottomUp noNote lst
-- footnotes in sections don't work unless you specify an optional -- footnotes in sections don't work unless you specify an optional
-- argument: \section[mysec]{mysec\footnote{blah}} -- argument: \section[mysec]{mysec\footnote{blah}}
optional <- if lstNoNotes == lst' optional <- if lstNoNotes == lst
then return empty then return empty
else do else do
res <- inlineListToLaTeX lstNoNotes res <- inlineListToLaTeX lstNoNotes
@ -280,7 +271,7 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
then return empty then return empty
else liftM ($$ "\\ML") else liftM ($$ "\\ML")
$ (tableRowToLaTeX True aligns widths) heads $ (tableRowToLaTeX True aligns widths) heads
captionText <- inlineListToLaTeX $ deVerb caption captionText <- inlineListToLaTeX caption
let capt = if isEmpty captionText let capt = if isEmpty captionText
then empty then empty
else text "caption = " <> captionText <> "," <> space else text "caption = " <> captionText <> "," <> space
@ -337,7 +328,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 term
def' <- liftM vsep $ mapM blockListToLaTeX defs def' <- liftM vsep $ mapM blockListToLaTeX defs
return $ "\\item" <> brackets term' $$ def' return $ "\\item" <> brackets term' $$ def'
@ -355,23 +346,23 @@ isQuoted _ = False
inlineToLaTeX :: Inline -- ^ Inline to convert inlineToLaTeX :: Inline -- ^ Inline to convert
-> State WriterState Doc -> State WriterState Doc
inlineToLaTeX (Emph lst) = inlineToLaTeX (Emph lst) =
inlineListToLaTeX (deVerb lst) >>= return . inCmd "emph" inlineListToLaTeX lst >>= return . inCmd "emph"
inlineToLaTeX (Strong lst) = inlineToLaTeX (Strong lst) =
inlineListToLaTeX (deVerb lst) >>= return . inCmd "textbf" inlineListToLaTeX lst >>= return . inCmd "textbf"
inlineToLaTeX (Strikeout lst) = do inlineToLaTeX (Strikeout lst) = do
contents <- inlineListToLaTeX $ deVerb lst contents <- inlineListToLaTeX lst
modify $ \s -> s{ stStrikeout = True } modify $ \s -> s{ stStrikeout = True }
return $ inCmd "sout" contents return $ inCmd "sout" contents
inlineToLaTeX (Superscript lst) = inlineToLaTeX (Superscript lst) =
inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsuperscript" inlineListToLaTeX lst >>= return . inCmd "textsuperscript"
inlineToLaTeX (Subscript lst) = do inlineToLaTeX (Subscript lst) = do
modify $ \s -> s{ stSubscript = True } modify $ \s -> s{ stSubscript = True }
contents <- inlineListToLaTeX $ deVerb lst contents <- inlineListToLaTeX lst
-- oddly, latex includes \textsuperscript but not \textsubscript -- oddly, latex includes \textsuperscript but not \textsubscript
-- so we have to define it (using a different name so as not to conflict with memoir class): -- so we have to define it (using a different name so as not to conflict with memoir class):
return $ inCmd "textsubscr" contents return $ inCmd "textsubscr" contents
inlineToLaTeX (SmallCaps lst) = inlineToLaTeX (SmallCaps lst) =
inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsc" inlineListToLaTeX lst >>= return . inCmd "textsc"
inlineToLaTeX (Cite cits lst) = do inlineToLaTeX (Cite cits lst) = do
st <- get st <- get
let opts = stOptions st let opts = stOptions st
@ -386,7 +377,7 @@ inlineToLaTeX (Code _ str) = do
let chr = ((enumFromTo '!' '~') \\ str) !! 0 let chr = ((enumFromTo '!' '~') \\ str) !! 0
if writerListings (stOptions st) if writerListings (stOptions st)
then return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr] then return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr]
else return $ text $ "\\verb" ++ [chr] ++ str ++ [chr] else return $ text $ "\\texttt{" ++ stringToLaTeX str ++ "}"
inlineToLaTeX (Quoted SingleQuote lst) = do inlineToLaTeX (Quoted SingleQuote lst) = do
contents <- inlineListToLaTeX lst contents <- inlineListToLaTeX lst
let s1 = if (not (null lst)) && (isQuoted (head lst)) let s1 = if (not (null lst)) && (isQuoted (head lst))
@ -422,7 +413,7 @@ inlineToLaTeX (Link txt (src, _)) =
[Code _ x] | x == src -> -- autolink [Code _ x] | x == src -> -- autolink
do modify $ \s -> s{ stUrl = True } do modify $ \s -> s{ stUrl = True }
return $ text $ "\\url{" ++ x ++ "}" return $ text $ "\\url{" ++ x ++ "}"
_ -> do contents <- inlineListToLaTeX $ deVerb txt _ -> do contents <- inlineListToLaTeX txt
return $ text ("\\href{" ++ stringToLaTeX src ++ "}{") <> return $ text ("\\href{" ++ stringToLaTeX src ++ "}{") <>
contents <> char '}' contents <> char '}'
inlineToLaTeX (Image _ (source, _)) = do inlineToLaTeX (Image _ (source, _)) = do

View file

@ -5,6 +5,7 @@
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref} \usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt} \setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt} \setlength{\parskip}{6pt plus 2pt minus 1pt}
\setlength{\emergencystretch}{3em} -- prevent overfull lines
\setcounter{secnumdepth}{0} \setcounter{secnumdepth}{0}
@ -12,7 +13,7 @@
\section{lhs test} \section{lhs test}
\verb!unsplit! is an arrow that takes a pair of values and combines them to \texttt{unsplit} is an arrow that takes a pair of values and combines them to
return a single value: return a single value:
\begin{verbatim} \begin{verbatim}
@ -20,9 +21,9 @@ unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
unsplit = arr . uncurry unsplit = arr . uncurry
-- arr (\op (x,y) -> x `op` y) -- arr (\op (x,y) -> x `op` y)
\end{verbatim} \end{verbatim}
\verb!(***)! combines two arrows into a new arrow by running the two arrows on \texttt{(***)} combines two arrows into a new arrow by running the two arrows
a pair of values (one arrow on the first item of the pair and one arrow on the on a pair of values (one arrow on the first item of the pair and one arrow on
second item of the pair). the second item of the pair).
\begin{verbatim} \begin{verbatim}
f *** g = first f >>> second g f *** g = first f >>> second g

View file

@ -7,6 +7,7 @@
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref} \usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt} \setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt} \setlength{\parskip}{6pt plus 2pt minus 1pt}
\setlength{\emergencystretch}{3em} -- prevent overfull lines
\setcounter{secnumdepth}{0} \setcounter{secnumdepth}{0}
@ -14,7 +15,7 @@
\section{lhs test} \section{lhs test}
\verb!unsplit! is an arrow that takes a pair of values and combines them to \texttt{unsplit} is an arrow that takes a pair of values and combines them to
return a single value: return a single value:
\begin{code} \begin{code}
@ -22,9 +23,9 @@ unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
unsplit = arr . uncurry unsplit = arr . uncurry
-- arr (\op (x,y) -> x `op` y) -- arr (\op (x,y) -> x `op` y)
\end{code} \end{code}
\verb!(***)! combines two arrows into a new arrow by running the two arrows on \texttt{(***)} combines two arrows into a new arrow by running the two arrows
a pair of values (one arrow on the first item of the pair and one arrow on the on a pair of values (one arrow on the first item of the pair and one arrow on
second item of the pair). the second item of the pair).
\begin{verbatim} \begin{verbatim}
f *** g = first f >>> second g f *** g = first f >>> second g

View file

@ -28,6 +28,7 @@
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref} \usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt} \setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt} \setlength{\parskip}{6pt plus 2pt minus 1pt}
\setlength{\emergencystretch}{3em} -- prevent overfull lines
\setcounter{secnumdepth}{0} \setcounter{secnumdepth}{0}
\VerbatimFootnotes % allows verbatim text in footnotes \VerbatimFootnotes % allows verbatim text in footnotes
@ -558,7 +559,8 @@ 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!\$!, \verb!<html>!. This is code: \texttt{\textgreater{}}, \texttt{\$}, \texttt{\textbackslash{}},
\texttt{\textbackslash{}\$}, \texttt{\textless{}html\textgreater{}}.
\sout{This is \emph{strikeout}.} \sout{This is \emph{strikeout}.}
@ -582,7 +584,7 @@ spaces: a\^{}b c\^{}d, a\ensuremath{\sim}b c\ensuremath{\sim}d.
`He said, ``I want to go.''\,' Were you alive in the 70's? `He said, ``I want to go.''\,' Were you alive in the 70's?
Here is some quoted `\verb!code!' and a Here is some quoted `\texttt{code}' and a
``\href{http://example.com/?foo=1\&bar=2}{quoted link}''. ``\href{http://example.com/?foo=1\&bar=2}{quoted link}''.
Some dashes: one---two --- three---four --- five. Some dashes: one---two --- three---four --- five.
@ -618,14 +620,14 @@ These shouldn't be math:
\begin{itemize} \begin{itemize}
\item \item
To get the famous equation, write \verb!$e = mc^2$!. To get the famous equation, write \texttt{\$e = mc\^{}2\$}.
\item \item
\$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if ``lot'' is \$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if ``lot'' is
emphasized.) emphasized.)
\item \item
Shoes (\$20) and socks (\$5). Shoes (\$20) and socks (\$5).
\item \item
Escaped \verb!$!: \$73 \emph{this should be emphasized} 23\$. Escaped \texttt{\$}: \$73 \emph{this should be emphasized} 23\$.
\end{itemize} \end{itemize}
Here's a LaTeX table: Here's a LaTeX table:
@ -777,7 +779,8 @@ An e-mail address:
Blockquoted: \url{http://example.com/} Blockquoted: \url{http://example.com/}
\end{quote} \end{quote}
Auto-links should not occur here: \verb!<http://example.com/>! Auto-links should not occur here:
\texttt{\textless{}http://example.com/\textgreater{}}
\begin{verbatim} \begin{verbatim}
or here: <http://example.com/> or here: <http://example.com/>
@ -815,8 +818,8 @@ Here is a footnote reference,\footnote{Here is the footnote. It can go
indent the first line of each block.} This should \emph{not} be a footnote indent the first line of each block.} This should \emph{not} be a footnote
reference, because it contains a space.{[}\^{}my note{]} Here is an inline reference, because it contains a space.{[}\^{}my note{]} Here is an inline
note.\footnote{This is \emph{easier} to type. Inline notes may contain note.\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 \texttt{{]}} verbatim characters, as
{[}bracketed text{]}.} well as {[}bracketed text{]}.}
\begin{quote} \begin{quote}
Notes can go in quotes.\footnote{In quote.} Notes can go in quotes.\footnote{In quote.}