graphviz-2999.20.0.2: Bindings to Graphviz for graph visualisation.

Copyright(c) Ivan Lazar Miljenovic
License3-Clause BSD-style
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.GraphViz.Printing

Description

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 printDotGraph (which produces a 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

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.

nest :: Functor m => Int -> m Doc -> m Doc #

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
  !
  

linebreak :: Applicative m => m Doc #

The linebreak document advances to the next line and indents to the current nesting level. Document linebreak behaves like empty if the line break is undone by group.

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 spaces 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 spaces 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 #

A monadic version of pretty; this is to allow you to use the Pretty class without having to create extra instances. Alternatively, you may wish to make a variant of Pretty using the actual Monad to be used.

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.

int :: Applicative m => Int -> m Doc #

The document (int 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 #

The document softbreak behaves like empty if the resulting output fits the page, otherwise it behaves like line.

softline :: Applicative m => m Doc #

The document softline behaves like space if the resulting output fits the page, otherwise it behaves like line.

(<$$>) :: 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)

beside :: Applicative m => m Doc -> m Doc -> m Doc infixr 6 #

The document (x beside y) concatenates document x and document y. It is an associative operation having empty as a left and right unit. (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.

displayB :: SimpleDoc -> Builder #

(displayB simpleDoc) takes the output simpleDoc from a rendering function and transforms it to a Builder type (for further manipulation before converting to a lazy Text).

renderOneLine :: Doc -> SimpleDoc #

(renderOneLine x) renders document x without adding any indentation or newlines.

data Doc #

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 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show DotCode # 
Instance details

Defined in Data.GraphViz.Printing

IsString Doc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

fromString :: String -> Doc #

IsString DotCode # 
Instance details

Defined in Data.GraphViz.Printing

Methods

fromString :: String -> DotCode #

Semigroup Doc

In particular, note that the document (x <> y) concatenates document x and document y. It is an associative operation having empty as a left and right unit. (infixr 6)

Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Semigroup DotCode # 
Instance details

Defined in Data.GraphViz.Printing

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid DotCode # 
Instance details

Defined in Data.GraphViz.Printing

Pretty Doc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Doc -> Doc #

prettyList :: [Doc] -> Doc #

data DotCodeM a #

A type alias to indicate what is being produced.

Instances
Monad DotCodeM # 
Instance details

Defined in Data.GraphViz.Printing

Methods

(>>=) :: DotCodeM a -> (a -> DotCodeM b) -> DotCodeM b #

(>>) :: DotCodeM a -> DotCodeM b -> DotCodeM b #

return :: a -> DotCodeM a #

fail :: String -> DotCodeM a #

Functor DotCodeM # 
Instance details

Defined in Data.GraphViz.Printing

Methods

fmap :: (a -> b) -> DotCodeM a -> DotCodeM b #

(<$) :: a -> DotCodeM b -> DotCodeM a #

Show DotCode # 
Instance details

Defined in Data.GraphViz.Printing

IsString DotCode # 
Instance details

Defined in Data.GraphViz.Printing

Methods

fromString :: String -> DotCode #

Applicative DotCodeM # 
Instance details

Defined in Data.GraphViz.Printing

Methods

pure :: a -> DotCodeM a #

(<*>) :: DotCodeM (a -> b) -> DotCodeM a -> DotCodeM b #

liftA2 :: (a -> b -> c) -> DotCodeM a -> DotCodeM b -> DotCodeM c #

(*>) :: DotCodeM a -> DotCodeM b -> DotCodeM b #

(<*) :: DotCodeM a -> DotCodeM b -> DotCodeM a #

Semigroup DotCode # 
Instance details

Defined in Data.GraphViz.Printing

Monoid DotCode # 
Instance details

Defined in Data.GraphViz.Printing

renderDot :: DotCode -> Text #

Correctly render Graphviz output.

class PrintDot a where #

A class used to correctly print parts of the Graphviz Dot language. Minimal implementation is unqtDot.

Minimal complete definition

unqtDot

Methods

unqtDot :: a -> DotCode #

The unquoted representation, for use when composing values to produce a larger printing value.

toDot :: a -> DotCode #

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 #

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 #

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
PrintDot Bool # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Char # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Double # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Int # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Integer # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Word8 # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Word16 # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Version #

Ignores versionTags and assumes 'not . null . versionBranch' (usually you want 'length . versionBranch == 2').

Instance details

Defined in Data.GraphViz.Printing

PrintDot Text # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Text # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot BrewerName # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot BrewerScheme # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot ColorScheme # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot GraphvizCommand # 
Instance details

Defined in Data.GraphViz.Commands.Available

PrintDot CompassPoint # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

PrintDot PortPos # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

PrintDot PortName # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

PrintDot X11Color # 
Instance details

Defined in Data.GraphViz.Attributes.Colors.X11

PrintDot SVGColor # 
Instance details

Defined in Data.GraphViz.Attributes.Colors.SVG

PrintDot WeightedColor # 
Instance details

Defined in Data.GraphViz.Attributes.Colors

PrintDot Color # 
Instance details

Defined in Data.GraphViz.Attributes.Colors

PrintDot Style # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Side # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Scale # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot CellFormat # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot VAlign # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Align # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Attribute # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Img # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Cell # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Row # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Table # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Format # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot TextItem # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Label # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot NodeSize # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Normalized # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Number # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Ratios # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Justification # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ScaleType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Paths # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot VerticalPlacement # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot FocusType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ViewPort # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot StyleName # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot StyleItem # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot STStyle # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot StartType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot SmoothType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Shape # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot RankDir # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot RankType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Root # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot QuadType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Spline # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot PageDir # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot EdgeType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Pos # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot PackMode # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Pack # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot OutputMode # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Order # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerList # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerID # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerRangeElem # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerListSep # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerSep # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Overlap # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Point # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LabelScheme # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot RecordField # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Label # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Model # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ModeType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot GraphSize # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot SVGFontNames # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot DPoint # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot DEConstraints # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot DirType # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ClusterMode # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Rect # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ArrowSide # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowFill # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowModifier # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowShape # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowType # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot Attribute # 
Instance details

Defined in Data.GraphViz.Attributes.Complete

PrintDot GlobalAttributes # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot GraphID # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot a => PrintDot [a] # 
Instance details

Defined in Data.GraphViz.Printing

Methods

unqtDot :: [a] -> DotCode #

toDot :: [a] -> DotCode #

unqtListToDot :: [[a]] -> DotCode #

listToDot :: [[a]] -> DotCode #

PrintDot n => PrintDot (DotEdge n) # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot n => PrintDot (DotNode n) # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot n => PrintDot (DotSubGraph n) # 
Instance details

Defined in Data.GraphViz.Types.Canonical

PrintDot n => PrintDot (DotStatements n) # 
Instance details

Defined in Data.GraphViz.Types.Canonical

PrintDot n => PrintDot (DotGraph n) # 
Instance details

Defined in Data.GraphViz.Types.Canonical

PrintDot n => PrintDot (DotSubGraph n) # 
Instance details

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotStatement n) # 
Instance details

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotGraph n) # 
Instance details

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotGraph n) #

Uses the PrintDot instance for canonical DotGraphs.

Instance details

Defined in Data.GraphViz.Types.Graph

unqtText :: Text -> DotCode #

For use with OverloadedStrings to avoid ambiguous type variable errors.

dotText :: Text -> DotCode #

For use with OverloadedStrings to avoid ambiguous type variable errors.

printIt :: PrintDot a => a -> Text #

Convert to DotCode; note that this has no indentation, as we can only have one of indentation and (possibly) infinite line lengths.

unqtEscaped :: [Char] -> Text -> DotCode #

Escape the specified chars as well as ".

printEscaped :: [Char] -> Text -> DotCode #

Escape the specified chars as well as " and then wrap the result in quotes.

commaDel :: (PrintDot a, PrintDot b) => a -> b -> DotCode #

printField :: PrintDot a => Text -> a -> DotCode #