Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Tag = Word32
- data WireField
- = VarintField !Tag !Word64
- | Fixed64Field !Tag !Word64
- | DelimitedField !Tag !ByteString
- | StartField !Tag
- | EndField !Tag
- | Fixed32Field !Tag !Word32
- wireFieldTag :: WireField -> Tag
- getWireField :: Get WireField
- class EncodeWire a where
- class DecodeWire a where
- zzEncode32 :: Int32 -> Word32
- zzEncode64 :: Int64 -> Word64
- zzDecode32 :: Word32 -> Int32
- zzDecode64 :: Word64 -> Int64
- getVarintPrefixedBS :: Get ByteString
- getVarInt :: (Integral a, Bits a) => Get a
- putVarintPrefixedBS :: ByteString -> Put
- putVarSInt :: (Integral a, Bits a) => a -> Put
- putVarUInt :: (Integral a, Bits a) => a -> Put
- newtype Field (n :: Nat) a = Field {
- runField :: a
- newtype Value a = Value {
- runValue :: a
- newtype Always a = Always {
- runAlways :: a
- newtype Enumeration a = Enumeration {
- runEnumeration :: a
- newtype RequiredField a = Required {
- runRequired :: a
- newtype OptionalField a = Optional {
- runOptional :: a
- newtype RepeatedField a = Repeated {
- runRepeated :: a
- newtype PackedField a = PackedField {
- runPackedField :: a
- newtype PackedList a = PackedList {
- unPackedList :: [a]
- newtype Message m = Message {
- runMessage :: m
- class GDecode (f :: * -> *)
- class GEncode (f :: * -> *)
- class GMessageMonoid (f :: * -> *)
Documentation
A representation of the wire format as described in https://developers.google.com/protocol-buffers/docs/encoding#structure
VarintField !Tag !Word64 | For: int32, int64, uint32, uint64, sint32, sint64, bool, enum |
Fixed64Field !Tag !Word64 | For: fixed64, sfixed64, double |
DelimitedField !Tag !ByteString | For: string, bytes, embedded messages, packed repeated fields |
StartField !Tag | For: groups (deprecated) |
EndField !Tag | For: groups (deprecated) |
Fixed32Field !Tag !Word32 | For: fixed32, sfixed32, float |
wireFieldTag :: WireField -> Tag Source #
class EncodeWire a where Source #
encodeWire :: Tag -> a -> Put Source #
class DecodeWire a where Source #
decodeWire :: WireField -> Get a Source #
zzEncode32 :: Int32 -> Word32 Source #
zzEncode64 :: Int64 -> Word64 Source #
zzDecode32 :: Word32 -> Int32 Source #
zzDecode64 :: Word64 -> Int64 Source #
putVarintPrefixedBS :: ByteString -> Put Source #
putVarSInt :: (Integral a, Bits a) => a -> Put Source #
This can be used on any Integral type and is needed for signed types; unsigned can use putVarUInt below. This has been changed to handle only up to 64 bit integral values (to match documentation).
putVarUInt :: (Integral a, Bits a) => a -> Put Source #
This should be used on unsigned Integral types only (not checked)
newtype Field (n :: Nat) a Source #
Fields are merely a way to hold a field tag along with its type, this shouldn't normally be referenced directly.
This provides better error messages than older versions which used Tagged
Value
selects the normal/typical way for encoding scalar (primitive) values.
To provide consistent instances for serialization a Traversable
Functor
is needed to
make Required
fields have the same shape as Optional
, Repeated
and Packed
.
newtype Enumeration a Source #
Enumeration
fields use fromEnum
and toEnum
when encoding and decoding messages.
newtype RequiredField a Source #
RequiredField
is a newtype wrapped used to break overlapping instances
for encoding and decoding values
Required | |
|
newtype OptionalField a Source #
OptionalField
is a newtype wrapped used to break overlapping instances
for encoding and decoding values
Optional | |
|
newtype RepeatedField a Source #
RepeatedField
is a newtype wrapped used to break overlapping instances
for encoding and decoding values
Repeated | |
|
Functor RepeatedField Source # | |
Foldable RepeatedField Source # | |
Traversable RepeatedField Source # | |
Bounded a => Bounded (RepeatedField a) Source # | |
Enum a => Enum (RepeatedField a) Source # | |
Eq a => Eq (RepeatedField a) Source # | |
Ord a => Ord (RepeatedField a) Source # | |
Show a => Show (RepeatedField a) Source # | |
Semigroup a => Semigroup (RepeatedField a) Source # | |
Monoid a => Monoid (RepeatedField a) Source # | |
NFData a => NFData (RepeatedField a) Source # | |
HasField (Field n (RepeatedField [Enumeration a])) Source # | Iso: |
HasField (Field n (RepeatedField [Value a])) Source # | |
HasField (Field n (RepeatedField [Message a])) Source # | |
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Repeated n a)) Source # | |
type FieldType (Field n (RepeatedField [Value a])) Source # | |
type FieldType (Field n (RepeatedField [Enumeration a])) Source # | |
type FieldType (Field n (RepeatedField [Message a])) Source # | |
newtype PackedField a Source #
A Traversable
Functor
used to select packed sequence encoding/decoding.
Functor PackedField Source # | |
Foldable PackedField Source # | |
Traversable PackedField Source # | |
Eq a => Eq (PackedField a) Source # | |
Ord a => Ord (PackedField a) Source # | |
Show a => Show (PackedField a) Source # | |
Semigroup a => Semigroup (PackedField a) Source # | |
Monoid a => Monoid (PackedField a) Source # | |
NFData a => NFData (PackedField a) Source # | |
HasField (Field n (PackedField (PackedList (Enumeration a)))) Source # | Iso: |
HasField (Field n (PackedField (PackedList (Value a)))) Source # | |
(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 * i (Packed n a)) Source # | |
type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # | |
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # | |
newtype PackedList a Source #
A list that is stored in a packed format.
PackedList | |
|
The way to embed a message within another message. These embedded messages are stored as length-delimited fields.
For example:
data Inner = Inner { innerField ::Required
'1' (Value
Int64
) } deriving (Generic
,Show
) instanceEncode
Inner instanceDecode
Inner data Outer = Outer { outerField ::Required
'1' (Message
Inner) } deriving (Generic
,Show
) instanceEncode
Outer instanceDecode
Outer
It's worth noting that
is a Message
a Monoid
and NFData
instance. The Monoid
behavior models
that of the Protocol Buffers documentation, effectively Last
. It's done with a fairly big hammer
and it isn't possible to override this behavior. This can cause some less-obvious compile errors for
paramterized Message
types:
data Inner = Inner{inner ::Required
'2' (Value
Float
)} deriving (Generic
,Show
) instanceEncode
Inner instanceDecode
Inner data Outer a = Outer{outer ::Required
'3' (Message
a)} deriving (Generic
,Show
) instanceEncode
a =>Encode
(Outer a) instanceDecode
a =>Decode
(Outer a)
This fails because Decode
needs to know that the message can be merged. The resulting error
implies that you may want to add a constraint to the internal GMessageMonoid
class:
/tmp/tst.hs:18:10: Could not deduce (protobuf-0.1:GMessageMonoid
(Rep
a)) arising from a use of `protobuf-0.1:Decode
.$gdmdecode' from the context (Decode
a) bound by the instance declaration at /tmp/tst.hs:18:10-39 Possible fix: add an instance declaration for (protobuf-0.1:GMessageMonoid
(Rep
a)) In the expression: (protobuf-0.1:Decode
.$gdmdecode) In an equation fordecode
: decode = (protobuf-0.1:Decode
.$gdmdecode) In the instance declaration for `Decode
(Outer a)'
The correct fix is to add the Monoid
constraint for the message:
- instance (Encode
a) =>Decode
(Outer a) + instance (Monoid
(Message
a),Decode
a) =>Decode
(Outer a)
Message | |
|
class GDecode (f :: * -> *) Source #
gdecode
GDecode (U1 *) Source # | |
(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 * i (Packed n a)) Source # | |
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Value a))))) Source # | |
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Repeated n a)) Source # | |
(Enum a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Enumeration a))))) Source # | |
(Enum a, KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Enumeration a))))) Source # | |
(DecodeWire a, KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Last (Value a))))) Source # | |
(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (OptionalField (Maybe (Message a))))) Source # | |
(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 * i (Field n (RequiredField (Always (Message a))))) Source # | |
(GDecode x, GDecode y) => GDecode ((:+:) * x y) Source # | |
(GDecode a, GDecode b) => GDecode ((:*:) * a b) Source # | |
GDecode a => GDecode (M1 * i c a) Source # | |
class GMessageMonoid (f :: * -> *) Source #
gmempty, gmappend
GMessageMonoid (U1 *) Source # | |
Monoid c => GMessageMonoid (K1 * i c) Source # | |
(GMessageMonoid x, GMessageMonoid y) => GMessageMonoid ((:+:) * x y) Source # | |
(GMessageMonoid x, GMessageMonoid y) => GMessageMonoid ((:*:) * x y) Source # | |
GMessageMonoid f => GMessageMonoid (M1 * i c f) Source # | |