- data Parser m
- data ParseStatus
- newParserIO :: IO (Parser IO)
- newParserST :: ST s (Parser (ST s))
- data Callback m a
- setCallback :: Parser m -> Callback m a -> a -> m ()
- clearCallback :: Parser m -> Callback m a -> m ()
- parsedBeginArray :: Callback m (m Bool)
- parsedEndArray :: Callback m (m Bool)
- parsedBeginObject :: Callback m (m Bool)
- parsedEndObject :: Callback m (m Bool)
- parsedNull :: Callback m (m Bool)
- parsedBoolean :: Callback m (Bool -> m Bool)
- parsedInteger :: Callback m (Integer -> m Bool)
- parsedDouble :: Callback m (Double -> m Bool)
- parsedNumber :: Callback m (ByteString -> m Bool)
- parsedAttributeText :: Callback m (Text -> m Bool)
- parsedAttributeBytes :: Callback m (ByteString -> m Bool)
- parsedAttributeBuffer :: Callback m ((Ptr Word8, Integer) -> m Bool)
- parsedText :: Callback m (Text -> m Bool)
- parsedBytes :: Callback m (ByteString -> m Bool)
- parsedBuffer :: Callback m ((Ptr Word8, Integer) -> m Bool)
- parseText :: Parser m -> Text -> m ParseStatus
- parseLazyText :: Parser m -> Text -> m ParseStatus
- parseBytes :: Parser m -> ByteString -> m ParseStatus
- parseLazyBytes :: Parser m -> ByteString -> m ParseStatus
- parseBuffer :: Parser m -> (Ptr Word8, Integer) -> m ParseStatus
- parseComplete :: Parser m -> m ParseStatus
- getBytesConsumed :: Parser m -> m Integer
- data Generator s
- data GeneratorConfig = GeneratorConfig {}
- data GeneratorError
- newGenerator :: GeneratorConfig -> ST s (Generator s)
- getBuffer :: Generator s -> ST s ByteString
- clearBuffer :: Generator s -> ST s ()
- generateNull :: Generator s -> ST s ()
- generateBoolean :: Generator s -> Bool -> ST s ()
- generateIntegral :: Integral a => Generator s -> a -> ST s ()
- generateDouble :: Generator s -> Double -> ST s ()
- generateNumber :: Generator s -> ByteString -> ST s ()
- generateText :: Generator s -> Text -> ST s ()
- generateBeginArray :: Generator s -> ST s ()
- generateEndArray :: Generator s -> ST s ()
- generateBeginObject :: Generator s -> ST s ()
- generateEndObject :: Generator s -> ST s ()
Parser
data ParseStatus Source
ParseFinished | |
ParseContinue | More input is required before parsing can complete. |
ParseCancelled | A callback returned |
ParseError Text | An error occured while parsing. The included message contains details about the error. |
newParserIO :: IO (Parser IO)Source
newParserST :: ST s (Parser (ST s))Source
Parser callbacks
setCallback :: Parser m -> Callback m a -> a -> m ()Source
clearCallback :: Parser m -> Callback m a -> m ()Source
Containers
parsedBeginArray :: Callback m (m Bool)Source
parsedEndArray :: Callback m (m Bool)Source
parsedBeginObject :: Callback m (m Bool)Source
parsedEndObject :: Callback m (m Bool)Source
Basic values
parsedNull :: Callback m (m Bool)Source
parsedBoolean :: Callback m (Bool -> m Bool)Source
Numeric callbacks
parsedInteger :: Callback m (Integer -> m Bool)Source
parsedDouble :: Callback m (Double -> m Bool)Source
parsedNumber :: Callback m (ByteString -> m Bool)Source
If parsedNumber
is set, it overrides parsedInteger
and parsedDouble
.
Registered functions for these callbacks will not receive any input until
parsedNumber
is unset.
If parsedNumber
is not set, but one of parsedInteger
or parsedDouble
is set, then any values which cannot be represented by CLong
or CDouble
will cause a parse error.
The ByteString
is in UTF-8.
Text callbacks
parsedAttributeText :: Callback m (Text -> m Bool)Source
Only one of parsedAttributeText
, parsedAttributeBytes
, or
parsedAttributeBuffer
may be set. If another of these callbacks is set,
it will unset the others.
parsedAttributeBytes :: Callback m (ByteString -> m Bool)Source
Only one of parsedAttributeText
, parsedAttributeBytes
, or
parsedAttributeBuffer
may be set. If another of these callbacks is set,
it will unset the others.
The ByteString
is in UTF-8.
parsedAttributeBuffer :: Callback m ((Ptr Word8, Integer) -> m Bool)Source
Only one of parsedAttributeText
, parsedAttributeBytes
, or
parsedAttributeBuffer
may be set. If another of these callbacks is set,
it will unset the others.
The buffer is in UTF-8.
parsedText :: Callback m (Text -> m Bool)Source
Only one of parsedText
, parsedBytes
, or parsedBuffer
may be set.
If another of these callbacks is set, it will unset the others.
parsedBytes :: Callback m (ByteString -> m Bool)Source
Only one of parsedText
, parsedBytes
, or parsedBuffer
may be set.
If another of these callbacks is set, it will unset the others.
The ByteString
is in UTF-8.
parsedBuffer :: Callback m ((Ptr Word8, Integer) -> m Bool)Source
Only one of parsedText
, parsedBytes
, or parsedBuffer
may be set.
If another of these callbacks is set, it will unset the others.
The buffer is in UTF-8.
Parser input
parseText :: Parser m -> Text -> m ParseStatusSource
parseLazyText :: Parser m -> Text -> m ParseStatusSource
parseBytes :: Parser m -> ByteString -> m ParseStatusSource
The input must be in UTF-8.
parseLazyBytes :: Parser m -> ByteString -> m ParseStatusSource
The input must be in UTF-8.
parseBuffer :: Parser m -> (Ptr Word8, Integer) -> m ParseStatusSource
The input must be in UTF-8.
parseComplete :: Parser m -> m ParseStatusSource
Clients should call this when no more input is available, to indicate EOF.
getBytesConsumed :: Parser m -> m IntegerSource
Get the number of bytes consumed from the last input chunk.
Note that if using parseText
or parseLazyText
, this corresponds to
UTF-8 bytes, not characters.
If the most recent call to parseBytes
, parseText
, etc, returned
ParseFinished
, this will indicate whether there are any un-parsed
bytes past the end of input.
If the most recent parse returned ParseError
, this will indicate where
the error occured.
Generator
data GeneratorConfig Source
GeneratorConfig | |
|
data GeneratorError Source
If an error is encountered when generating data, a GeneratorError
will be thrown.
With the exception of MaximumDepthExceeded
, this is usually due to
incorrect use of the library.
newGenerator :: GeneratorConfig -> ST s (Generator s)Source
Create a new, empty generator with the given configuration.
getBuffer :: Generator s -> ST s ByteStringSource
Retrieve the NUL
-terminated byte buffer.
clearBuffer :: Generator s -> ST s ()Source
Clear the generator's output buffer. This does not change the state of the generator.
Generator events
generateNull :: Generator s -> ST s ()Source
generateNumber :: Generator s -> ByteString -> ST s ()Source
generateBeginArray :: Generator s -> ST s ()Source
generateEndArray :: Generator s -> ST s ()Source
generateBeginObject :: Generator s -> ST s ()Source
generateEndObject :: Generator s -> ST s ()Source