| Copyright | Ivan Lazar Miljenovic (c) 2010 Daan Leijen (c) 2000 http://www.cs.uu.nl/~daan | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Ivan.Miljenovic@gmail.com | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Text.PrettyPrint.Leijen.Text.Monadic
Contents
Description
This module provides a version of
 Text.PrettyPrint.Leijen.Text where the combinators have been
 lifted into a Monad.  The main usage for this is for state-based
 pretty-printing.
- data Doc
- empty :: Applicative m => m Doc
- char :: Applicative m => Char -> m Doc
- text :: Applicative m => Text -> m Doc
- textStrict :: Monad m => Text -> m Doc
- (<>) :: Applicative m => m Doc -> m Doc -> m Doc
- nest :: Functor m => Int -> m Doc -> m Doc
- line :: Applicative m => m Doc
- linebreak :: Applicative m => m Doc
- group :: Functor m => m Doc -> m Doc
- softline :: Applicative m => m Doc
- softbreak :: Applicative m => m Doc
- spacebreak :: Applicative m => m Doc
- align :: Functor m => m Doc -> m Doc
- hang :: Functor m => Int -> m Doc -> m Doc
- indent :: Functor m => Int -> m Doc -> m Doc
- encloseSep :: Applicative m => m Doc -> m Doc -> m Doc -> m [Doc] -> m Doc
- list :: Functor m => m [Doc] -> m Doc
- tupled :: Functor m => m [Doc] -> m Doc
- semiBraces :: Functor m => m [Doc] -> m Doc
- (<+>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<++>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<$>) :: Applicative m => m Doc -> m Doc -> m Doc
- (</>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<$$>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<//>) :: Applicative m => m Doc -> m Doc -> m Doc
- hsep :: Functor m => m [Doc] -> m Doc
- vsep :: Functor m => m [Doc] -> m Doc
- fillSep :: Functor m => m [Doc] -> m Doc
- sep :: Functor m => m [Doc] -> m Doc
- hcat :: Functor m => m [Doc] -> m Doc
- vcat :: Functor m => m [Doc] -> m Doc
- fillCat :: Functor m => m [Doc] -> m Doc
- cat :: Functor m => m [Doc] -> m Doc
- punctuate :: Applicative m => m Doc -> m [Doc] -> m [Doc]
- fill :: Functor m => Int -> m Doc -> m Doc
- fillBreak :: Functor m => Int -> m Doc -> m Doc
- enclose :: Applicative m => m Doc -> m Doc -> m Doc -> m Doc
- squotes :: Functor m => m Doc -> m Doc
- dquotes :: Functor m => m Doc -> m Doc
- parens :: Functor m => m Doc -> m Doc
- angles :: Functor m => m Doc -> m Doc
- braces :: Functor m => m Doc -> m Doc
- brackets :: Functor m => m Doc -> m Doc
- lparen :: Applicative m => m Doc
- rparen :: Applicative m => m Doc
- langle :: Applicative m => m Doc
- rangle :: Applicative m => m Doc
- lbrace :: Applicative m => m Doc
- rbrace :: Applicative m => m Doc
- lbracket :: Applicative m => m Doc
- rbracket :: Applicative m => m Doc
- squote :: Applicative m => m Doc
- dquote :: Applicative m => m Doc
- semi :: Applicative m => m Doc
- colon :: Applicative m => m Doc
- comma :: Applicative m => m Doc
- space :: Applicative m => m Doc
- dot :: Applicative m => m Doc
- backslash :: Applicative m => m Doc
- equals :: Applicative m => m Doc
- string :: Applicative m => Text -> m Doc
- stringStrict :: Monad m => Text -> m Doc
- int :: Applicative m => Int -> m Doc
- integer :: Applicative m => Integer -> m Doc
- float :: Applicative m => Float -> m Doc
- double :: Applicative m => Double -> m Doc
- rational :: Applicative m => Rational -> m Doc
- bool :: Applicative m => Bool -> m Doc
- column :: Functor m => m (Int -> Doc) -> m Doc
- nesting :: Functor m => m (Int -> Doc) -> m Doc
- width :: Applicative m => m Doc -> m (Int -> Doc) -> m Doc
- class Pretty a where
- prettyM :: (Pretty a, Applicative m) => a -> m Doc
- data SimpleDoc
- renderPretty :: Float -> Int -> Doc -> SimpleDoc
- renderCompact :: Doc -> SimpleDoc
- renderOneLine :: Doc -> SimpleDoc
- displayB :: SimpleDoc -> Builder
- displayT :: SimpleDoc -> Text
- displayTStrict :: SimpleDoc -> Text
- displayIO :: Handle -> SimpleDoc -> IO ()
- putDoc :: Doc -> IO ()
- hPutDoc :: Handle -> Doc -> IO ()
Documents
The abstract data type Doc represents pretty documents.
Doc is an instance of the Show class. (show doc) pretty
   prints document doc with a page width of 100 characters and a
   ribbon width of 40 characters.
show (text "hello" <$> text "world")
Which would return the string "hello\nworld", i.e.
hello world
Basic combinators
empty :: Applicative m => m Doc Source #
The empty document is, indeed, empty. Although empty has no
   content, it does have a 'height' of 1 and behaves exactly like
   (text "") (and is therefore not a unit of <$>).
char :: Applicative m => Char -> m Doc Source #
The document (char c) contains the literal character c. The
   character shouldn't be a newline ('\n'), the function line
   should be used for line breaks.
text :: Applicative m => Text -> m Doc Source #
The document (text s) contains the literal string s. The
   string shouldn't contain any newline ('\n') characters. If the
   string contains newline characters, the function string should
   be used.
(<>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 6 Source #
The document (x <> y) concatenates document x and document
   y. It is an associative operation having empty as a left and
   right unit.  (infixr 6)
line :: Applicative m => m Doc Source #
The line document advances to the next line and indents to the
   current nesting level. Document line behaves like (text "
   ") if the line break is undone by group or if rendered with
   renderOneLine.
linebreak :: Applicative m => m Doc Source #
group :: Functor m => m Doc -> m Doc Source #
The group combinator is used to specify alternative
   layouts. The document (group x) undoes all line breaks in
   document x. The resulting line is added to the current line if
   that fits the page. Otherwise, the document x is rendered
   without any changes.
softline :: Applicative m => m Doc Source #
softbreak :: Applicative m => m Doc Source #
spacebreak :: Applicative m => m Doc Source #
The document spacebreak behaves like space when rendered normally
 but like empty when using renderCompact or renderOneLine.
Alignment
The combinators in this section can not be described by Wadler's
   original combinators. They align their output relative to the
   current output position - in contrast to nest which always
   aligns to the current nesting level. This deprives these
   combinators from being `optimal'. In practice however they
   prove to be very useful. The combinators in this section should
   be used with care, since they are more expensive than the other
   combinators. For example, align shouldn't be used to pretty
   print all top-level declarations of a language, but using hang
   for let expressions is fine.
align :: Functor m => m Doc -> m Doc Source #
The document (align x) renders document x with the nesting
   level set to the current column. It is used for example to
   implement hang.
As an example, we will put a document right above another one, regardless of the current nesting level:
x $$ y = align (x <$> y)
test = text "hi" <+> (text "nice" $$ text "world")
which will be laid out as:
  hi nice
     world
  hang :: Functor m => Int -> m Doc -> m Doc Source #
The hang combinator implements hanging indentation. The document
   (hang i x) renders document x with a nesting level set to the
   current column plus i. The following example uses hanging
   indentation for some text:
test = hang 4 (fillSep (map text
        (words "the hang combinator indents these words !")))Which lays out on a page with a width of 20 characters as:
  the hang combinator
      indents these
      words !
  The hang combinator is implemented as:
hang i x = align (nest i x)
indent :: Functor m => Int -> m Doc -> m Doc Source #
The document (indent i x) indents document x with i spaces.
test = indent 4 (fillSep (map text
        (words "the indent combinator indents these words !")))Which lays out with a page width of 20 as:
      the indent
      combinator
      indents these
      words !
  encloseSep :: Applicative m => m Doc -> m Doc -> m Doc -> m [Doc] -> m Doc Source #
The document (encloseSep l r sep xs) concatenates the documents
   xs separated by sep and encloses the resulting document by
   l and r. The documents are rendered horizontally if that fits
   the page. Otherwise they are aligned vertically. All separators
   are put in front of the elements. For example, the combinator
   list can be defined with encloseSep:
list xs = encloseSep lbracket rbracket comma xs test = text "list" <+> (list (map int [10,200,3000]))
Which is laid out with a page width of 20 as:
list [10,200,3000]
But when the page width is 15, it is laid out as:
  list [10
       ,200
       ,3000]
  list :: Functor m => m [Doc] -> m Doc Source #
The document (list xs) comma separates the documents xs and
   encloses them in square brackets. The documents are rendered
   horizontally if that fits the page. Otherwise they are aligned
   vertically. All comma separators are put in front of the
   elements.
tupled :: Functor m => m [Doc] -> m Doc Source #
The document (tupled xs) comma separates the documents xs and
   encloses them in parenthesis. The documents are rendered
   horizontally if that fits the page. Otherwise they are aligned
   vertically. All comma separators are put in front of the
   elements.
semiBraces :: Functor m => m [Doc] -> m Doc Source #
The document (semiBraces xs) separates the documents xs with
   semi colons and encloses them in braces. The documents are
   rendered horizontally if that fits the page. Otherwise they are
   aligned vertically. All semi colons are put in front of the
   elements.
Operators
(<+>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 6 Source #
The document (x <+> y) concatenates document x and y with
   a space in between.  (infixr 6)
(<++>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 6 Source #
The document (x <++> y) concatenates document x and y with
   a spacebreak in between.  (infixr 6)
(<$>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 Source #
The document (x <$> y) concatenates document x and y with
   a line in between. (infixr 5)
(</>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 Source #
The document (x </> y) concatenates document x and y
   with a softline in between. This effectively puts x and y
   either next to each other (with a space in between) or
   underneath each other. (infixr 5)
(<$$>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 Source #
The document (x <$$> y) concatenates document x and y
   with a linebreak in between. (infixr 5)
(<//>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 Source #
The document (x <//> y) concatenates document x and y
   with a softbreak in between. This effectively puts x and y
   either right next to each other or underneath each other. (infixr
   5)
List combinators
hsep :: Functor m => m [Doc] -> m Doc Source #
The document (hsep xs) concatenates all documents xs
   horizontally with (<+>).
vsep :: Functor m => m [Doc] -> m Doc Source #
The document (vsep xs) concatenates all documents xs
   vertically with (<$>). If a group undoes the line breaks
   inserted by vsep, all documents are separated with a space.
someText = map text (words ("text to lay out"))
test = text "some" <+> vsep someTextThis is laid out as:
some text to lay out
The align combinator can be used to align the documents under
   their first element
test = text "some" <+> align (vsep someText)
Which is printed as:
  some text
       to
       lay
       out
  fillSep :: Functor m => m [Doc] -> m Doc Source #
The document (fillSep xs) concatenates documents xs
   horizontally with (<+>) as long as its fits the page, then
   inserts a line and continues doing that for all documents in
   xs.
fillSep xs = foldr (</>) empty xs
sep :: Functor m => m [Doc] -> m Doc Source #
The document (sep xs) concatenates all documents xs either
   horizontally with (<+>), if it fits the page, or vertically
   with (<$>).
sep xs = group (vsep xs)
hcat :: Functor m => m [Doc] -> m Doc Source #
The document (hcat xs) concatenates all documents xs
   horizontally with (<>).
vcat :: Functor m => m [Doc] -> m Doc Source #
The document (vcat xs) concatenates all documents xs
   vertically with (<$$>). If a group undoes the line breaks
   inserted by vcat, all documents are directly concatenated.
fillCat :: Functor m => m [Doc] -> m Doc Source #
The document (fillCat xs) concatenates documents xs
   horizontally with (<>) as long as its fits the page, then
   inserts a linebreak and continues doing that for all documents
   in xs.
fillCat xs = foldr (<//>) empty xs
cat :: Functor m => m [Doc] -> m Doc Source #
The document (cat xs) concatenates all documents xs either
   horizontally with (<>), if it fits the page, or vertically
   with (<$$>).
cat xs = group (vcat xs)
punctuate :: Applicative m => m Doc -> m [Doc] -> m [Doc] Source #
(punctuate p xs) concatenates all documents in xs with
   document p except for the last document.
someText = map text ["words","in","a","tuple"] test = parens (align (cat (punctuate comma someText)))
This is laid out on a page width of 20 as:
(words,in,a,tuple)
But when the page width is 15, it is laid out as:
(words, in, a, tuple)
(If you want put the commas in front of their elements instead of
   at the end, you should use tupled or, in general, encloseSep.)
Fillers
fill :: Functor m => Int -> m Doc -> m Doc Source #
The document (fill i x) renders document x. It then appends
   spaces until the width is equal to i. If the width of x is
   already larger, nothing is appended. This combinator is quite
   useful in practice to output a list of bindings. The following
   example demonstrates this.
types = [("empty","Doc")
         ,("nest","Int -> Doc -> Doc")
         ,("linebreak","Doc")]
ptype (name,tp)
= fill 6 (text name) <+> text "::" <+> text tp
test = text "let" <+> align (vcat (map ptype types))Which is laid out as:
  let empty  :: Doc
      nest   :: Int -> Doc -> Doc
      linebreak :: Doc
  fillBreak :: Functor m => Int -> m Doc -> m Doc Source #
The document (fillBreak i x) first renders document x. It
   then appends spaces until the width is equal to i. If the
   width of x is already larger than i, the nesting level is
   increased by i and a line is appended. When we redefine
   ptype in the previous example to use fillBreak, we get a
   useful variation of the previous output:
ptype (name,tp) = fillBreak 6 (text name) <+> text "::" <+> text tp
The output will now be:
  let empty  :: Doc
      nest   :: Int -> Doc -> Doc
      linebreak
             :: Doc
  Bracketing combinators
enclose :: Applicative m => m Doc -> m Doc -> m Doc -> m Doc Source #
The document (enclose l r x) encloses document x between
   documents l and r using (<>).
enclose l r x = l <> x <> r
squotes :: Functor m => m Doc -> m Doc Source #
Document (squotes x) encloses document x with single quotes
   "'".
dquotes :: Functor m => m Doc -> m Doc Source #
Document (dquotes x) encloses document x with double quotes
   '"'.
parens :: Functor m => m Doc -> m Doc Source #
Document (parens x) encloses document x in parenthesis, "("
   and ")".
angles :: Functor m => m Doc -> m Doc Source #
Document (angles x) encloses document x in angles, "<" and
   ">".
braces :: Functor m => m Doc -> m Doc Source #
Document (braces x) encloses document x in braces, "{" and
   "}".
brackets :: Functor m => m Doc -> m Doc Source #
Document (brackets x) encloses document x in square brackets,
   "[" and "]".
Character documents
lparen :: Applicative m => m Doc Source #
The document lparen contains a left parenthesis, "(".
rparen :: Applicative m => m Doc Source #
The document rparen contains a right parenthesis, ")".
langle :: Applicative m => m Doc Source #
The document langle contains a left angle, "<".
rangle :: Applicative m => m Doc Source #
The document rangle contains a right angle, ">".
lbrace :: Applicative m => m Doc Source #
The document lbrace contains a left brace, "{".
rbrace :: Applicative m => m Doc Source #
The document rbrace contains a right brace, "}".
lbracket :: Applicative m => m Doc Source #
The document lbracket contains a left square bracket, "[".
rbracket :: Applicative m => m Doc Source #
The document rbracket contains a right square bracket, "]".
squote :: Applicative m => m Doc Source #
The document squote contains a single quote, "'".
dquote :: Applicative m => m Doc Source #
The document dquote contains a double quote, '"'.
semi :: Applicative m => m Doc Source #
The document semi contains a semi colon, ";".
colon :: Applicative m => m Doc Source #
The document colon contains a colon, ":".
comma :: Applicative m => m Doc Source #
The document comma contains a comma, ",".
space :: Applicative m => m Doc Source #
The document space contains a single space, " ".
x <+> y = x <> space <> y
dot :: Applicative m => m Doc Source #
The document dot contains a single dot, ".".
backslash :: Applicative m => m Doc Source #
The document backslash contains a back slash, "\".
equals :: Applicative m => m Doc Source #
The document equals contains an equal sign, "=".
Primitive type documents
string :: Applicative m => Text -> m Doc Source #
The document (string s) concatenates all characters in s
   using line for newline characters and char for all other
   characters. It is used instead of text whenever the text
   contains newline characters.
int :: Applicative m => Int -> m Doc Source #
The document (int i) shows the literal integer i using
   text.
integer :: Applicative m => Integer -> m Doc Source #
The document (integer i) shows the literal integer i using
   text.
float :: Applicative m => Float -> m Doc Source #
The document (float f) shows the literal float f using
   text.
double :: Applicative m => Double -> m Doc Source #
The document (double d) shows the literal double d using
   text.
rational :: Applicative m => Rational -> m Doc Source #
The document (rational r) shows the literal rational r using
   text.
bool :: Applicative m => Bool -> m Doc Source #
The document (bool b) shows the literal boolean b using
   text.
Position-based combinators
column :: Functor m => m (Int -> Doc) -> m Doc Source #
Specifies how to create the document based upon which column it is in.
nesting :: Functor m => m (Int -> Doc) -> m Doc Source #
Specifies how to nest the document based upon which column it is being nested in.
Pretty class
The member prettyList is only used to define the instance
   Pretty a => Pretty [a]. In normal circumstances only the
   pretty function is used.
Minimal complete definition
Instances
| Pretty Bool Source # | |
| Pretty Char Source # | |
| Pretty Double Source # | |
| Pretty Float Source # | |
| Pretty Int Source # | |
| Pretty Integer Source # | |
| Pretty () Source # | |
| Pretty Text Source # | |
| Pretty Text Source # | |
| Pretty Doc Source # | |
| Pretty a => Pretty [a] Source # | |
| Pretty a => Pretty (Maybe a) Source # | |
| (Pretty a, Pretty b) => Pretty (a, b) Source # | |
| (Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) Source # | |
Rendering
The data type SimpleDoc represents rendered documents and is
   used by the display functions.
The Int in SText contains the length of the string. The Int
   in SLine contains the indentation for that line. The library
   provides two default display functions displayS and
   displayIO. You can provide your own display function by writing
   a function from a SimpleDoc to your own output format.
renderPretty :: Float -> Int -> Doc -> SimpleDoc Source #
This is the default pretty printer which is used by show,
   putDoc and hPutDoc. (renderPretty ribbonfrac width x)
   renders document x with a page width of width and a ribbon
   width of (ribbonfrac * width) characters. The ribbon width is
   the maximal amount of non-indentation characters on a line. The
   parameter ribbonfrac should be between 0.0 and 1.0. If it
   is lower or higher, the ribbon width will be 0 or width
   respectively.
renderCompact :: Doc -> SimpleDoc Source #
(renderCompact x) renders document x without adding any
   indentation. Since no 'pretty' printing is involved, this
   renderer is very fast. The resulting output contains fewer
   characters than a pretty printed version and can be used for
   output that is read by other programs.
renderOneLine :: Doc -> SimpleDoc Source #
(renderOneLine x) renders document x without adding any
   indentation or newlines.
displayT :: SimpleDoc -> Text Source #
(displayT simpleDoc) takes the output simpleDoc from a
   rendering function and transforms it to a lazy Text value.
showWidth :: Int -> Doc -> Text showWidth w x = displayT (renderPretty 0.4 w x)
displayTStrict :: SimpleDoc -> Text Source #
displayIO :: Handle -> SimpleDoc -> IO () Source #
(displayIO handle simpleDoc) writes simpleDoc to the
   file handle handle. This function is used for example by
   hPutDoc:
hPutDoc handle doc = displayIO handle (renderPretty 0.4 100 doc)
putDoc :: Doc -> IO () Source #
The action (putDoc doc) pretty prints document doc to the
 standard output, with a page width of 100 characters and a ribbon
 width of 40 characters.
main :: IO ()
main = do{ putDoc (text "hello" <+> text "world") }Which would output
hello world
hPutDoc :: Handle -> Doc -> IO () Source #
(hPutDoc handle doc) pretty prints document doc to the file
   handle handle with a page width of 100 characters and a ribbon
   width of 40 characters.
main = do handle <- 'openFile' "MyFile" 'WriteMode'
          'hPutDoc' handle ('vcat' ('map' 'text'
                          ['T.pack' "vertical", 'T.pack' "text"]))
          'hClose' handleOrphan instances
| Applicative m => IsString (m Doc) Source # | |