Maintainer | Ivan.Miljenovic@gmail.com |
---|---|
Safe Haskell | None |
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
, you should use
DotRepr
rather than its parseDotGraph
ParseDot
instance.
- module Text.ParserCombinators.Poly.StateText
- type Parse a = Parser GraphvizState a
- class ParseDot a where
- parseIt :: ParseDot a => Text -> (a, Text)
- parseIt' :: ParseDot a => Text -> a
- runParser :: Parse a -> Text -> (Either String a, Text)
- runParser' :: Parse a -> Text -> a
- checkValidParse :: Either String a -> a
- bracket :: Parse bra -> Parse ket -> Parse a -> Parse a
- ignoreSep :: (a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse c
- onlyBool :: Parse Bool
- quotelessString :: Parse Text
- stringBlock :: Parse Text
- numString :: Parse Text
- isNumString :: Text -> Bool
- isIntString :: Text -> Bool
- quotedString :: Parse Text
- parseEscaped :: Bool -> [Char] -> [Char] -> Parse Text
- parseAndSpace :: Parse a -> Parse a
- string :: String -> Parse ()
- strings :: [String] -> Parse ()
- character :: Char -> Parse Char
- parseStrictFloat :: Parse Double
- noneOf :: [Char] -> Parse Char
- whitespace1 :: Parse ()
- whitespace :: Parse ()
- wrapWhitespace :: Parse a -> Parse a
- optionalQuotedString :: String -> Parse ()
- optionalQuoted :: Parse a -> Parse a
- quotedParse :: Parse a -> Parse a
- orQuote :: Parse Char -> Parse Char
- quoteChar :: Char
- newline :: Parse ()
- newline' :: Parse ()
- parseComma :: Parse ()
- parseEq :: Parse ()
- tryParseList :: ParseDot a => Parse [a]
- tryParseList' :: Parse [a] -> Parse [a]
- consumeLine :: Parse Text
- commaSep :: (ParseDot a, ParseDot b) => Parse (a, b)
- commaSepUnqt :: (ParseDot a, ParseDot b) => Parse (a, b)
- commaSep' :: Parse a -> Parse b -> Parse (a, b)
- stringRep :: a -> String -> Parse a
- stringReps :: a -> [String] -> Parse a
- stringParse :: [(String, Parse a)] -> Parse a
- stringValue :: [(String, a)] -> Parse a
- parseAngled :: Parse a -> Parse a
- parseBraced :: Parse a -> Parse a
- parseColorScheme :: Bool -> Parse ColorScheme
Re-exporting pertinent parts of Polyparse.
The ParseDot class.
parseUnqtList :: Parse [a]Source
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.
ignoreSep :: (a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse cSource
The opposite of bracket
.
quotelessString :: Parse TextSource
Parse a String
that doesn't need to be quoted.
stringBlock :: Parse TextSource
isNumString :: Text -> BoolSource
Determine if this String represents a number.
isIntString :: Text -> BoolSource
quotedString :: Parse TextSource
Used when quotes are explicitly required;
parseAndSpace :: Parse a -> Parse aSource
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 surrounding whitespace.
optionalQuotedString :: String -> Parse ()Source
optionalQuoted :: Parse a -> Parse aSource
quotedParse :: Parse a -> Parse aSource
Consume all whitespace and newlines until a line with non-whitespace is reached. The whitespace on that line is not consumed.
parseComma :: Parse ()Source
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.
commaSepUnqt :: (ParseDot a, ParseDot b) => Parse (a, b)Source
stringReps :: a -> [String] -> Parse aSource
stringParse :: [(String, Parse a)] -> Parse aSource
stringValue :: [(String, a)] -> Parse aSource
parseAngled :: Parse a -> Parse aSource
parseBraced :: Parse a -> Parse aSource