graphviz-2999.17.0.0: Bindings to Graphviz for graph visualisation.

MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone

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 aSource

A ReadS-like type alias.

class ParseDot a whereSource

Instances

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

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

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

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

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

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 -> aSource

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

runParser' :: Parse a -> Text -> aSource

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 -> GraphvizStateSource

checkValidParse :: Either String a -> aSource

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

Convenience parsing combinators.

ignoreSep :: (a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse cSource

The opposite of bracket.

onlyBool :: Parse BoolSource

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

quotelessString :: Parse TextSource

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

isNumString :: Text -> BoolSource

Determine if this String represents a number.

quotedString :: Parse TextSource

Used when quotes are explicitly required;

parseEscaped :: Bool -> [Char] -> [Char] -> Parse TextSource

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 CharSource

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

parseStrictFloat :: Bool -> Parse DoubleSource

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 aSource

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 TextSource

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

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