Copyright | (c) Matthew Sackman Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | Safe |
Language | Haskell2010 |
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
- runParserWith :: (GraphvizState -> GraphvizState) -> Parse a -> Text -> (Either String a, Text)
- parseLiberally :: GraphvizState -> GraphvizState
- checkValidParse :: Either String a -> a
- checkValidParseWithRest :: (Either String a, Text) -> a
- ignoreSep :: (a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse c
- onlyBool :: Parse Bool
- quotelessString :: Parse Text
- stringBlock :: Parse Text
- numString :: Bool -> Parse Text
- isNumString :: Bool -> 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 :: Bool -> Parse Double
- parseSignedFloat :: Bool -> 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.
class ParseDot a where Source #
parseUnqtList :: Parse [a] Source #
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 #
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
.
stringBlock :: Parse Text Source #
isNumString :: Bool -> Text -> Bool Source #
Determine if this String represents a number. Boolean parameter determines if exponents are considered part of numbers for this.
isIntString :: Text -> Bool Source #
quotedString :: Parse Text Source #
Used when quotes are explicitly required;
parseAndSpace :: Parse a -> Parse a Source #
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.
optionalQuotedString :: String -> Parse () Source #
optionalQuoted :: Parse a -> Parse a Source #
quotedParse :: Parse a -> Parse a Source #
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 Text Source #
Parses and returns all characters up till the end of the line, but does not touch the newline characters.
stringReps :: a -> [String] -> Parse a Source #
stringValue :: [(String, a)] -> Parse a Source #
parseAngled :: Parse a -> Parse a Source #
parseBraced :: Parse a -> Parse a Source #
parseColorScheme :: Bool -> Parse ColorScheme Source #