diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ea3d471fe..5e5567aec 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -152,21 +152,13 @@ stringToLaTeX = escapeStringUsing latexEscapes
inCmd :: String -> Doc -> Doc
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.
blockToLaTeX :: Block -- ^ Block to convert
-> State WriterState Doc
blockToLaTeX Null = return empty
blockToLaTeX (Plain lst) = inlineListToLaTeX lst
blockToLaTeX (Para [Image txt (src,tit)]) = do
- capt <- inlineListToLaTeX $ deVerb txt
+ capt <- inlineListToLaTeX txt
img <- inlineToLaTeX (Image txt (src,tit))
return $ "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$
("\\caption{" <> capt <> char '}') $$ "\\end{figure}" $$ blankline
@@ -250,14 +242,13 @@ blockToLaTeX (DefinitionList lst) = do
blockToLaTeX HorizontalRule = return $
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}" $$ blankline
blockToLaTeX (Header level lst) = do
- let lst' = deVerb lst
- txt <- inlineListToLaTeX lst'
+ txt <- inlineListToLaTeX lst
let noNote (Note _) = Str ""
noNote x = x
- let lstNoNotes = bottomUp noNote lst'
+ let lstNoNotes = bottomUp noNote lst
-- footnotes in sections don't work unless you specify an optional
-- argument: \section[mysec]{mysec\footnote{blah}}
- optional <- if lstNoNotes == lst'
+ optional <- if lstNoNotes == lst
then return empty
else do
res <- inlineListToLaTeX lstNoNotes
@@ -280,7 +271,7 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
then return empty
else liftM ($$ "\\ML")
$ (tableRowToLaTeX True aligns widths) heads
- captionText <- inlineListToLaTeX $ deVerb caption
+ captionText <- inlineListToLaTeX caption
let capt = if isEmpty captionText
then empty
else text "caption = " <> captionText <> "," <> space
@@ -337,7 +328,7 @@ listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc
defListItemToLaTeX (term, defs) = do
- term' <- inlineListToLaTeX $ deVerb term
+ term' <- inlineListToLaTeX term
def' <- liftM vsep $ mapM blockListToLaTeX defs
return $ "\\item" <> brackets term' $$ def'
@@ -355,23 +346,23 @@ isQuoted _ = False
inlineToLaTeX :: Inline -- ^ Inline to convert
-> State WriterState Doc
inlineToLaTeX (Emph lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "emph"
+ inlineListToLaTeX lst >>= return . inCmd "emph"
inlineToLaTeX (Strong lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "textbf"
+ inlineListToLaTeX lst >>= return . inCmd "textbf"
inlineToLaTeX (Strikeout lst) = do
- contents <- inlineListToLaTeX $ deVerb lst
+ contents <- inlineListToLaTeX lst
modify $ \s -> s{ stStrikeout = True }
return $ inCmd "sout" contents
inlineToLaTeX (Superscript lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsuperscript"
+ inlineListToLaTeX lst >>= return . inCmd "textsuperscript"
inlineToLaTeX (Subscript lst) = do
modify $ \s -> s{ stSubscript = True }
- contents <- inlineListToLaTeX $ deVerb lst
+ contents <- inlineListToLaTeX lst
-- 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):
return $ inCmd "textsubscr" contents
inlineToLaTeX (SmallCaps lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsc"
+ inlineListToLaTeX lst >>= return . inCmd "textsc"
inlineToLaTeX (Cite cits lst) = do
st <- get
let opts = stOptions st
@@ -386,7 +377,7 @@ inlineToLaTeX (Code _ str) = do
let chr = ((enumFromTo '!' '~') \\ str) !! 0
if writerListings (stOptions st)
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
contents <- inlineListToLaTeX lst
let s1 = if (not (null lst)) && (isQuoted (head lst))
@@ -422,7 +413,7 @@ inlineToLaTeX (Link txt (src, _)) =
[Code _ x] | x == src -> -- autolink
do modify $ \s -> s{ stUrl = True }
return $ text $ "\\url{" ++ x ++ "}"
- _ -> do contents <- inlineListToLaTeX $ deVerb txt
+ _ -> do contents <- inlineListToLaTeX txt
return $ text ("\\href{" ++ stringToLaTeX src ++ "}{") <>
contents <> char '}'
inlineToLaTeX (Image _ (source, _)) = do
diff --git a/tests/lhs-test.latex b/tests/lhs-test.latex
index d34c21090..f8851900a 100644
--- a/tests/lhs-test.latex
+++ b/tests/lhs-test.latex
@@ -5,6 +5,7 @@
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt}
+\setlength{\emergencystretch}{3em} -- prevent overfull lines
\setcounter{secnumdepth}{0}
@@ -12,7 +13,7 @@
\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:
\begin{verbatim}
@@ -20,9 +21,9 @@ unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
unsplit = arr . uncurry
-- arr (\op (x,y) -> x `op` y)
\end{verbatim}
-\verb!(***)! combines two arrows into a new arrow by running the two arrows on
-a pair of values (one arrow on the first item of the pair and one arrow on the
-second item of the pair).
+\texttt{(***)} combines two arrows into a new arrow by running the two arrows
+on a pair of values (one arrow on the first item of the pair and one arrow on
+the second item of the pair).
\begin{verbatim}
f *** g = first f >>> second g
diff --git a/tests/lhs-test.latex+lhs b/tests/lhs-test.latex+lhs
index 29237f820..6222866ea 100644
--- a/tests/lhs-test.latex+lhs
+++ b/tests/lhs-test.latex+lhs
@@ -7,6 +7,7 @@
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt}
+\setlength{\emergencystretch}{3em} -- prevent overfull lines
\setcounter{secnumdepth}{0}
@@ -14,7 +15,7 @@
\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:
\begin{code}
@@ -22,9 +23,9 @@ unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
unsplit = arr . uncurry
-- arr (\op (x,y) -> x `op` y)
\end{code}
-\verb!(***)! combines two arrows into a new arrow by running the two arrows on
-a pair of values (one arrow on the first item of the pair and one arrow on the
-second item of the pair).
+\texttt{(***)} combines two arrows into a new arrow by running the two arrows
+on a pair of values (one arrow on the first item of the pair and one arrow on
+the second item of the pair).
\begin{verbatim}
f *** g = first f >>> second g
diff --git a/tests/writer.latex b/tests/writer.latex
index 8cf7d4887..b13f93ac4 100644
--- a/tests/writer.latex
+++ b/tests/writer.latex
@@ -28,6 +28,7 @@
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt}
+\setlength{\emergencystretch}{3em} -- prevent overfull lines
\setcounter{secnumdepth}{0}
\VerbatimFootnotes % allows verbatim text in footnotes
@@ -558,7 +559,8 @@ So is \textbf{\emph{this}} word.
So is \textbf{\emph{this}} word.
-This is code: \verb!>!, \verb!$!, \verb!\!, \verb!\$!, \verb!!.
+This is code: \texttt{\textgreater{}}, \texttt{\$}, \texttt{\textbackslash{}},
+\texttt{\textbackslash{}\$}, \texttt{\textless{}html\textgreater{}}.
\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?
-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}''.
Some dashes: one---two --- three---four --- five.
@@ -618,14 +620,14 @@ These shouldn't be math:
\begin{itemize}
\item
- To get the famous equation, write \verb!$e = mc^2$!.
+ To get the famous equation, write \texttt{\$e = mc\^{}2\$}.
\item
\$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if ``lot'' is
emphasized.)
\item
Shoes (\$20) and socks (\$5).
\item
- Escaped \verb!$!: \$73 \emph{this should be emphasized} 23\$.
+ Escaped \texttt{\$}: \$73 \emph{this should be emphasized} 23\$.
\end{itemize}
Here's a LaTeX table:
@@ -777,7 +779,8 @@ An e-mail address:
Blockquoted: \url{http://example.com/}
\end{quote}
-Auto-links should not occur here: \verb!!
+Auto-links should not occur here:
+\texttt{\textless{}http://example.com/\textgreater{}}
\begin{verbatim}
or here:
@@ -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
reference, because it contains a space.{[}\^{}my note{]} Here is an inline
note.\footnote{This is \emph{easier} to type. Inline notes may contain
- \href{http://google.com}{links} and \verb!]! verbatim characters, as well as
- {[}bracketed text{]}.}
+ \href{http://google.com}{links} and \texttt{{]}} verbatim characters, as
+ well as {[}bracketed text{]}.}
\begin{quote}
Notes can go in quotes.\footnote{In quote.}