diff options
author | John MacFarlane <jgm@berkeley.edu> | 2010-12-22 00:34:36 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2010-12-22 00:34:36 -0800 |
commit | f15d479fc2c85fe75dc97d80bc25001d3e10e958 (patch) | |
tree | 03d3b2bbe8c8e9649f2d54ee6fefe2dda2d5d63b | |
parent | 21d2d918ac8bec6e239fd362b19445da9550a536 (diff) | |
download | pandoc-f15d479fc2c85fe75dc97d80bc25001d3e10e958.tar.gz |
Shared: Removed unneeded prettyprinting functions:
wrapped, wrapIfNeeded, wrappedTeX, wrapTeXIfNeeded, hang'.
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 75 |
1 files changed, 0 insertions, 75 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 302648a45..401d6bb05 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -46,12 +46,6 @@ module Text.Pandoc.Shared ( escapeURI, unescapeURI, tabFilter, - -- * Prettyprinting - wrapped, - wrapIfNeeded, - wrappedTeX, - wrapTeXIfNeeded, - hang', -- * Pandoc block and inline list processing orderedListMarkers, normalizeSpaces, @@ -78,8 +72,6 @@ module Text.Pandoc.Shared ( import Text.Pandoc.Definition import qualified Text.Pandoc.UTF8 as UTF8 (readFile) -import Text.PrettyPrint.HughesPJ ( Doc, fsep, ($$), (<>), empty, nest ) -import qualified Text.PrettyPrint.HughesPJ as PP import Data.Char ( toLower, isLower, isUpper, isAlpha, isAscii, isLetter, isDigit ) import Data.List ( find, isPrefixOf, intercalate ) @@ -220,73 +212,6 @@ tabFilter tabStop = in go tabStop -- --- Prettyprinting --- - --- | Wrap inlines to line length. -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 :: Inline -> Bool -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 - => Bool - -> ([Inline] -> m Doc) - -> [Inline] - -> m Doc -wrappedTeX includePercent 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 - let (rest1, rest2) = break (== Space) rest' - -- rest1 is whatever comes between the note and a Space. - -- if the note is followed directly by a Space, rest1 is null. - -- rest1 is printed after the note but before the line break, - -- to avoid spurious blank space the note and immediately - -- following punctuation. - rest1Out <- if null rest1 - then return empty - else listWriter rest1 - rest2Wrapped <- if null rest2 - then return empty - else wrappedTeX includePercent listWriter (tail rest2) - noteText <- listWriter [note] - return $ (firstpartWrapped <> if includePercent then PP.char '%' else empty) $$ - (noteText <> rest1Out) $$ - rest2Wrapped - --- | Wrap inlines if the text wrap option is selected, specialized --- for LaTeX and ConTeXt. -wrapTeXIfNeeded :: Monad m - => WriterOptions - -> Bool - -> ([Inline] -> m Doc) - -> [Inline] - -> m Doc -wrapTeXIfNeeded opts includePercent = if writerWrapText opts - then wrappedTeX includePercent - else ($) - --- | A version of hang that works like the version in pretty-1.0.0.0 -hang' :: Doc -> Int -> Doc -> Doc -hang' d1 n d2 = d1 $$ (nest n d2) - --- -- Pandoc block and inline list processing -- |