pretty-compact-1.0: Pretty-printing library

Safe HaskellSafe-Inferred

Text.PrettyPrint.Compact

Contents

Synopsis

Documents

data Doc Source

Instances

Show Doc 
IsString Doc 
Monoid Doc 

Basic combinators

mempty :: Monoid a => a

char :: Char -> DocSource

text :: String -> DocSource

(<>) :: Monoid m => m -> m -> m

nest :: Indentation -> Doc -> DocSource

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 :: DocSource

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 :: DocSource

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.

softline :: DocSource

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

 softline = group line

softbreak :: DocSource

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

 softbreak  = group linebreak

Alignment

align :: Doc -> DocSource

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 :: Indentation -> Doc -> DocSource

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 :: Indentation -> Doc -> DocSource

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] -> DocSource

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] -> DocSource

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] -> DocSource

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] -> DocSource

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 -> DocSource

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

(<$>) :: Functor f => (a -> b) -> f a -> f b

(</>) :: Doc -> Doc -> DocSource

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 -> DocSource

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

(<//>) :: Doc -> Doc -> DocSource

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] -> DocSource

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

vsep :: [Doc] -> DocSource

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] -> DocSource

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] -> DocSource

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] -> DocSource

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

vcat :: [Doc] -> DocSource

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] -> DocSource

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] -> DocSource

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

Fillers

fill :: Indentation -> Doc -> DocSource

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","Indentation -> 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   :: Indentation -> Doc -> Doc
     linebreak :: Doc

fillBreak :: Indentation -> Doc -> DocSource

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   :: Indentation -> Doc -> Doc
     linebreak
            :: Doc

Bracketing combinators

enclose :: Doc -> Doc -> Doc -> DocSource

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

squotes :: Doc -> DocSource

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

dquotes :: Doc -> DocSource

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

parens :: Doc -> DocSource

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

angles :: Doc -> DocSource

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

braces :: Doc -> DocSource

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

brackets :: Doc -> DocSource

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

Character documents

lparen :: DocSource

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

rparen :: DocSource

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

langle :: DocSource

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

rangle :: DocSource

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

lbrace :: DocSource

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

rbrace :: DocSource

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

lbracket :: DocSource

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

rbracket :: DocSource

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

squote :: DocSource

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

dquote :: DocSource

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

semi :: DocSource

The document semi contains a semi colon, ";".

colon :: DocSource

The document colon contains a colon, ":".

comma :: DocSource

The document comma contains a comma, ",".

dot :: DocSource

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

backslash :: DocSource

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

equals :: DocSource

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

Primitive type documents

string :: String -> DocSource

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 -> DocSource

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

integer :: Integer -> DocSource

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

float :: Float -> DocSource

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

double :: Double -> DocSource

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

rational :: Rational -> DocSource

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

bool :: Bool -> DocSource

Rendering

render :: Double -> Indentation -> Doc -> StringSource

Undocumented