pretty-1.0.1.0: Pretty-printing libraryContentsIndex
Text.PrettyPrint.HughesPJ
Portabilityportable
Stabilityprovisional
Maintainerlibraries@haskell.org
Contents
The document type
Constructing documents
Converting values into documents
Simple derived documents
Wrapping documents in delimiters
Combining documents
Predicates on documents
Rendering documents
Default rendering
Rendering with a particular style
General rendering
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

Synopsis
data Doc
char :: Char -> Doc
text :: String -> Doc
ptext :: String -> Doc
zeroWidthText :: String -> Doc
int :: Int -> Doc
integer :: Integer -> Doc
float :: Float -> Doc
double :: Double -> Doc
rational :: Rational -> Doc
semi :: Doc
comma :: Doc
colon :: Doc
space :: Doc
equals :: Doc
lparen :: Doc
rparen :: Doc
lbrack :: Doc
rbrack :: Doc
lbrace :: Doc
rbrace :: Doc
parens :: Doc -> Doc
brackets :: Doc -> Doc
braces :: Doc -> Doc
quotes :: Doc -> Doc
doubleQuotes :: Doc -> Doc
empty :: Doc
(<>) :: Doc -> Doc -> Doc
(<+>) :: Doc -> Doc -> Doc
hcat :: [Doc] -> Doc
hsep :: [Doc] -> Doc
($$) :: Doc -> Doc -> Doc
($+$) :: Doc -> Doc -> Doc
vcat :: [Doc] -> Doc
sep :: [Doc] -> Doc
cat :: [Doc] -> Doc
fsep :: [Doc] -> Doc
fcat :: [Doc] -> Doc
nest :: Int -> Doc -> Doc
hang :: Doc -> Int -> Doc -> Doc
punctuate :: Doc -> [Doc] -> [Doc]
isEmpty :: Doc -> Bool
render :: Doc -> String
data Style = Style {
mode :: Mode
lineLength :: Int
ribbonsPerLine :: Float
}
style :: Style
renderStyle :: Style -> Doc -> String
fullRender :: Mode -> Int -> Float -> (TextDetails -> a -> a) -> a -> Doc -> a
data Mode
= PageMode
| ZigZagMode
| LeftMode
| OneLineMode
data TextDetails
= Chr Char
| Str String
| PStr String
The document type
data Doc
The abstract type of documents. The Show instance is equivalent to using render.
show/hide Instances
Constructing documents
Converting values into documents
char :: Char -> Doc
A document of height and width 1, containing a literal character.
text :: String -> Doc

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 -> Doc
An obsolete function, now identical to text.
zeroWidthText :: String -> Doc
Some text, but without any width. Use for non-printing text such as a HTML or Latex tags
int :: Int -> Doc
int n = text (show n)
integer :: Integer -> Doc
integer n = text (show n)
float :: Float -> Doc
float n = text (show n)
double :: Double -> Doc
double n = text (show n)
rational :: Rational -> Doc
rational n = text (show n)
Simple derived documents
semi :: Doc
A ';' character
comma :: Doc
A ',' character
colon :: Doc
A ':' character
space :: Doc
A space character
equals :: Doc
A '=' character
lparen :: Doc
A '(' character
rparen :: Doc
A ')' character
lbrack :: Doc
A '[' character
rbrack :: Doc
A ']' character
lbrace :: Doc
A '{' character
rbrace :: Doc
A '}' character
Wrapping documents in delimiters
parens :: Doc -> Doc
Wrap document in (...)
brackets :: Doc -> Doc
Wrap document in [...]
braces :: Doc -> Doc
Wrap document in {...}
quotes :: Doc -> Doc
Wrap document in '...'
doubleQuotes :: Doc -> Doc
Wrap document in "..."
Combining documents
empty :: Doc
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.
(<>) :: Doc -> Doc -> Doc
Beside. <> is associative, with identity empty.
(<+>) :: Doc -> Doc -> Doc
Beside, separated by space, unless one of the arguments is empty. <+> is associative, with identity empty.
hcat :: [Doc] -> Doc
List version of <>.
hsep :: [Doc] -> Doc
List version of <+>.
($$) :: Doc -> Doc -> Doc

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.
($+$) :: Doc -> Doc -> Doc
Above, with no overlapping. $+$ is associative, with identity empty.
vcat :: [Doc] -> Doc
List version of $$.
sep :: [Doc] -> Doc
Either hsep or vcat.
cat :: [Doc] -> Doc
Either hcat or vcat.
fsep :: [Doc] -> Doc
"Paragraph fill" version of sep.
fcat :: [Doc] -> Doc
"Paragraph fill" version of cat.
nest :: Int -> Doc -> Doc

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 :: Doc -> Int -> Doc -> Doc
hang d1 n d2 = sep [d1, nest n d2]
punctuate :: Doc -> [Doc] -> [Doc]
punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
Predicates on documents
isEmpty :: Doc -> Bool
Returns True if the document is empty
Rendering documents
Default rendering
render :: Doc -> String
Renders the document as a string using the default style.
Rendering with a particular style
data Style
A rendering style.
Constructors
Style
mode :: ModeThe rendering mode
lineLength :: IntLength of line, in chars
ribbonsPerLine :: FloatRatio of ribbon length to line length
style :: Style
The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).
renderStyle :: Style -> Doc -> String
Render the document as a string using a specified style.
General rendering
fullRender
::
=> ModeRendering mode
-> IntLine length
-> FloatRibbons per line
-> TextDetails -> a -> aWhat to do with text
-> aWhat to do at the end
-> DocThe document
-> aResult
The general rendering interface.
data Mode
Rendering mode.
Constructors
PageModeNormal
ZigZagModeWith zig-zag cuts
LeftModeNo indentation, infinitely long lines
OneLineModeAll on one line
data TextDetails
Constructors
Chr Char
Str String
PStr String
Produced by Haddock version 2.3.0