Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Lower-level flatparse parsers
Synopsis
- data Error
- prettyError :: ByteString -> Error -> ByteString
- keyword :: String -> Q Exp
- keyword' :: String -> Q Exp
- symbol :: String -> Q Exp
- symbol' :: String -> Q Exp
- ws :: Parser e ()
- token :: Parser e a -> Parser e a
- ident :: Parser e ByteString
- cut :: Parser Error a -> [ByteString] -> Parser Error a
- cut' :: Parser Error a -> ByteString -> Parser Error a
- testParser :: Show a => Parser Error a -> ByteString -> IO ()
- runParser_ :: Parser Error a -> ByteString -> a
- int :: Parser Error Int
- double :: Parser Error Double
- signed :: Num b => Parser e b -> Parser e b
- quoted :: Parser Error String
- htmlLike :: Parser e String
- sepP :: Parser e ()
- wrapSquareP :: Parser Error a -> Parser Error a
- wrapSquarePrint :: ByteString -> ByteString
- wrapCurlyP :: Parser Error a -> Parser Error a
- wrapCurlyPrint :: ByteString -> ByteString
- wrapQuotePrint :: ByteString -> ByteString
- pointP :: Parser Error (Point Double)
- data Spline = Spline {}
- splineP :: Parser Error Spline
- rectP :: Parser Error (Rect Double)
- boolP :: Parser Error Bool
- nonEmptyP :: Parser e a -> Parser e () -> Parser e (NonEmpty a)
Documentation
A parsing error.
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. |
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.
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
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\"" ""
wrapSquarePrint :: ByteString -> ByteString Source #
print wrapping square brackets
wrapCurlyPrint :: ByteString -> ByteString Source #
print wrapping curly brackets
wrapQuotePrint :: ByteString -> ByteString Source #
print wrapping quotes
dot specification of a cubic spline (and an arrow head which is ignored here)
Instances
Generic Spline Source # | |
Show Spline Source # | |
Eq Spline Source # | |
type Rep Spline Source # | |
Defined in DotParse.FlatParse type Rep Spline = D1 ('MetaData "Spline" "DotParse.FlatParse" "dotparse-0.1.1.0-7ksB5EWrjOr2Em2eE9iYUk" '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)])))) |