Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module re-exports some of the interface for Text.PrettyPrint.Annotated.Leijen along with additional definitions useful for stack.
- class Display a where
- type Ann a
- type AnsiDoc = Doc AnsiAnn
- newtype AnsiAnn = AnsiAnn [SGR]
- class HasAnsiAnn a where
- hDisplayAnsi :: (Display a, HasAnsiAnn (Ann a), MonadIO m) => Handle -> Int -> a -> m ()
- displayAnsi :: (Display a, HasAnsiAnn (Ann a)) => Int -> a -> Text
- displayPlain :: Display a => Int -> a -> Text
- renderDefault :: Int -> Doc a -> SimpleDoc a
- black :: Doc AnsiAnn -> Doc AnsiAnn
- red :: Doc AnsiAnn -> Doc AnsiAnn
- green :: Doc AnsiAnn -> Doc AnsiAnn
- yellow :: Doc AnsiAnn -> Doc AnsiAnn
- blue :: Doc AnsiAnn -> Doc AnsiAnn
- magenta :: Doc AnsiAnn -> Doc AnsiAnn
- cyan :: Doc AnsiAnn -> Doc AnsiAnn
- white :: Doc AnsiAnn -> Doc AnsiAnn
- dullblack :: Doc AnsiAnn -> Doc AnsiAnn
- dullred :: Doc AnsiAnn -> Doc AnsiAnn
- dullgreen :: Doc AnsiAnn -> Doc AnsiAnn
- dullyellow :: Doc AnsiAnn -> Doc AnsiAnn
- dullblue :: Doc AnsiAnn -> Doc AnsiAnn
- dullmagenta :: Doc AnsiAnn -> Doc AnsiAnn
- dullcyan :: Doc AnsiAnn -> Doc AnsiAnn
- dullwhite :: Doc AnsiAnn -> Doc AnsiAnn
- onblack :: Doc AnsiAnn -> Doc AnsiAnn
- onred :: Doc AnsiAnn -> Doc AnsiAnn
- ongreen :: Doc AnsiAnn -> Doc AnsiAnn
- onyellow :: Doc AnsiAnn -> Doc AnsiAnn
- onblue :: Doc AnsiAnn -> Doc AnsiAnn
- onmagenta :: Doc AnsiAnn -> Doc AnsiAnn
- oncyan :: Doc AnsiAnn -> Doc AnsiAnn
- onwhite :: Doc AnsiAnn -> Doc AnsiAnn
- ondullblack :: Doc AnsiAnn -> Doc AnsiAnn
- ondullred :: Doc AnsiAnn -> Doc AnsiAnn
- ondullgreen :: Doc AnsiAnn -> Doc AnsiAnn
- ondullyellow :: Doc AnsiAnn -> Doc AnsiAnn
- ondullblue :: Doc AnsiAnn -> Doc AnsiAnn
- ondullmagenta :: Doc AnsiAnn -> Doc AnsiAnn
- ondullcyan :: Doc AnsiAnn -> Doc AnsiAnn
- ondullwhite :: Doc AnsiAnn -> Doc AnsiAnn
- bold :: Doc AnsiAnn -> Doc AnsiAnn
- faint :: Doc AnsiAnn -> Doc AnsiAnn
- normal :: Doc AnsiAnn -> Doc AnsiAnn
- data Doc a :: * -> *
- nest :: Int -> Doc a -> Doc a
- line :: Doc a
- linebreak :: Doc a
- group :: Doc a -> Doc a
- softline :: Doc a
- softbreak :: Doc a
- align :: Doc a -> Doc a
- hang :: Int -> Doc a -> Doc a
- indent :: Int -> Doc a -> Doc a
- encloseSep :: Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a
- (<+>) :: Doc a -> Doc a -> Doc a
- hsep :: [Doc a] -> Doc a
- vsep :: [Doc a] -> Doc a
- fillSep :: [Doc a] -> Doc a
- sep :: [Doc a] -> Doc a
- hcat :: [Doc a] -> Doc a
- vcat :: [Doc a] -> Doc a
- fillCat :: [Doc a] -> Doc a
- cat :: [Doc a] -> Doc a
- punctuate :: Doc a -> [Doc a] -> [Doc a]
- fill :: Int -> Doc a -> Doc a
- fillBreak :: Int -> Doc a -> Doc a
- enclose :: Doc a -> Doc a -> Doc a -> Doc a
- squotes :: Doc a -> Doc a
- dquotes :: Doc a -> Doc a
- parens :: Doc a -> Doc a
- angles :: Doc a -> Doc a
- braces :: Doc a -> Doc a
- brackets :: Doc a -> Doc a
- annotate :: a -> Doc a -> Doc a
- noAnnotate :: Doc a -> Doc a
Pretty-print typeclass
Ansi terminal Doc
class HasAnsiAnn a where Source #
hDisplayAnsi :: (Display a, HasAnsiAnn (Ann a), MonadIO m) => Handle -> Int -> a -> m () Source #
displayAnsi :: (Display a, HasAnsiAnn (Ann a)) => Int -> a -> Text Source #
Color combinators
Intensity combinators
Selective re-exports from Text.PrettyPrint.Annotated.Leijen
Documents, parametrized by their annotations
The abstract data type Doc a
represents pretty documents.
Doc a
is an instance of the Show
class. (show doc)
pretty
prints document doc
with a page width of 100 characters and a
ribbon width of 40 characters.
show (text "hello" <$> text "world")
Which would return the string "hello\nworld", i.e.
hello world
Basic combinators
The line
document advances to the next line and indents to the
current nesting level. Doc aument line
behaves like (text " ")
if the line break is undone by group
.
The group
combinator is used to specify alternative
layouts. The document (group x)
undoes all line breaks in
document x
. The resulting line is added to the current line if
that fits the page. Otherwise, the document x
is rendered without
any changes.
Alignment
The document (align x)
renders document x
with the nesting
level set to the current column. It is used for example to
implement hang
.
As an example, we will put a document right above another one, regardless of the current nesting level:
x $$ y = align (x <$> y)
test = text "hi" <+> (text "nice" $$ text "world")
which will be layed out as:
hi nice world
hang :: Int -> Doc a -> Doc a #
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)
indent :: Int -> Doc a -> Doc a #
The document (indent i x)
indents document x
with i
spaces.
test = indent 4 (fillSep (map text (words "the indent combinator indents these words !")))
Which lays out with a page width of 20 as:
the indent combinator indents these words !
encloseSep :: Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a #
The document (encloseSep 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 encloseSep
:
list xs = encloseSep 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]
Operators
(<+>) :: Doc a -> Doc a -> Doc a infixr 6 #
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 (vsep xs)
concatenates all documents xs
vertically with (<$>)
. If a group
undoes the line breaks
inserted by vsep
, all documents are separated with a space.
someText = map text (words ("text to lay out")) test = text "some" <+> vsep someText
This is layed out as:
some text to lay out
The align
combinator can be used to align the documents under
their first element
test = text "some" <+> align (vsep someText)
Which is printed as:
some text to lay out
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
The document (sep xs)
concatenates all documents xs
either
horizontally with (<+>)
, if it fits the page, or vertically with
(<$>)
.
sep xs = group (vsep xs)
The document (hcat xs)
concatenates all documents xs
horizontally with (<>)
.
The document (vcat xs)
concatenates all documents xs
vertically with (<$$>)
. If a group
undoes the line breaks
inserted by vcat
, all documents are directly concatenated.
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
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 a -> [Doc a] -> [Doc a] #
(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
.)
Fillers
fill :: Int -> Doc a -> Doc a #
The document (fill i x)
renders document x
. It than appends
space
s until the width is equal to i
. If the width of x
is
already larger, nothing is appended. This combinator is quite
useful in practice to output a list of bindings. The following
example demonstrates this.
types = [("empty","Doc a") ,("nest","Int -> Doc a -> Doc a") ,("linebreak","Doc a")] ptype (name,tp) = fill 6 (text name) <+> text "::" <+> text tp test = text "let" <+> align (vcat (map ptype types))
Which is layed out as:
let empty :: Doc a nest :: Int -> Doc a -> Doc a linebreak :: Doc a
fillBreak :: Int -> Doc a -> Doc a #
The document (fillBreak i x)
first renders document x
. It
than appends space
s until the width is equal to i
. If the
width of x
is already larger than i
, the nesting level is
increased by i
and a line
is appended. When we redefine ptype
in the previous example to use fillBreak
, we get a useful
variation of the previous output:
ptype (name,tp) = fillBreak 6 (text name) <+> text "::" <+> text tp
The output will now be:
let empty :: Doc a nest :: Int -> Doc a -> Doc a linebreak :: Doc a
Bracketing combinators
enclose :: Doc a -> Doc a -> Doc a -> Doc a #
The document (enclose l r x)
encloses document x
between
documents l
and r
using (<>)
.
enclose l r x = l <> x <> r
Document (brackets x)
encloses document x
in square brackets,
"[" and "]".
Character documents
Primitive type documents
Semantic annotations
noAnnotate :: Doc a -> Doc a #
Strip annotations from a document. This is useful for re-using the textual formatting of some sub-document, but applying a different high-level annotation.