aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2007-11-15 03:09:31 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2007-11-15 03:09:31 +0000
commite73c3d3561a743e0687536695e8241e9eaa3f565 (patch)
tree909db372393f04ec6d01a13416dbab4b550e49b3 /src/Text
parent1ba0c8f483e35b1e33b61c9ca66dad3b57cb836a (diff)
downloadpandoc-e73c3d3561a743e0687536695e8241e9eaa3f565.tar.gz
Added wrappedTeX and wrapTeXIfNeeded functions to Text.Pandoc.Shared.
These ensure that footnotes occur on lines by themselves (to make them easier to move around), and that they don't screw up text wrapping. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1070 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Shared.hs33
1 files changed, 32 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index f27c3ae75..811978476 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -45,6 +45,8 @@ module Text.Pandoc.Shared (
toRomanNumeral,
wrapped,
wrapIfNeeded,
+ wrappedTeX,
+ wrapTeXIfNeeded,
-- * Parsing
(>>~),
anyLine,
@@ -96,7 +98,8 @@ module Text.Pandoc.Shared (
import Text.Pandoc.Definition
import Text.ParserCombinators.Parsec
-import Text.PrettyPrint.HughesPJ ( Doc, fsep )
+import Text.PrettyPrint.HughesPJ ( Doc, fsep, ($$), (<>), empty )
+import qualified Text.PrettyPrint.HughesPJ as PP
import Text.Pandoc.CharacterReferences ( characterReference )
import Data.Char ( toLower, toUpper, ord, isLower, isUpper )
import Data.List ( find, isPrefixOf )
@@ -211,12 +214,40 @@ wrapped :: Monad m => ([Inline] -> m Doc) -> [Inline] -> m Doc
wrapped listWriter sect = (mapM listWriter $ splitBy Space sect) >>=
return . fsep
+-- | Wrap inlines if the text wrap option is selected.
wrapIfNeeded :: Monad m => WriterOptions -> ([Inline] -> m Doc) ->
[Inline] -> m Doc
wrapIfNeeded opts = if writerWrapText opts
then wrapped
else ($)
+-- auxiliary function for wrappedTeX
+isNote (Note _) = True
+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
+ let (firstpart, rest) = break isNote sect
+ firstpartWrapped <- wrapped listWriter firstpart
+ if null rest
+ then return firstpartWrapped
+ else do let (note:rest') = rest
+ restWrapped <- if null rest'
+ then return empty
+ else wrappedTeX listWriter rest'
+ noteText <- listWriter [note]
+ return $ firstpartWrapped <> PP.char '%' $$ 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 ($)
+
--
-- Parsing
--