dotparse-0.1.0.0: dot language parsing and printing.
Safe HaskellSafe-Inferred
LanguageGHC2021

DotParse.FlatParse

Description

Lower-level flatparse parsers

Synopsis

Documentation

data Error Source #

A parsing error.

Constructors

Precise Pos ByteString

A precisely known error, like leaving out "in" from "let".

Imprecise Pos [ByteString]

An imprecise error, when we expect a number of different things, but parse something else.

Instances

Instances details
Show Error Source # 
Instance details

Defined in DotParse.FlatParse.TH

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in DotParse.FlatParse.TH

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

prettyError :: ByteString -> Error -> ByteString Source #

Pretty print an error. The ByteString input is the source file. The offending line from the source is displayed in the output.

keyword :: String -> Q Exp Source #

Parse a keyword string.

keyword' :: String -> Q Exp Source #

Parse a keyword string, throw precise error on failure.

symbol :: String -> Q Exp Source #

Parse a non-keyword string.

symbol' :: String -> Q Exp Source #

Parser a non-keyword string, throw precise error on failure.

ws :: Parser e () Source #

Consume whitespace.

token :: Parser e a -> Parser e a Source #

Consume whitespace after running a parser.

ident :: Parser e ByteString Source #

Parse an identifier.

cut :: Parser Error a -> [ByteString] -> Parser Error a Source #

Imprecise cut: we slap a list of items on inner errors.

cut' :: Parser Error a -> ByteString -> Parser Error a Source #

Precise cut: we propagate at most a single error.

testParser :: Show a => Parser Error a -> ByteString -> IO () Source #

Run parser, print pretty error on failure.

runParser_ :: Parser Error a -> ByteString -> a Source #

run a Parser, erroring on leftovers, Fail or Err

int :: Parser Error Int Source #

(unsigned) Int parser

double :: Parser Error Double Source #

>>> runParser double "1.234x"
OK 1.234 "x"
>>> runParser double "."
Fail
>>> runParser double "123"
OK 123.0 ""
>>> runParser double ".123"
OK 0.123 ""
>>> runParser double "123."
OK 123.0 ""

signed :: Num b => Parser e b -> Parser e b Source #

>>> runParser (signed double) "-1.234x"
OK (-1.234) "x"

quoted :: Parser Error String Source #

Looks ahead for a "/"" that may be in the quoted string. >>> runParser quoted (strToUtf8 ""hello"") OK "hello" ""

>>> runParser quoted (strToUtf8 "\"hello/\"\"")
OK "hello\"" ""

htmlLike :: Parser e String Source #

Parse a HTML-Like string by counting the angle brackets

sepP :: Parser e () Source #

optional separators

wrapSquareP :: Parser Error a -> Parser Error a Source #

parse wrapping square brackets

wrapSquarePrint :: ByteString -> ByteString Source #

print wrapping square brackets

wrapCurlyP :: Parser Error a -> Parser Error a Source #

parse wrapping square brackets

wrapCurlyPrint :: ByteString -> ByteString Source #

print wrapping curly brackets

wrapQuotePrint :: ByteString -> ByteString Source #

print wrapping quotes

pointP :: Parser Error (Point Double) Source #

comma separated Point

data Spline Source #

dot specification of a cubic spline (and an arrow head which is ignored here)

Instances

Instances details
Generic Spline Source # 
Instance details

Defined in DotParse.FlatParse

Associated Types

type Rep Spline :: Type -> Type #

Methods

from :: Spline -> Rep Spline x #

to :: Rep Spline x -> Spline #

Show Spline Source # 
Instance details

Defined in DotParse.FlatParse

Eq Spline Source # 
Instance details

Defined in DotParse.FlatParse

Methods

(==) :: Spline -> Spline -> Bool #

(/=) :: Spline -> Spline -> Bool #

type Rep Spline Source # 
Instance details

Defined in DotParse.FlatParse

type Rep Spline = D1 ('MetaData "Spline" "DotParse.FlatParse" "dotparse-0.1.0.0-Glh386MQdGkE2gsLJXwO3r" 'False) (C1 ('MetaCons "Spline" 'PrefixI 'True) ((S1 ('MetaSel ('Just "splineEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Point Double))) :*: S1 ('MetaSel ('Just "splineStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Point Double)))) :*: (S1 ('MetaSel ('Just "splineP1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point Double)) :*: S1 ('MetaSel ('Just "splineTriples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Point Double, Point Double, Point Double)]))))

rectP :: Parser Error (Rect Double) Source #

comma separated rectangle or bounding box

boolP :: Parser Error Bool Source #

true | false

nonEmptyP :: Parser e a -> Parser e () -> Parser e (NonEmpty a) Source #

NonEmpty version of many