| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DotParse
Description
Parser & Printer for the dot language of graphviz
See DotParse.Examples for usage.
Synopsis
- module DotParse.Types
- module DotParse.FlatParse
- anyInt64be :: Parser e Int64
- anyInt64le :: Parser e Int64
- anyInt32be :: Parser e Int32
- anyInt32le :: Parser e Int32
- anyInt16be :: Parser e Int16
- anyInt16le :: Parser e Int16
- anyWord64be :: Parser e Word64
- anyWord64le :: Parser e Word64
- anyWord32be :: Parser e Word32
- anyWord32le :: Parser e Word32
- anyWord16be :: Parser e Word16
- anyWord16le :: Parser e Word16
- anyInt :: Parser e Int
- anyInt64 :: Parser e Int64
- anyInt32 :: Parser e Int32
- anyInt16 :: Parser e Int16
- anyInt8 :: Parser e Int8
- anyWord_ :: Parser e ()
- anyWord :: Parser e Word
- anyWord64_ :: Parser e ()
- anyWord64 :: Parser e Word64
- anyWord32_ :: Parser e ()
- anyWord32 :: Parser e Word32
- anyWord16_ :: Parser e ()
- anyWord16 :: Parser e Word16
- anyWord8_ :: Parser e ()
- anyWord8 :: Parser e Word8
- scanBytes# :: [Word] -> Q Exp
- setBack# :: Int -> Parser e ()
- scanAny8# :: Parser e Word8
- scan64# :: Word -> Parser e ()
- scan32# :: Word32 -> Parser e ()
- scan16# :: Word16 -> Parser e ()
- scan8# :: Word8 -> Parser e ()
- ensureBytes# :: Int -> Parser e ()
- unpackUTF8 :: ByteString -> String
- traceRest :: Parser e String
- takeRest :: Parser e String
- traceLine :: Parser e String
- takeLine :: Parser e String
- mkPos :: ByteString -> (Int, Int) -> Pos
- unsafeSpanToByteString :: Span -> Parser e ByteString
- posLineCols :: ByteString -> [Pos] -> [(Int, Int)]
- validPos :: ByteString -> Pos -> Bool
- inSpan :: Span -> Parser e a -> Parser e a
- byteStringed :: Parser e a -> (a -> ByteString -> Parser e b) -> Parser e b
- byteStringOf :: Parser e a -> Parser e ByteString
- spanned :: Parser e a -> (a -> Span -> Parser e b) -> Parser e b
- spanOf :: Parser e a -> Parser e Span
- endPos :: Pos
- setPos :: Pos -> Parser e ()
- getPos :: Parser e Pos
- notFollowedBy :: Parser e a -> Parser e b -> Parser e a
- some_ :: Parser e a -> Parser e ()
- some :: Parser e a -> Parser e [a]
- many_ :: Parser e a -> Parser e ()
- many :: Parser e a -> Parser e [a]
- chainr :: (a -> b -> b) -> Parser e a -> Parser e b -> Parser e b
- chainl :: (b -> a -> b) -> Parser e b -> Parser e a -> Parser e b
- branch :: Parser e a -> Parser e b -> Parser e b -> Parser e b
- (<|>) :: Parser e a -> Parser e a -> Parser e a
- readInteger :: Parser e Integer
- readInt :: Parser e Int
- anyCharASCII_ :: Parser e ()
- anyCharASCII :: Parser e Char
- anyChar_ :: Parser e ()
- anyChar :: Parser e Char
- fusedSatisfy_ :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> Parser e ()
- fusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> Parser e Char
- satisfyASCII_ :: (Char -> Bool) -> Parser e ()
- satisfyASCII :: (Char -> Bool) -> Parser e Char
- satisfy_ :: (Char -> Bool) -> Parser e ()
- satisfy :: (Char -> Bool) -> Parser e Char
- rawSwitchWithPost :: Maybe (Q Exp) -> [(String, Q Exp)] -> Maybe (Q Exp) -> Q Exp
- switchWithPost :: Maybe (Q Exp) -> Q Exp -> Q Exp
- switch :: Q Exp -> Q Exp
- string :: String -> Q Exp
- bytes :: [Word] -> Q Exp
- byte :: Word8 -> Parser e ()
- char :: Char -> Q Exp
- eof :: Parser e ()
- cutting :: Parser e a -> e -> (e -> e -> e) -> Parser e a
- optioned :: Parser e a -> (a -> Parser e b) -> Parser e b -> Parser e b
- optional_ :: Parser e a -> Parser e ()
- optional :: Parser e a -> Parser e (Maybe a)
- try :: Parser e a -> Parser e a
- fails :: Parser e a -> Parser e ()
- lookahead :: Parser e a -> Parser e a
- err :: e -> Parser e a
- empty :: Parser e a
- runParserS :: Parser e a -> String -> Result e a
- runParser :: Parser e a -> ByteString -> Result e a
- pattern OK# :: a -> Addr# -> Res# e a
- pattern Err# :: e -> Res# e a
- pattern Fail# :: Res# e a
- type Res# e a = (# (# a, Addr# #) | (# #) | (# e #) #)
- newtype Parser e a = Parser {
- runParser# :: ForeignPtrContents -> Addr# -> Addr# -> Res# e a
- data Result e a
- = OK a !ByteString
- | Fail
- | Err !e
- packUTF8 :: String -> ByteString
- unsafeSlice :: ByteString -> Span -> ByteString
- isGreekLetter :: Char -> Bool
- isLatinLetter :: Char -> Bool
- isDigit :: Char -> Bool
- newtype Pos = Pos Int
- data Span = Span !Pos !Pos
- module NeatInterpolation
Documentation
module DotParse.Types
module DotParse.FlatParse
anyInt64be :: Parser e Int64 #
Parse any Int64 (big-endian).
anyInt64le :: Parser e Int64 #
Parse any Int64 (little-endian).
anyInt32be :: Parser e Int32 #
Parse any Int32 (big-endian).
anyInt32le :: Parser e Int32 #
Parse any Int32 (little-endian).
anyInt16be :: Parser e Int16 #
Parse any Int16 (big-endian).
anyInt16le :: Parser e Int16 #
Parse any Int16 (little-endian).
anyWord64be :: Parser e Word64 #
Parse any Word64 (big-endian).
anyWord64le :: Parser e Word64 #
Parse any Word64 (little-endian).
anyWord32be :: Parser e Word32 #
Parse any Word32 (big-endian).
anyWord32le :: Parser e Word32 #
Parse any Word32 (little-endian).
anyWord16be :: Parser e Word16 #
Parse any Word16 (big-endian).
anyWord16le :: Parser e Word16 #
Parse any Word16 (little-endian).
anyWord64_ :: Parser e () #
Skip any Word64.
anyWord32_ :: Parser e () #
Skip any Word32.
anyWord16_ :: Parser e () #
Skip any Word16.
scanBytes# :: [Word] -> Q Exp #
Template function, creates a Parser e () which unsafely scans a given
sequence of bytes.
Unsafely read and return a byte from the input. It's not checked that the input is non-empty.
scan64# :: Word -> Parser e () #
Unsafely read eight concrete bytes from the input. It's not checked that the input has enough bytes.
scan32# :: Word32 -> Parser e () #
Unsafely read four concrete bytes from the input. It's not checked that the input has enough bytes.
scan16# :: Word16 -> Parser e () #
Unsafely read two concrete bytes from the input. It's not checked that the input has enough bytes.
scan8# :: Word8 -> Parser e () #
Unsafely read a concrete byte from the input. It's not checked that the input has enough bytes.
ensureBytes# :: Int -> Parser e () #
Check that the input has at least the given number of bytes.
unpackUTF8 :: ByteString -> String #
Convert an UTF-8-coded ByteString to a String.
traceRest :: Parser e String #
Get the rest of the input as a String, but restore the parsing state. Assumes UTF-8 encoding.
This can be used for debugging.
traceLine :: Parser e String #
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.
Parse the rest of the current line as a String. Assumes UTF-8 encoding,
throws an error if the encoding is invalid.
mkPos :: ByteString -> (Int, Int) -> Pos #
Create a Pos from a line and column number. Throws an error on out-of-bounds
line and column numbers.
unsafeSpanToByteString :: Span -> Parser e ByteString #
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.
posLineCols :: ByteString -> [Pos] -> [(Int, Int)] #
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.
validPos :: ByteString -> Pos -> Bool #
Check whether a Pos points into a ByteString.
inSpan :: Span -> Parser e a -> Parser e a #
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.
byteStringed :: Parser e a -> (a -> ByteString -> Parser e b) -> Parser e b #
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.
byteStringOf :: Parser e a -> Parser e ByteString #
Return the ByteString consumed by a parser. Note: it's more efficient to use spanOf and
spanned instead.
spanned :: Parser e a -> (a -> Span -> Parser e b) -> Parser e b #
Bind the result together with the span of the result. CPS'd version of spanOf
for better unboxing.
notFollowedBy :: Parser e a -> Parser e b -> Parser e a #
Succeed if the first parser succeeds and the second one fails.
some :: Parser e a -> Parser e [a] #
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.
many :: Parser e a -> Parser e [a] #
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.
branch :: Parser e a -> Parser e b -> Parser e b -> Parser e b #
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.
(<|>) :: Parser e a -> Parser e a -> Parser e a infixr 6 #
Choose between two parsers. If the first parser fails, try the second one, but if the first one throws an error, propagate the error.
readInteger :: Parser e Integer #
Read an Integer from the input, as a non-empty digit sequence.
anyCharASCII_ :: Parser e () #
anyCharASCII :: Parser e Char #
fusedSatisfy_ :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> Parser e () #
Skipping variant of fusedSatisfy.
fusedSatisfy :: (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> (Char -> Bool) -> Parser e Char #
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.
satisfyASCII_ :: (Char -> Bool) -> Parser e () #
rawSwitchWithPost :: Maybe (Q Exp) -> [(String, Q Exp)] -> Maybe (Q Exp) -> Q Exp #
Version of switchWithPost without syntactic sugar. The second argument is the
list of cases, the third is the default case.
switchWithPost :: Maybe (Q Exp) -> Q Exp -> Q Exp #
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 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.
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.
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 ().
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 ().
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 ().
cutting :: Parser e a -> e -> (e -> e -> e) -> Parser e a #
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.
lookahead :: Parser e a -> Parser e a #
Save the parsing state, then run a parser, then restore the state.
The failing parser. By default, parser choice (<|>) arbitrarily backtracks
on parser failure.
runParserS :: Parser e a -> String -> Result e a #
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.
runParser :: Parser e a -> ByteString -> Result e a #
Run a parser.
pattern OK# :: a -> Addr# -> Res# e a #
Contains return value and a pointer to the rest of the input buffer.
Parser e a has an error type e and a return type a.
Constructors
| Parser | |
Fields
| |
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. |
packUTF8 :: String -> ByteString #
Convert a String to an UTF-8-coded ByteString.
unsafeSlice :: ByteString -> Span -> ByteString #
Slice into a ByteString using a Span. The result is invalid if the Span
is not a valid slice of the first argument.
isGreekLetter :: Char -> Bool #
isGreekLetter c = ('Α' <= c && c <= 'Ω') || ('α' <= c && c <= 'ω')isLatinLetter :: Char -> Bool #
isLatinLetter c = ('A' <= c && c <= 'Z') || ('a' <= c && c <= 'z')A pair of positions.
module NeatInterpolation