Haskell Hierarchical Libraries (base package)ContentsIndex
Text.PrettyPrint.HughesPJ
Portability portable
Stability provisional
Maintainer libraries@haskell.org
Contents
The document type
Primitive Documents
Converting values into 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
empty :: Doc
semi :: Doc
comma :: Doc
colon :: Doc
space :: Doc
equals :: Doc
lparen :: Doc
rparen :: Doc
lbrack :: Doc
rbrack :: Doc
lbrace :: Doc
rbrace :: Doc
text :: String -> Doc
char :: Char -> Doc
ptext :: String -> Doc
int :: Int -> Doc
integer :: Integer -> Doc
float :: Float -> Doc
double :: Double -> Doc
rational :: Rational -> Doc
parens :: Doc -> Doc
brackets :: Doc -> Doc
braces :: Doc -> Doc
quotes :: Doc -> Doc
doubleQuotes :: Doc -> 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
Instances
Show Doc
Primitive Documents
empty :: Doc
An empty document
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
Converting values into documents
text :: String -> Doc
char :: Char -> Doc
ptext :: String -> Doc
int :: Int -> Doc
integer :: Integer -> Doc
float :: Float -> Doc
double :: Double -> Doc
rational :: Rational -> Doc
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
(<>) :: Doc -> Doc -> Doc
Beside
(<+>) :: Doc -> Doc -> Doc
Beside, separated by space
hcat :: [Doc] -> Doc
List version of <>
hsep :: [Doc] -> Doc
List version of <+>
($$) :: Doc -> Doc -> Doc
Above; if there is no overlap it "dovetails" the two
($+$) :: Doc -> Doc -> Doc
Above, without dovetailing.
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
Nested
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 -> a)What 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 0.6