aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2007-11-17 18:42:11 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2007-11-17 18:42:11 +0000
commit09b57fcf9ca4deab5fd7d8979863b36922edf6c3 (patch)
treef5d71e92b481163cbbf46b9dfe38dd9dfd7ffcc5 /src/Text/Pandoc
parent780b77c14790f8053f7b2c8239bb4a5d6a22c8d7 (diff)
downloadpandoc-09b57fcf9ca4deab5fd7d8979863b36922edf6c3.tar.gz
Adjusted formatting of LaTeX and ConTeXt footnotes:
- in ConTeXt, % is not needed at end of line before note, since space is gobbled. - beginning of footnote indented four spaces. - this required an additional parameter in wrappedTeX and wrapTeXIfNeeded, in Text.Pandoc.Shared. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1080 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src/Text/Pandoc')
-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
3 files changed, 25 insertions, 15 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 '}'