Safe Haskell | None |
---|---|
Language | Haskell98 |
Compact pretty-printer.
Examples
Assume that we want to pretty print S-Expressions, which can either be atom or a list of S-Expressions.
>>>
data SExpr = SExpr [SExpr] | Atom String deriving Show
>>>
let pretty :: SExpr -> Doc (); pretty (Atom s) = text s; pretty (SExpr xs) = text "(" <> (sep $ map pretty xs) <> text ")"
Using the above representation, the S-Expression (a b c d)
has the following encoding:
>>>
let abcd = SExpr [Atom "a",Atom "b",Atom "c",Atom "d"]
The legible layouts of the abcd
S-Expression defined above would be either
>>>
putStrLn $ render $ pretty abcd
(a b c d)
or
>>>
putStrLn $ renderWith defaultOptions { optsPageWidth = 5 } $ pretty abcd
(a b c d)
The testData
S-Expression is specially crafted to
demonstrate general shortcomings of both Hughes and Wadler libraries.
>>>
let abcd4 = SExpr [abcd,abcd,abcd,abcd]
>>>
let testData = SExpr [ SExpr [Atom "abcde", abcd4], SExpr [Atom "abcdefgh", abcd4]]
>>>
putStrLn $ render $ pretty testData
((abcde ((a b c d) (a b c d) (a b c d) (a b c d))) (abcdefgh ((a b c d) (a b c d) (a b c d) (a b c d))))
on 20-column-wide page
>>>
putStrLn $ renderWith defaultOptions { optsPageWidth = 20 } $ pretty testData
((abcde ((a b c d) (a b c d) (a b c d) (a b c d))) (abcdefgh ((a b c d) (a b c d) (a b c d) (a b c d))))
Yet, neither Hughes' nor Wadler's library can deliver those results.
Annotations
For example we can annotate every car element of S-Expressions, and in the rendering phase emphasise them by rendering them in uppercase.
>>>
let pretty' :: SExpr -> Doc Any; pretty' (Atom s) = text s; pretty' (SExpr []) = text "()"; pretty' (SExpr (x:xs)) = text "(" <> (sep $ annotate (Any True) (pretty' x) : map pretty' xs) <> text ")"
>>>
let render' = renderWith defaultOptions { optsAnnotate = \a x -> if a == Any True then map toUpper x else x }
>>>
putStrLn $ render' $ pretty' testData
((ABCDE ((A B C D) (A B C D) (A B C D) (A B C D))) (ABCDEFGH ((A B C D) (A b c d) (A b c d) (A b c d))))
- type Doc = DDoc
- module Data.Monoid
- text :: (Layout d, Monoid a) => String -> d a
- flush :: (Layout d, Monoid a) => d a -> d a
- char :: Annotation a => Char -> Doc a
- hang :: Annotation a => Int -> Doc a -> Doc a -> Doc a
- encloseSep :: Annotation a => Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a
- list :: Annotation a => [Doc a] -> Doc a
- tupled :: Annotation a => [Doc a] -> Doc a
- semiBraces :: Annotation a => [Doc a] -> Doc a
- (<+>) :: Annotation a => Doc a -> Doc a -> Doc a
- ($$) :: Annotation a => Doc a -> Doc a -> Doc a
- (</>) :: Annotation a => Doc a -> Doc a -> Doc a
- (<//>) :: Annotation a => Doc a -> Doc a -> Doc a
- (<$$>) :: Annotation a => Doc a -> Doc a -> Doc a
- (<|>) :: (Document d, Eq a) => d a -> d a -> d a
- hsep :: Annotation a => [Doc a] -> Doc a
- sep :: Annotation a => [Doc a] -> Doc a
- hcat :: Annotation a => [Doc a] -> Doc a
- vcat :: Annotation a => [Doc a] -> Doc a
- cat :: Annotation a => [Doc a] -> Doc a
- punctuate :: Annotation a => Doc a -> [Doc a] -> [Doc a]
- fillSep :: Annotation a => [Doc a] -> Doc a
- fillCat :: Annotation a => [Doc a] -> Doc a
- enclose :: Annotation a => Doc a -> Doc a -> Doc a -> Doc a
- squotes :: Annotation a => Doc a -> Doc a
- dquotes :: Annotation a => Doc a -> Doc a
- parens :: Annotation a => Doc a -> Doc a
- angles :: Annotation a => Doc a -> Doc a
- braces :: Annotation a => Doc a -> Doc a
- brackets :: Annotation a => Doc a -> Doc a
- lparen :: Annotation a => Doc a
- rparen :: Annotation a => Doc a
- langle :: Annotation a => Doc a
- rangle :: Annotation a => Doc a
- lbrace :: Annotation a => Doc a
- rbrace :: Annotation a => Doc a
- lbracket :: Annotation a => Doc a
- rbracket :: Annotation a => Doc a
- squote :: Annotation a => Doc a
- dquote :: Annotation a => Doc a
- semi :: Annotation a => Doc a
- colon :: Annotation a => Doc a
- comma :: Annotation a => Doc a
- space :: Annotation a => Doc a
- dot :: Annotation a => Doc a
- backslash :: Annotation a => Doc a
- equals :: Annotation a => Doc a
- string :: Annotation a => String -> Doc a
- int :: Annotation a => Int -> Doc a
- integer :: Annotation a => Integer -> Doc a
- float :: Annotation a => Float -> Doc a
- double :: Annotation a => Double -> Doc a
- rational :: Annotation a => Rational -> Doc a
- bool :: Annotation a => Bool -> Doc a
- renderWith :: (Monoid r, Monoid a, Eq a) => Options a r -> Doc a -> r
- render :: Annotation a => Doc a -> String
- data Options a r = Options {
- optsPageWidth :: !Int
- optsAnnotate :: a -> String -> r
- defaultOptions :: Options a String
- annotate :: forall a. (Layout d, Monoid a) => a -> d a -> d a
Documents
Basic combinators
module Data.Monoid
hang :: Annotation a => Int -> Doc a -> Doc a -> Doc a Source #
The hang combinator implements hanging indentation. The document
(hang i x)
renders document x
with a nesting level set to the
current column plus i
. The following example uses hanging
indentation for some text:
test = hang 4 (fillSep (map text (words "the hang combinator indents these words !")))
Which lays out on a page with a width of 20 characters as:
the hang combinator indents these words !
The hang
combinator is implemented as:
hang i x = align (nest i x)
encloseSep :: Annotation a => Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a Source #
The document (enclosure l r sep xs)
concatenates the documents
xs
separated by sep
and encloses the resulting document by l
and r
. The documents are rendered horizontally if that fits the
page. Otherwise they are aligned vertically. All separators are put
in front of the elements. For example, the combinator list
can be
defined with enclosure
:
list xs = enclosure lbracket rbracket comma xs test = text "list" <+> (list (map int [10,200,3000]))
Which is layed out with a page width of 20 as:
list [10,200,3000]
But when the page width is 15, it is layed out as:
list [10 ,200 ,3000]
list :: Annotation a => [Doc a] -> Doc a Source #
The document (list xs)
comma separates the documents xs
and
encloses them in square brackets. The documents are rendered
horizontally if that fits the page. Otherwise they are aligned
vertically. All comma separators are put in front of the elements.
tupled :: Annotation a => [Doc a] -> Doc a Source #
The document (tupled xs)
comma separates the documents xs
and
encloses them in parenthesis. The documents are rendered
horizontally if that fits the page. Otherwise they are aligned
vertically. All comma separators are put in front of the elements.
semiBraces :: Annotation a => [Doc a] -> Doc a Source #
The document (semiBraces xs)
separates the documents xs
with
semi colons and encloses them in braces. The documents are rendered
horizontally if that fits the page. Otherwise they are aligned
vertically. All semi colons are put in front of the elements.
Operators
(<+>) :: Annotation a => Doc a -> Doc a -> Doc a Source #
The document (x <+> y)
concatenates document x
and y
with a
space
in between. (infixr 6)
($$) :: Annotation a => Doc a -> Doc a -> Doc a Source #
The document (x <$$> y)
concatenates document x
and y
with
a linebreak in between. (infixr 5)
(</>) :: Annotation a => Doc a -> Doc a -> Doc a Source #
The document (x </> y)
puts x
and y
either next to each other
(with a space
in between) if x
fits on a single line, or underneath each other. (infixr 5)
(<//>) :: Annotation a => Doc a -> Doc a -> Doc a Source #
The document (x <//> y)
puts x
and y
either right next
to each other (if x
fits on a single line) or underneath each
other. (infixr 5)
(<$$>) :: Annotation a => Doc a -> Doc a -> Doc a Source #
The document (x <$$> y)
concatenates document x
and y
with
a linebreak in between. (infixr 5)
List combinators
hsep :: Annotation a => [Doc a] -> Doc a Source #
The document (hsep xs)
concatenates all documents xs
horizontally with (<+>)
.
sep :: Annotation a => [Doc a] -> Doc a Source #
The document (sep xs)
concatenates all documents xs
either
horizontally with (<+>)
, if it fits the page, or vertically with
(<$>)
.
hcat :: Annotation a => [Doc a] -> Doc a Source #
The document (hcat xs)
concatenates all documents xs
horizontally with (<->)
.
vcat :: Annotation a => [Doc a] -> Doc a Source #
The document (vcat xs)
concatenates all documents xs
vertically with ($$)
.
cat :: Annotation a => [Doc a] -> Doc a Source #
The document (cat xs)
concatenates all documents xs
either
horizontally with (<>)
, if it fits the page, or vertically with
(<$$>)
.
cat xs = group (vcat xs)
punctuate :: Annotation a => Doc a -> [Doc a] -> [Doc a] Source #
(punctuate p xs)
concatenates all documents in xs
with
document p
except for the last document.
someText = map text ["words","in","a","tuple"] test = parens (align (cat (punctuate comma someText)))
This is layed out on a page width of 20 as:
(words,in,a,tuple)
But when the page width is 15, it is layed out as:
(words, in, a, tuple)
(If you want put the commas in front of their elements instead of
at the end, you should use tupled
or, in general, encloseSep
.)
Fill combiantors
fillSep :: Annotation a => [Doc a] -> Doc a Source #
The document (fillSep xs)
concatenates documents xs
horizontally with (<+>)
as long as its fits the page, than
inserts a line
and continues doing that for all documents in
xs
.
fillSep xs = foldr (\<\/\>) empty xs
fillCat :: Annotation a => [Doc a] -> Doc a Source #
The document (fillCat xs)
concatenates documents xs
horizontally with (<>)
as long as its fits the page, than inserts
a linebreak
and continues doing that for all documents in xs
.
fillCat xs = foldr (\<\/\/\>) empty xs
Bracketing combinators
enclose :: Annotation a => Doc a -> Doc a -> Doc a -> Doc a Source #
The document (enclose l r x)
encloses document x
between
documents l
and r
using (<>)
.
squotes :: Annotation a => Doc a -> Doc a Source #
Document (squotes x)
encloses document x
with single quotes
"'".
dquotes :: Annotation a => Doc a -> Doc a Source #
Document (dquotes x)
encloses document x
with double quotes
'"'.
parens :: Annotation a => Doc a -> Doc a Source #
Document (parens x)
encloses document x
in parenthesis, "("
and ")".
angles :: Annotation a => Doc a -> Doc a Source #
Document (angles x)
encloses document x
in angles, "<" and
">".
braces :: Annotation a => Doc a -> Doc a Source #
Document (braces x)
encloses document x
in braces, "{" and
"}".
brackets :: Annotation a => Doc a -> Doc a Source #
Document (brackets x)
encloses document x
in square brackets,
"[" and "]".
Character documents
lparen :: Annotation a => Doc a Source #
The document lparen
contains a left parenthesis, "(".
rparen :: Annotation a => Doc a Source #
The document rparen
contains a right parenthesis, ")".
langle :: Annotation a => Doc a Source #
The document langle
contains a left angle, "<".
rangle :: Annotation a => Doc a Source #
The document rangle
contains a right angle, ">".
lbrace :: Annotation a => Doc a Source #
The document lbrace
contains a left brace, "{".
rbrace :: Annotation a => Doc a Source #
The document rbrace
contains a right brace, "}".
lbracket :: Annotation a => Doc a Source #
The document lbracket
contains a left square bracket, "[".
rbracket :: Annotation a => Doc a Source #
The document rbracket
contains a right square bracket, "]".
squote :: Annotation a => Doc a Source #
The document squote
contains a single quote, "'".
dquote :: Annotation a => Doc a Source #
The document dquote
contains a double quote, '"'.
semi :: Annotation a => Doc a Source #
The document semi
contains a semi colon, ";".
colon :: Annotation a => Doc a Source #
The document colon
contains a colon, ":".
comma :: Annotation a => Doc a Source #
The document comma
contains a comma, ",".
space :: Annotation a => Doc a Source #
The document (nest i x)
renders document x
with the current
indentation level increased by i (See also hang
, align
and
indent
).
nest 2 (text "hello" <$$$> text "world") <$$$> text "!"
outputs as:
hello world !
dot :: Annotation a => Doc a Source #
The document dot
contains a single dot, ".".
backslash :: Annotation a => Doc a Source #
The document backslash
contains a back slash, "\".
equals :: Annotation a => Doc a Source #
The document equals
contains an equal sign, "=".
Primitive type documents
string :: Annotation a => String -> Doc a Source #
The document (string s)
concatenates all characters in s
using line
for newline characters and char
for all other
characters. It is used instead of text
whenever the text contains
newline characters.
int :: Annotation a => Int -> Doc a Source #
The document (int i)
shows the literal integer i
using
text
.
integer :: Annotation a => Integer -> Doc a Source #
The document (integer i)
shows the literal integer i
using
text
.
float :: Annotation a => Float -> Doc a Source #
The document (float f)
shows the literal float f
using
text
.
double :: Annotation a => Double -> Doc a Source #
The document (double d)
shows the literal double d
using
text
.
rational :: Annotation a => Rational -> Doc a Source #
The document (rational r)
shows the literal rational r
using
text
.
Rendering
Options | |
|
defaultOptions :: Options a String Source #