prettify-1.0: Haskell2010 structured text formatting

Portabilityportable
Stabilityexperimental
MaintainerHans Hoglund <hans@hanshoglund.se>
Safe HaskellSafe-Inferred

Text.Pretty

Contents

Description

This library was based on The Design of a Pretty-printing Library by Jeuring and Meijer.

Heavily modified by Simon Peyton Jones (December 1996).

Lightly modified by Hans Hoglund (October 2012).

Synopsis

The Pretty typeclass

class Pretty a whereSource

Class of types that can be pretty-printed.

The Pretty class is similar to Show, but converts values to Printers instead of Strings. A printer is essentially a string with some extra structural information such as length and indentation.

Note that the instances for primitive types, lists and tuples all satisfy

 (show . pretty) x == show x

Methods

pretty :: a -> PrinterSource

Return a printer for the given value.

prettyList :: [a] -> PrinterSource

The method prettyList is provided to allow the programmer to give a specialised way of printing lists of values. For example, this is used by the predefined Pretty instance of the Char type, where values of type String should be shown in double quotes, rather than between square brackets.

The Printer type

data Printer Source

The abstract type of printers.

Construction

Primitive types

char :: Char -> PrinterSource

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

string :: String -> PrinterSource

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

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

sizedText :: Int -> String -> PrinterSource

Some string with any width. (string s = sizedText (length s) s)

zeroWidthText :: String -> PrinterSource

Some string, but without any width. Use for non-printing string such as a HTML or Latex tags

Combinators

empty :: PrinterSource

The empty printer, 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.

(<->) :: Printer -> Printer -> PrinterSource

Beside. <> is associative, with identity empty.

(<+>) :: Printer -> Printer -> PrinterSource

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

hcat :: [Printer] -> PrinterSource

List version of <>.

hsep :: [Printer] -> PrinterSource

List version of <+>.

(</>) :: Printer -> Printer -> PrinterSource

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:

    string "hi" </> nest 5 (string "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.

(<//>) :: Printer -> Printer -> PrinterSource

Above, with no overlapping. <//> is associative, with identity empty.

vcat :: [Printer] -> PrinterSource

List version of </>.

sep :: [Printer] -> PrinterSource

Either hsep or vcat.

cat :: [Printer] -> PrinterSource

Either hcat or vcat.

fsep :: [Printer] -> PrinterSource

"Paragraph fill" version of sep.

fcat :: [Printer] -> PrinterSource

"Paragraph fill" version of cat.

Wrapping and punctuation

wrap :: Char -> Char -> Printer -> PrinterSource

Wrap printer in the given characters.

parens :: Printer -> PrinterSource

Wrap printer in (...)

brackets :: Printer -> PrinterSource

Wrap printer in [...]

braces :: Printer -> PrinterSource

Wrap printer in {...}

quotes :: Printer -> PrinterSource

Wrap printer in '...'

doubleQuotes :: Printer -> PrinterSource

Wrap printer in "..."

nest :: Int -> Printer -> PrinterSource

Nest (or indent) a printer 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 :: Printer -> Int -> Printer -> PrinterSource

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

sepBy :: Printer -> [Printer] -> PrinterSource

Join with separator.

 sepBy q [x1,x2..xn] = x1 <> q <> x2 <> q .. xn.

initBy :: Printer -> [Printer] -> PrinterSource

Join with initiator.

 initBy q [x1,x2..xn] = q <> x1 <> q <> x2 <> q .. xn.

termBy :: Printer -> [Printer] -> PrinterSource

Join with terminator.

 termBy q [x1,x2..xn] = x1 <> q <> x2 <> q .. xn <> q.

sepByS :: Printer -> [Printer] -> PrinterSource

Join with separator followed by space.

 sepByS q [x1,x2..xn] = x1 <> q <+> x2 <> q <+>.. xn.

initByS :: Printer -> [Printer] -> PrinterSource

Join with initiator followed by space.

 initByS q [x1,x2..xn] = q <+> x1 <> q <+> x2 <> q <+> .. xn.

termByS :: Printer -> [Printer] -> PrinterSource

Join with terminator followed by space.

 termByS q [x1,x2..xn] = x1 <> q <+> x2 <> q <+> .. xn <> q.

Predicates on printers

isEmpty :: Printer -> BoolSource

Returns True if the printer is empty

Rendering printers

runPrinter :: Printer -> StringSource

Render the Printer to a String using the default Style.

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 Style Source

A printing style.

Constructors

Style 

Fields

mode :: Mode

The printing 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).

runPrinterStyle :: Style -> Printer -> StringSource

Render the Printer to a String using the given Style.