graphviz-2999.13.0.3: Bindings to Graphviz for graph visualisation.

MaintainerIvan.Miljenovic@gmail.com
Safe HaskellSafe-Infered

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 Text 
ParseDot BrewerName 
ParseDot BrewerScheme 
ParseDot ColorScheme 
ParseDot X11Color 
ParseDot CompassPoint 
ParseDot PortPos 
ParseDot PortName 
ParseDot SVGColor 
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 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 LayerRange 
ParseDot LayerSep 
ParseDot Overlap 
ParseDot Point 
ParseDot LabelScheme 
ParseDot RecordField 
ParseDot Label 
ParseDot Model 
ParseDot ModeType 
ParseDot DPoint 
ParseDot DEConstraints 
ParseDot DirType 
ParseDot ClusterMode 
ParseDot Rect 
ParseDot AspectType 
ParseDot ArrowSide 
ParseDot ArrowFill 
ParseDot ArrowModifier 
ParseDot ArrowShape 
ParseDot ArrowType 
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 String 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 String.

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).

checkValidParse :: Either String a -> aSource

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

Convenience parsing combinators.

bracket :: Parse bra -> Parse ket -> Parse a -> Parse aSource

Parse a bracketed item, discarding the brackets.

The definition of bracket defined in Polyparse uses adjustErrBad and thus doesn't allow backtracking and trying the next possible parser. This is a version of bracket that does.

onlyBool :: Parse BoolSource

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

quotelessString :: Parse TextSource

Parse a String 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 String 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 Strings are allowed or not.

parseStrictFloat :: Parse DoubleSource

Parse a floating point number that actually contains decimals.

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

consumeLine :: Parse TextSource

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

parseField :: ParseDot a => (a -> b) -> String -> [(String, Parse b)]Source

parseFields :: ParseDot a => (a -> b) -> [String] -> [(String, Parse b)]Source

parseFieldsBool :: (Bool -> b) -> [String] -> [(String, Parse b)]Source

parseFieldDef :: ParseDot a => (a -> b) -> a -> String -> [(String, Parse b)]Source

For Bool-like data structures where the presence of the field name without a value implies a default value.

parseFieldsDef :: ParseDot a => (a -> b) -> a -> [String] -> [(String, Parse b)]Source

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