proto3-wire-1.4.1: A low-level implementation of the Protocol Buffers (version 3) wire format
Safe HaskellSafe-Inferred
LanguageHaskell2010

Proto3.Wire.Decode

Description

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

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

Instances details
Show ParsedField Source # 
Instance details

Defined in Proto3.Wire.Decode

Eq ParsedField Source # 
Instance details

Defined in Proto3.Wire.Decode

Parser Types

newtype Parser input a Source #

A parsing function type synonym, to tidy up type signatures.

This synonym is used in three ways:

Many of the combinators in this module are used to combine and convert between these three parser types.

Parsers can be combined using the Applicative, Monad and Alternative instances.

Constructors

Parser 

Fields

Instances

Instances details
Applicative (Parser input) Source # 
Instance details

Defined in Proto3.Wire.Decode

Methods

pure :: a -> Parser input a #

(<*>) :: Parser input (a -> b) -> Parser input a -> Parser input b #

liftA2 :: (a -> b -> c) -> Parser input a -> Parser input b -> Parser input c #

(*>) :: Parser input a -> Parser input b -> Parser input b #

(<*) :: Parser input a -> Parser input b -> Parser input a #

Functor (Parser input) Source # 
Instance details

Defined in Proto3.Wire.Decode

Methods

fmap :: (a -> b) -> Parser input a -> Parser input b #

(<$) :: a -> Parser input b -> Parser input a #

Monad (Parser input) Source # 
Instance details

Defined in Proto3.Wire.Decode

Methods

(>>=) :: Parser input a -> (a -> Parser input b) -> Parser input b #

(>>) :: Parser input a -> Parser input b -> Parser input b #

return :: a -> Parser input a #

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 FieldNumbers to the those values associated with that FieldNumber.

data ParseError Source #

Type describing possible errors that can be encountered while parsing.

Constructors

WireTypeError Text

A WireTypeError occurs when the type of the data in the protobuf binary format does not match the type encountered by the parser. This can indicate that the type of a field has changed or is incorrect.

BinaryError Text

A BinaryError occurs when we can't successfully parse the contents of the field.

EmbeddedError Text (Maybe ParseError)

An EmbeddedError occurs when we encounter an error while parsing an embedded message.

Instances

Instances details
Exception ParseError Source #

This library does not use this instance, but it is provided for convenience, so that ParseError may be used with functions like throwIO

Instance details

Defined in Proto3.Wire.Decode

Show ParseError Source # 
Instance details

Defined in Proto3.Wire.Decode

Eq ParseError Source # 
Instance details

Defined in Proto3.Wire.Decode

Ord ParseError Source # 
Instance details

Defined in Proto3.Wire.Decode

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

bool :: Parser RawPrimitive Bool Source #

Parse a Boolean value.

int32 :: Parser RawPrimitive Int32 Source #

Parse a primitive with the int32 wire type.

int64 :: Parser RawPrimitive Int64 Source #

Parse a primitive with the int64 wire type.

uint32 :: Parser RawPrimitive Word32 Source #

Parse a primitive with the uint32 wire type.

uint64 :: Parser RawPrimitive Word64 Source #

Parse a primitive with the uint64 wire type.

sint32 :: Parser RawPrimitive Int32 Source #

Parse a primitive with the sint32 wire type.

sint64 :: Parser RawPrimitive Int64 Source #

Parse a primitive with the sint64 wire type.

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.

text :: Parser RawPrimitive Text Source #

Parse a primitive with the bytes wire type as Text.

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)

oneof Source #

Arguments

:: 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