ansi-wl-pprint-0.6.9: The Wadler/Leijen Pretty Printer for colored ANSI terminal output

CopyrightDaan Leijen (c) 2000 http://www.cs.uu.nl/~daan
Max Bolingbroke (c) 2008 http://blog.omega-prime.co.uk
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Text.PrettyPrint.ANSI.Leijen

Contents

Description

This module is an extended implementation of the functional pretty printer given by Philip Wadler (1997):

     "A prettier printer"
     Draft paper, April 1997, revised March 1998.
     https://homepages.inf.ed.ac.uk/wadler/papers/prettier/prettier.pdf

In their bare essence, the combinators given by Wadler are not expressive enough to describe some commonly occurring layouts. This library adds new primitives to describe these layouts and works well in practice.

The library is based on a single way to concatenate documents, which is associative and has both a left and right unit. This simple design leads to an efficient and short implementation. The simplicity is reflected in the predictable behaviour of the combinators which make them easy to use in practice.

A thorough description of the primitive combinators and their implementation can be found in Philip Wadler's paper. The main differences with his original paper are:

  • The nil document is called empty.
  • The above combinator is called <$>. The operator </> is used for soft line breaks.
  • There are three new primitives: align, fill and fillBreak. These are very useful in practice.
  • There are many additional useful combinators, like fillSep and list.
  • There are two renderers: renderPretty for pretty printing, and renderCompact for quickly rendered, compact output more suitable for generating input to other programs.
  • The pretty printing algorithm used by renderPretty extends the algorithm given by Wadler to take into account a "ribbon width", i.e., a desired maximum number of non-indentation characters to output on any one line.
  • There are two displayers, displayS for strings and displayIO for file-based output.
  • There is a Pretty class.
  • The implementation uses optimised representations and strictness annotations.
  • The library has been extended to allow formatting text for output to ANSI style consoles. New combinators allow control of foreground and background color and the ability to make parts of the text bold or underlined.
Synopsis

The algebra of pretty-printing

The combinators in this library satisfy many algebraic laws.

The concatenation operator <> is associative and has empty as a left and right unit:

x <> (y <> z)           = (x <> y) <> z
x <> empty              = x
empty <> x              = x

The text combinator is a homomorphism from string concatenation to document concatenation:

text (s ++ t)           = text s <> text t
text ""                 = empty

The char combinator behaves like one-element text:

char c                  = text [c]

The nest combinator is a homomorphism from addition to document composition. nest also distributes through document concatenation and is absorbed by text and align:

nest (i + j) x          = nest i (nest j x)
nest 0 x                = x
nest i (x <> y)         = nest i x <> nest i y
nest i empty            = empty
nest i (text s)         = text s
nest i (align x)        = align x

The group combinator is absorbed by empty. group is commutative with nest and align:

group empty             = empty
group (text s <> x)     = text s <> group x
group (nest i x)        = nest i (group x)
group (align x)         = align (group x)

The align combinator is absorbed by empty and text. align is idempotent:

align empty             = empty
align (text s)          = text s
align (align x)         = align x

From the laws of the primitive combinators, we can derive many other laws for the derived combinators. For example, the above operator <$> is defined as:

x <$> y                 = x <> line <> y

It follows that <$> is associative and that <$> and <> associate with each other:

x <$> (y <$> z)         = (x <$> y) <$> z
x <> (y <$> z)          = (x <> y) <$> z
x <$> (y <> z)          = (x <$> y) <> z

Similar laws also hold for the other line break operators </>, <$$>, and <//>.

Documents

data Doc Source #

The abstract data type Doc represents pretty documents.

More specifically, a value of type Doc represents a non-empty set of possible renderings of a document. The rendering functions select one of these possibilities.

Doc is an instance of the Show class. (show doc) pretty prints document doc with a page width of 80 characters and a ribbon width of 32 characters.

show (text "hello" <$> text "world")

Which would return the string "hello\nworld", i.e.

hello
world
Instances
Show Doc Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

fromString :: String -> Doc #

Semigroup Doc Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Pretty Doc Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: Doc -> Doc Source #

prettyList :: [Doc] -> Doc Source #

Basic combinators

empty :: 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 :: Char -> 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 :: String -> 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.

string :: String -> 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 :: Int -> Doc Source #

The document (int i) shows the literal integer i using text.

integer :: Integer -> Doc Source #

The document (integer i) shows the literal integer i using text.

float :: Float -> Doc Source #

The document (float f) shows the literal float f using text.

double :: Double -> Doc Source #

The document (double d) shows the literal double d using text.

rational :: Rational -> Doc Source #

The document (rational r) shows the literal rational r using text.

bool :: Bool -> Doc Source #

The document (bool b) shows the literal bool b using text.

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

nest :: Int -> Doc -> Doc Source #

The document (nest i x) renders document x with the current indentation level increased by i (See also hang, align and indent).

nest 2 (text "hello" <$> text "world") <$> text "!"

outputs as:

hello
  world
!

line :: 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.

linebreak :: Doc Source #

The linebreak document advances to the next line and indents to the current nesting level. Document linebreak behaves like empty if the line break is undone by group.

group :: Doc -> 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 :: Doc Source #

The document softline behaves like space if the resulting output fits the page, otherwise it behaves like line.

softline = group line

softbreak :: Doc Source #

The document softbreak behaves like empty if the resulting output fits the page, otherwise it behaves like line.

softbreak  = group linebreak

hardline :: Doc Source #

A linebreak that will never be flattened; it is guaranteed to render as a newline.

flatAlt :: Doc -> Doc -> Doc Source #

A document that is normally rendered as the first argument, but when flattened, is rendered as the second document.

Alignment combinators

The combinators in this section cannot 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 :: Doc -> 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 layed out as:

hi nice
   world

hang :: Int -> Doc -> 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 :: Int -> Doc -> 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 :: Doc -> Doc -> Doc -> [Doc] -> 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 layed out with a page width of 20 as:

list [10,200,3000]

But when the page width is 15, it is layed out as:

list [10
     ,200
     ,3000]

list :: [Doc] -> 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 :: [Doc] -> 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 :: [Doc] -> Doc Source #

The document (semiBraces xs) separates the documents xs with semicolons and encloses them in braces. The documents are rendered horizontally if that fits the page. Otherwise they are aligned vertically. All semicolons are put in front of the elements.

Operators

(<+>) :: Doc -> Doc -> Doc infixr 6 Source #

The document (x <+> y) concatenates document x and y with a space in between. (infixr 6)

(<$>) :: Doc -> Doc -> Doc infixr 5 Source #

The document (x <$> y) concatenates document x and y with a line in between. (infixr 5)

(</>) :: Doc -> Doc -> 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)

(<$$>) :: Doc -> Doc -> Doc infixr 5 Source #

The document (x <$$> y) concatenates document x and y with a linebreak in between. (infixr 5)

(<//>) :: Doc -> Doc -> 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 :: [Doc] -> Doc Source #

The document (hsep xs) concatenates all documents xs horizontally with (<+>).

vsep :: [Doc] -> 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 someText

This is layed 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 :: [Doc] -> Doc Source #

The document (fillSep xs) concatenates documents xs horizontally with (<+>) as long as its fits the page, than inserts a line and continues doing that for all documents in xs.

fillSep xs  = foldr (</>) empty xs

sep :: [Doc] -> 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 :: [Doc] -> Doc Source #

The document (hcat xs) concatenates all documents xs horizontally with (<>).

vcat :: [Doc] -> 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 :: [Doc] -> Doc Source #

The document (fillCat xs) concatenates documents xs horizontally with (<>) as long as its fits the page, than inserts a linebreak and continues doing that for all documents in xs.

fillCat xs  = foldr (<//>) empty xs

cat :: [Doc] -> 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 :: Doc -> [Doc] -> [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 layed out on a page width of 20 as:

(words,in,a,tuple)

But when the page width is 15, it is layed 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.)

Filler combinators

fill :: Int -> Doc -> Doc Source #

The document (fill i x) renders document x. It than 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 layed out as:

let empty  :: Doc
    nest   :: Int -> Doc -> Doc
    linebreak :: Doc

fillBreak :: Int -> Doc -> Doc Source #

The document (fillBreak i x) first renders document x. It than 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 :: Doc -> Doc -> Doc -> 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 :: Doc -> Doc Source #

Document (squotes x) encloses document x with single quotes "'".

dquotes :: Doc -> Doc Source #

Document (dquotes x) encloses document x with double quotes '"'.

parens :: Doc -> Doc Source #

Document (parens x) encloses document x in parenthesis, "(" and ")".

angles :: Doc -> Doc Source #

Document (angles x) encloses document x in angles, "<" and ">".

braces :: Doc -> Doc Source #

Document (braces x) encloses document x in braces, "{" and "}".

brackets :: Doc -> Doc Source #

Document (brackets x) encloses document x in square brackets, "[" and "]".

Named character combinators

lparen :: Doc Source #

The document lparen contains a left parenthesis, "(".

rparen :: Doc Source #

The document rparen contains a right parenthesis, ")".

langle :: Doc Source #

The document langle contains a left angle, "<".

rangle :: Doc Source #

The document rangle contains a right angle, ">".

lbrace :: Doc Source #

The document lbrace contains a left brace, "{".

rbrace :: Doc Source #

The document rbrace contains a right brace, "}".

lbracket :: Doc Source #

The document lbracket contains a left square bracket, "[".

rbracket :: Doc Source #

The document rbracket contains a right square bracket, "]".

squote :: Doc Source #

The document squote contains a single quote, "'".

dquote :: Doc Source #

The document dquote contains a double quote, '"'.

semi :: Doc Source #

The document semi contains a semicolon, ";".

colon :: Doc Source #

The document colon contains a colon, ":".

comma :: Doc Source #

The document comma contains a comma, ",".

space :: Doc Source #

The document space contains a single space, " ".

x <+> y   = x <> space <> y

dot :: Doc Source #

The document dot contains a single dot, ".".

backslash :: Doc Source #

The document backslash contains a back slash, "\".

equals :: Doc Source #

The document equals contains an equal sign, "=".

ANSI formatting combinators

This terminal formatting functionality is, as far as possible, portable across platforms with their varying terminals. However, note that to display ANSI colors and formatting will only be displayed on Windows consoles if the Doc value is output using the putDoc function or one of its friends. Rendering the Doc to a String and then outputing that will only work on Unix-style operating systems.

Forecolor combinators

black :: Doc -> Doc Source #

Displays a document with the black forecolor

red :: Doc -> Doc Source #

Displays a document with the red forecolor

green :: Doc -> Doc Source #

Displays a document with the green forecolor

yellow :: Doc -> Doc Source #

Displays a document with the yellow forecolor

blue :: Doc -> Doc Source #

Displays a document with the blue forecolor

magenta :: Doc -> Doc Source #

Displays a document with the magenta forecolor

cyan :: Doc -> Doc Source #

Displays a document with the cyan forecolor

white :: Doc -> Doc Source #

Displays a document with the white forecolor

dullblack :: Doc -> Doc Source #

Displays a document with the dull black forecolor

dullred :: Doc -> Doc Source #

Displays a document with the dull red forecolor

dullgreen :: Doc -> Doc Source #

Displays a document with the dull green forecolor

dullyellow :: Doc -> Doc Source #

Displays a document with the dull yellow forecolor

dullblue :: Doc -> Doc Source #

Displays a document with the dull blue forecolor

dullmagenta :: Doc -> Doc Source #

Displays a document with the dull magenta forecolor

dullcyan :: Doc -> Doc Source #

Displays a document with the dull cyan forecolor

dullwhite :: Doc -> Doc Source #

Displays a document with the dull white forecolor

Backcolor combinators

onblack :: Doc -> Doc Source #

Displays a document with the black backcolor

onred :: Doc -> Doc Source #

Displays a document with the red backcolor

ongreen :: Doc -> Doc Source #

Displays a document with the green backcolor

onyellow :: Doc -> Doc Source #

Displays a document with the yellow backcolor

onblue :: Doc -> Doc Source #

Displays a document with the blue backcolor

onmagenta :: Doc -> Doc Source #

Displays a document with the magenta backcolor

oncyan :: Doc -> Doc Source #

Displays a document with the cyan backcolor

onwhite :: Doc -> Doc Source #

Displays a document with the white backcolor

ondullblack :: Doc -> Doc Source #

Displays a document with the dull black backcolor

ondullred :: Doc -> Doc Source #

Displays a document with the dull red backcolor

ondullgreen :: Doc -> Doc Source #

Displays a document with the dull green backcolor

ondullyellow :: Doc -> Doc Source #

Displays a document with the dull yellow backcolor

ondullblue :: Doc -> Doc Source #

Displays a document with the dull blue backcolor

ondullmagenta :: Doc -> Doc Source #

Displays a document with the dull magenta backcolor

ondullcyan :: Doc -> Doc Source #

Displays a document with the dull cyan backcolor

ondullwhite :: Doc -> Doc Source #

Displays a document with the dull white backcolor

Emboldening combinators

bold :: Doc -> Doc Source #

Displays a document in a heavier font weight

debold :: Doc -> Doc Source #

Displays a document in the normal font weight

Underlining combinators

underline :: Doc -> Doc Source #

Displays a document with underlining

deunderline :: Doc -> Doc Source #

Displays a document with no underlining

Formatting elimination combinators

plain :: Doc -> Doc Source #

Removes all colorisation, emboldening and underlining from a document

Pretty class

class Pretty a where Source #

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

pretty

Methods

pretty :: a -> Doc Source #

prettyList :: [a] -> Doc Source #

Instances
Pretty Bool Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Pretty Char Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Pretty Double Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Pretty Float Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Pretty Int Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: Int -> Doc Source #

prettyList :: [Int] -> Doc Source #

Pretty Integer Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Pretty () Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: () -> Doc Source #

prettyList :: [()] -> Doc Source #

Pretty Doc Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: Doc -> Doc Source #

prettyList :: [Doc] -> Doc Source #

Pretty a => Pretty [a] Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: [a] -> Doc Source #

prettyList :: [[a]] -> Doc Source #

Pretty a => Pretty (Maybe a) Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: Maybe a -> Doc Source #

prettyList :: [Maybe a] -> Doc Source #

(Pretty a, Pretty b) => Pretty (a, b) Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: (a, b) -> Doc Source #

prettyList :: [(a, b)] -> Doc Source #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) Source # 
Instance details

Defined in Text.PrettyPrint.ANSI.Leijen.Internal

Methods

pretty :: (a, b, c) -> Doc Source #

prettyList :: [(a, b, c)] -> Doc Source #

Rendering and displaying documents

Simple (i.e., rendered) documents

data SimpleDoc Source #

The data type SimpleDoc represents rendered documents and is used by the display functions.

Whereas values of the data type Doc represent non-empty sets of possible renderings of a document, values of the data type SimpleDoc represent single renderings of a document.

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.

This rendering function does not add any colorisation information.

renderSmart :: Float -> Int -> Doc -> SimpleDoc Source #

A slightly smarter rendering algorithm with more lookahead. It provides provide earlier breaking on deeply nested structures For example, consider this python-ish pseudocode: fun(fun(fun(fun(fun([abcdefg, abcdefg]))))) If we put a softbreak (+ nesting 2) after each open parenthesis, and align the elements of the list to match the opening brackets, this will render with renderPretty and a page width of 20 as: fun(fun(fun(fun(fun([ | abcdef, | abcdef, ] ))))) | Where the 20c. boundary has been marked with |. Because renderPretty only uses one-line lookahead, it sees that the first line fits, and is stuck putting the second and third lines after the 20-c mark. In contrast, renderSmart will continue to check that the potential document up to the end of the indentation level. Thus, it will format the document as:

fun(                |
  fun(              |
    fun(            |
      fun(          |
        fun([       |
              abcdef,
              abcdef,
            ]       |
  )))))             |

Which fits within the 20c. boundary.

displayS :: SimpleDoc -> ShowS Source #

(displayS simpleDoc) takes the output simpleDoc from a rendering function and transforms it to a ShowS type (for use in the Show class).

showWidth :: Int -> Doc -> String
showWidth w x   = displayS (renderPretty 0.4 w x) ""

ANSI color information will be discarded by this function unless you are running on a Unix-like operating system. This is due to a technical limitation in Windows ANSI support.

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 80 doc)

Any ANSI colorisation in simpleDoc will be output.

Simultaneous rendering and displaying of documents

putDoc :: Doc -> IO () Source #

The action (putDoc doc) pretty prints document doc to the standard output, with a page width of 80 characters and a ribbon width of 32 characters.

main :: IO ()
main = do{ putDoc (text "hello" <+> text "world") }

Which would output

hello world

Any ANSI colorisation in doc will be output.

hPutDoc :: Handle -> Doc -> IO () Source #

(hPutDoc handle doc) pretty prints document doc to the file handle handle with a page width of 80 characters and a ribbon width of 32 characters.

main = do{ handle <- openFile "MyFile" WriteMode
         ; hPutDoc handle (vcat (map text
                           ["vertical","text"]))
         ; hClose handle
         }

Any ANSI colorisation in doc will be output.

Undocumented

column :: (Int -> Doc) -> Doc Source #

nesting :: (Int -> Doc) -> Doc Source #

width :: Doc -> (Int -> Doc) -> Doc Source #