Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype ParserT (st :: ZeroBitType) r e a = ParserT {
- runParserT# :: ForeignPtrContents -> r -> Addr# -> Addr# -> Int# -> st -> Res# st e a
- type Parser = ParserT PureMode
- type ParserIO = ParserT IOMode
- type ParserST s = ParserT (STMode s)
- data Result e a
- = OK a Int !ByteString
- | Fail
- | Err !e
- runParser :: Parser r e a -> r -> Int -> ByteString -> Result e a
- runParserUtf8 :: Parser r e a -> r -> Int -> String -> Result e a
- runParserIO :: ParserIO r e a -> r -> Int -> ByteString -> IO (Result e a)
- runParserST :: ParserST s r e a -> r -> Int -> ByteString -> ST s (Result e a)
- embedParserST :: forall r e a. (forall s. ParserST s r e a) -> Parser r e a
- type Res# (st :: ZeroBitType) e a = (# st, ResI# e a #)
- pattern OK# :: (st :: ZeroBitType) -> a -> Addr# -> Int# -> Res# st e a
- pattern Err# :: (st :: ZeroBitType) -> e -> Res# st e a
- pattern Fail# :: (st :: ZeroBitType) -> Res# st e a
- type ResI# e a = (# (# a, Addr#, Int# #) | (# #) | (# e #) #)
- liftST :: ST s a -> ParserST s r e a
- ask :: ParserT st r e r
- local :: (r -> r) -> ParserT st r e a -> ParserT st r e a
- get :: ParserT st r e Int
- put :: Int -> ParserT st r e ()
- modify :: (Int -> Int) -> ParserT st r e ()
- strToUtf8 :: String -> ByteString
- utf8ToStr :: ByteString -> String
- isDigit :: Char -> Bool
- isLatinLetter :: Char -> Bool
- isGreekLetter :: Char -> Bool
- eof :: ParserT st r e ()
- take :: Int -> ParserT st r e ByteString
- take# :: Int# -> ParserT st r e ByteString
- takeUnsafe# :: Int# -> ParserT st r e ByteString
- takeRest :: ParserT st r e ByteString
- skip :: Int -> ParserT st r e ()
- skip# :: Int# -> ParserT st r e ()
- skipBack :: Int -> ParserT st r e ()
- skipBack# :: Int# -> ParserT st r e ()
- atSkip# :: Int# -> ParserT st r e ret -> ParserT st r e ret
- atSkipUnsafe# :: Int# -> ParserT st r e ret -> ParserT st r e ret
- bytes :: [Word] -> Q Exp
- bytesUnsafe :: [Word] -> Q Exp
- byteString :: ByteString -> ParserT st r e ()
- anyCString :: ParserT st r e ByteString
- anyVarintProtobuf :: ParserT st r e Int
- (<|>) :: ParserT st r e a -> ParserT st r e a -> ParserT st r e a
- branch :: ParserT st r e a -> ParserT st r e b -> ParserT st r e b -> ParserT st r e b
- notFollowedBy :: ParserT st r e a -> ParserT st r e b -> ParserT st r e a
- chainl :: (b -> a -> b) -> ParserT st r e b -> ParserT st r e a -> ParserT st r e b
- chainr :: (a -> b -> b) -> ParserT st r e a -> ParserT st r e b -> ParserT st r e b
- lookahead :: ParserT st r e a -> ParserT st r e a
- ensure :: Int -> ParserT st r e ()
- ensure# :: Int# -> ParserT st r e ()
- withEnsure :: Int -> ParserT st r e ret -> ParserT st r e ret
- withEnsure1 :: ParserT st r e ret -> ParserT st r e ret
- withEnsure# :: Int# -> ParserT st r e ret -> ParserT st r e ret
- isolate :: Int -> ParserT st r e a -> ParserT st r e a
- isolateToNextNull :: ParserT st r e a -> ParserT st r e a
- isolate# :: Int# -> ParserT st r e a -> ParserT st r e a
- isolateUnsafe# :: Int# -> ParserT st r e ret -> ParserT st r e ret
- switch :: Q Exp -> Q Exp
- switchWithPost :: Maybe (Q Exp) -> Q Exp -> Q Exp
- rawSwitchWithPost :: Maybe (Q Exp) -> [(String, Q Exp)] -> Maybe (Q Exp) -> Q Exp
- many :: Alternative f => f a -> f [a]
- skipMany :: ParserT st r e a -> ParserT st r e ()
- some :: Alternative f => f a -> f [a]
- skipSome :: ParserT st r e a -> ParserT st r e ()
- empty :: Alternative f => f a
- failed :: ParserT st r e a
- try :: ParserT st r e a -> ParserT st r e a
- err :: e -> ParserT st r e a
- withError :: ParserT st r e b -> (e -> ParserT st r e b) -> ParserT st r e b
- withAnyResult :: ParserT st r t a -> (a -> ParserT st r e b) -> ParserT st r e b -> (t -> ParserT st r e b) -> ParserT st r e b
- fails :: ParserT st r e a -> ParserT st r e ()
- cut :: ParserT st r e a -> e -> ParserT st r e a
- cutting :: ParserT st r e a -> e -> (e -> e -> e) -> ParserT st r e a
- optional :: ParserT st r e a -> ParserT st r e (Maybe a)
- optional_ :: ParserT st r e a -> ParserT st r e ()
- withOption :: ParserT st r e a -> (a -> ParserT st r e ret) -> ParserT st r e ret -> ParserT st r e ret
- newtype Pos = Pos {}
- endPos :: Pos
- addrToPos# :: Addr# -> Addr# -> Pos
- posToAddr# :: Addr# -> Pos -> Addr#
- data Span = Span !Pos !Pos
- unsafeSlice :: ByteString -> Span -> ByteString
- getPos :: ParserT st r e Pos
- setPos :: Pos -> ParserT st r e ()
- spanOf :: ParserT st r e a -> ParserT st r e Span
- withSpan :: ParserT st r e a -> (a -> Span -> ParserT st r e b) -> ParserT st r e b
- byteStringOf :: ParserT st r e a -> ParserT st r e ByteString
- withByteString :: ParserT st r e a -> (a -> ByteString -> ParserT st r e b) -> ParserT st r e b
- inSpan :: Span -> ParserT st r e a -> ParserT st r e a
- validPos :: ByteString -> Pos -> Bool
- posLineCols :: ByteString -> [Pos] -> [(Int, Int)]
- mkPos :: ByteString -> (Int, Int) -> Pos
- char :: Char -> Q Exp
- string :: String -> Q Exp
- anyChar :: ParserT st r e Char
- skipAnyChar :: ParserT st r e ()
- satisfy :: (Char -> Bool) -> ParserT st r e Char
- skipSatisfy :: (Char -> Bool) -> ParserT st r e ()
- fusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> ParserT st r e Char
- skipFusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> ParserT st r e ()
- takeLine :: ParserT st r e String
- takeRestString :: ParserT st r e String
- linesUtf8 :: ByteString -> [String]
- anyAsciiChar :: ParserT st r e Char
- skipAnyAsciiChar :: ParserT st r e ()
- satisfyAscii :: (Char -> Bool) -> ParserT st r e Char
- skipSatisfyAscii :: (Char -> Bool) -> ParserT st r e ()
- anyAsciiDecimalWord :: ParserT st r e Word
- anyAsciiDecimalInt :: ParserT st r e Int
- anyAsciiDecimalInteger :: ParserT st r e Integer
- anyAsciiHexWord :: ParserT st r e Word
- anyAsciiHexInt :: ParserT st r e Int
- module FlatParse.Stateful.Integers
- traceLine :: ParserT st r e String
- traceRest :: ParserT st r e String
- unsafeSpanToByteString :: Span -> ParserT st r e ByteString
- unsafeLiftIO :: IO a -> ParserT st r e a
- module FlatParse.Stateful.Addr
- anyCStringUnsafe :: ParserT st r e ByteString
Parser types
newtype ParserT (st :: ZeroBitType) r e a Source #
ParserT st r e a
is a parser with a state token type st
, a reader
environment r
, an error type e
and a return type a
. The different
state token types support different embedded effects; see Parser
,
ParserIO
and ParserST
below.
ParserT | |
|
Instances
MonadIO (ParserT IOMode r e) Source # | |
Alternative (ParserT st r e) Source # | |
Applicative (ParserT st r e) Source # | |
Defined in FlatParse.Stateful.Parser pure :: a -> ParserT st r e a # (<*>) :: ParserT st r e (a -> b) -> ParserT st r e a -> ParserT st r e b # liftA2 :: (a -> b -> c) -> ParserT st r e a -> ParserT st r e b -> ParserT st r e c # (*>) :: ParserT st r e a -> ParserT st r e b -> ParserT st r e b # (<*) :: ParserT st r e a -> ParserT st r e b -> ParserT st r e a # | |
Functor (ParserT st r e) Source # | |
Monad (ParserT st r e) Source # | |
MonadPlus (ParserT st r e) Source # | |
Running parsers
Higher-level boxed data type for parsing results.
OK a Int !ByteString | Contains return value, last |
Fail | Recoverable-by-default failure. |
Err !e | Unrecoverble-by-default error. |
runParser :: Parser r e a -> r -> Int -> ByteString -> Result e a Source #
Run a pure parser. The Int
argument is the initial state.
runParserUtf8 :: Parser r e a -> r -> Int -> String -> Result e a Source #
Run a parser on a String
, converting it to the corresponding UTF-8 bytes.
The Int
argument is the initial state.
Reminder: OverloadedStrings
for ByteString
does not yield a valid UTF-8
encoding! For non-ASCII ByteString
literal input, use this wrapper or
convert your input using strToUtf8
.
runParserIO :: ParserIO r e a -> r -> Int -> ByteString -> IO (Result e a) Source #
runParserST :: ParserST s r e a -> r -> Int -> ByteString -> ST s (Result e a) Source #
embedParserST :: forall r e a. (forall s. ParserST s r e a) -> Parser r e a Source #
Run a ParserST
inside a pure parser.
Primitive result types
type Res# (st :: ZeroBitType) e a = (# st, ResI# e a #) Source #
pattern Err# :: (st :: ZeroBitType) -> e -> Res# st e a Source #
Res#
constructor for errors which are by default non-recoverable.
Contains the error, plus a state token.
pattern Fail# :: (st :: ZeroBitType) -> Res# st e a Source #
Res#
constructor for recoverable failure.
Contains only a state token.
Embedding ST
operations
Environment operations
local :: (r -> r) -> ParserT st r e a -> ParserT st r e a Source #
Run a parser in a modified environment.
State operations
UTF conversion
strToUtf8 :: String -> ByteString Source #
Convert an UTF8-encoded String
to a ByteString
.
utf8ToStr :: ByteString -> String Source #
Convert a ByteString
to an UTF8-encoded String
.
Character predicates
isLatinLetter :: Char -> Bool Source #
isLatinLetter c = ('A' <= c && c <= 'Z') || ('a' <= c && c <= 'z')
isGreekLetter :: Char -> Bool Source #
isGreekLetter c = ('Α' <= c && c <= 'Ω') || ('α' <= c && c <= 'ω')
Parsers
Bytewise
take :: Int -> ParserT st r e ByteString Source #
Read n
bytes as a ByteString
. Fails if fewer than n
bytes are
available.
Throws a runtime error if given a negative integer.
This does no copying. The ByteString
returned is a "slice" of the input,
and will keep it alive. To avoid this, use copy
on the output.
take# :: Int# -> ParserT st r e ByteString Source #
Read n#
bytes as a ByteString
. Fails if fewer than n#
bytes are
available.
Throws a runtime error if given a negative integer.
This does no copying. The ByteString
returned is a "slice" of the input,
and will keep it alive. To avoid this, use copy
on the output.
takeUnsafe# :: Int# -> ParserT st r e ByteString Source #
Read i#
bytes as a ByteString
. Fails if newer than i#
bytes are
available.
Undefined behaviour if given a negative integer.
This does no copying. The ByteString
returned is a "slice" of the input,
and will keep it alive. To avoid this, use copy
on the output.
takeRest :: ParserT st r e ByteString Source #
Consume the rest of the input. May return the empty bytestring.
This does no copying. The ByteString
returned is a "slice" of the input,
and will keep it alive. To avoid this, use copy
on the output.
skip :: Int -> ParserT st r e () Source #
Skip forward n
bytes. Fails if fewer than n
bytes are available.
Throws a runtime error if given a negative integer.
skip# :: Int# -> ParserT st r e () Source #
Skip forward n
bytes. Fails if fewer than n
bytes are available.
Throws a runtime error if given a negative integer.
skipBack :: Int -> ParserT st r e () Source #
Go back i
bytes in the input. Takes a positive integer.
Extremely unsafe. Makes no checks. Almost certainly a Bad Idea.
skipBack# :: Int# -> ParserT st r e () Source #
Go back i#
bytes in the input. Takes a positive integer.
Extremely unsafe. Makes no checks. Almost certainly a Bad Idea.
atSkip# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #
Skip forward n#
bytes and run the given parser. Fails if fewer than n#
bytes are available.
Throws a runtime error if given a negative integer.
atSkipUnsafe# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #
Skip forward i#
bytes and run the given parser. Fails if fewer than i
bytes are available.
Undefined behaviour if given a negative integer.
bytes :: [Word] -> Q Exp Source #
Read a sequence of bytes. This is a template function, you can use it as
$(bytes [3, 4, 5])
, for example, and the splice has type Parser e
()
. For a non-TH variant see byteString
.
bytesUnsafe :: [Word] -> Q Exp Source #
Template function, creates a Parser e ()
which unsafely parses a given
sequence of bytes.
The caller must guarantee that the input has enough bytes.
byteString :: ByteString -> ParserT st r e () Source #
Parse a given ByteString
. If the bytestring is statically known, consider using bytes
instead.
anyCString :: ParserT st r e ByteString Source #
Read a null-terminated bytestring (a C-style string).
Consumes the null terminator.
anyVarintProtobuf :: ParserT st r e Int Source #
Read a protobuf-style varint into a positive Int
.
protobuf-style varints are byte-aligned. For each byte, the lower 7 bits are data and the MSB indicates if there are further bytes. Once fully parsed, the 7-bit payloads are concatenated and interpreted as a little-endian unsigned integer.
Fails if the varint exceeds the positive Int
range.
Really, these are varnats. They also match with the LEB128 varint encoding.
protobuf encodes negatives in unsigned integers using zigzag encoding. See
the fromZigzag
family of functions for this functionality.
Further reading: https://developers.google.com/protocol-buffers/docs/encoding#varints
Combinators
(<|>) :: ParserT st r e a -> ParserT st r e a -> ParserT st r e a infixr 6 Source #
Choose between two parsers. If the first parser fails, try the second one, but if the first one throws an error, propagate the error. This operation can arbitrarily backtrack.
Note: this exported operator has different fixity than the same operator in
Applicative
. Hide this operator if you want to use the
Alternative
version.
branch :: ParserT st r e a -> ParserT st r e b -> ParserT st r e b -> ParserT st r e b Source #
Branch on a parser: if the first argument succeeds, continue with the second, else with the third.
This can produce slightly more efficient code than (<|>)
. Moreover, ḃranch
does not
backtrack from the true/false cases.
notFollowedBy :: ParserT st r e a -> ParserT st r e b -> ParserT st r e a Source #
Succeed if the first parser succeeds and the second one fails.
lookahead :: ParserT st r e a -> ParserT st r e a Source #
Save the parsing state, then run a parser, then restore the state.
ensure :: Int -> ParserT st r e () Source #
Assert that there are at least n
bytes remaining.
Undefined behaviour if given a negative integer.
ensure# :: Int# -> ParserT st r e () Source #
Assert that there are at least n#
bytes remaining.
Undefined behaviour if given a negative integer.
withEnsure :: Int -> ParserT st r e ret -> ParserT st r e ret Source #
Assert that there are at least n#
bytes remaining (CPS).
Undefined behaviour if given a negative integer.
withEnsure1 :: ParserT st r e ret -> ParserT st r e ret Source #
Assert that there is at least 1 byte remaining (CPS).
Undefined behaviour if given a negative integer.
withEnsure# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #
Assert that there are at least n#
bytes remaining (CPS).
Undefined behaviour if given a negative integer.
isolate :: Int -> ParserT st r e a -> ParserT st r e a Source #
isolate n p
runs the parser p
isolated to the next n
bytes.
All isolated bytes must be consumed.
Throws a runtime error if given a negative integer.
isolateToNextNull :: ParserT st r e a -> ParserT st r e a Source #
Isolate the given parser up to (excluding) the next null byte.
Like isolate
, all isolated bytes must be consumed. The null byte is
consumed afterwards.
Useful for defining parsers for null-terminated data.
isolate# :: Int# -> ParserT st r e a -> ParserT st r e a Source #
isolate# n# p
runs the parser p
isolated to the next n#
bytes.
All isolated bytes must be consumed.
Throws a runtime error if given a negative integer.
isolateUnsafe# :: Int# -> ParserT st r e ret -> ParserT st r e ret Source #
isolateUnsafe# i# p
runs the parser p
isolated to the next i#
bytes.
All isolated bytes must be consumed.
Undefined behaviour if given a negative integer.
switch :: Q Exp -> Q Exp Source #
This is a template function which makes it possible to branch on a collection of string literals in
an efficient way. By using switch
, such branching is compiled to a trie of primitive parsing
operations, which has optimized control flow, vectorized reads and grouped checking for needed input
bytes.
The syntax is slightly magical, it overloads the usual case
expression. An example:
$(switch [| case _ of "foo" -> pure True "bar" -> pure False |])
The underscore is mandatory in case _ of
. Each branch must be a string literal, but optionally
we may have a default case, like in
$(switch [| case _ of "foo" -> pure 10 "bar" -> pure 20 _ -> pure 30 |])
All case right hand sides must be parsers with the same type. That type is also the type
of the whole switch
expression.
A switch
has longest match semantics, and the order of cases does not matter, except for
the default case, which may only appear as the last case.
If a switch
does not have a default case, and no case matches the input, then it returns with
failure, without having consumed any input. A fallthrough to the default case also does not
consume any input.
switchWithPost :: Maybe (Q Exp) -> Q Exp -> Q Exp Source #
Switch expression with an optional first argument for performing a post-processing action after
every successful branch matching. For example, if we have ws :: ParserT st r e ()
for a
whitespace parser, we might want to consume whitespace after matching on any of the switch
cases. For that case, we can define a "lexeme" version of switch
as follows.
switch' :: Q Exp -> Q Exp switch' = switchWithPost (Just [| ws |])
Note that this switch'
function cannot be used in the same module it's defined in, because of the
stage restriction of Template Haskell.
rawSwitchWithPost :: Maybe (Q Exp) -> [(String, Q Exp)] -> Maybe (Q Exp) -> Q Exp Source #
Version of switchWithPost
without syntactic sugar. The second argument is the
list of cases, the third is the default case.
many :: Alternative f => f a -> f [a] #
Zero or more.
some :: Alternative f => f a -> f [a] #
One or more.
Errors and failures
empty :: Alternative f => f a #
The identity of <|>
withError :: ParserT st r e b -> (e -> ParserT st r e b) -> ParserT st r e b Source #
Run the parser, if an error is thrown, handle it with the given function.
:: ParserT st r t a | The parser to run. |
-> (a -> ParserT st r e b) | The parser to run in case of success. |
-> ParserT st r e b | The parser to run in case of failure. |
-> (t -> ParserT st r e b) | The parser to run in case of error. |
-> ParserT st r e b |
Run the parser, and handle each possible result.
cutting :: ParserT st r e a -> e -> (e -> e -> e) -> ParserT st r e a Source #
Run the parser, if we get a failure, throw the given error, but if we get an error, merge the
inner and the newly given errors using the e -> e -> e
function. This can be useful for
implementing parsing errors which may propagate hints or accummulate contextual information.
optional :: ParserT st r e a -> ParserT st r e (Maybe a) Source #
Convert a parsing failure to a Maybe
. If possible, use withOption
instead.
withOption :: ParserT st r e a -> (a -> ParserT st r e ret) -> ParserT st r e ret -> ParserT st r e ret Source #
Positions
Byte offset counted backwards from the end of the buffer.
Note: the Ord
instance for Pos
considers the earlier positions to be
smaller.
addrToPos# :: Addr# -> Addr# -> Pos Source #
Very unsafe conversion between a primitive address and a position. The first argument points to the end of the buffer, the second argument is being converted.
posToAddr# :: Addr# -> Pos -> Addr# Source #
Very unsafe conversion between a primitive address and a position. The first argument points to the end of the buffer.
A pair of positions.
unsafeSlice :: ByteString -> Span -> ByteString Source #
Slice into a ByteString
using a Span
. The result is invalid if the Span
is not a valid slice of the first argument.
spanOf :: ParserT st r e a -> ParserT st r e Span Source #
Return the consumed span of a parser. Use withSpan
if possible for better efficiency.
withSpan :: ParserT st r e a -> (a -> Span -> ParserT st r e b) -> ParserT st r e b Source #
Bind the result together with the span of the result. CPS'd version of spanOf
for better unboxing.
byteStringOf :: ParserT st r e a -> ParserT st r e ByteString Source #
Return the ByteString
consumed by a parser. Note: it's more efficient to use spanOf
and
withSpan
instead.
withByteString :: ParserT st r e a -> (a -> ByteString -> ParserT st r e b) -> ParserT st r e b Source #
CPS'd version of byteStringOf
. Can be more efficient, because the result is more eagerly unboxed
by GHC. It's more efficient to use spanOf
or withSpan
instead.
inSpan :: Span -> ParserT st r e a -> ParserT st r e a Source #
Run a parser in a given input Span
.
The input position and the parser state is restored after the parser is
finished, so inSpan
does not consume input and has no side effect.
Warning: this operation may crash if the given span points outside the
current parsing buffer. It's always safe to use inSpan
if the Span
comes
from a previous withSpan
or spanOf
call on the current input.
validPos :: ByteString -> Pos -> Bool Source #
Check whether a Pos
points into a ByteString
.
posLineCols :: ByteString -> [Pos] -> [(Int, Int)] Source #
Compute corresponding line and column numbers (both starting from 0) for each Pos
in a list,
assuming UTF8 encoding. Throw an error on invalid positions. Note:
computing lines and columns may traverse the ByteString
, but it
traverses it only once regardless of the length of the position list.
mkPos :: ByteString -> (Int, Int) -> Pos Source #
Create a Pos
from a line and column number. Throws an error on out-of-bounds
line and column numbers.
Text
UTF-8
char :: Char -> Q Exp Source #
Parse a UTF-8 character literal. This is a template function, you can use it as
$(char 'x')
, for example, and the splice in this case has type Parser e ()
.
string :: String -> Q Exp Source #
Parse a UTF-8 string literal. This is a template function, you can use it as $(string "foo")
,
for example, and the splice has type Parser e ()
.
anyChar :: ParserT st r e Char Source #
Parse any single Unicode character encoded using UTF-8 as a Char
.
skipAnyChar :: ParserT st r e () Source #
Skip any single Unicode character encoded using UTF-8.
satisfy :: (Char -> Bool) -> ParserT st r e Char Source #
Parse a UTF-8 Char
for which a predicate holds.
skipSatisfy :: (Char -> Bool) -> ParserT st r e () Source #
Skip a UTF-8 Char
for which a predicate holds.
fusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> ParserT st r e Char Source #
This is a variant of satisfy
which allows more optimization. We can pick four testing
functions for the four cases for the possible number of bytes in the UTF-8 character. So in
fusedSatisfy f1 f2 f3 f4
, if we read a one-byte character, the result is scrutinized with
f1
, for two-bytes, with f2
, and so on. This can result in dramatic lexing speedups.
For example, if we want to accept any letter, the naive solution would be to use
isLetter
, but this accesses a large lookup table of Unicode character classes. We
can do better with fusedSatisfy isLatinLetter isLetter isLetter isLetter
, since here the
isLatinLetter
is inlined into the UTF-8 decoding, and it probably handles a great majority of
all cases without accessing the character table.
skipFusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> ParserT st r e () Source #
Skipping variant of fusedSatisfy
.
takeLine :: ParserT st r e String Source #
Parse the rest of the current line as a String
. Assumes UTF-8 encoding,
throws an error if the encoding is invalid.
takeRestString :: ParserT st r e String Source #
Take the rest of the input as a String
. Assumes UTF-8 encoding.
linesUtf8 :: ByteString -> [String] Source #
Break an UTF-8-coded ByteString
to lines. Throws an error on invalid input.
This is mostly useful for grabbing specific source lines for displaying error
messages.
ASCII
anyAsciiChar :: ParserT st r e Char Source #
skipAnyAsciiChar :: ParserT st r e () Source #
Skip any single ASCII character (a single byte).
More efficient than anyChar_
for ASCII-only input.
ASCII-encoded numbers
anyAsciiDecimalWord :: ParserT st r e Word Source #
Parse a non-empty ASCII decimal digit sequence as a Word
.
Fails on overflow.
anyAsciiDecimalInt :: ParserT st r e Int Source #
Parse a non-empty ASCII decimal digit sequence as a positive Int
.
Fails on overflow.
anyAsciiDecimalInteger :: ParserT st r e Integer Source #
Parse a non-empty ASCII decimal digit sequence as a positive Integer
.
anyAsciiHexWord :: ParserT st r e Word Source #
Parse a non-empty, case-insensitive ASCII hexadecimal digit sequence as a
Word
.
Fails on overflow.
anyAsciiHexInt :: ParserT st r e Int Source #
Parse a non-empty, case-insensitive ASCII hexadecimal digit sequence as a
positive Int
.
Fails on overflow.
Machine integers
module FlatParse.Stateful.Integers
Debugging parsers
traceLine :: ParserT st r e String Source #
Parse the rest of the current line as a String
, but restore the parsing state.
Assumes UTF-8 encoding. This can be used for debugging.
traceRest :: ParserT st r e String Source #
Get the rest of the input as a String
, but restore the parsing state. Assumes UTF-8 encoding.
This can be used for debugging.
Unsafe
unsafeSpanToByteString :: Span -> ParserT st r e ByteString Source #
Create a ByteString
from a Span
.
The result is invalid if the Span
points outside the current buffer, or if
the Span
start is greater than the end position.
IO
unsafeLiftIO :: IO a -> ParserT st r e a Source #
Embed an IO action in a ParserT
. This is slightly safer than unsafePerformIO
because
it will sequenced correctly with respect to the surrounding actions, and its execution is guaranteed.
Parsers
module FlatParse.Stateful.Addr
anyCStringUnsafe :: ParserT st r e ByteString Source #
Read a null-terminated bytestring (a C-style string), where the bytestring is known to be null-terminated somewhere in the input.
Highly unsafe. Unless you have a guarantee that the string will be null
terminated before the input ends, use anyCString
instead. Honestly, I'm not
sure if this is a good function to define. But here it is.
Fails on GHC versions older than 9.0, since we make use of the
cstringLength#
primop introduced in GHC 9.0, and we aren't very useful
without it.
Consumes the null terminator.