From 5b888e8b3be01aebb8ecf7ba4ebee61d2a3d3f31 Mon Sep 17 00:00:00 2001
From: fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>
Date: Thu, 27 Sep 2007 01:23:44 +0000
Subject: Added a writer option for wrapped text and a command-line option
 '--no-wrap', which disables text wrapping.  (Resolves Issue #26.)

+ Added support for '--no-wrap' to Main.hs.
+ Added wrapIfNeeded function to Text.Pandoc.Shared.
+ Use wrapIfNeeded instead of wrapped in the RST, Man, Docbook, and
  Markdown writers.
+ Note:  Not yet implemented in HTML, LaTeX, or ConTeXt writers.
  No documentation yet.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@1034 788f1e2b-df1e-0410-8736-df70ead52e1b
---
 src/Main.hs                         | 11 +++++++++-
 src/Text/Pandoc/Shared.hs           | 40 +++++++++++++++++++++++--------------
 src/Text/Pandoc/Writers/Docbook.hs  |  4 +++-
 src/Text/Pandoc/Writers/Man.hs      |  5 +++--
 src/Text/Pandoc/Writers/Markdown.hs |  2 +-
 src/Text/Pandoc/Writers/RST.hs      |  5 ++---
 6 files changed, 44 insertions(+), 23 deletions(-)

(limited to 'src')

diff --git a/src/Main.hs b/src/Main.hs
index f985a9270..b3171c2b4 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -107,6 +107,7 @@ data Opt = Opt
     , optIgnoreArgs        :: Bool    -- ^ Ignore command-line arguments
     , optStrict            :: Bool    -- ^ Use strict markdown syntax
     , optReferenceLinks    :: Bool    -- ^ Use reference links in writing markdown, rst
+    , optWrapText          :: Bool    -- ^ Wrap text
     }
 
 -- | Defaults for command-line options.
@@ -135,6 +136,7 @@ defaultOpts = Opt
     , optIgnoreArgs        = False
     , optStrict            = False
     , optReferenceLinks    = False
+    , optWrapText          = True
     }
 
 -- | A list of functions, each transforming the options data structure
@@ -213,6 +215,11 @@ options =
                   (\opt -> return opt { optNumberSections = True }))
                  "" -- "Number sections in LaTeX"
 
+    , Option "" ["no-wrap"]
+                 (NoArg
+                  (\opt -> return opt { optWrapText = False }))
+                 "" -- "Do not wrap text in output"
+
     , Option "" ["toc", "table-of-contents"]
                 (NoArg
                  (\opt -> return opt { optTableOfContents = True }))
@@ -408,6 +415,7 @@ main = do
               , optIgnoreArgs        = ignoreArgs
               , optStrict            = strict
               , optReferenceLinks    = referenceLinks
+              , optWrapText          = wrap
              } = opts
 
   if dumpArgs
@@ -491,7 +499,8 @@ main = do
                                       writerIncludeBefore  = includeBefore, 
                                       writerIncludeAfter   = includeAfter,
                                       writerStrictMarkdown = strict,
-                                      writerReferenceLinks = referenceLinks }
+                                      writerReferenceLinks = referenceLinks,
+                                      writerWrapText       = wrap }
 
   (readSources sources) >>= (hPutStrLn output . toUTF8 . 
                              (writer writerOptions) . 
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 397e681ea..553a93f28 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -44,6 +44,7 @@ module Text.Pandoc.Shared (
                      camelCaseToHyphenated,
                      toRomanNumeral,
                      wrapped,
+                     wrapIfNeeded,
                      -- * Parsing
                      (>>~),
                      anyLine,
@@ -210,6 +211,12 @@ wrapped :: Monad m => ([Inline] -> m Doc) -> [Inline] -> m Doc
 wrapped listWriter sect = (mapM listWriter $ splitBy Space sect) >>= 
                           return . fsep
 
+wrapIfNeeded :: Monad m => WriterOptions -> ([Inline] -> m Doc) -> 
+                           [Inline] -> m Doc
+wrapIfNeeded opts = if writerWrapText opts
+                       then wrapped 
+                       else ($)
+
 --
 -- Parsing
 --
@@ -760,23 +767,26 @@ data WriterOptions = WriterOptions
   , writerIncludeAfter    :: String -- ^ String to include after the body
   , writerStrictMarkdown  :: Bool   -- ^ Use strict markdown syntax
   , writerReferenceLinks  :: Bool   -- ^ Use reference links in writing markdown, rst
+  , writerWrapText        :: Bool   -- ^ Wrap text to line length
   } deriving Show
 
 -- | Default writer options.
 defaultWriterOptions :: WriterOptions
 defaultWriterOptions = 
-  WriterOptions { writerStandalone      = False,
-                  writerHeader          = "",
-                  writerTitlePrefix     = "",
-                  writerTabStop         = 4,
-                  writerTableOfContents = False,
-                  writerS5              = False,
-                  writerUseASCIIMathML  = False,
-                  writerASCIIMathMLURL  = Nothing,
-                  writerIgnoreNotes     = False,
-                  writerIncremental     = False,
-                  writerNumberSections  = False,
-                  writerIncludeBefore   = "",
-                  writerIncludeAfter    = "",
-                  writerStrictMarkdown  = False,
-                  writerReferenceLinks  = False }
+  WriterOptions { writerStandalone      = False
+                , writerHeader          = ""
+                , writerTitlePrefix     = ""
+                , writerTabStop         = 4
+                , writerTableOfContents = False
+                , writerS5              = False
+                , writerUseASCIIMathML  = False
+                , writerASCIIMathMLURL  = Nothing
+                , writerIgnoreNotes     = False
+                , writerIncremental     = False
+                , writerNumberSections  = False
+                , writerIncludeBefore   = ""
+                , writerIncludeAfter    = ""
+                , writerStrictMarkdown  = False
+                , writerReferenceLinks  = False
+                , writerWrapText        = True
+                }
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index e34b1959c..13dc8585d 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -244,7 +244,9 @@ tableItemToDocbook opts tag align width item =
 
 -- | Take list of inline elements and return wrapped doc.
 wrap :: WriterOptions -> [Inline] -> Doc
-wrap opts lst = fsep $ map (inlinesToDocbook opts) (splitBy Space lst)
+wrap opts lst = if writerWrapText opts
+                   then fsep $ map (inlinesToDocbook opts) (splitBy Space lst)
+                   else inlinesToDocbook opts lst
 
 -- | Convert a list of inline elements to Docbook.
 inlinesToDocbook :: WriterOptions -> [Inline] -> Doc
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index fd04732c6..8e14c2bf0 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -115,9 +115,10 @@ blockToMan :: WriterOptions -- ^ Options
                 -> Block         -- ^ Block element
                 -> State WriterState Doc 
 blockToMan opts Null = return empty
-blockToMan opts (Plain inlines) = wrapped (inlineListToMan opts) inlines
+blockToMan opts (Plain inlines) = 
+  wrapIfNeeded opts (inlineListToMan opts) inlines
 blockToMan opts (Para inlines) = do
-  contents <- wrapped (inlineListToMan opts) inlines
+  contents <- wrapIfNeeded opts (inlineListToMan opts) inlines
   return $ text ".PP" $$ contents 
 blockToMan opts (RawHtml str) = return $ text str
 blockToMan opts HorizontalRule = return $ text $ ".PP\n   *   *   *   *   *"
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 554e0a059..275156e52 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -162,7 +162,7 @@ wrappedMarkdown opts inlines = do
   let chunks' = if null chunks
                    then []
                    else (map (++ [Str "  "]) $ init chunks) ++ [last chunks]
-  lns <- mapM (wrapped (inlineListToMarkdown opts)) chunks'
+  lns <- mapM (wrapIfNeeded opts (inlineListToMarkdown opts)) chunks'
   return $ vcat lns
 
 -- | Convert Pandoc block element to markdown.
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 2e02ee662..ddcbf95c0 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -109,9 +109,8 @@ pictToRST opts (label, (src, _)) = do
 
 -- | Take list of inline elements and return wrapped doc.
 wrappedRST :: WriterOptions -> [Inline] -> State WriterState Doc
-wrappedRST opts inlines = 
-  mapM (wrapped (inlineListToRST opts)) (splitBy LineBreak inlines) >>= 
-  return . vcat
+wrappedRST opts inlines = mapM (wrapIfNeeded opts (inlineListToRST opts))
+                          (splitBy LineBreak inlines) >>= return . vcat
 
 -- | Escape special characters for RST.
 escapeString :: String -> String
-- 
cgit v1.2.3