Copyright | (c) Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
This module defines simple helper functions for use with Text.PrettyPrint. It also re-exports all the pretty-printing combinators from that module.
Note that the PrintDot
instances for Bool
, etc. match those
specified for use with Graphviz.
You should only be using this module if you are writing custom node
types for use with Data.GraphViz.Types. For actual printing of
code, use
(which produces a
printDotGraph
Text
value).
The Dot language specification specifies that any identifier is in one of four forms:
- Any string of alphabetic ([a-zA-Z\200-\377]) characters, underscores ('_') or digits ([0-9]), not beginning with a digit;
- a number [-]?(.[0-9]+ | [0-9]+(.[0-9]*)? );
- any double-quoted string ("...") possibly containing escaped quotes (\");
- an HTML string (<...>).
(Note that the first restriction is referring to a byte-by-byte
comparison using octal values; when using UTF-8 this corresponds to
all characters c
where ord c >= 128
.)
Due to these restrictions, you should only use text
when you are
sure that the Text
in question is static and quotes are
definitely needed/unneeded; it is better to use the Text
instance for PrintDot
. For more information, see the
specification page:
http://graphviz.org/doc/info/lang.html
Synopsis
- group :: Functor m => m Doc -> m Doc
- nesting :: Functor m => m (Int -> Doc) -> m Doc
- column :: Functor m => m (Int -> Doc) -> m Doc
- nest :: Functor m => Int -> m Doc -> m Doc
- linebreak :: Applicative m => m Doc
- line :: Applicative m => m Doc
- textStrict :: Monad m => Text -> m Doc
- text :: Applicative m => Text -> m Doc
- char :: Applicative m => Char -> m Doc
- empty :: Applicative m => m Doc
- align :: Functor m => m Doc -> m Doc
- hang :: Functor m => Int -> m Doc -> m Doc
- indent :: Functor m => Int -> m Doc -> m Doc
- fillBreak :: Functor m => Int -> m Doc -> m Doc
- fill :: Functor m => Int -> m Doc -> m Doc
- prettyM :: (Pretty a, Applicative m) => a -> m Doc
- rational :: Applicative m => Rational -> m Doc
- double :: Applicative m => Double -> m Doc
- float :: Applicative m => Float -> m Doc
- integer :: Applicative m => Integer -> m Doc
- int :: Applicative m => Int -> m Doc
- stringStrict :: Monad m => Text -> m Doc
- equals :: Applicative m => m Doc
- backslash :: Applicative m => m Doc
- dot :: Applicative m => m Doc
- space :: Applicative m => m Doc
- comma :: Applicative m => m Doc
- colon :: Applicative m => m Doc
- semi :: Applicative m => m Doc
- dquote :: Applicative m => m Doc
- squote :: Applicative m => m Doc
- rbracket :: Applicative m => m Doc
- lbracket :: Applicative m => m Doc
- rbrace :: Applicative m => m Doc
- lbrace :: Applicative m => m Doc
- rangle :: Applicative m => m Doc
- langle :: Applicative m => m Doc
- rparen :: Applicative m => m Doc
- lparen :: Applicative m => m Doc
- enclose :: Applicative m => m Doc -> m Doc -> m Doc -> m Doc
- brackets :: Functor m => m Doc -> m Doc
- angles :: Functor m => m Doc -> m Doc
- parens :: Functor m => m Doc -> m Doc
- braces :: Functor m => m Doc -> m Doc
- dquotes :: Functor m => m Doc -> m Doc
- squotes :: Functor m => m Doc -> m Doc
- spacebreak :: Applicative m => m Doc
- softbreak :: Applicative m => m Doc
- softline :: Applicative m => m Doc
- (<$$>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<//>) :: Applicative m => m Doc -> m Doc -> m Doc
- (</>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<++>) :: Applicative m => m Doc -> m Doc -> m Doc
- (<+>) :: Applicative m => m Doc -> m Doc -> m Doc
- beside :: Applicative m => m Doc -> m Doc -> m Doc
- vcat :: Functor m => m [Doc] -> m Doc
- hcat :: Functor m => m [Doc] -> m Doc
- fillCat :: Functor m => m [Doc] -> m Doc
- cat :: Functor m => m [Doc] -> m Doc
- vsep :: Functor m => m [Doc] -> m Doc
- hsep :: Functor m => m [Doc] -> m Doc
- fillSep :: Functor m => m [Doc] -> m Doc
- sep :: Functor m => m [Doc] -> m Doc
- punctuate :: Applicative m => m Doc -> m [Doc] -> m [Doc]
- encloseSep :: Applicative m => m Doc -> m Doc -> m Doc -> m [Doc] -> m Doc
- semiBraces :: Functor m => m [Doc] -> m Doc
- tupled :: Functor m => m [Doc] -> m Doc
- list :: Functor m => m [Doc] -> m Doc
- displayTStrict :: SimpleDoc -> Text
- displayB :: SimpleDoc -> Builder
- renderOneLine :: Doc -> SimpleDoc
- data Doc
- type DotCode = DotCodeM Doc
- data DotCodeM a
- runDotCode :: DotCode -> Doc
- renderDot :: DotCode -> Text
- class PrintDot a where
- unqtText :: Text -> DotCode
- dotText :: Text -> DotCode
- printIt :: PrintDot a => a -> Text
- addQuotes :: Text -> DotCode -> DotCode
- unqtEscaped :: [Char] -> Text -> DotCode
- printEscaped :: [Char] -> Text -> DotCode
- wrap :: DotCode -> DotCode -> DotCode -> DotCode
- commaDel :: (PrintDot a, PrintDot b) => a -> b -> DotCode
- printField :: PrintDot a => Text -> a -> DotCode
- angled :: DotCode -> DotCode
- fslash :: DotCode
- printColorScheme :: Bool -> ColorScheme -> DotCode
Documentation
group :: Functor m => m Doc -> m Doc #
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.
nesting :: Functor m => m (Int -> Doc) -> m Doc #
Specifies how to nest the document based upon which column it is being nested in.
column :: Functor m => m (Int -> Doc) -> m Doc #
Specifies how to create the document based upon which column it is in.
linebreak :: Applicative m => m Doc #
line :: Applicative m => m Doc #
The line
document advances to the next line and indents to the
current nesting level. Document line
behaves like (text "
")
if the line break is undone by group
or if rendered with
renderOneLine
.
textStrict :: Monad m => Text -> m Doc #
text :: Applicative m => Text -> m Doc #
The document (text s)
contains the literal string s
. The
string shouldn't contain any newline ('\n'
) characters. If the
string contains newline characters, the function string
should
be used.
char :: Applicative m => Char -> m Doc #
The document (char c)
contains the literal character c
. The
character shouldn't be a newline ('\n'
), the function line
should be used for line breaks.
empty :: Applicative m => m Doc #
The empty document is, indeed, empty. Although empty
has no
content, it does have a 'height' of 1 and behaves exactly like
(text "")
(and is therefore not a unit of <$>
).
align :: Functor m => m Doc -> m Doc #
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 laid out as:
hi nice world
hang :: Functor m => Int -> m Doc -> m Doc #
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 :: Functor m => Int -> m Doc -> m Doc #
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 !
fillBreak :: Functor m => Int -> m Doc -> m Doc #
The document (fillBreak i x)
first renders document x
. It
then 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 nest :: Int -> Doc -> Doc linebreak :: Doc
fill :: Functor m => Int -> m Doc -> m Doc #
The document (fill i x)
renders document x
. It then 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") ,("nest","Int -> Doc -> Doc") ,("linebreak","Doc")] ptype (name,tp) = fill 6 (text name) <+> text "::" <+> text tp test = text "let" <+> align (vcat (map ptype types))
Which is laid out as:
let empty :: Doc nest :: Int -> Doc -> Doc linebreak :: Doc
prettyM :: (Pretty a, Applicative m) => a -> m Doc #
rational :: Applicative m => Rational -> m Doc #
The document (rational r)
shows the literal rational r
using
text
.
double :: Applicative m => Double -> m Doc #
The document (double d)
shows the literal double d
using
text
.
float :: Applicative m => Float -> m Doc #
The document (float f)
shows the literal float f
using
text
.
integer :: Applicative m => Integer -> m Doc #
The document (integer i)
shows the literal integer i
using
text
.
stringStrict :: Monad m => Text -> m Doc #
equals :: Applicative m => m Doc #
The document equals
contains an equal sign, "=".
backslash :: Applicative m => m Doc #
The document backslash
contains a back slash, "\".
dot :: Applicative m => m Doc #
The document dot
contains a single dot, ".".
space :: Applicative m => m Doc #
The document space
contains a single space, " ".
x <+> y = x `beside` space `beside` y
comma :: Applicative m => m Doc #
The document comma
contains a comma, ",".
colon :: Applicative m => m Doc #
The document colon
contains a colon, ":".
semi :: Applicative m => m Doc #
The document semi
contains a semi colon, ";".
dquote :: Applicative m => m Doc #
The document dquote
contains a double quote, '"'.
squote :: Applicative m => m Doc #
The document squote
contains a single quote, "'".
rbracket :: Applicative m => m Doc #
The document rbracket
contains a right square bracket, "]".
lbracket :: Applicative m => m Doc #
The document lbracket
contains a left square bracket, "[".
rbrace :: Applicative m => m Doc #
The document rbrace
contains a right brace, "}".
lbrace :: Applicative m => m Doc #
The document lbrace
contains a left brace, "{".
rangle :: Applicative m => m Doc #
The document rangle
contains a right angle, ">".
langle :: Applicative m => m Doc #
The document langle
contains a left angle, "<".
rparen :: Applicative m => m Doc #
The document rparen
contains a right parenthesis, ")".
lparen :: Applicative m => m Doc #
The document lparen
contains a left parenthesis, "(".
enclose :: Applicative m => m Doc -> m Doc -> m Doc -> m Doc #
The document (enclose l r x)
encloses document x
between
documents l
and r
using
.beside
enclose l r x = l `beside` x `beside` r
brackets :: Functor m => m Doc -> m Doc #
Document (brackets x)
encloses document x
in square brackets,
"[" and "]".
angles :: Functor m => m Doc -> m Doc #
Document (angles x)
encloses document x
in angles, "<" and
">".
parens :: Functor m => m Doc -> m Doc #
Document (parens x)
encloses document x
in parenthesis, "("
and ")".
braces :: Functor m => m Doc -> m Doc #
Document (braces x)
encloses document x
in braces, "{" and
"}".
dquotes :: Functor m => m Doc -> m Doc #
Document (dquotes x)
encloses document x
with double quotes
'"'.
squotes :: Functor m => m Doc -> m Doc #
Document (squotes x)
encloses document x
with single quotes
"'".
spacebreak :: Applicative m => m Doc #
The document spacebreak
behaves like space
when rendered normally
but like empty
when using renderCompact
or renderOneLine
.
softbreak :: Applicative m => m Doc #
softline :: Applicative m => m Doc #
(<$$>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 #
The document (x <$$> y)
concatenates document x
and y
with a linebreak
in between. (infixr 5)
(<//>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 #
The document (x <//> y)
concatenates document x
and y
with a softbreak
in between. This effectively puts x
and y
either right next to each other or underneath each other. (infixr
5)
(</>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 5 #
The document (x </> y)
concatenates document x
and y
with a softline
in between. This effectively puts x
and y
either next to each other (with a space
in between) or
underneath each other. (infixr 5)
(<++>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 6 #
The document (x <++> y)
concatenates document x
and y
with
a spacebreak
in between. (infixr 6)
(<+>) :: Applicative m => m Doc -> m Doc -> m Doc infixr 6 #
The document (x <+> y)
concatenates document x
and y
with
a space
in between. (infixr 6)
vcat :: Functor m => m [Doc] -> m Doc #
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.
hcat :: Functor m => m [Doc] -> m Doc #
The document (hcat xs)
concatenates all documents xs
horizontally with (<>)
.
fillCat :: Functor m => m [Doc] -> m Doc #
The document (fillCat xs)
concatenates documents xs
horizontally with (<>)
as long as its fits the page, then
inserts a linebreak
and continues doing that for all documents
in xs
.
fillCat xs = foldr (<//>) empty xs
cat :: Functor m => m [Doc] -> m Doc #
The document (cat xs)
concatenates all documents xs
either
horizontally with (<>)
, if it fits the page, or vertically
with (<$$>)
.
cat xs = group (vcat xs)
vsep :: Functor m => m [Doc] -> m Doc #
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 laid 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
hsep :: Functor m => m [Doc] -> m Doc #
The document (hsep xs)
concatenates all documents xs
horizontally with (<+>)
.
fillSep :: Functor m => m [Doc] -> m Doc #
The document (fillSep xs)
concatenates documents xs
horizontally with (<+>)
as long as its fits the page, then
inserts a line
and continues doing that for all documents in
xs
.
fillSep xs = foldr (</>) empty xs
sep :: Functor m => m [Doc] -> m Doc #
The document (sep xs)
concatenates all documents xs
either
horizontally with (<+>)
, if it fits the page, or vertically
with (<$>)
.
sep xs = group (vsep xs)
punctuate :: Applicative m => m Doc -> m [Doc] -> m [Doc] #
(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 laid out on a page width of 20 as:
(words,in,a,tuple)
But when the page width is 15, it is laid 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
.)
encloseSep :: Applicative m => m Doc -> m Doc -> m Doc -> m [Doc] -> m Doc #
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 laid out with a page width of 20 as:
list [10,200,3000]
But when the page width is 15, it is laid out as:
list [10 ,200 ,3000]
semiBraces :: Functor m => m [Doc] -> m Doc #
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.
tupled :: Functor m => m [Doc] -> m Doc #
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.
list :: Functor m => m [Doc] -> m Doc #
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.
displayTStrict :: SimpleDoc -> Text #
renderOneLine :: Doc -> SimpleDoc #
(renderOneLine x)
renders document x
without adding any
indentation or newlines.
The abstract data type Doc
represents pretty documents.
Doc
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
Instances
Show Doc | |
Show DotCode Source # | |
IsString Doc | |
Defined in Text.PrettyPrint.Leijen.Text fromString :: String -> Doc # | |
IsString DotCode Source # | |
Defined in Data.GraphViz.Printing fromString :: String -> DotCode # | |
Semigroup Doc | In particular, note that the document |
Semigroup DotCode Source # | |
Monoid Doc | |
Monoid DotCode Source # | |
Pretty Doc | |
Defined in Text.PrettyPrint.Leijen.Text |
A type alias to indicate what is being produced.
runDotCode :: DotCode -> Doc Source #
class PrintDot a where Source #
A class used to correctly print parts of the Graphviz Dot language.
Minimal implementation is unqtDot
.
unqtDot :: a -> DotCode Source #
The unquoted representation, for use when composing values to produce a larger printing value.
toDot :: a -> DotCode Source #
The actual quoted representation; this should be quoted if it
contains characters not permitted a plain ID String, a number
or it is not an HTML string. Defaults to unqtDot
.
unqtListToDot :: [a] -> DotCode Source #
The correct way of representing a list of this value when printed; not all Dot values require this to be implemented. Defaults to Haskell-like list representation.
listToDot :: [a] -> DotCode Source #
The quoted form of unqtListToDot
; defaults to wrapping double
quotes around the result of unqtListToDot
(since the default
implementation has characters that must be quoted).
Instances
unqtText :: Text -> DotCode Source #
For use with OverloadedStrings
to avoid ambiguous type variable errors.
dotText :: Text -> DotCode Source #
For use with OverloadedStrings
to avoid ambiguous type variable errors.
printIt :: PrintDot a => a -> Text Source #
Convert to DotCode; note that this has no indentation, as we can only have one of indentation and (possibly) infinite line lengths.
printEscaped :: [Char] -> Text -> DotCode Source #
Escape the specified chars as well as "
and then wrap the
result in quotes.
printColorScheme :: Bool -> ColorScheme -> DotCode Source #