pretty-compact-2.0: Pretty-printing library

Safe HaskellNone
LanguageHaskell98

Text.PrettyPrint.Compact

Contents

Synopsis

Documents

Basic combinators

text :: Layout d => String -> d Source

flush :: Layout d => d -> d Source

hang :: Int -> Doc -> 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)

encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc Source

The document (enclosure 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 enclosure:

list xs = enclosure 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 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

(<+>) :: Doc -> Doc -> Doc Source

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

($$) :: Doc -> Doc -> Doc Source

List combinators

hsep :: [Doc] -> Doc Source

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

sep :: [Doc] -> Doc Source

The document (sep xs) concatenates all documents xs either horizontally with (<+>), if it fits the page, or vertically with (<$>).

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 ($$).

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.)

Bracketing combinators

enclose :: Doc -> Doc -> Doc -> Doc Source

The document (enclose l r x) encloses document x between documents l and r using (<>).

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 "]".

Character documents

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 semi colon, ";".

colon :: Doc Source

The document colon contains a colon, ":".

comma :: Doc Source

The document comma contains a comma, ",".

space :: 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
!

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, "=".

Primitive type documents

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.

Rendering

render :: Layout d => d -> String Source

Undocumented