Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Parser r e a = Parser {
- runParser# :: ForeignPtrContents -> r -> Addr# -> Addr# -> Int# -> Res# e a
- type Res# e a = (# (# a, Addr#, Int# #) | (# #) | (# e #) #)
- pattern OK# :: a -> Addr# -> Int# -> Res# e a
- pattern Fail# :: Res# e a
- pattern Err# :: e -> Res# e a
- data Result e a
- = OK a Int !ByteString
- | Fail
- | Err !e
- runParser :: Parser r e a -> r -> Int -> ByteString -> Result e a
- runParserS :: Parser r e a -> r -> Int -> String -> Result e a
- get :: Parser r e Int
- put :: Int -> Parser r e ()
- modify :: (Int -> Int) -> Parser r e ()
- ask :: Parser r e r
- local :: (r' -> r) -> Parser r e a -> Parser r' e a
- empty :: Parser r e a
- err :: e -> Parser r e a
- lookahead :: Parser r e a -> Parser r e a
- fails :: Parser r e a -> Parser r e ()
- try :: Parser r e a -> Parser r e a
- optional :: Parser r e a -> Parser r e (Maybe a)
- optioned :: Parser r e a -> (a -> Parser r e b) -> Parser r e b -> Parser r e b
- cut :: Parser r e a -> e -> Parser r e a
- cutting :: Parser r e a -> e -> (e -> e -> e) -> Parser r e a
- eof :: Parser r e ()
- char :: Char -> Q Exp
- byte :: Word8 -> Parser r e ()
- bytes :: [Word8] -> Q Exp
- string :: String -> Q Exp
- 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
- satisfy :: (Char -> Bool) -> Parser r e Char
- satisfyASCII :: (Char -> Bool) -> Parser r e Char
- satisfyASCII_ :: (Char -> Bool) -> Parser r e ()
- fusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> Parser r e Char
- anyWord8 :: Parser r e Word8
- anyWord16 :: Parser r e Word16
- anyWord32 :: Parser r e Word32
- anyWord :: Parser r e Word
- anyChar :: Parser r e Char
- anyChar_ :: Parser r e ()
- anyCharASCII :: Parser r e Char
- anyCharASCII_ :: Parser r e ()
- isDigit :: Char -> Bool
- isGreekLetter :: Char -> Bool
- isLatinLetter :: Char -> Bool
- (<|>) :: Parser r e a -> Parser r e a -> Parser r e a
- branch :: Parser r e a -> Parser r e b -> Parser r e b -> Parser r e b
- chainl :: (b -> a -> b) -> Parser r e b -> Parser r e a -> Parser r e b
- chainr :: (a -> b -> b) -> Parser r e a -> Parser r e b -> Parser r e b
- many :: Parser r e a -> Parser r e [a]
- many_ :: Parser r e a -> Parser r e ()
- some :: Parser r e a -> Parser r e [a]
- some_ :: Parser r e a -> Parser r e ()
- notFollowedBy :: Parser r e a -> Parser r e b -> Parser r e a
- newtype Pos = Pos Int
- data Span = Span !Pos !Pos
- getPos :: Parser r e Pos
- setPos :: Pos -> Parser r e ()
- endPos :: Pos
- spanOf :: Parser r e a -> Parser r e Span
- spanned :: Parser r e a -> (a -> Span -> Parser r e b) -> Parser r e b
- byteStringOf :: Parser r e a -> Parser r e ByteString
- byteStringed :: Parser r e a -> (a -> ByteString -> Parser r e b) -> Parser r e b
- inSpan :: Span -> Parser r e a -> Parser r e a
- validPos :: ByteString -> Pos -> Bool
- posLineCols :: ByteString -> [Pos] -> [(Int, Int)]
- unsafeSpanToByteString :: Span -> Parser r e ByteString
- mkPos :: ByteString -> (Int, Int) -> Pos
- lines :: ByteString -> [String]
- takeLine :: Parser r e String
- traceLine :: Parser r e String
- takeRest :: Parser r e String
- traceRest :: Parser r e String
- ensureBytes# :: Int -> Parser r e ()
- scan8# :: Word -> Parser r e ()
- scan16# :: Word -> Parser r e ()
- scan32# :: Word -> Parser r e ()
- scan64# :: Word -> Parser r e ()
- scanAny8# :: Parser r e Word8
- scanBytes# :: [Word8] -> Q Exp
- setBack# :: Int -> Parser r e ()
- packUTF8 :: String -> ByteString
Parser types and constructors
Parser r e a
has a reader environment r
, an error type e
and a return type a
.
Parser | |
|
pattern OK# :: a -> Addr# -> Int# -> Res# e a Source #
Contains return value, pointer to the rest of the input buffer and the nex Int
state.
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. |
Running parsers
runParserS :: Parser r e a -> r -> Int -> String -> Result e a Source #
Run a parser on a String
input. Reminder: OverloadedStrings
for ByteString
does not
yield a valid UTF-8 encoding! For non-ASCII ByteString
literal input, use runParserS
or
packUTF8
for testing.
Actions on the state and the environment
Errors and failures
empty :: Parser r e a Source #
The failing parser. By default, parser choice (<|>)
arbitrarily backtracks
on parser failure.
lookahead :: Parser r e a -> Parser r e a Source #
Save the parsing state, then run a parser, then restore the state.
cutting :: Parser r e a -> e -> (e -> e -> e) -> Parser 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.
Basic lexing and parsing
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 r e ()
.
bytes :: [Word8] -> 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 r 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 r e ()
.
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 :: Parser 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.
satisfy :: (Char -> Bool) -> Parser r e Char Source #
Parse a UTF-8 Char
for which a predicate holds.
satisfyASCII_ :: (Char -> Bool) -> Parser r e () Source #
Parse an ASCII Char
for which a predicate holds.
fusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> Parser 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.
anyCharASCII :: Parser r e Char Source #
anyCharASCII_ :: Parser r e () Source #
isGreekLetter :: Char -> Bool Source #
isGreekLetter c = ('Α' <= c && c <= 'Ω') || ('α' <= c && c <= 'ω')
isLatinLetter :: Char -> Bool Source #
isLatinLetter c = ('A' <= c && c <= 'Z') || ('a' <= c && c <= 'z')
Combinators
(<|>) :: Parser r e a -> Parser r e a -> Parser 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.
branch :: Parser r e a -> Parser r e b -> Parser r e b -> Parser r e b Source #
Branch on a parser: if the first argument fails, 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.
many :: Parser r e a -> Parser r e [a] Source #
Run a parser zero or more times, collect the results in a list. Note: for optimal performance, try to avoid this. Often it is possible to get rid of the intermediate list by using a combinator or a custom parser.
some :: Parser r e a -> Parser r e [a] Source #
Run a parser one or more times, collect the results in a list. Note: for optimal performance, try to avoid this. Often it is possible to get rid of the intermediate list by using a combinator or a custom parser.
notFollowedBy :: Parser r e a -> Parser r e b -> Parser r e a Source #
Succeed if the first parser succeeds and the second one fails. The parsing state is restored to the point of the first argument's success.
Positions and spans
Byte offset counted backwards from the end of the buffer.
A pair of positions.
spanOf :: Parser r e a -> Parser r e Span Source #
Return the consumed span of a parser. Use spanned
if possible for better efficiency.
spanned :: Parser r e a -> (a -> Span -> Parser r e b) -> Parser r e b Source #
Bind the result together with the span of the result. CPS'd version of spanOf
for better unboxing.
byteStringOf :: Parser r e a -> Parser r e ByteString Source #
Return the ByteString
consumed by a parser. Note: it's more efficient to use spanOf
and
spanned
instead.
byteStringed :: Parser r e a -> (a -> ByteString -> Parser r e b) -> Parser 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 spanned
instead.
inSpan :: Span -> Parser r e a -> Parser r e a Source #
Run a parser in a given input span. The input position and the Int
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 spanned
or spanOf
call on
the current input.
Position and span conversions
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 for each Pos
in a list. 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.
unsafeSpanToByteString :: Span -> Parser r e ByteString Source #
Create a ByteString
from a Span
. The result is invalid is the Span
points
outside the current buffer, or if the Span
start is greater than the end position.
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.
lines :: 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.
Getting the rest of the input
takeLine :: Parser 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.
traceLine :: Parser 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.
takeRest :: Parser r e String Source #
Take the rest of the input as a String
. Assumes UTF-8 encoding.
traceRest :: Parser 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.
Internal functions
ensureBytes# :: Int -> Parser r e () Source #
Check that the input has at least the given number of bytes.
scan8# :: Word -> Parser r e () Source #
Unsafely read a concrete byte from the input. It's not checked that the input has enough bytes.
scan16# :: Word -> Parser r e () Source #
Unsafely read two concrete bytes from the input. It's not checked that the input has enough bytes.
scan32# :: Word -> Parser r e () Source #
Unsafely read four concrete bytes from the input. It's not checked that the input has enough bytes.
scan64# :: Word -> Parser r e () Source #
Unsafely read eight concrete bytes from the input. It's not checked that the input has enough bytes.
scanAny8# :: Parser r e Word8 Source #
Unsafely read and return a byte from the input. It's not checked that the input is non-empty.
scanBytes# :: [Word8] -> Q Exp Source #
Template function, creates a Parser r e ()
which unsafely scans a given
sequence of bytes.
setBack# :: Int -> Parser r e () Source #
Decrease the current input position by the given number of bytes.
packUTF8 :: String -> ByteString Source #
Convert a String
to an UTF-8-coded ByteString
.