mainland-pretty-0.2.7.1: Pretty printing designed for printing source code.

Copyright(c) Harvard University 2006-2011 (c) Geoffrey Mainland 2011-2012
LicenseBSD-style
Maintainermainland@eecs.harvard.edu
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.PrettyPrint.Mainland

Contents

Description

This module is based on A Prettier Printer by Phil Wadler in /The Fun of Programming/, Jeremy Gibbons and Oege de Moor (eds) http://homepages.inf.ed.ac.uk/wadler/papers/prettier/prettier.pdf

At the time it was originally written I didn't know about Daan Leijen's pretty printing module based on the same paper. I have since incorporated many of his improvements. This module is geared towards pretty printing source code; its main advantages over other libraries are a Pretty class that handles precedence and the ability to automatically track the source locations associated with pretty printed values and output appropriate #line pragmas.

Synopsis

The document type

data Doc Source

Instances

Basic combinators

empty :: Doc Source

The empty document.

text :: String -> Doc Source

The document text s consists of the string s, which should not contain any newlines. For a string that may include newlines, use string.

char :: Char -> Doc Source

The document char c consists the single character c.

string :: String -> Doc Source

The document string s consists of all the characters in s but with newlines replaced by line.

fromText :: Text -> Doc Source

The document fromText s consists of the Text s, which should not contain any newlines.

fromLazyText :: Text -> Doc Source

The document fromLazyText s consists of the Text s, which should not contain any newlines.

line :: Doc Source

The document line advances to the next line and indents to the current indentation level. When undone by group, it behaves like space.

nest :: Int -> Doc -> Doc Source

The document nest i d renders the document d with the current indentation level increased by i.

srcloc :: Located a => a -> Doc Source

The document srcloc x adds the.

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

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

Operators

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

An infix synonym for mappend.

Since: 4.5.0.0

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

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

(<+/>) :: Doc -> Doc -> Doc infixr 5 Source

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

Character documents

backquote :: Doc Source

The document backquote consists of a backquote, "`".

colon :: Doc Source

The document colon consists of a colon, ":".

comma :: Doc Source

The document comma consists of a comma, ",".

dot :: Doc Source

The document dot consists of a period, ".".

dquote :: Doc Source

The document dquote consists of a double quote, "\"".

equals :: Doc Source

The document equals consists of an equals sign, "=".

semi :: Doc Source

The document semi consists of a semicolon, ";".

space :: Doc Source

The document space consists of a space, " ".

spaces :: Int -> Doc Source

The document space n consists of n spaces.

squote :: Doc Source

The document squote consists of a single quote, "\'".

star :: Doc Source

The document star consists of an asterisk, "*".

langle :: Doc Source

The document langle consists of a less-than sign, "<".

rangle :: Doc Source

The document rangle consists of a greater-than sign, ">".

lbrace :: Doc Source

The document lbrace consists of a left brace, "{".

rbrace :: Doc Source

The document rbrace consists of a right brace, "}".

lbracket :: Doc Source

The document lbracket consists of a right brace, "[".

rbracket :: Doc Source

The document rbracket consists of a right brace, "]".

lparen :: Doc Source

The document lparen consists of a right brace, "(".

rparen :: Doc Source

The document rparen consists of a right brace, ")".

Bracketing combinators

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

The document enclose l r d) encloses the document d between the documents l and r using <>. It obeys the law

enclose l r d = l <> d <> r

angles :: Doc -> Doc Source

The document angles d encloses the aligned document d in ....

backquotes :: Doc -> Doc Source

The document backquotes d encloses the aligned document d in ....

braces :: Doc -> Doc Source

The document braces d encloses the aligned document d in {...}.

brackets :: Doc -> Doc Source

The document brackets d encloses the aligned document d in [...].

dquotes :: Doc -> Doc Source

The document dquotes d encloses the aligned document d in "...".

parens :: Doc -> Doc Source

The document parens d encloses the aligned document d in (...).

parensIf :: Bool -> Doc -> Doc Source

The document parensIf p d encloses the document d in parenthesis if p is True, and otherwise yields just d.

squotes :: Doc -> Doc Source

The document parens d encloses the document d in ....

Alignment and indentation

align :: Doc -> Doc Source

The document align d renders d with a nesting level set to the current column.

hang :: Int -> Doc -> Doc Source

The document hang i d renders d with a nesting level set to the current column plus i. This differs from indent in that the first line of d is not indented.

indent :: Int -> Doc -> Doc Source

The document indent i d indents d i spaces relative to the current column. This differs from hang in that the first line of d is indented.

Combining lists of documents

folddoc :: (Doc -> Doc -> Doc) -> [Doc] -> Doc Source

The document folddoc f ds obeys the laws:

spread :: [Doc] -> Doc Source

The document spread ds concatenates the documents ds using +.

stack :: [Doc] -> Doc Source

The document stack ds concatenates the documents ds using /.

cat :: [Doc] -> Doc Source

The document cat ds separates the documents ds with the empty document as long as there is room, and uses newlines when there isn't.

sep :: [Doc] -> Doc Source

The document sep ds separates the documents ds with the empty document as long as there is room, and uses spaces when there isn't.

punctuate :: Doc -> [Doc] -> [Doc] Source

The document punctuate p ds obeys the law:

punctuate p [d1, d2, ..., dn] = [d1 <> p, d2 <> p, ..., dn]

commasep :: [Doc] -> Doc Source

The document commasep ds comma-space separates ds, aligning the resulting document to the current nesting level.

semisep :: [Doc] -> Doc Source

The document semisep ds semicolon-space separates ds, aligning the resulting document to the current nesting level.

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

The document encloseSep l r p ds separates ds with the punctuation p and encloses the result using l and r. When wrapped, punctuation appears at the end of the line. The enclosed portion of the document is aligned one column to the right of the opening document.

> ws = map text (words "The quick brown fox jumps over the lazy dog")
> test = pretty 15 (encloseSep lparen rparen comma ws)

will be layed out as:

(The, quick,
 brown, fox,
 jumps, over,
 the, lazy,
 dog)

tuple :: [Doc] -> Doc Source

The document tuple ds separates ds with commas and encloses them with parentheses.

list :: [Doc] -> Doc Source

The document tuple ds separates ds with commas and encloses them with brackets.

The rendered document type

data RDoc Source

A rendered document.

Constructors

REmpty

The empty document

RChar Char RDoc

A single character

RString !Int String RDoc

String with associated length (to avoid recomputation)

RText Text RDoc

Text

RLazyText Text RDoc

Text

RPos Pos RDoc

Tag output with source location

RLine !Int RDoc

A newline with the indentation of the subsequent line

Document rendering

render :: Int -> Doc -> RDoc Source

Render a document given a maximum width.

renderCompact :: Doc -> RDoc Source

Render a document without indentation on infinitely long lines. Since no 'pretty' printing is involved, this renderer is fast. The resulting output contains fewer characters.

displayS :: RDoc -> ShowS Source

Display a rendered document.

prettyS :: Int -> Doc -> ShowS Source

Render and display a document.

pretty :: Int -> Doc -> String Source

Render and convert a document to a String.

displayPragmaS :: RDoc -> ShowS Source

Display a rendered document with #line pragmas.

prettyPragmaS :: Int -> Doc -> ShowS Source

Render and display a document with #line pragmas.

prettyPragma :: Int -> Doc -> String Source

Render and convert a document to a String with #line pragmas.

displayLazyText :: RDoc -> Text Source

Display a rendered document as Text. Uses a builder.

prettyLazyText :: Int -> Doc -> Text Source

Render and display a document as Text. Uses a builder.

displayPragmaLazyText :: RDoc -> Text Source

Display a rendered document with #line pragmas as Text. Uses a builder.

prettyPragmaLazyText :: Int -> Doc -> Text Source

Render and convert a document to Text with #line pragmas. Uses a builder.

Document output

putDoc :: Doc -> IO () Source

Render a document with a width of 80 and print it to standard output.

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

Render a document with a width of 80 and print it to the specified handle.

The Pretty type class for pretty printing

class Pretty a where Source

Minimal complete definition

Nothing

Methods

ppr :: a -> Doc Source

pprPrec :: Int -> a -> Doc Source

pprList :: [a] -> Doc Source

Instances

Pretty Bool 
Pretty Char 
Pretty Double 
Pretty Float 
Pretty Int 
Pretty Int8 
Pretty Int16 
Pretty Int32 
Pretty Int64 
Pretty Integer 
Pretty Word8 
Pretty Word16 
Pretty Word32 
Pretty Word64 
Pretty () 
Pretty Pos 
Pretty Loc 
Pretty Text 
Pretty Text 
Pretty a => Pretty [a] 
(Integral a, Pretty a) => Pretty (Ratio a) 
Pretty a => Pretty (Maybe a) 
Pretty a => Pretty (Set a) 
Pretty x => Pretty (L x) 
(Pretty a, Pretty b) => Pretty (a, b) 
(Pretty k, Pretty v) => Pretty (Map k v) 
(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i) => Pretty (a, b, c, d, e, f, g, h, i) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j) => Pretty (a, b, c, d, e, f, g, h, i, j) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k) => Pretty (a, b, c, d, e, f, g, h, i, j, k) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l, Pretty m) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l, Pretty m, Pretty n) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l, Pretty m, Pretty n, Pretty o) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

faildoc :: Monad m => Doc -> m a Source

Equivalent of fail, but with a document instead of a string.

errordoc :: Doc -> a Source

Equivalent of error, but with a document instead of a string.