Repository : ssh://darcs.haskell.org//srv/darcs/packages/pretty

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/6169601cfb864d8b25c0f1cb32f44a7a7949db93

>---------------------------------------------------------------

commit 6169601cfb864d8b25c0f1cb32f44a7a7949db93
Author: David Terei <[email protected]>
Date:   Tue Jul 19 12:10:18 2011 -0700

    Make Text.PrettyPrint the recommended module

>---------------------------------------------------------------

 Text/PrettyPrint.hs          |   49 +++++++++++++++++++++++++++++++++++++++--
 Text/PrettyPrint/HughesPJ.hs |   37 ++++++++++++++++++------------
 2 files changed, 68 insertions(+), 18 deletions(-)

diff --git a/Text/PrettyPrint.hs b/Text/PrettyPrint.hs
index 7365213..e3c265b 100644
--- a/Text/PrettyPrint.hs
+++ b/Text/PrettyPrint.hs
@@ -11,13 +11,56 @@
 -- The default interface to the pretty-printing library. Provides a collection
 -- of pretty printer combinators.
 --
--- This should be used as opposed to the "Text.PrettyPrint.HughesPJ" module 
that
--- contains the actual implementation that this module simply re-exports.
+-- This module should be used as opposed to the "Text.PrettyPrint.HughesPJ"
+-- module. Both are equivalent though as this module simply re-exports the
+-- other.
 --
 -----------------------------------------------------------------------------
 
 module Text.PrettyPrint ( 
-        module Text.PrettyPrint.HughesPJ
+
+        -- * The document type
+        Doc,
+
+        -- * Constructing documents
+
+        -- ** Converting values into documents
+        char, text, ptext, sizedText, zeroWidthText,
+        int, integer, float, double, rational,
+
+        -- ** Simple derived documents
+        semi, comma, colon, space, equals,
+        lparen, rparen, lbrack, rbrack, lbrace, rbrace,
+
+        -- ** Wrapping documents in delimiters
+        parens, brackets, braces, quotes, doubleQuotes,
+
+        -- ** Combining documents
+        empty,
+        (<>), (<+>), hcat, hsep,
+        ($$), ($+$), vcat,
+        sep, cat,
+        fsep, fcat,
+        nest,
+        hang, punctuate,
+
+        -- * Predicates on documents
+        isEmpty,
+
+        -- * Rendering documents
+
+        -- ** Default rendering
+        render,
+
+        -- ** Rendering with a particular style
+        Style(..),
+        style,
+        renderStyle,
+
+        -- ** General rendering
+        fullRender,
+        Mode(..), TextDetails(..)
+
     ) where
 
 import Text.PrettyPrint.HughesPJ
diff --git a/Text/PrettyPrint/HughesPJ.hs b/Text/PrettyPrint/HughesPJ.hs
index 3c53431..77cf489 100644
--- a/Text/PrettyPrint/HughesPJ.hs
+++ b/Text/PrettyPrint/HughesPJ.hs
@@ -173,7 +173,7 @@ Relative to John's original paper, there are the following 
new features:
 module Text.PrettyPrint.HughesPJ (
 
         -- * The document type
-        Doc,            -- Abstract
+        Doc,
 
         -- * Constructing documents
 
@@ -373,13 +373,13 @@ instance Show Doc where
 render     :: Doc -> String
 
 -- | The general rendering interface.
-fullRender :: Mode                      -- ^Rendering mode
-           -> Int                       -- ^Line length
-           -> Float                     -- ^Ribbons per line
-           -> (TextDetails -> a -> a)   -- ^What to do with text
-           -> a                         -- ^What to do at the end
-           -> Doc                       -- ^The document
-           -> a                         -- ^Result
+fullRender :: Mode                      -- ^ Rendering mode
+           -> Int                       -- ^ Line length
+           -> Float                     -- ^ Ribbons per line
+           -> (TextDetails -> a -> a)   -- ^ What to do with text
+           -> a                         -- ^ What to do at the end
+           -> Doc                       -- ^ The document
+           -> a                         -- ^ Result
 
 -- | Render the document as a string using a specified style.
 renderStyle  :: Style -> Doc -> String
@@ -396,10 +396,10 @@ style :: Style
 style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode }
 
 -- | Rendering mode.
-data Mode = PageMode            -- ^Normal
-          | ZigZagMode          -- ^With zig-zag cuts
-          | LeftMode            -- ^No indentation, infinitely long lines
-          | OneLineMode         -- ^All on one line
+data Mode = PageMode            -- ^ Normal
+          | ZigZagMode          -- ^ With zig-zag cuts
+          | LeftMode            -- ^ No indentation, infinitely long lines
+          | OneLineMode         -- ^ All on one line
 
 -- ---------------------------------------------------------------------------
 -- The Doc calculus
@@ -561,9 +561,16 @@ reduceDoc (Above  p g q) = above  p g (reduceDoc q)
 reduceDoc p              = p
 
 
-data TextDetails = Chr  Char
-                 | Str  String
-                 | PStr String
+-- | The TextDetails data type
+--
+-- A TextDetails represents a *fragement* of text that will be
+-- output at some point.
+data TextDetails = Chr  Char   -- ^ A single Char fragment
+                 | Str  String -- ^ A whole String fragment
+                 | PStr String -- ^ Used to represent a Fast String fragment
+                               --   but now deprecated and identical to the
+                               --   Str constructor.
+
 space_text, nl_text :: TextDetails
 space_text = Chr ' '
 nl_text    = Chr '\n'



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to