markup-parse-0.1.1: A markup parser.
Safe HaskellSafe-Inferred
LanguageGHC2021

MarkupParse.FlatParse

Description

Various flatparse helpers and combinators.

Synopsis

Parsing

data ParserWarning Source #

Warnings covering leftovers, Errs and Fail

>>> runParserWarn ws " x"
These (ParserLeftover "x") ' '
>>> runParserWarn ws "x"
This ParserUncaught
>>> runParserWarn (ws `cut` "no whitespace") "x"
This (ParserError "no whitespace")

Instances

Instances details
Generic ParserWarning Source # 
Instance details

Defined in MarkupParse.FlatParse

Associated Types

type Rep ParserWarning :: Type -> Type #

Show ParserWarning Source # 
Instance details

Defined in MarkupParse.FlatParse

NFData ParserWarning Source # 
Instance details

Defined in MarkupParse.FlatParse

Methods

rnf :: ParserWarning -> () #

Eq ParserWarning Source # 
Instance details

Defined in MarkupParse.FlatParse

Ord ParserWarning Source # 
Instance details

Defined in MarkupParse.FlatParse

type Rep ParserWarning Source # 
Instance details

Defined in MarkupParse.FlatParse

type Rep ParserWarning = D1 ('MetaData "ParserWarning" "MarkupParse.FlatParse" "markup-parse-0.1.1-BdYhv7KNpuBDovL7j9hJZ4" 'False) (C1 ('MetaCons "ParserLeftover" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: (C1 ('MetaCons "ParserError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "ParserUncaught" 'PrefixI 'False) (U1 :: Type -> Type)))

runParserMaybe :: Parser e a -> ByteString -> Maybe a Source #

Run a Parser, throwing away leftovers. Nothing on Fail or Err.

>>> runParserMaybe ws "x"
Nothing
>>> runParserMaybe ws " x"
Just ' '

runParserEither :: IsString e => Parser e a -> ByteString -> Either e a Source #

Run a Parser, throwing away leftovers. Returns Left on Fail or Err.

>>> runParserEither ws " x"
Right ' '

runParserWarn :: Parser ByteString a -> ByteString -> These ParserWarning a Source #

Run parser, returning leftovers and errors as ParserWarnings.

>>> runParserWarn ws " "
That ' '
>>> runParserWarn ws "x"
This ParserUncaught
>>> runParserWarn ws " x"
These (ParserLeftover "x") ' '

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

Run parser, discards leftovers & throws an error on failure.

>>> runParser_ ws " "
' '
>>> runParser_ ws "x"
*** Exception: uncaught parse error
...

Flatparse re-exports

runParser :: Parser e a -> ByteString -> Result e a #

Run a parser.

type Parser = ParserT PureMode #

The type of pure parsers.

data Result e a #

Higher-level boxed data type for parsing results.

Constructors

OK a !ByteString

Contains return value and unconsumed input.

Fail

Recoverable-by-default failure.

Err !e

Unrecoverble-by-default error.

Instances

Instances details
Functor (Result e) 
Instance details

Defined in FlatParse.Basic

Methods

fmap :: (a -> b) -> Result e a -> Result e b #

(<$) :: a -> Result e b -> Result e a #

(Show a, Show e) => Show (Result e a) 
Instance details

Defined in FlatParse.Basic

Methods

showsPrec :: Int -> Result e a -> ShowS #

show :: Result e a -> String #

showList :: [Result e a] -> ShowS #

Parsers

isWhitespace :: Char -> Bool Source #

\n \t \f \r and space

ws_ :: Parser e () Source #

Consume whitespace.

>>> runParser ws_ " \nx"
OK () "x"
>>> runParser ws_ "x"
OK () "x"

ws :: Parser e Char Source #

single whitespace

>>> runParser ws " \nx"
OK ' ' "\nx"

wss :: Parser e ByteString Source #

multiple whitespace

>>> runParser wss " \nx"
OK " \n" "x"
>>> runParser wss "x"
Fail

nota :: Char -> Parser e ByteString Source #

Parse whilst not a specific character

>>> runParser (nota 'x') "abcxyz"
OK "abc" "xyz"

isa :: (Char -> Bool) -> Parser e ByteString Source #

Parse whilst satisfying a predicate.

>>> runParser (isa (=='x')) "xxxabc"
OK "xxx" "abc"

sq :: ParserT st e () Source #

Single quote

>>> runParserMaybe sq "'"
Just ()

dq :: ParserT st e () Source #

Double quote

>>> runParserMaybe dq "\""
Just ()

wrappedDq :: Parser b ByteString Source #

A double-quoted string.

wrappedSq :: Parser b ByteString Source #

A single-quoted string.

wrappedQ :: Parser e ByteString Source #

A single-quoted or double-quoted string.

>>> runParserMaybe wrappedQ "\"quoted\""
Just "quoted"
>>> runParserMaybe wrappedQ "'quoted'"
Just "quoted"

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

A single-quoted or double-quoted wrapped parser.

>>> runParser (wrappedQNoGuard (many $ satisfy (/= '"'))) "\"name\""
OK "name" ""

Will consume quotes if the underlying parser does.

>>> runParser (wrappedQNoGuard (many anyChar)) "\"name\""
Fail

eq :: Parser e () Source #

xml production [25]

>>> runParserMaybe eq " = "
Just ()
>>> runParserMaybe eq "="
Just ()

sep :: Parser e s -> Parser e a -> Parser e [a] Source #

Some with a separator.

>>> runParser (sep ws (many (satisfy (/= ' ')))) "a b c"
OK ["a","b","c"] ""

bracketed :: Parser e b -> Parser e b -> Parser e a -> Parser e a Source #

Parser bracketed by two other parsers.

>>> runParser (bracketed ($(char '[')) ($(char ']')) (many (satisfy (/= ']')))) "[bracketed]"
OK "bracketed" ""

bracketedSB :: Parser e [Char] Source #

Parser bracketed by square brackets.

>>> runParser bracketedSB "[bracketed]"
OK "bracketed" ""

wrapped :: Parser e () -> Parser e a -> Parser e a Source #

Parser wrapped by another parser.

>>> runParser (wrapped ($(char '"')) (many (satisfy (/= '"')))) "\"wrapped\""
OK "wrapped" ""

digit :: Parser e Int Source #

A single digit

>>> runParserMaybe digit "5"
Just 5

int :: Parser e Int Source #

An (unsigned) Int parser

>>> runParserMaybe int "567"
Just 567

double :: Parser e Double Source #

A Double parser.

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

Parser for a signed prefix to a number.

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

byteStringOf' :: Parser e a -> Parser e ByteString Source #

byteStringOf but using withSpan internally. Doesn't seems faster...

comma :: Parser e () Source #

Comma parser

>>> runParserMaybe comma ","
Just ()