Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module is based, in part, on some of the interface for Text.PrettyPrint.Annotated.Leijen.
Synopsis
- class Pretty a where
- newtype StyleDoc = StyleDoc {}
- newtype StyleAnn = StyleAnn (Maybe Style)
- displayAnsi :: (Pretty a, HasLogFunc env, HasStylesUpdate env, MonadReader env m, HasCallStack) => Int -> a -> m Utf8Builder
- displayPlain :: (Pretty a, HasLogFunc env, HasStylesUpdate env, MonadReader env m, HasCallStack) => Int -> a -> m Utf8Builder
- renderDefault :: Int -> Doc a -> SimpleDoc a
- nest :: Int -> StyleDoc -> StyleDoc
- line :: StyleDoc
- linebreak :: StyleDoc
- group :: StyleDoc -> StyleDoc
- softline :: StyleDoc
- softbreak :: StyleDoc
- align :: StyleDoc -> StyleDoc
- hang :: Int -> StyleDoc -> StyleDoc
- indent :: Int -> StyleDoc -> StyleDoc
- encloseSep :: StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc
- (<+>) :: StyleDoc -> StyleDoc -> StyleDoc
- hsep :: [StyleDoc] -> StyleDoc
- vsep :: [StyleDoc] -> StyleDoc
- fillSep :: [StyleDoc] -> StyleDoc
- sep :: [StyleDoc] -> StyleDoc
- hcat :: [StyleDoc] -> StyleDoc
- vcat :: [StyleDoc] -> StyleDoc
- fillCat :: [StyleDoc] -> StyleDoc
- cat :: [StyleDoc] -> StyleDoc
- punctuate :: StyleDoc -> [StyleDoc] -> [StyleDoc]
- fill :: Int -> StyleDoc -> StyleDoc
- fillBreak :: Int -> StyleDoc -> StyleDoc
- enclose :: StyleDoc -> StyleDoc -> StyleDoc -> StyleDoc
- squotes :: StyleDoc -> StyleDoc
- dquotes :: StyleDoc -> StyleDoc
- parens :: StyleDoc -> StyleDoc
- angles :: StyleDoc -> StyleDoc
- braces :: StyleDoc -> StyleDoc
- brackets :: StyleDoc -> StyleDoc
- string :: String -> StyleDoc
- annotate :: StyleAnn -> StyleDoc -> StyleDoc
- noAnnotate :: StyleDoc -> StyleDoc
- styleAnn :: Style -> StyleDoc -> StyleDoc
Pretty-print typeclass
Nothing
Instances
Pretty ModuleName Source # | |
Defined in Text.PrettyPrint.Leijen.Extended pretty :: ModuleName -> StyleDoc Source # | |
Pretty PrettyException Source # | |
Defined in RIO.PrettyPrint.PrettyException pretty :: PrettyException -> StyleDoc Source # | |
Pretty StyleDoc Source # | |
Pretty (SomeBase Dir) Source # | |
Pretty (SomeBase File) Source # | |
Pretty (Path b Dir) Source # | |
Pretty (Path b File) Source # | |
Documents annotated by a style
A document annotated by a style.
A style annotation.
displayAnsi :: (Pretty a, HasLogFunc env, HasStylesUpdate env, MonadReader env m, HasCallStack) => Int -> a -> m Utf8Builder Source #
displayPlain :: (Pretty a, HasLogFunc env, HasStylesUpdate env, MonadReader env m, HasCallStack) => Int -> a -> m Utf8Builder Source #
Selective use of the Text.PrettyPrint.Annotated.Leijen interface
Documented omissions by reference to package
annotated-wl-pprint-0.7.0
.
Documents, parametrized by their annotations
Omitted compared to original:
Doc, putDoc, hPutDoc
Basic combinators
Omitted compared to the original:
empty, char, text, (<>)
Instead of empty
, use mempty
.
Instead of char
and text
, use fromString
.
The line
document advances to the next line and indents to the current
nesting level. Document line
behaves like (fromString " ")
if the line
break is undone by group
.
group :: StyleDoc -> StyleDoc Source #
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.
The document softline
behaves like (fromString " ")
if the resulting
output fits the page, otherwise it behaves like line
.
softline = group line
Alignment
The combinators in this section can not be described by Wadler's
original combinators. They align their output relative to the current
output position - in contrast to nest
which always aligns to the
current nesting level. This deprives these combinators from being
`optimal'. In practice however they prove to be very useful. The
combinators in this section should be used with care, since they are more
expensive than the other combinators. For example, align
shouldn't be
used to pretty print all top-level declarations of a language, but using
hang
for let
expressions is fine.
Omitted compared to the original:
list, tupled, semiBraces
align :: StyleDoc -> StyleDoc Source #
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 <> line <> y)
test = fromString "hi" <+> (fromString "nice" $$ fromString "world")
which will be layed out as:
hi nice world
hang :: Int -> StyleDoc -> StyleDoc 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 fromString (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 -> StyleDoc -> StyleDoc Source #
The document (indent i x)
indents document x
with i
spaces.
test = indent 4 (fillSep (map fromString (words "the indent combinator indents these words !")))
Which lays out with a page width of 20 as:
the indent combinator indents these words !
encloseSep :: StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc Source #
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 = fromString "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
Omitted compared to the original:
(<$>), (</>), (<$$>), (<//>)
(<+>) :: StyleDoc -> StyleDoc -> StyleDoc Source #
The document (x <+> y)
concatenates document x
and y
with a
(fromString " ")
in between. (infixr 6)
List combinators
hsep :: [StyleDoc] -> StyleDoc Source #
The document (hsep xs)
concatenates all documents xs
horizontally with
(
.<+>
)
vsep :: [StyleDoc] -> StyleDoc Source #
The document (vsep xs)
concatenates all documents xs
vertically with
(<> line <>)
. If a group
undoes the line breaks inserted by vsep
,
all documents are separated with a space.
someText = map fromString (words ("text to lay out")) test = fromString "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 = fromString "some" <+> align (vsep someText)
Which is printed as:
some text to lay out
sep :: [StyleDoc] -> StyleDoc Source #
The document (sep xs)
concatenates all documents xs
either horizontally
with (<+>)
, if it fits the page, or vertically with (<> line <>)
.
sep xs = group (vsep xs)
hcat :: [StyleDoc] -> StyleDoc Source #
The document (hcat xs)
concatenates all documents xs
horizontally with
(<>)
.
fillCat :: [StyleDoc] -> StyleDoc 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 (<> softbreak <>) mempty xs
cat :: [StyleDoc] -> StyleDoc Source #
The document (cat xs)
concatenates all documents xs
either
horizontally with (<>)
, if it fits the page, or vertically with
(<> linebreak <>)
.
cat xs = group (vcat xs)
punctuate :: StyleDoc -> [StyleDoc] -> [StyleDoc] Source #
(punctuate p xs)
concatenates all documents in xs
with document p
except for the last document.
someText = map fromString ["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 encloseSep
.)
Fillers
fill :: Int -> StyleDoc -> StyleDoc Source #
The document (fill i x)
renders document x
. It than appends
(fromString " ")
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 (fromString name) <+> fromString "::" <+> fromString tp test = fromString "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 -> StyleDoc -> StyleDoc Source #
The document (fillBreak i x)
first renders document x
. It then appends
(fromString " ")
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 (fromString name) <+> fromString "::" <+> fromString tp
The output will now be:
let empty :: Doc a nest :: Int -> Doc a -> Doc a linebreak :: Doc a
Bracketing combinators
enclose :: StyleDoc -> StyleDoc -> StyleDoc -> StyleDoc Source #
The document (enclose l r x)
encloses document x
between documents l
and r
using (<>)
.
enclose l r x = l <> x <> r
squotes :: StyleDoc -> StyleDoc Source #
Document (squotes x)
encloses document x
with single quotes "'".
dquotes :: StyleDoc -> StyleDoc Source #
Document (dquotes x)
encloses document x
with double quotes '"'.
parens :: StyleDoc -> StyleDoc Source #
Document (parens x)
encloses document x
in parenthesis, "(" and
")".
angles :: StyleDoc -> StyleDoc Source #
Document (angles x)
encloses document x
in angles, "<" and ">".
braces :: StyleDoc -> StyleDoc Source #
Document (braces x)
encloses document x
in braces, "{" and "}".
brackets :: StyleDoc -> StyleDoc Source #
Document (brackets x)
encloses document x
in square brackets, "[" and
"]".
Character documents
Entirely omitted:
lparen, rparen, langle, rangle, lbrace, rbrace, lbracket, rbracket, squote, dquote, semi, colon, comma, space, dot, backslash, equals, pipe
Primitive type documents
Omitted compared to the original:
int, integer, float, double, rational, bool
string :: String -> StyleDoc Source #
The document string s
concatenates all characters in s
using line
for
newline characters and fromString
for all other characters. It is used
whenever the text contains newline characters.
Since: 0.1.4.0
Semantic annotations
noAnnotate :: StyleDoc -> StyleDoc Source #
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.
Rendering
Entirely omitted:
SimpleDoc (..), renderPretty, renderCompact, displayDecorated, displayDecoratedA, display, displayS, displayIO, SpanList (..), displaySpans
Undocumented
Entirely omitted:
column, nesting, width