aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Shared.hs28
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs6
-rw-r--r--tests/writer.context20
-rw-r--r--tests/writer.latex10
5 files changed, 40 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 811978476..42d9acaf0 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -227,8 +227,12 @@ isNote _ = False
-- | Wrap inlines to line length, treating footnotes in a way that
-- makes sense in LaTeX and ConTeXt.
-wrappedTeX :: Monad m => ([Inline] -> m Doc) -> [Inline] -> m Doc
-wrappedTeX listWriter sect = do
+wrappedTeX :: Monad m
+ => Bool -- | Include % on line before notes.
+ -> ([Inline] -> m Doc) -- | Inline list writer.
+ -> [Inline]
+ -> m Doc
+wrappedTeX includePercent listWriter sect = do
let (firstpart, rest) = break isNote sect
firstpartWrapped <- wrapped listWriter firstpart
if null rest
@@ -236,17 +240,23 @@ wrappedTeX listWriter sect = do
else do let (note:rest') = rest
restWrapped <- if null rest'
then return empty
- else wrappedTeX listWriter rest'
+ else wrappedTeX includePercent listWriter rest'
noteText <- listWriter [note]
- return $ firstpartWrapped <> PP.char '%' $$ noteText $$ restWrapped
+ return $ firstpartWrapped <>
+ (if includePercent then PP.char '%' else empty) $$
+ noteText $$ restWrapped
-- | Wrap inlines if the text wrap option is selected, specialized
-- for LaTeX and ConTeXt.
-wrapTeXIfNeeded :: Monad m => WriterOptions -> ([Inline] -> m Doc) ->
- [Inline] -> m Doc
-wrapTeXIfNeeded opts = if writerWrapText opts
- then wrappedTeX
- else ($)
+wrapTeXIfNeeded :: Monad m
+ => WriterOptions
+ -> Bool -- | Include % on line before notes.
+ -> ([Inline] -> m Doc) -- | Inline list writer.
+ -> [Inline]
+ -> m Doc
+wrapTeXIfNeeded opts includePercent = if writerWrapText opts
+ then wrappedTeX includePercent
+ else ($)
--
-- Parsing
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 612f7360b..40cd721c6 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -116,9 +116,9 @@ blockToConTeXt :: WriterOptions
-> State WriterState Doc
blockToConTeXt opts Null = return empty
blockToConTeXt opts (Plain lst) =
- wrapTeXIfNeeded opts (inlineListToConTeXt opts) lst >>= return
+ wrapTeXIfNeeded opts False (inlineListToConTeXt opts) lst >>= return
blockToConTeXt opts (Para lst) =
- wrapTeXIfNeeded opts (inlineListToConTeXt opts) lst >>= return . (<> char '\n')
+ wrapTeXIfNeeded opts False (inlineListToConTeXt opts) lst >>= return . (<> char '\n')
blockToConTeXt opts (BlockQuote lst) = do
contents <- blockListToConTeXt opts lst
return $ text "\\startblockquote\n" $$ contents $$ text "\\stopblockquote"
@@ -270,7 +270,7 @@ inlineToConTeXt opts (Image alternate (src, tit)) = do
text tit <> text "}\n{\\externalfigure[" <> text src <> text "]}"
inlineToConTeXt opts (Note contents) = do
contents' <- blockListToConTeXt opts contents
- return $ text "\\footnote{" <>
+ return $ text " \\footnote{" <>
text (stripTrailingNewlines $ render contents') <>
char '}'
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index dd290569f..88050cc65 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -137,11 +137,11 @@ blockToLaTeX Null = return empty
blockToLaTeX (Plain lst) = do
st <- get
let opts = stOptions st
- wrapTeXIfNeeded opts inlineListToLaTeX lst
+ wrapTeXIfNeeded opts True inlineListToLaTeX lst
blockToLaTeX (Para lst) = do
st <- get
let opts = stOptions st
- result <- wrapTeXIfNeeded opts inlineListToLaTeX lst
+ result <- wrapTeXIfNeeded opts True inlineListToLaTeX lst
return $ result <> char '\n'
blockToLaTeX (BlockQuote lst) = do
contents <- blockListToLaTeX lst
@@ -314,5 +314,5 @@ inlineToLaTeX (Note contents) = do
let rawnote = stripTrailingNewlines $ render contents'
-- note: a \n before } is needed when note ends with a Verbatim environment
let optNewline = "\\end{Verbatim}" `isSuffixOf` rawnote
- return $ text "\\footnote{" <>
+ return $ text " \\footnote{" <>
text rawnote <> (if optNewline then char '\n' else empty) <> char '}'
diff --git a/tests/writer.context b/tests/writer.context
index 98cbe8a98..ae417a051 100644
--- a/tests/writer.context
+++ b/tests/writer.context
@@ -821,11 +821,11 @@ Here is a movie
\subject{Footnotes}
-Here is a footnote reference,%
-\footnote{Here is the footnote. It can go anywhere after the footnote
+Here is a footnote reference,
+ \footnote{Here is the footnote. It can go anywhere after the footnote
reference. It need not be placed at the end of the document.}
-and another.%
-\footnote{Here's the long note. This one contains multiple blocks.
+and another.
+ \footnote{Here's the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the
footnote (as with list items).
@@ -837,20 +837,20 @@ footnote (as with list items).
If you want, you can indent every line, but you can also be lazy
and just indent the first line of each block.}
This should {\em not} be a footnote reference, because it contains
-a space.[\letterhat{}my note] Here is an inline note.%
-\footnote{This is {\em easier} to type. Inline notes may contain
+a space.[\letterhat{}my note] Here is an inline note.
+ \footnote{This is {\em easier} to type. Inline notes may contain
\useurl[31][http://google.com][][links]\from[31] and \type{]}
verbatim characters, as well as [bracketed text].}
\startblockquote
-Notes can go in quotes.%
-\footnote{In quote.}
+Notes can go in quotes.
+ \footnote{In quote.}
\stopblockquote
\startitemize
\sym{1.}
- And in list items.%
- \footnote{In list.}
+ And in list items.
+ \footnote{In list.}
\stopitemize
This paragraph should not be part of the note, as it is not
indented.
diff --git a/tests/writer.latex b/tests/writer.latex
index 0d19d6296..bbb430809 100644
--- a/tests/writer.latex
+++ b/tests/writer.latex
@@ -792,10 +792,10 @@ Here is a movie \includegraphics{movie.jpg} icon.
\section{Footnotes}
Here is a footnote reference,%
-\footnote{Here is the footnote. It can go anywhere after the footnote
+ \footnote{Here is the footnote. It can go anywhere after the footnote
reference. It need not be placed at the end of the document.}
and another.%
-\footnote{Here's the long note. This one contains multiple blocks.
+ \footnote{Here's the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the
footnote (as with list items).
@@ -807,19 +807,19 @@ If you want, you can indent every line, but you can also be lazy
and just 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
+ \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].}
\begin{quote}
Notes can go in quotes.%
-\footnote{In quote.}
+ \footnote{In quote.}
\end{quote}
\begin{enumerate}[1.]
\item
And in list items.%
- \footnote{In list.}
+ \footnote{In list.}
\end{enumerate}
This paragraph should not be part of the note, as it is not
indented.