Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Low level functions for reading data in the protobufs wire format.
This module exports a function decodeWire
which parses data in the raw wire
format into an untyped Map
representation.
This module also provides Parser
types and functions for reading messages
from the untyped Map
representation obtained from decodeWire
.
Synopsis
- data ParsedField
- decodeWire :: ByteString -> Either String [(FieldNumber, ParsedField)]
- newtype Parser input a = Parser {
- runParser :: input -> Either ParseError a
- type RawPrimitive = ParsedField
- type RawField = [RawPrimitive]
- type RawMessage = IntMap RawField
- data ParseError
- foldFields :: IntMap (Parser RawPrimitive a, a -> acc -> acc) -> acc -> [(FieldNumber, ParsedField)] -> Either ParseError acc
- parse :: Parser RawMessage a -> ByteString -> Either ParseError a
- bool :: Parser RawPrimitive Bool
- int32 :: Parser RawPrimitive Int32
- int64 :: Parser RawPrimitive Int64
- uint32 :: Parser RawPrimitive Word32
- uint64 :: Parser RawPrimitive Word64
- sint32 :: Parser RawPrimitive Int32
- sint64 :: Parser RawPrimitive Int64
- enum :: forall e. ProtoEnum e => Parser RawPrimitive (Either Int32 e)
- byteString :: Parser RawPrimitive ByteString
- lazyByteString :: Parser RawPrimitive ByteString
- shortByteString :: Parser RawPrimitive ShortByteString
- text :: Parser RawPrimitive Text
- shortText :: Parser RawPrimitive ShortText
- packedVarints :: Integral a => Parser RawPrimitive [a]
- packedFixed32 :: Integral a => Parser RawPrimitive [a]
- packedFixed64 :: Integral a => Parser RawPrimitive [a]
- packedFloats :: Parser RawPrimitive [Float]
- packedDoubles :: Parser RawPrimitive [Double]
- fixed32 :: Parser RawPrimitive Word32
- fixed64 :: Parser RawPrimitive Word64
- sfixed32 :: Parser RawPrimitive Int32
- sfixed64 :: Parser RawPrimitive Int64
- float :: Parser RawPrimitive Float
- double :: Parser RawPrimitive Double
- at :: Parser RawField a -> FieldNumber -> Parser RawMessage a
- oneof :: a -> [(FieldNumber, Parser RawField a)] -> Parser RawMessage a
- one :: Parser RawPrimitive a -> a -> Parser RawField a
- repeated :: Parser RawPrimitive a -> Parser RawField [a]
- embedded :: Parser RawMessage a -> Parser RawField (Maybe a)
- embedded' :: Parser RawMessage a -> Parser RawPrimitive a
- zigZagDecode :: (Num a, Bits a) => a -> a
Untyped Representation
data ParsedField Source #
One field in a protobuf message.
We don't know what's inside some of these fields until we know what type
we're deserializing to, so we leave them as ByteString
until a later step
in the process.
Instances
Show ParsedField Source # | |
Defined in Proto3.Wire.Decode showsPrec :: Int -> ParsedField -> ShowS # show :: ParsedField -> String # showList :: [ParsedField] -> ShowS # | |
Eq ParsedField Source # | |
Defined in Proto3.Wire.Decode (==) :: ParsedField -> ParsedField -> Bool # (/=) :: ParsedField -> ParsedField -> Bool # |
decodeWire :: ByteString -> Either String [(FieldNumber, ParsedField)] Source #
Parser Types
newtype Parser input a Source #
A parsing function type synonym, to tidy up type signatures.
This synonym is used in three ways:
- Applied to
RawPrimitive
, to parse primitive fields. - Applied to
RawField
, to parse fields which correspond to a singleFieldNumber
. - Applied to
RawMessage
, to parse entire messages.
Many of the combinators in this module are used to combine and convert between these three parser types.
Parser
s can be combined using the Applicative
, Monad
and Alternative
instances.
Parser | |
|
type RawPrimitive = ParsedField Source #
Raw data corresponding to a single encoded key/value pair.
type RawField = [RawPrimitive] Source #
Raw data corresponding to a single FieldNumber
.
type RawMessage = IntMap RawField Source #
Raw data corresponding to an entire message.
A Map
from FieldNumber
s to the those values associated with
that FieldNumber
.
data ParseError Source #
Type describing possible errors that can be encountered while parsing.
WireTypeError Text | A |
BinaryError Text | A |
EmbeddedError Text (Maybe ParseError) | An |
Instances
Exception ParseError Source # | This library does not use this instance, but it is provided for convenience,
so that |
Defined in Proto3.Wire.Decode toException :: ParseError -> SomeException # fromException :: SomeException -> Maybe ParseError # displayException :: ParseError -> String # | |
Show ParseError Source # | |
Defined in Proto3.Wire.Decode showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Eq ParseError Source # | |
Defined in Proto3.Wire.Decode (==) :: ParseError -> ParseError -> Bool # (/=) :: ParseError -> ParseError -> Bool # | |
Ord ParseError Source # | |
Defined in Proto3.Wire.Decode compare :: ParseError -> ParseError -> Ordering # (<) :: ParseError -> ParseError -> Bool # (<=) :: ParseError -> ParseError -> Bool # (>) :: ParseError -> ParseError -> Bool # (>=) :: ParseError -> ParseError -> Bool # max :: ParseError -> ParseError -> ParseError # min :: ParseError -> ParseError -> ParseError # |
foldFields :: IntMap (Parser RawPrimitive a, a -> acc -> acc) -> acc -> [(FieldNumber, ParsedField)] -> Either ParseError acc Source #
Fold over a list of parsed fields accumulating a result
parse :: Parser RawMessage a -> ByteString -> Either ParseError a Source #
Parse a message (encoded in the raw wire format) using the specified
Parser
.
Primitives
enum :: forall e. ProtoEnum e => Parser RawPrimitive (Either Int32 e) Source #
Parse a primitive with an enumerated type.
This parser will return Left
if the encoded integer value
is not a code for a known enumerator.
byteString :: Parser RawPrimitive ByteString Source #
Parse a primitive with the bytes
wire type as a ByteString
.
lazyByteString :: Parser RawPrimitive ByteString Source #
Parse a primitive with the bytes
wire type as a lazy ByteString
.
shortByteString :: Parser RawPrimitive ShortByteString Source #
Parse a primitive with the bytes
wire type as a ShortByteString
.
shortText :: Parser RawPrimitive ShortText Source #
Parse a primitive with the bytes
wire type as ShortText
.
packedVarints :: Integral a => Parser RawPrimitive [a] Source #
Parse a packed collection of variable-width integer values (any of int32
,
int64
, sint32
, sint64
, uint32
, uint64
or enumerations).
packedFixed32 :: Integral a => Parser RawPrimitive [a] Source #
Parse a packed collection of fixed32
values.
packedFixed64 :: Integral a => Parser RawPrimitive [a] Source #
Parse a packed collection of fixed64
values.
packedFloats :: Parser RawPrimitive [Float] Source #
Parse a packed collection of float
values.
packedDoubles :: Parser RawPrimitive [Double] Source #
Parse a packed collection of double
values.
fixed32 :: Parser RawPrimitive Word32 Source #
Parse an integer primitive with the fixed32
wire type.
fixed64 :: Parser RawPrimitive Word64 Source #
Parse an integer primitive with the fixed64
wire type.
sfixed32 :: Parser RawPrimitive Int32 Source #
Parse a signed integer primitive with the fixed32
wire type.
sfixed64 :: Parser RawPrimitive Int64 Source #
Parse a signed integer primitive with the fixed64
wire type.
Decoding Messages
at :: Parser RawField a -> FieldNumber -> Parser RawMessage a Source #
Turn a field parser into a message parser, by specifying the FieldNumber
.
This parser will fail if the specified FieldNumber
is not present.
For example:
one float `at` fieldNumber 1 :: Parser RawMessage (Maybe Float)
:: a | The value to produce when no field numbers belonging to the oneof are present in the input |
-> [(FieldNumber, Parser RawField a)] | Left-biased oneof field parsers, one per field number belonging to the oneof |
-> Parser RawMessage a |
Try to parse different field numbers with their respective parsers. This is used to express alternative between possible fields of a oneof.
TODO: contrary to the protobuf spec, in the case of multiple fields number matching the oneof content, the choice of field is biased to the order of the list, instead of being biased to the last field of group of field number in the oneof. This is related to the Map used for input that preserve order across multiple invocation of the same field, but not across a group of field.
one :: Parser RawPrimitive a -> a -> Parser RawField a Source #
This turns a primitive parser into a field parser by keeping the last received value, or return a default value if the field number is missing.
Used to ensure that we return the last value with the given field number in the message, in compliance with the protobuf standard.
The protocol buffers specification specifies default values for primitive types.
For example:
one float 0 :: Parser RawField Float
repeated :: Parser RawPrimitive a -> Parser RawField [a] Source #
Parse a repeated field, or an unpacked collection of primitives.
Each value with the identified FieldNumber
will be passed to the parser
in the first argument, to be converted into a value of the correct type.
For example, to parse a packed collection of uint32
values:
repeated uint32 :: Parser RawField ([Word32])
or to parse a collection of embedded messages:
repeated . embedded' :: Parser RawMessage a -> Parser RawField ([a])
embedded :: Parser RawMessage a -> Parser RawField (Maybe a) Source #
Create a field parser for an embedded message, from a message parser.
The protobuf spec requires that embedded messages be mergeable, so that protobuf encoding has the flexibility to transmit embedded messages in pieces. This function reassembles the pieces, and must be used to parse all embedded non-repeated messages.
If the embedded message is not found in the outer message, this function
returns Nothing
.
embedded' :: Parser RawMessage a -> Parser RawPrimitive a Source #
Create a primitive parser for an embedded message from a message parser.
This parser does no merging of fields if multiple message fragments are sent separately.
ZigZag codec
zigZagDecode :: (Num a, Bits a) => a -> a Source #
Decode a zigzag-encoded numeric type. See: http://stackoverflow.com/questions/2210923/zig-zag-decoding