Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Doc
- module Data.Monoid
- text :: Layout d => String -> d
- flush :: Layout d => d -> d
- char :: Char -> Doc
- hang :: Int -> Doc -> Doc -> Doc
- encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc
- list :: [Doc] -> Doc
- tupled :: [Doc] -> Doc
- semiBraces :: [Doc] -> Doc
- (<+>) :: Doc -> Doc -> Doc
- ($$) :: Doc -> Doc -> Doc
- hsep :: [Doc] -> Doc
- sep :: [Doc] -> Doc
- hcat :: [Doc] -> Doc
- vcat :: [Doc] -> Doc
- cat :: [Doc] -> Doc
- punctuate :: Doc -> [Doc] -> [Doc]
- enclose :: Doc -> Doc -> Doc -> Doc
- squotes :: Doc -> Doc
- dquotes :: Doc -> Doc
- parens :: Doc -> Doc
- angles :: Doc -> Doc
- braces :: Doc -> Doc
- brackets :: Doc -> Doc
- lparen :: Doc
- rparen :: Doc
- langle :: Doc
- rangle :: Doc
- lbrace :: Doc
- rbrace :: Doc
- lbracket :: Doc
- rbracket :: Doc
- squote :: Doc
- dquote :: Doc
- semi :: Doc
- colon :: Doc
- comma :: Doc
- space :: Doc
- dot :: Doc
- backslash :: Doc
- equals :: Doc
- string :: String -> Doc
- int :: Int -> Doc
- integer :: Integer -> Doc
- float :: Float -> Doc
- double :: Double -> Doc
- rational :: Rational -> Doc
- bool :: Bool -> Doc
- render :: Layout d => d -> String
Documents
Basic combinators
module Data.Monoid
hang :: Int -> Doc -> Doc -> Doc 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 :: Doc -> Doc -> Doc -> [Doc] -> Doc 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]
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.
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 :: [Doc] -> Doc 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
(<+>) :: Doc -> Doc -> Doc Source
The document (x <+> y)
concatenates document x
and y
with a
space
in between. (infixr 6)
List combinators
The document (hsep xs)
concatenates all documents xs
horizontally with (<+>)
.
The document (sep xs)
concatenates all documents xs
either
horizontally with (<+>)
, if it fits the page, or vertically with
(<$>)
.
The document (hcat xs)
concatenates all documents xs
horizontally with (<>)
.
The document (vcat xs)
concatenates all documents xs
vertically with ($$)
.
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 :: Doc -> [Doc] -> [Doc] 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
.)
Bracketing combinators
enclose :: Doc -> Doc -> Doc -> Doc Source
The document (enclose l r x)
encloses document x
between
documents l
and r
using (<>)
.
Document (brackets x)
encloses document x
in square brackets,
"[" and "]".
Character documents
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 !
Primitive type documents
string :: String -> Doc 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.
rational :: Rational -> Doc Source
The document (rational r)
shows the literal rational r
using
text
.