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

Copyright(c) 2006-2011 Harvard University
(c) 2011-2012 Geoffrey Mainland
(c) 2015-2017 Drexel University
LicenseBSD-style
Maintainermainland@drexel.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 the ability to automatically track the source locations associated with pretty printed values and output appropriate #line pragmas and the use of Text for output.

Synopsis

The document type

data Doc Source #

The abstract type of documents.

Instances

IsString Doc Source # 

Methods

fromString :: String -> Doc #

Semigroup Doc Source # 

Methods

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

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc Source # 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Pretty Doc Source # 

Methods

ppr :: Doc -> Doc Source #

pprPrec :: Int -> Doc -> Doc Source #

pprList :: [Doc] -> Doc Source #

Constructing documents

Converting values into documents

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.

bool :: Bool -> Doc Source #

The document bool b is equivalent to text (show b).

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.

int :: Int -> Doc Source #

The document int i is equivalent to text (show i).

integer :: Integer -> Doc Source #

The document integer i is equivalent to text (show i). text.

float :: Float -> Doc Source #

The document float f is equivalent to text (show f).

double :: Double -> Doc Source #

The document double d is equivalent to text (show d).

rational :: Rational -> Doc Source #

The document rational r is equivalent to text (show r).

strictText :: Text -> Doc Source #

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

lazyText :: Text -> Doc Source #

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

Simple documents documents

star :: Doc Source #

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

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

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.

backquote :: Doc Source #

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

squote :: Doc Source #

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

dquote :: Doc Source #

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

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

Basic document combinators

empty :: Doc Source #

The empty document.

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

The document srcloc x tags the current line with locOf x. Only shown when running prettyPragma and friends.

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.

softline :: Doc Source #

Becomes space if there is room, otherwise line.

pretty 11 $ text "foo" <+/> text "bar" <+/> text "baz" =="foo bar baz"
pretty  7 $ text "foo" <+/> text "bar" <+/> text "baz" == "foo bar\nbaz"
pretty  6 $ text "foo" <+/> text "bar" <+/> text "baz" == "foo\nbar\nbaz"

softbreak :: Doc Source #

Becomes empty if there is room, otherwise line.

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

(<|>) :: Doc -> Doc -> Doc infixl 3 Source #

Provide alternative layouts of the same content. Invariant: both arguments must flatten to the same document.

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

Concatenates two documents with a space in between, with identity empty.

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

Concatenates two documents with a line in between, with identity empty.

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

Concatenates two documents with a softline in between, with identity empty.

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

Concatenates two documents with a softbreak in between.

group :: Doc -> Doc Source #

The document group d will flatten d to one line if there is room for it, otherwise the original d.

flatten :: Doc -> Doc Source #

The document flatten d will flatten d to one line.

Wrapping documents in delimiters

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

squotes :: Doc -> Doc Source #

The document squotes d encloses the alinged document d in '...'.

dquotes :: Doc -> Doc Source #

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

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

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.

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 with space.

stack :: [Doc] -> Doc Source #

The document stack ds concatenates the documents ds with line.

cat :: [Doc] -> Doc Source #

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

sep :: [Doc] -> Doc Source #

The document sep ds concatenates the documents ds with the space document as long as there is room, and uses line 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 list ds separates ds with commas and encloses them with brackets.

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, not including the first line.

indent :: Int -> Doc -> Doc Source #

The document indent i d renders d with a nesting level set to the current column plus i, including the first line.

nest :: Int -> Doc -> Doc Source #

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

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

The document column f is produced by calling f with the current column.

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

The document column f is produced by calling f with the current nesting level.

width :: Doc -> (Int -> Doc) -> Doc Source #

The document width d f is produced by concatenating d with the result of calling f with the width of the document d.

fill :: Int -> Doc -> Doc Source #

The document fill i d renders document x, appending spaces until the width is equal to i. If the width of d is already greater than i, nothing is appended.

fillbreak :: Int -> Doc -> Doc Source #

The document fillbreak i d renders document d, appending spaces until the width is equal to i. If the width of d is already greater than i, the nesting level is increased by i and a line is appended.

Utilities

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.

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. If this is followed by a RPos, output an appropriate #line pragma before the newline.

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.

prettyCompactS :: Doc -> ShowS Source #

Render and display a document compactly.

prettyCompact :: Doc -> String Source #

Render and convert a document to a String compactly.

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.

> let loc = Loc (Pos "filename" 3 5 7) (Pos "filename" 5 7 9)
> in  putStrLn $ prettyPragma 80 $ srcloc loc <> text "foo" </> text "bar" </> text "baz"

will be printed as

foo
#line 3 "filename"
bar
baz

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.

putDocLn :: Doc -> IO () Source #

Render a document with a width of 80 and print it to standard output, followed by a newline.

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

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

hPutDocLn :: Handle -> Doc -> IO () Source #

Render a document with a width of 80 and print it to the specified handle, followed by a newline.