graphviz-2999.20.0.2: Bindings to Graphviz for graph visualisation.

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

Data.GraphViz.Parsing

Contents

Description

This module defines simple helper functions for use with Text.ParserCombinators.Poly.Lazy.

Note that the ParseDot instances for Bool, etc. match those specified for use with Graphviz (e.g. non-zero integers are equivalent to True).

You should not be using this module; rather, it is here for informative/documentative reasons. If you want to parse a DotRepr, you should use parseDotGraph rather than its ParseDot instance.

Synopsis

Re-exporting pertinent parts of Polyparse.

The ParseDot class.

type Parse a = Parser GraphvizState a Source #

A ReadS-like type alias.

class ParseDot a where Source #

Minimal complete definition

parseUnqt

Instances

ParseDot Bool Source # 
ParseDot Char Source # 
ParseDot Double Source # 
ParseDot Int Source # 
ParseDot Integer Source # 
ParseDot Word8 Source # 
ParseDot Word16 Source # 
ParseDot Version Source #

Ignores versionTags and assumes 'not . null . versionBranch' (usually you want 'length . versionBranch == 2') and that all such values are non-negative.

ParseDot Text Source # 
ParseDot Text Source # 
ParseDot BrewerName Source # 
ParseDot BrewerScheme Source # 
ParseDot ColorScheme Source # 
ParseDot GraphvizCommand Source # 
ParseDot CompassPoint Source # 
ParseDot PortPos Source # 
ParseDot PortName Source # 
ParseDot X11Color Source # 
ParseDot SVGColor Source # 
ParseDot WeightedColor Source # 
ParseDot Color Source # 
ParseDot Style Source # 
ParseDot Side Source # 
ParseDot Scale Source # 
ParseDot CellFormat Source # 
ParseDot VAlign Source # 
ParseDot Align Source # 
ParseDot Attribute Source # 
ParseDot Img Source # 
ParseDot Cell Source # 
ParseDot Row Source # 
ParseDot Table Source # 
ParseDot Format Source # 
ParseDot TextItem Source # 
ParseDot Label Source # 
ParseDot NodeSize Source # 
ParseDot Normalized Source # 
ParseDot Number Source # 
ParseDot Ratios Source # 
ParseDot Justification Source # 
ParseDot ScaleType Source # 
ParseDot Paths Source # 
ParseDot VerticalPlacement Source # 
ParseDot FocusType Source # 
ParseDot ViewPort Source # 
ParseDot StyleName Source # 
ParseDot StyleItem Source # 
ParseDot STStyle Source # 
ParseDot StartType Source # 
ParseDot SmoothType Source # 
ParseDot Shape Source # 
ParseDot RankDir Source # 
ParseDot RankType Source # 
ParseDot Root Source # 
ParseDot QuadType Source # 
ParseDot Spline Source # 
ParseDot PageDir Source # 
ParseDot EdgeType Source # 
ParseDot Pos Source # 
ParseDot PackMode Source # 
ParseDot Pack Source # 
ParseDot OutputMode Source # 
ParseDot Order Source # 
ParseDot LayerList Source # 
ParseDot LayerID Source # 
ParseDot LayerRangeElem Source # 
ParseDot LayerListSep Source # 
ParseDot LayerSep Source # 
ParseDot Overlap Source #

Note that overlap=false defaults to PrismOverlap Nothing, but if the Prism library isn't available then it is equivalent to VoronoiOverlap.

ParseDot Point Source # 
ParseDot LabelScheme Source # 
ParseDot RecordField Source # 
ParseDot Label Source # 
ParseDot Model Source # 
ParseDot ModeType Source # 
ParseDot GraphSize Source # 
ParseDot SVGFontNames Source # 
ParseDot DPoint Source # 
ParseDot DEConstraints Source # 
ParseDot DirType Source # 
ParseDot ClusterMode Source # 
ParseDot Rect Source # 
ParseDot ArrowSide Source # 
ParseDot ArrowFill Source # 
ParseDot ArrowModifier Source # 
ParseDot ArrowShape Source # 
ParseDot ArrowType Source # 
ParseDot Attribute Source # 
ParseDot GlobalAttributes Source # 
ParseDot GraphID Source # 
ParseDot a => ParseDot [a] Source # 
ParseDot n => ParseDot (DotEdge n) Source # 
ParseDot n => ParseDot (DotNode n) Source # 
ParseDot n => ParseDot (DotSubGraph n) Source # 
ParseDot n => ParseDot (DotStatements n) Source # 
ParseDot n => ParseDot (DotGraph n) Source # 
ParseDot n => ParseDot (DotSubGraph n) Source # 
ParseDot n => ParseDot (DotStatement n) Source # 
ParseDot n => ParseDot (DotGraph n) Source # 
(Ord n, ParseDot n) => ParseDot (DotGraph n) Source #

Uses the ParseDot instance for generalised DotGraphs.

parseIt :: ParseDot a => Text -> (a, Text) Source #

Parse the required value, returning also the rest of the input Text that hasn't been parsed (for debugging purposes).

parseIt' :: ParseDot a => Text -> a Source #

Parse the required value with the assumption that it will parse all of the input Text.

runParser' :: Parse a -> Text -> a Source #

A variant of runParser where it is assumed that the provided parsing function consumes all of the Text input (with the exception of whitespace at the end).

runParserWith :: (GraphvizState -> GraphvizState) -> Parse a -> Text -> (Either String a, Text) Source #

parseLiberally :: GraphvizState -> GraphvizState Source #

checkValidParse :: Either String a -> a Source #

If unable to parse Dot code properly, throw a GraphvizException.

checkValidParseWithRest :: (Either String a, Text) -> a Source #

If unable to parse Dot code properly, throw a GraphvizException, with the error containing the remaining unparsed code..

Convenience parsing combinators.

ignoreSep :: (a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse c Source #

The opposite of bracket.

onlyBool :: Parse Bool Source #

Use this when you do not want numbers to be treated as Bool values.

quotelessString :: Parse Text Source #

Parse a Text that doesn't need to be quoted.

isNumString :: Bool -> Text -> Bool Source #

Determine if this String represents a number. Boolean parameter determines if exponents are considered part of numbers for this.

quotedString :: Parse Text Source #

Used when quotes are explicitly required;

parseEscaped :: Bool -> [Char] -> [Char] -> Parse Text Source #

Parse a Text where the provided Chars (as well as " and \) are escaped and the second list of Chars are those that are not permitted. Note: does not parse surrounding quotes. The Bool value indicates whether empty Texts are allowed or not.

character :: Char -> Parse Char Source #

Assumes that any letter is ASCII for case-insensitive comparisons.

parseStrictFloat :: Bool -> Parse Double Source #

Parse a floating point number that actually contains decimals. Bool flag indicates whether values that need to be quoted are parsed.

whitespace1 :: Parse () Source #

Parses at least one whitespace character.

whitespace :: Parse () Source #

Parses zero or more whitespace characters.

wrapWhitespace :: Parse a -> Parse a Source #

Parse and discard optional surrounding whitespace.

newline :: Parse () Source #

Parses a newline.

newline' :: Parse () Source #

Consume all whitespace and newlines until a line with non-whitespace is reached. The whitespace on that line is not consumed.

tryParseList :: ParseDot a => Parse [a] Source #

Try to parse a list of the specified type; returns an empty list if parsing fails.

tryParseList' :: Parse [a] -> Parse [a] Source #

Return an empty list if parsing a list fails.

consumeLine :: Parse Text Source #

Parses and returns all characters up till the end of the line, but does not touch the newline characters.

commaSep :: (ParseDot a, ParseDot b) => Parse (a, b) Source #

commaSep' :: Parse a -> Parse b -> Parse (a, b) Source #

stringReps :: a -> [String] -> Parse a Source #