uu-cco-0.1.0.4: Utilities for compiler construction: core functionality

Copyright(c) 2008 Utrecht University
LicenseAll rights reserved
Maintainerstefan@cs.uu.nl
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

CCO.Printing

Contents

Description

A combinator library for pretty printing.

Inspired by

  • S. Doaitse Swierstra, Pablo R. Azero Alcocer, and Joao Saraiva. Designing and implementing combinator languages. In S. Doaitse Swierstra and Pedro Rangel Henriques, and Jose Nuno Oliveira, editors, Advanced Functional Programming, Third International School, Braga, Portugal, September 12-19, 1998, Revised Lectures, volume 1608 of Lecture Notes in Computer Science, pages 150-206. Springer-Verlag, 1999.

Synopsis

Abstract document type

data Doc Source

The type of documents.

isEmpty :: Doc -> Bool Source

Indicates whether a document is empty.

Primitive document constructors

empty :: Doc Source

The empty document. Left and right unit of >-< and >|<.

text :: String -> Doc Source

text txt produces a document containing the text txt.

wrapped :: String -> Doc Source

wrapped txt produces a document containing the text txt, possibly wrapping its contents to fit the available space

Elementary document combinators

indent :: Int -> Doc -> Doc Source

Indents a document by a given amount of space.

(>-<) :: Doc -> Doc -> Doc infixr 2 Source

"Above": puts one document on top of another.

above :: [Doc] -> Doc Source

Stacks multiple documents: above = foldr (>-<) empty.

(>|<) :: Doc -> Doc -> Doc infixr 3 Source

"Besides": puts two documents next to eachother by "dovetailing" them.

besides :: [Doc] -> Doc Source

Queues multiple documents: besides = foldr (>|<) empty.

Parallelisation

(>//<) :: Doc -> Doc -> Doc infixr 1 Source

"Split": introduces two alternative ("parallel") formattings.

split :: [Doc] -> Doc Source

Introduces multiple alternative formattings: split = foldr (>//<) empty.

join :: Doc -> Doc Source

Selects the most space-efficient of all alternative formattings for a document.

(>^<) :: Doc -> Doc -> Doc infixr 1 Source

Immediate choice: l >^< r = join (l >//< r).

choose :: [Doc] -> Doc Source

Immediate choice: choose = foldr (>^<) empty.

Punctuation

space :: Doc Source

A space character: space = text " ".

period :: Doc Source

A full stop: period = text ".".

comma :: Doc Source

A comma: comma = text ",".

semicolon :: Doc Source

A semicolon: semicolon = text ";".

colon :: Doc Source

A colon: colon = text ":".

sepBy :: [Doc] -> Doc -> Doc Source

Inserts a delimiter between all adjacent nonempty documents in a list.

(>#<) :: Doc -> Doc -> Doc infixr 3 Source

Inserts a space between two documents. If one of the documents is empty, the other one is returned: l >#< r = [l, r] `sepBy` space.

lparen :: Doc Source

Parentheses:

lparen = text "("
rparen = text ")"

rparen :: Doc Source

Parentheses:

lparen = text "("
rparen = text ")"

lbracket :: Doc Source

Square brackets:

lbracket = text "["
rbracket = text "]"

rbracket :: Doc Source

Square brackets:

lbracket = text "["
rbracket = text "]"

lbrace :: Doc Source

Curly braces:

lbrace = text "{"
rbrace = text "}"

rbrace :: Doc Source

Curly braces:

lbrace = text "{"
rbrace = text "}"

langle :: Doc Source

Angle brackets:

langle = text "<"
rangle = text ">"

rangle :: Doc Source

Angle brackets:

langle = text "<"
rangle = text ">"

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

Encloses a document in brackets: enclose l r d = l >|< d >|< r.

parens :: Doc -> Doc Source

Encloses a document in parentheses: parens = enclose lparen rparen.

brackets :: Doc -> Doc Source

Encloses a document in square brackets: brackets = enclose lbracket rbracket.

braces :: Doc -> Doc Source

Encloses a document in curly braces: braces = enclose lbrace rbrace.

angles :: Doc -> Doc Source

Encloses a document in angle brackets: angles = enclose langle rangle.

Colours

black :: Doc -> Doc Source

Sets the foreground colour of a document to black.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

red :: Doc -> Doc Source

Sets the foreground colour of a document to red.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

green :: Doc -> Doc Source

Sets the foreground colour of a document to green.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

blue :: Doc -> Doc Source

Sets the foreground colour of a document to blue.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

yellow :: Doc -> Doc Source

Sets the foreground colour of a document to yellow.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

magenta :: Doc -> Doc Source

Sets the foreground colour of a document to magenta.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

cyan :: Doc -> Doc Source

Sets the foreground colour of a document to cyan.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

white :: Doc -> Doc Source

Sets the foreground colour of a document to white.

(Note: colours are only taken into account when a document is rendered by means of renderIO or renderIO_. They are ignored if render or render_ are used.)

Rendering

render :: Int -> Doc -> Maybe String Source

Tries to render a document within a specified amount of horizontal space.

render_ :: Int -> Doc -> String Source

Tries to render a document within a specified amount of horizontal space. If the document cannot be rendered within the given amount of space, the amount of space is, until the document fits, repeatedly enlarged by 10 percent.

renderHeight :: Int -> Doc -> Maybe (String, Int) Source

Tries to render a document within a specified amount of horizontal space. A resulting rendering is tupled with the number of new lines claimed by the rendering.

renderIO :: Int -> Doc -> Maybe (IO ()) Source

Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel.

renderIO_ :: Int -> Doc -> IO () Source

Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel. If the document cannot be rendered within the given amount of space, the amount of space is, until the document fits, repeatedly enlarged by 10 percent.

renderIOHeight :: Int -> Doc -> Maybe (IO (), Int) Source

Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel. A resulting rendering is tupled with the number of new lines claimed by the rendering.

renderIOHeight_ :: Int -> Doc -> (IO (), Int) Source

Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel. If the document cannot be rendered within the given amount of space, the amount of space is, until the document fits, repeatedly enlarged by 10 percent. The resulting rendering is tupled with the number of new lines claimed by the rendering.

The class Printable

class Printable a where Source

The class Printable. Instances of Printable provide a pretty printer for their values.

A minimal complete definition must supply the method pp.

Methods

pp :: a -> Doc Source

Retrieves a pretty-printable document for a value.

Printing showables

showable :: Show a => a -> Doc Source

Prints a Showable value: showable = text . show.