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

Portabilityportable
Stabilityprovisional
Maintainerstefan@cs.uu.nl
Safe HaskellSafe-Inferred

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

Indicates whether a document is empty.

Primitive document constructors

empty :: DocSource

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

text :: String -> DocSource

text txt produces a document containing the text txt.

wrapped :: String -> DocSource

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

Elementary document combinators

indent :: Int -> Doc -> DocSource

Indents a document by a given amount of space.

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

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

above :: [Doc] -> DocSource

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

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

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

besides :: [Doc] -> DocSource

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

Parallelisation

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

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

split :: [Doc] -> DocSource

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

join :: Doc -> DocSource

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

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

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

choose :: [Doc] -> DocSource

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

Punctuation

space :: DocSource

A space character: space = text " ".

period :: DocSource

A full stop: period = text ".".

comma :: DocSource

A comma: comma = text ",".

semicolon :: DocSource

A semicolon: semicolon = text ";".

colon :: DocSource

A colon: colon = text ":".

sepBy :: [Doc] -> Doc -> DocSource

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

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

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

Parentheses:

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

rparen :: DocSource

Parentheses:

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

lbracket :: DocSource

Square brackets:

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

rbracket :: DocSource

Square brackets:

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

lbrace :: DocSource

Curly braces:

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

rbrace :: DocSource

Curly braces:

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

langle :: DocSource

Angle brackets:

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

rangle :: DocSource

Angle brackets:

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

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

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

parens :: Doc -> DocSource

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

brackets :: Doc -> DocSource

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

braces :: Doc -> DocSource

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

angles :: Doc -> DocSource

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

Colours

black :: Doc -> DocSource

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

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

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

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

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

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

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

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 StringSource

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

render_ :: Int -> Doc -> StringSource

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.

renderHeight_ :: Int -> Doc -> (String, Int)Source

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 whereSource

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

Retrieves a pretty-printable document for a value.

Instances

Printable Char 
Printable Double 
Printable Float 
Printable Int 
Printable Integer 
Printable ATerm 

Printing showables

showable :: Show a => a -> DocSource

Prints a Showable value: showable = text . show.