marked-pretty-0.1: Pretty-printing library, with scoping, based on pretty-1.0.0.0

Portabilityportable
Stabilityprovisional
Maintainerandygill@ku.edu

Text.PrettyPrint.MarkedHughesPJ

Contents

Description

John Hughes's and Simon Peyton Jones's Pretty Printer Combinators

Based on The Design of a Pretty-printing Library in Advanced Functional Programming, Johan Jeuring and Erik Meijer (eds), LNCS 925 http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps

Heavily modified by Simon Peyton Jones, Dec 96

Marking added by Andy Gill, Oct 08.

Synopsis

The document type

data MDoc a Source

The abstract type of documents. The Show instance is equivalent to using render.

Instances

Show (MDoc a) 

Constructing documents

Converting values into documents

char :: Char -> MDoc aSource

A document of height and width 1, containing a literal character.

text :: String -> MDoc aSource

A document of height 1 containing a literal string. text satisfies the following laws:

The side condition on the last law is necessary because text "" has height 1, while empty has no height.

ptext :: String -> MDoc aSource

An obsolete function, now identical to text.

int :: Int -> MDoc aSource

int n = text (show n)

integer :: Integer -> MDoc aSource

integer n = text (show n)

float :: Float -> MDoc aSource

float n = text (show n)

double :: Double -> MDoc aSource

double n = text (show n)

rational :: Rational -> MDoc aSource

rational n = text (show n)

Simple derived documents

semi :: MDoc aSource

A ';' character

comma :: MDoc aSource

A ',' character

colon :: MDoc aSource

A : character

space :: MDoc aSource

A space character

equals :: MDoc aSource

A '=' character

lparen :: MDoc aSource

A '(' character

rparen :: MDoc aSource

A ')' character

lbrack :: MDoc aSource

A '[' character

rbrack :: MDoc aSource

A ']' character

lbrace :: MDoc aSource

A '{' character

rbrace :: MDoc aSource

A '}' character

Wrapping documents in delimiters

parens :: MDoc a -> MDoc aSource

Wrap document in (...)

brackets :: MDoc a -> MDoc aSource

Wrap document in [...]

braces :: MDoc a -> MDoc aSource

Wrap document in {...}

quotes :: MDoc a -> MDoc aSource

Wrap document in '...'

doubleQuotes :: MDoc a -> MDoc aSource

Wrap document in "..."

Combining documents

empty :: MDoc aSource

The empty document, with no height and no width. empty is the identity for <>, <+>, $$ and $+$, and anywhere in the argument list for sep, hcat, hsep, vcat, fcat etc.

(<>) :: MDoc a -> MDoc a -> MDoc aSource

Beside. <> is associative, with identity empty.

(<+>) :: MDoc a -> MDoc a -> MDoc aSource

Beside, separated by space, unless one of the arguments is empty. <+> is associative, with identity empty.

hcat :: [MDoc a] -> MDoc aSource

List version of <>.

hsep :: [MDoc a] -> MDoc aSource

List version of <+>.

($$) :: MDoc a -> MDoc a -> MDoc aSource

Above, except that if the last line of the first argument stops at least one position before the first line of the second begins, these two lines are overlapped. For example:

    text "hi" $$ nest 5 (text "there")

lays out as

    hi   there

rather than

    hi
         there

$$ is associative, with identity empty, and also satisfies

  • (x $$ y) <> z = x $$ (y <> z), if y non-empty.

($+$) :: MDoc a -> MDoc a -> MDoc aSource

Above, with no overlapping. $+$ is associative, with identity empty.

vcat :: [MDoc a] -> MDoc aSource

List version of $$.

sep :: [MDoc a] -> MDoc aSource

Either hsep or vcat.

cat :: [MDoc a] -> MDoc aSource

Either hcat or vcat.

fsep :: [MDoc a] -> MDoc aSource

"Paragraph fill" version of sep.

fcat :: [MDoc a] -> MDoc aSource

"Paragraph fill" version of cat.

nest :: Int -> MDoc a -> MDoc aSource

Nest (or indent) a document by a given number of positions (which may also be negative). nest satisfies the laws:

The side condition on the last law is needed because empty is a left identity for <>.

hang :: MDoc a -> Int -> MDoc a -> MDoc aSource

hang d1 n d2 = sep [d1, nest n d2]

punctuate :: MDoc a -> [MDoc a] -> [MDoc a]Source

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

Predicates on documents

isEmpty :: MDoc a -> BoolSource

Returns True if the document is empty

Rendering documents

Default rendering

render :: MDoc a -> StringSource

Renders the document as a string using the default style.

Rendering with a particular style

data Style Source

A rendering style.

Constructors

Style 

Fields

mode :: Mode

The rendering mode

lineLength :: Int

Length of line, in chars

ribbonsPerLine :: Float

Ratio of ribbon length to line length

style :: StyleSource

The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).

renderStyle :: Style -> MDoc a -> StringSource

Render the document as a string using a specified style.

General rendering

fullRenderSource

Arguments

:: Mode

Rendering mode

-> Int

Line length

-> Float

Ribbons per line

-> (TextDetails b -> a -> a)

What to do with text

-> a

What to do at the end

-> MDoc b

The document

-> a

Result

The general rendering interface.

data Mode Source

Rendering mode.

Constructors

PageMode

Normal

ZigZagMode

With zig-zag cuts

LeftMode

No indentation, infinitely long lines

OneLineMode

All on one line

data TextDetails a Source

Constructors

Chr Char 
Str String 
PStr String 
Mark a 

Markup extension

mark :: a -> MDoc aSource

mark inserts a zero width mark into the output document