Portability | portable |
---|---|
Stability | provisional |
Maintainer | libraries@haskell.org |
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
- 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
The document type
Constructing documents
Converting values into documents
zeroWidthText :: String -> DocSource
Some text, but without any width. Use for non-printing text such as a HTML or Latex tags
Simple derived documents
Wrapping documents in delimiters
doubleQuotes :: Doc -> DocSource
Wrap document in "..."
Combining documents
($$) :: Doc -> Doc -> DocSource
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
nest :: Int -> Doc -> DocSource
Nest (or indent) a document by a given number of positions
(which may also be negative). nest
satisfies the laws:
nest
0 x = xnest
k (nest
k' x) =nest
(k+k') xnest
k (x<>
y) =nest
k z<>
nest
k ynest
k (x$$
y) =nest
k x$$
nest
k ynest
kempty
=empty
-
x
, if<>
nest
k y = x<>
yx
non-empty
The side condition on the last law is needed because
empty
is a left identity for <>
.
punctuate :: Doc -> [Doc] -> [Doc]Source
punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
Predicates on documents
Rendering documents
Default rendering
Rendering with a particular style
A rendering style.
Style | |
|
renderStyle :: Style -> Doc -> StringSource
Render the document as a string using a specified style.
General rendering
:: Mode | Rendering mode |
-> Int | Line length |
-> Float | Ribbons per line |
-> (TextDetails -> a -> a) | What to do with text |
-> a | What to do at the end |
-> Doc | The document |
-> a | Result |
The general rendering interface.
Rendering mode.
PageMode | Normal |
ZigZagMode | With zig-zag cuts |
LeftMode | No indentation, infinitely long lines |
OneLineMode | All on one line |